pact-time-0.2.0.1: Time Library for Pact
CopyrightCopyright © 2021 Kadena LLC.
LicenseMIT
MaintainerLars Kuhtz <lars@kadena.io>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pact.Time

Description

A minimal time library for usage with the Pact Smart Contract Language.

The focus of this library is on minimality, performance, and binary level stability. Time is represented as 64-bit integral value that counts nominal micro-seconds since the modified Julian date epoch (MJD). The implementation ignores leap seconds.

While the library can parse date-time values with time zones, internally all date-times are represented as UTC and formatting only supports UTC. Only the default English language locale is supported.

Details about supported formats can be found in the Pact Language Reference.

Synopsis

NominalDiffTime

newtype NominalDiffTime Source #

A time interval as measured by UTC, that does not take leap-seconds into account.

Constructors

NominalDiffTime 

Instances

Instances details
Show NominalDiffTime Source # 
Instance details

Defined in Pact.Time.Format.Internal

Serialize NominalDiffTime Source #

Serializes NominalDiffTime as 64-bit signed microseconds in little endian encoding.

Instance details

Defined in Pact.Time.Internal

NFData NominalDiffTime Source # 
Instance details

Defined in Pact.Time.Internal

Methods

rnf :: NominalDiffTime -> () #

Eq NominalDiffTime Source # 
Instance details

Defined in Pact.Time.Internal

Ord NominalDiffTime Source # 
Instance details

Defined in Pact.Time.Internal

AdditiveGroup NominalDiffTime Source # 
Instance details

Defined in Pact.Time.Internal

VectorSpace NominalDiffTime Source # 
Instance details

Defined in Pact.Time.Internal

Associated Types

type Scalar NominalDiffTime #

type Scalar NominalDiffTime Source # 
Instance details

Defined in Pact.Time.Internal

toMicroseconds :: NominalDiffTime -> Micros Source #

Convert from NominalDiffTime to a 64-bit representation of microseconds.

fromMicroseconds :: Micros -> NominalDiffTime Source #

Convert from a 64-bit representation of microseconds to NominalDiffTime.

toSeconds :: NominalDiffTime -> Decimal Source #

Convert from NominalDiffTime to a Decimal representation of seconds.

fromSeconds :: Decimal -> NominalDiffTime Source #

Convert from Decimal representation of seconds to NominalDiffTime.

The result is rounded using banker's method, i.e. remainders of 0.5 a rounded to the next even integer.

nominalDay :: NominalDiffTime Source #

The nominal length of a day: precisely 86400 SI seconds.

UTCTime

data UTCTime Source #

UTCTime with microseconds precision. Internally it is represented as 64-bit count nominal microseconds since MJD Epoch.

This implementation ignores leap seconds. Time differences are measured as nominal time, with a nominal day having exaxtly 24 * 60 * 60 SI seconds. As a consequence the difference between two dates as computed by this module is generally equal or smaller than what is actually measured by a clock.

Instances

Instances details
FromJSON UTCTime Source # 
Instance details

Defined in Pact.Time.Format.Internal

ToJSON UTCTime Source # 
Instance details

Defined in Pact.Time.Format.Internal

Generic UTCTime Source # 
Instance details

Defined in Pact.Time.Internal

Associated Types

type Rep UTCTime :: Type -> Type #

Methods

from :: UTCTime -> Rep UTCTime x #

to :: Rep UTCTime x -> UTCTime #

Read UTCTime Source # 
Instance details

Defined in Pact.Time.Format.Internal

Show UTCTime Source # 
Instance details

Defined in Pact.Time.Format.Internal

Serialize UTCTime Source # 
Instance details

Defined in Pact.Time.Internal

NFData UTCTime Source # 
Instance details

Defined in Pact.Time.Internal

Methods

rnf :: UTCTime -> () #

Eq UTCTime Source # 
Instance details

Defined in Pact.Time.Internal

Methods

(==) :: UTCTime -> UTCTime -> Bool #

(/=) :: UTCTime -> UTCTime -> Bool #

Ord UTCTime Source # 
Instance details

Defined in Pact.Time.Internal

AffineSpace UTCTime Source # 
Instance details

Defined in Pact.Time.Internal

Associated Types

type Diff UTCTime #

type Rep UTCTime Source # 
Instance details

Defined in Pact.Time.Internal

type Rep UTCTime = D1 ('MetaData "UTCTime" "Pact.Time.Internal" "pact-time-0.2.0.1-9K8MkxWuTDqEe3hC1elqXk" 'True) (C1 ('MetaCons "UTCTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "_utcTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NominalDiffTime)))
type Diff UTCTime Source # 
Instance details

Defined in Pact.Time.Internal

day :: Lens' UTCTime ModifiedJulianDay Source #

The date of a UTCTime value represented as modified Julian Day.

dayTime :: Lens' UTCTime NominalDiffTime Source #

The day time of a UTCTime value represented as NominalDiffTime since 00:00:00 of that respective day.

fromDayAndDayTime :: ModifiedJulianDay -> NominalDiffTime -> UTCTime Source #

Create a UTCTime from a date and a daytime. The date is represented as modified Julian Day and the day time is represented as NominalDiffTime since '00:00:00' of the respective day.

Note that this implementation does not support representation of leap seconds.

posixEpoch :: UTCTime Source #

The POSIX Epoch represented as UTCTime.

mjdEpoch :: UTCTime Source #

The Epoch of the modified Julian day represented as UTCTime.

Formatting and Parsing

formatTime :: FormatTime t => String -> t -> String Source #

Reexports

class AdditiveGroup (Diff p) => AffineSpace p where #

Minimal complete definition

Nothing

Associated Types

type Diff p #

Associated vector space

type Diff p = GenericDiff p

Methods

(.-.) :: p -> p -> Diff p infix 6 #

Subtract points

(.+^) :: p -> Diff p -> p infixl 6 #

Point plus vector

Instances

Instances details
AffineSpace CDouble 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff CDouble #

AffineSpace CFloat 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff CFloat #

AffineSpace CInt 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff CInt #

Methods

(.-.) :: CInt -> CInt -> Diff CInt #

(.+^) :: CInt -> Diff CInt -> CInt #

AffineSpace CIntMax 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff CIntMax #

AffineSpace CLLong 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff CLLong #

AffineSpace CLong 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff CLong #

Methods

(.-.) :: CLong -> CLong -> Diff CLong #

(.+^) :: CLong -> Diff CLong -> CLong #

AffineSpace CSChar 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff CSChar #

AffineSpace CShort 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff CShort #

AffineSpace UTCTime Source # 
Instance details

Defined in Pact.Time.Internal

Associated Types

type Diff UTCTime #

AffineSpace Integer 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff Integer #

AffineSpace Double 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff Double #

AffineSpace Float 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff Float #

Methods

(.-.) :: Float -> Float -> Diff Float #

(.+^) :: Float -> Diff Float -> Float #

AffineSpace Int 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff Int #

Methods

(.-.) :: Int -> Int -> Diff Int #

(.+^) :: Int -> Diff Int -> Int #

Integral a => AffineSpace (Ratio a) 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff (Ratio a) #

Methods

(.-.) :: Ratio a -> Ratio a -> Diff (Ratio a) #

(.+^) :: Ratio a -> Diff (Ratio a) -> Ratio a #

AffineSpace p => AffineSpace (a -> p) 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff (a -> p) #

Methods

(.-.) :: (a -> p) -> (a -> p) -> Diff (a -> p) #

(.+^) :: (a -> p) -> Diff (a -> p) -> a -> p #

(AffineSpace p, AffineSpace q) => AffineSpace (p, q) 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff (p, q) #

Methods

(.-.) :: (p, q) -> (p, q) -> Diff (p, q) #

(.+^) :: (p, q) -> Diff (p, q) -> (p, q) #

AffineSpace a => AffineSpace (Rec0 a s) 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff (Rec0 a s) #

Methods

(.-.) :: Rec0 a s -> Rec0 a s -> Diff (Rec0 a s) #

(.+^) :: Rec0 a s -> Diff (Rec0 a s) -> Rec0 a s #

(AffineSpace (f p), AffineSpace (g p)) => AffineSpace (AffineDiffProductSpace f g p) 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff (AffineDiffProductSpace f g p) #

Methods

(.-.) :: AffineDiffProductSpace f g p -> AffineDiffProductSpace f g p -> Diff (AffineDiffProductSpace f g p) #

(.+^) :: AffineDiffProductSpace f g p -> Diff (AffineDiffProductSpace f g p) -> AffineDiffProductSpace f g p #

(AffineSpace p, AffineSpace q, AffineSpace r) => AffineSpace (p, q, r) 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff (p, q, r) #

Methods

(.-.) :: (p, q, r) -> (p, q, r) -> Diff (p, q, r) #

(.+^) :: (p, q, r) -> Diff (p, q, r) -> (p, q, r) #

(AffineSpace (f p), AffineSpace (g p)) => AffineSpace ((f :*: g) p) 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff ((f :*: g) p) #

Methods

(.-.) :: (f :*: g) p -> (f :*: g) p -> Diff ((f :*: g) p) #

(.+^) :: (f :*: g) p -> Diff ((f :*: g) p) -> (f :*: g) p #

AffineSpace (f p) => AffineSpace (M1 i c f p) 
Instance details

Defined in Data.AffineSpace

Associated Types

type Diff (M1 i c f p) #

Methods

(.-.) :: M1 i c f p -> M1 i c f p -> Diff (M1 i c f p) #

(.+^) :: M1 i c f p -> Diff (M1 i c f p) -> M1 i c f p #

class AdditiveGroup v => VectorSpace v where #

Vector space v.

Minimal complete definition

Nothing

Associated Types

type Scalar v #

type Scalar v = Scalar (VRep v)

Methods

(*^) :: Scalar v -> v -> v infixr 7 #

Scale a vector

Instances

Instances details
VectorSpace CDouble 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar CDouble #

VectorSpace CFloat 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar CFloat #

Methods

(*^) :: Scalar CFloat -> CFloat -> CFloat #

VectorSpace CInt 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar CInt #

Methods

(*^) :: Scalar CInt -> CInt -> CInt #

VectorSpace CIntMax 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar CIntMax #

VectorSpace CLLong 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar CLLong #

Methods

(*^) :: Scalar CLLong -> CLLong -> CLLong #

VectorSpace CLong 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar CLong #

Methods

(*^) :: Scalar CLong -> CLong -> CLong #

VectorSpace CSChar 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar CSChar #

Methods

(*^) :: Scalar CSChar -> CSChar -> CSChar #

VectorSpace CShort 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar CShort #

Methods

(*^) :: Scalar CShort -> CShort -> CShort #

VectorSpace NominalDiffTime Source # 
Instance details

Defined in Pact.Time.Internal

Associated Types

type Scalar NominalDiffTime #

VectorSpace Integer 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar Integer #

VectorSpace Double 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar Double #

Methods

(*^) :: Scalar Double -> Double -> Double #

VectorSpace Float 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar Float #

Methods

(*^) :: Scalar Float -> Float -> Float #

VectorSpace Int 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar Int #

Methods

(*^) :: Scalar Int -> Int -> Int #

(RealFloat v, VectorSpace v) => VectorSpace (Complex v) 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar (Complex v) #

Methods

(*^) :: Scalar (Complex v) -> Complex v -> Complex v #

Integral a => VectorSpace (Ratio a) 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar (Ratio a) #

Methods

(*^) :: Scalar (Ratio a) -> Ratio a -> Ratio a #

VectorSpace (Diff (VRep p)) => VectorSpace (GenericDiff p) 
Instance details

Defined in Data.AffineSpace

Associated Types

type Scalar (GenericDiff p) #

Methods

(*^) :: Scalar (GenericDiff p) -> GenericDiff p -> GenericDiff p #

VectorSpace v => VectorSpace (Maybe v) 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar (Maybe v) #

Methods

(*^) :: Scalar (Maybe v) -> Maybe v -> Maybe v #

(HasTrie a, VectorSpace v) => VectorSpace (a :->: v) 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar (a :->: v) #

Methods

(*^) :: Scalar (a :->: v) -> (a :->: v) -> a :->: v #

VectorSpace v => VectorSpace (a -> v) 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar (a -> v) #

Methods

(*^) :: Scalar (a -> v) -> (a -> v) -> a -> v #

(VectorSpace u, s ~ Scalar u, VectorSpace v, s ~ Scalar v) => VectorSpace (u, v) 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar (u, v) #

Methods

(*^) :: Scalar (u, v) -> (u, v) -> (u, v) #

VectorSpace a => VectorSpace (Rec0 a s) 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar (Rec0 a s) #

Methods

(*^) :: Scalar (Rec0 a s) -> Rec0 a s -> Rec0 a s #

(AffineSpace (f p), AffineSpace (g p), VectorSpace (Diff (f p)), VectorSpace (Diff (g p)), Scalar (Diff (f p)) ~ Scalar (Diff (g p))) => VectorSpace (AffineDiffProductSpace f g p) 
Instance details

Defined in Data.AffineSpace

Associated Types

type Scalar (AffineDiffProductSpace f g p) #

Methods

(*^) :: Scalar (AffineDiffProductSpace f g p) -> AffineDiffProductSpace f g p -> AffineDiffProductSpace f g p #

(VectorSpace u, s ~ Scalar u, VectorSpace v, s ~ Scalar v, VectorSpace w, s ~ Scalar w) => VectorSpace (u, v, w) 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar (u, v, w) #

Methods

(*^) :: Scalar (u, v, w) -> (u, v, w) -> (u, v, w) #

(VectorSpace (f p), VectorSpace (g p), Scalar (f p) ~ Scalar (g p)) => VectorSpace ((f :*: g) p) 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar ((f :*: g) p) #

Methods

(*^) :: Scalar ((f :*: g) p) -> (f :*: g) p -> (f :*: g) p #

(VectorSpace u, s ~ Scalar u, VectorSpace v, s ~ Scalar v, VectorSpace w, s ~ Scalar w, VectorSpace x, s ~ Scalar x) => VectorSpace (u, v, w, x) 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar (u, v, w, x) #

Methods

(*^) :: Scalar (u, v, w, x) -> (u, v, w, x) -> (u, v, w, x) #

VectorSpace (f p) => VectorSpace (M1 i c f p) 
Instance details

Defined in Data.VectorSpace

Associated Types

type Scalar (M1 i c f p) #

Methods

(*^) :: Scalar (M1 i c f p) -> M1 i c f p -> M1 i c f p #