Copyright | (c) 2024-2025 Sayo contributors |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Data.Effect.Concurrent.Timer
Description
Effects for controlling time-related operations.
Synopsis
- data Timer (a :: Type -> Type) b where
- data TimerLabel
- clock :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Timer :> es) => f DiffTime
- clock' :: forall {k} (key :: k) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key Timer es) => f DiffTime
- clock'' :: forall {k} (tag :: k) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag Timer :> es) => f DiffTime
- clock'_ :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In Timer es) => f DiffTime
- sleep :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Timer :> es) => DiffTime -> f ()
- sleep' :: forall {k} (key :: k) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key Timer es) => DiffTime -> f ()
- sleep'' :: forall {k} (tag :: k) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag Timer :> es) => DiffTime -> f ()
- sleep'_ :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In Timer es) => DiffTime -> f ()
- withElapsedTime :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Monad (Eff ff es), Free c ff) => (Eff ff es DiffTime -> Eff ff es a) -> Eff ff es a
- measureTime :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Monad (Eff ff es), Free c ff) => Eff ff es a -> Eff ff es (DiffTime, a)
- sleepUntil :: forall (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Monad (Eff ff es), Free c ff) => DiffTime -> Eff ff es (Maybe DiffTime)
- runCyclic :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Monad (Eff ff es), Free c ff) => Eff ff es DiffTime -> Eff ff es () -> Eff ff es a
- runPeriodic :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Monad (Eff ff es), Free c ff) => DiffTime -> Eff ff es () -> Eff ff es a
- periodicTimer :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Yield () () :> es, Monad (Eff ff es), Free c ff) => DiffTime -> Eff ff es a
- cyclicTimer :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Yield () DiffTime :> es, Monad (Eff ff es), Free c ff) => Eff ff es a
- data CyclicTimer (a :: Type -> Type) b where
- Wait :: forall (a :: Type -> Type). DiffTime -> CyclicTimer a ()
- data CyclicTimerLabel
- wait :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, CyclicTimer :> es) => DiffTime -> f ()
- wait' :: forall {k} (key :: k) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key CyclicTimer es) => DiffTime -> f ()
- wait'' :: forall {k} (tag :: k) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag CyclicTimer :> es) => DiffTime -> f ()
- wait'_ :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In CyclicTimer es) => DiffTime -> f ()
- runTimerIO :: forall a (ff :: (Type -> Type) -> Type -> Type) (es :: [Effect]) (c :: (Type -> Type) -> Constraint). (Emb IO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Timer ': es) a -> Eff ff es a
- restartClock :: forall a (ff :: (Type -> Type) -> Type -> Type) (es :: [Effect]) (c :: (Type -> Type) -> Constraint). (Timer :> es, Monad (Eff ff es), Free c ff) => Eff ff es a -> Eff ff es a
Documentation
data Timer (a :: Type -> Type) b where Source #
An effect for time-related operations.
Constructors
Clock :: forall (a :: Type -> Type). Timer a DiffTime | Retrieves the current relative time from an arbitrary fixed reference point. The reference point does not change within the context of that scope. |
Sleep :: forall (a :: Type -> Type). DiffTime -> Timer a () | Temporarily suspends computation for the specified duration. |
Instances
FirstOrder Timer Source # | |
Defined in Data.Effect.Concurrent.Timer | |
PolyHFunctor Timer Source # | |
Defined in Data.Effect.Concurrent.Timer | |
HFunctor Timer Source # | |
Defined in Data.Effect.Concurrent.Timer | |
type FormOf Timer Source # | |
Defined in Data.Effect.Concurrent.Timer | |
type LabelOf Timer Source # | |
Defined in Data.Effect.Concurrent.Timer | |
type OrderOf Timer Source # | |
Defined in Data.Effect.Concurrent.Timer |
data TimerLabel Source #
clock :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Timer :> es) => f DiffTime Source #
Retrieves the current relative time from an arbitrary fixed reference point. The reference point does not change within the context of that scope.
clock' :: forall {k} (key :: k) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key Timer es) => f DiffTime Source #
Retrieves the current relative time from an arbitrary fixed reference point. The reference point does not change within the context of that scope.
clock'' :: forall {k} (tag :: k) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag Timer :> es) => f DiffTime Source #
Retrieves the current relative time from an arbitrary fixed reference point. The reference point does not change within the context of that scope.
clock'_ :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In Timer es) => f DiffTime Source #
Retrieves the current relative time from an arbitrary fixed reference point. The reference point does not change within the context of that scope.
sleep :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Timer :> es) => DiffTime -> f () Source #
Temporarily suspends computation for the specified duration.
sleep' :: forall {k} (key :: k) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key Timer es) => DiffTime -> f () Source #
Temporarily suspends computation for the specified duration.
sleep'' :: forall {k} (tag :: k) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag Timer :> es) => DiffTime -> f () Source #
Temporarily suspends computation for the specified duration.
sleep'_ :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In Timer es) => DiffTime -> f () Source #
Temporarily suspends computation for the specified duration.
Arguments
:: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Monad (Eff ff es), Free c ff) | |
=> (Eff ff es DiffTime -> Eff ff es a) | A scope where the elapsed time can be obtained. An action to retrieve the elapsed time is passed as an argument. |
-> Eff ff es a |
Creates a scope where elapsed time can be obtained. An action to retrieve the elapsed time, re-zeroed at the start of the scope, is passed to the scope.
measureTime :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Monad (Eff ff es), Free c ff) => Eff ff es a -> Eff ff es (DiffTime, a) Source #
Returns the time taken for a computation along with the result as a pair.
sleepUntil :: forall (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Monad (Eff ff es), Free c ff) => DiffTime -> Eff ff es (Maybe DiffTime) Source #
Temporarily suspends computation until the relative time from the fixed reference point in the current scope's context, as given by the argument.
If the specified resume time has already passed, returns the elapsed time (positive value) in Just
.
Arguments
:: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Monad (Eff ff es), Free c ff) | |
=> Eff ff es DiffTime | An action called at the start of each loop to determine the time interval until the next loop.
For example, |
-> Eff ff es () | The computation to repeat. |
-> Eff ff es a |
Repeats a computation indefinitely. Controls so that each loop occurs at a specific time interval. If the computation time exceeds and the requested interval cannot be realized, the excess delay occurs, which accumulates and is not canceled.
Arguments
:: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Monad (Eff ff es), Free c ff) | |
=> DiffTime | Loop interval |
-> Eff ff es () | The computation to repeat. |
-> Eff ff es a |
Controls to repeat a specified computation at fixed time intervals. A specialized version of runCyclic
.
If the computation time exceeds and the requested interval cannot be realized, the excess delay occurs, which accumulates and is not canceled.
periodicTimer :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Yield () () :> es, Monad (Eff ff es), Free c ff) => DiffTime -> Eff ff es a Source #
Calls yield
of a coroutine at fixed intervals.
If the computation time exceeds and the requested interval cannot be realized, the excess delay occurs, which accumulates and is not canceled.
cyclicTimer :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Timer :> es, Yield () DiffTime :> es, Monad (Eff ff es), Free c ff) => Eff ff es a Source #
data CyclicTimer (a :: Type -> Type) b where Source #
An effect that realizes control of wait times such that the specified time becomes the interval until the next wait
when wait
is executed repeatedly.
Constructors
Wait :: forall (a :: Type -> Type). DiffTime -> CyclicTimer a () | Controls the wait time so that when |
Instances
FirstOrder CyclicTimer Source # | |
Defined in Data.Effect.Concurrent.Timer | |
PolyHFunctor CyclicTimer Source # | |
Defined in Data.Effect.Concurrent.Timer | |
HFunctor CyclicTimer Source # | |
Defined in Data.Effect.Concurrent.Timer Methods hfmap :: (forall x. f x -> g x) -> CyclicTimer f a -> CyclicTimer g a # | |
type FormOf CyclicTimer Source # | |
Defined in Data.Effect.Concurrent.Timer | |
type LabelOf CyclicTimer Source # | |
Defined in Data.Effect.Concurrent.Timer | |
type OrderOf CyclicTimer Source # | |
Defined in Data.Effect.Concurrent.Timer |
data CyclicTimerLabel Source #
wait :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, CyclicTimer :> es) => DiffTime -> f () Source #
Controls the wait time so that when wait
is executed repeatedly, the specified time becomes the interval until the next wait
.
wait' :: forall {k} (key :: k) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key CyclicTimer es) => DiffTime -> f () Source #
Controls the wait time so that when wait
is executed repeatedly, the specified time becomes the interval until the next wait
.
wait'' :: forall {k} (tag :: k) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag CyclicTimer :> es) => DiffTime -> f () Source #
Controls the wait time so that when wait
is executed repeatedly, the specified time becomes the interval until the next wait
.
wait'_ :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In CyclicTimer es) => DiffTime -> f () Source #
Controls the wait time so that when wait
is executed repeatedly, the specified time becomes the interval until the next wait
.