Safe Haskell | None |
---|---|
Language | GHC2021 |
Effectful.Time.Dynamic
Description
Provides a dynamic effect for Data.Time.
Since: 0.1
Synopsis
- data Time (a :: Type -> Type) b where
- GetSystemZonedTime :: forall (a :: Type -> Type). Time a ZonedTime
- GetTimeZone :: forall (a :: Type -> Type). UTCTime -> Time a TimeZone
- UtcToLocalZonedTime :: forall (a :: Type -> Type). UTCTime -> Time a ZonedTime
- LoadLocalTZ :: forall (a :: Type -> Type). Time a TZ
- GetMonotonicTime :: forall (a :: Type -> Type). Time a Double
- getSystemTime :: forall (es :: [Effect]). (HasCallStack, Time :> es) => Eff es LocalTime
- getSystemZonedTime :: forall (es :: [Effect]). (HasCallStack, Time :> es) => Eff es ZonedTime
- getTimeZone :: forall (es :: [Effect]). (HasCallStack, Time :> es) => UTCTime -> Eff es TimeZone
- utcToLocalZonedTime :: forall (es :: [Effect]). (HasCallStack, Time :> es) => UTCTime -> Eff es ZonedTime
- loadLocalTZ :: forall (es :: [Effect]). (HasCallStack, Time :> es) => Eff es TZ
- getMonotonicTime :: forall (es :: [Effect]). (HasCallStack, Time :> es) => Eff es Double
- runTime :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => Eff (Time ': es) a -> Eff es a
- withTiming :: forall (es :: [Effect]) a. (HasCallStack, Time :> es) => Eff es a -> Eff es (TimeSpec, a)
- withTiming_ :: forall (es :: [Effect]) a. (HasCallStack, Time :> es) => Eff es a -> Eff es TimeSpec
- data TimeSpec = MkTimeSpec {}
- fromSeconds :: Double -> TimeSpec
- fromNanoSeconds :: Natural -> TimeSpec
- toSeconds :: TimeSpec -> Double
- toNanoSeconds :: TimeSpec -> Natural
- diffTimeSpec :: TimeSpec -> TimeSpec -> TimeSpec
- normalizeTimeSpec :: TimeSpec -> TimeSpec
- formatLocalTime :: LocalTime -> String
- formatZonedTime :: ZonedTime -> String
- parseLocalTime :: (HasCallStack, MonadFail f) => String -> f LocalTime
- parseZonedTime :: (HasCallStack, MonadFail f) => String -> f ZonedTime
- getSystemTimeString :: forall (es :: [Effect]). (HasCallStack, Time :> es) => Eff es String
- getSystemZonedTimeString :: forall (es :: [Effect]). (HasCallStack, Time :> es) => Eff es String
- data LocalTime = LocalTime {}
- data ZonedTime = ZonedTime {}
Effect
data Time (a :: Type -> Type) b where Source #
Dynamic effect for Data.Time.
Since: 0.1
Constructors
GetSystemZonedTime :: forall (a :: Type -> Type). Time a ZonedTime | |
GetTimeZone :: forall (a :: Type -> Type). UTCTime -> Time a TimeZone | |
UtcToLocalZonedTime :: forall (a :: Type -> Type). UTCTime -> Time a ZonedTime | |
LoadLocalTZ :: forall (a :: Type -> Type). Time a TZ | |
GetMonotonicTime :: forall (a :: Type -> Type). Time a Double |
Instances
ShowEffect Time Source # | Since: 0.1 |
Defined in Effectful.Time.Dynamic | |
type DispatchOf Time Source # | Since: 0.1 |
Defined in Effectful.Time.Dynamic |
getSystemTime :: forall (es :: [Effect]). (HasCallStack, Time :> es) => Eff es LocalTime Source #
Returns the local system time.
Since: 0.1
getSystemZonedTime :: forall (es :: [Effect]). (HasCallStack, Time :> es) => Eff es ZonedTime Source #
Returns the zoned system time.
Since: 0.1
getTimeZone :: forall (es :: [Effect]). (HasCallStack, Time :> es) => UTCTime -> Eff es TimeZone Source #
Lifted getTimeZone
.
Since: 0.1
utcToLocalZonedTime :: forall (es :: [Effect]). (HasCallStack, Time :> es) => UTCTime -> Eff es ZonedTime Source #
Lifted utcToLocalZonedTime
.
Since: 0.1
loadLocalTZ :: forall (es :: [Effect]). (HasCallStack, Time :> es) => Eff es TZ Source #
Lifted loadLocalTZ
.
Since: 0.1
getMonotonicTime :: forall (es :: [Effect]). (HasCallStack, Time :> es) => Eff es Double Source #
Returns the zoned system time
Since: 0.1
Handlers
runTime :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => Eff (Time ': es) a -> Eff es a Source #
Timing
withTiming :: forall (es :: [Effect]) a. (HasCallStack, Time :> es) => Eff es a -> Eff es (TimeSpec, a) Source #
Runs an action, returning the elapsed time.
Since: 0.1
withTiming_ :: forall (es :: [Effect]) a. (HasCallStack, Time :> es) => Eff es a -> Eff es TimeSpec Source #
withTiming
but ignores the result value.
Since: 0.1
TimeSpec
Structure for holding time data. Eq
and Ord
are defined in terms of
an equivalence class e.g.
MkTimeSpec s n === MkTimeSpec 0 (s * 1_000_000_000 + n)
Since: 0.1
Constructors
MkTimeSpec | |
Instances
Creation
fromNanoSeconds :: Natural -> TimeSpec Source #
Elimination
toNanoSeconds :: TimeSpec -> Natural Source #
Operations
diffTimeSpec :: TimeSpec -> TimeSpec -> TimeSpec Source #
Returns the absolute difference of two TimeSpec
s.
Since: 0.1
normalizeTimeSpec :: TimeSpec -> TimeSpec Source #
Normalizes nanoseconds < 1 second.
Since: 0.1
Formatting
formatLocalTime :: LocalTime -> String Source #
Formats the LocalTime
to YYYY-MM-DD HH:MM:SS
.
Since: 0.1
formatZonedTime :: ZonedTime -> String Source #
Formats the ZonedTime
to YYYY-MM-DD HH:MM:SS Z
.
Since: 0.1
Parsing
parseLocalTime :: (HasCallStack, MonadFail f) => String -> f LocalTime Source #
Parses the LocalTime
from YYYY-MM-DD HH:MM:SS
.
Since: 0.1
parseZonedTime :: (HasCallStack, MonadFail f) => String -> f ZonedTime Source #
Parses the ZonedTime
from YYYY-MM-DD HH:MM:SS Z
.
Known Timezones
- UTC
- UT
- GMT
- EST
- EDT
- CST
- CDT
- MST
- MDT
- PST
- PDT
- +HHMM (e.g. +1300)
Since: 0.1
Misc
getSystemTimeString :: forall (es :: [Effect]). (HasCallStack, Time :> es) => Eff es String Source #
Retrieves the formatted LocalTime
.
Since: 0.1
getSystemZonedTimeString :: forall (es :: [Effect]). (HasCallStack, Time :> es) => Eff es String Source #
Retrieves the formatted ZonedTime
.
Since: 0.1
Re-exports
A simple day and time aggregate, where the day is of the specified parameter, and the time is a TimeOfDay. Conversion of this (as local civil time) to UTC depends on the time zone. Conversion of this (as local mean time) to UT1 depends on the longitude.
Constructors
LocalTime | |
Fields
|
Instances
NFData LocalTime | |
Defined in Data.Time.LocalTime.Internal.LocalTime | |
Data LocalTime | |
Defined in Data.Time.LocalTime.Internal.LocalTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocalTime -> c LocalTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocalTime # toConstr :: LocalTime -> Constr # dataTypeOf :: LocalTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LocalTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocalTime) # gmapT :: (forall b. Data b => b -> b) -> LocalTime -> LocalTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocalTime -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocalTime -> r # gmapQ :: (forall d. Data d => d -> u) -> LocalTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LocalTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime # | |
Show LocalTime | |
Eq LocalTime | |
Ord LocalTime | |
Defined in Data.Time.LocalTime.Internal.LocalTime | |
ISO8601 LocalTime |
|
Defined in Data.Time.Format.ISO8601 Methods |
A local time together with a time zone.
There is no Eq
instance for ZonedTime
.
If you want to compare local times, use zonedTimeToLocalTime
.
If you want to compare absolute times, use zonedTimeToUTC
.
Constructors
ZonedTime | |
Fields |
Instances
NFData ZonedTime | |
Defined in Data.Time.LocalTime.Internal.ZonedTime | |
Data ZonedTime | |
Defined in Data.Time.LocalTime.Internal.ZonedTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ZonedTime -> c ZonedTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ZonedTime # toConstr :: ZonedTime -> Constr # dataTypeOf :: ZonedTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ZonedTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ZonedTime) # gmapT :: (forall b. Data b => b -> b) -> ZonedTime -> ZonedTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZonedTime -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZonedTime -> r # gmapQ :: (forall d. Data d => d -> u) -> ZonedTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ZonedTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime # | |
Show ZonedTime | For the time zone, this only shows the name, or offset if the name is empty. |
ISO8601 ZonedTime |
|
Defined in Data.Time.Format.ISO8601 Methods |