polysemy-time-0.1.4.0: Polysemy Effect for Time
Safe HaskellNone
LanguageHaskell2010

Polysemy.Time.Data.Time

Synopsis

Documentation

data Time (time :: Type) (date :: Type) :: Effect where Source #

The Time effect.

Constructors

Now :: Time t d m t

Produce the current time, possibly relative to what was set with SetTime or SetDate

Today :: Time t d m d

Produce the current date, possibly relative to what was set with SetTime or SetDate

Sleep :: TimeUnit u => u -> Time t d m ()

Suspend the current computation for the specified time span.

SetTime :: t -> Time t d m ()

Set the current time, if the interpreter supports it.

Adjust :: AddTimeUnit t u1 u2 => u1 -> Time t d m ()

Adjust the current time relatively, if the interpreter supports it.

SetDate :: d -> Time t d m ()

Set the current date, if the interpreter supports it.

Instances

Instances details
type DefiningModule Time Source # 
Instance details

Defined in Polysemy.Time.Data.Time

type DefiningModule Time = "Polysemy.Time.Data.Time"

setDate :: forall t d r. MemberWithError (Time t d) r => d -> Sem r () Source #

adjust :: forall t d r u1 u2. (MemberWithError (Time t d) r, AddTimeUnit t u1 u2) => u1 -> Sem r () Source #

setTime :: forall t d r. MemberWithError (Time t d) r => t -> Sem r () Source #

sleep :: forall t d r u. (MemberWithError (Time t d) r, TimeUnit u) => u -> Sem r () Source #

today :: forall t d r. MemberWithError (Time t d) r => Sem r d Source #

now :: forall t d r. MemberWithError (Time t d) r => Sem r t Source #