Copyright | Copyright © 2021 Kadena LLC. |
---|---|
License | MIT |
Maintainer | Lars Kuhtz <lars@kadena.io> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
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
- newtype NominalDiffTime = NominalDiffTime {}
- toMicroseconds :: NominalDiffTime -> Micros
- fromMicroseconds :: Micros -> NominalDiffTime
- toSeconds :: NominalDiffTime -> Decimal
- fromSeconds :: Decimal -> NominalDiffTime
- nominalDay :: NominalDiffTime
- data UTCTime
- getCurrentTime :: IO UTCTime
- day :: Lens' UTCTime ModifiedJulianDay
- dayTime :: Lens' UTCTime NominalDiffTime
- fromDayAndDayTime :: ModifiedJulianDay -> NominalDiffTime -> UTCTime
- toPosixTimestampMicros :: UTCTime -> Micros
- fromPosixTimestampMicros :: Micros -> UTCTime
- posixEpoch :: UTCTime
- mjdEpoch :: UTCTime
- parseTime :: String -> String -> Maybe UTCTime
- formatTime :: FormatTime t => String -> t -> String
- class AdditiveGroup (Diff p) => AffineSpace p where
- class AdditiveGroup v => VectorSpace v where
NominalDiffTime
newtype NominalDiffTime Source #
A time interval as measured by UTC, that does not take leap-seconds into account.
Instances
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
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
Eq UTCTime Source # | |
Ord UTCTime Source # | |
Read UTCTime Source # | |
Show UTCTime Source # | |
Generic UTCTime Source # | |
ToJSON UTCTime Source # | |
Defined in Data.Time.Format.Internal | |
FromJSON UTCTime Source # | |
Serialize UTCTime Source # | |
NFData UTCTime Source # | |
Defined in Data.Time.Internal | |
AffineSpace UTCTime Source # | |
type Rep UTCTime Source # | |
Defined in Data.Time.Internal type Rep UTCTime = D1 ('MetaData "UTCTime" "Data.Time.Internal" "pact-time-0.1.0.0-J0u9zqoTruKI1WkGAcBqUA" 'True) (C1 ('MetaCons "UTCTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "_utcTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NominalDiffTime))) | |
type Diff UTCTime Source # | |
Defined in Data.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.
Formatting and Parsing
formatTime :: FormatTime t => String -> t -> String Source #
Reexports
class AdditiveGroup (Diff p) => AffineSpace p where #
Nothing
(.-.) :: p -> p -> Diff p infix 6 #
Subtract points
(.+^) :: p -> Diff p -> p infixl 6 #
Point plus vector
Instances
AffineSpace Double | |
AffineSpace Float | |
AffineSpace Int | |
AffineSpace Integer | |
AffineSpace CSChar | |
AffineSpace CShort | |
AffineSpace CInt | |
AffineSpace CLong | |
AffineSpace CLLong | |
AffineSpace CFloat | |
AffineSpace CDouble | |
AffineSpace CIntMax | |
AffineSpace UTCTime Source # | |
Integral a => AffineSpace (Ratio a) | |
AffineSpace p => AffineSpace (a -> p) | |
(AffineSpace p, AffineSpace q) => AffineSpace (p, q) | |
AffineSpace a => AffineSpace (Rec0 a s) | |
(AffineSpace p, AffineSpace q, AffineSpace r) => AffineSpace (p, q, r) | |
(AffineSpace (f p), AffineSpace (g p)) => AffineSpace (AffineDiffProductSpace f g p) | |
(AffineSpace (f p), AffineSpace (g p)) => AffineSpace ((f :*: g) p) | |
AffineSpace (f p) => AffineSpace (M1 i c f p) | |
class AdditiveGroup v => VectorSpace v where #
Vector space v
.
Nothing