Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This package provides a Polysemy effect for interacting with the current time and sleeping, as well as some time-related data types and classes.
Synopsis
- data Time (time :: Type) (date :: Type) :: Effect where
- now :: forall t d r. Member (Time t d) r => Sem r t
- today :: forall t d r. Member (Time t d) r => Sem r d
- sleep :: forall t d u r. TimeUnit u => Member (Time t d) r => u -> Sem r ()
- setTime :: forall t d r. Member (Time t d) r => t -> Sem r ()
- adjust :: forall t d u1 u2 r. AddTimeUnit t u1 u2 => Member (Time t d) r => u1 -> Sem r ()
- setDate :: forall t d r. Member (Time t d) r => d -> Sem r ()
- type GhcTime = Time UTCTime Day
- interpretTimeGhc :: Member (Embed IO) r => InterpreterFor GhcTime r
- interpretTimeGhcAt :: Member (Embed IO) r => UTCTime -> InterpreterFor GhcTime r
- interpretTimeGhcConstant :: Member (Embed IO) r => UTCTime -> InterpreterFor GhcTime r
- interpretTimeGhcConstantNow :: Member (Embed IO) r => InterpreterFor GhcTime r
- newtype NanoSeconds = NanoSeconds {}
- newtype MicroSeconds = MicroSeconds {}
- newtype MilliSeconds = MilliSeconds {}
- newtype Seconds = Seconds {}
- newtype Minutes = Minutes {}
- newtype Hours = Hours {}
- newtype Days = Days {}
- newtype Weeks = Weeks {}
- newtype Months = Months {}
- newtype Years = Years {}
- class TimeUnit u
- convert :: TimeUnit a => TimeUnit b => a -> b
- class Calendar dt where
- type CalendarDate dt :: Type
- type CalendarTime dt :: Type
- mkDate :: Int64 -> Int64 -> Int64 -> CalendarDate dt
- mkTime :: Int64 -> Int64 -> Int64 -> CalendarTime dt
- mkDatetime :: Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> dt
- class HasDay t where
- class HasHour t where
- class HasMinute t where
- class HasMonth t where
- class HasNanoSecond t where
- nanoSecond :: t -> NanoSeconds
- class HasSecond t where
- class HasYear t where
- measure :: forall dt t d u r a. TimeUnit u => Torsor dt u => Instant t dt => Member (Time t d) r => Sem r a -> Sem r (u, a)
- while :: forall t d u r. Member (Time t d) r => TimeUnit u => u -> Sem r Bool -> Sem r ()
- loop :: forall t d u a r. Member (Time t d) r => TimeUnit u => u -> a -> (a -> Sem r a) -> Sem r ()
- loop_ :: forall t d u r. Member (Time t d) r => TimeUnit u => u -> Sem r () -> Sem r ()
- diff :: forall dt u i1 i2. TimeUnit u => Torsor dt u => Instant i1 dt => Instant i2 dt => i1 -> i2 -> u
Documentation
import Data.Time (UTCTime) import Polysemy (Members, runM) import Polysemy.Chronos (interpretTimeChronos) import qualified Polysemy.Time as Time import Polysemy.Time (MilliSeconds(MilliSeconds), Seconds(Seconds), Time, interpretTimeGhcAt, mkDatetime, year) prog :: Ord t => Member (Time t d) r => Sem r () prog = do time1 <- Time.now Time.sleep (MilliSeconds 10) time2 <- Time.now print (time1 < time2) -- True testTime :: UTCTime testTime = mkDatetime 1845 12 31 23 59 59 main :: IO () main = runM do interpretTimeChronos prog interpretTimeGhcAt testTime do Time.sleep (Seconds 1) time <- Time.now print (year time) -- Years { unYear = 1846 }
data Time (time :: Type) (date :: Type) :: Effect where Source #
The Time effect.
Now :: Time t d m t | Produce the current time, possibly relative to what was set with |
Today :: Time t d m d | Produce the current date, possibly relative to what was set with |
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
type DefiningModule Time Source # | |
Defined in Polysemy.Time.Effect.Time |
sleep :: forall t d u r. TimeUnit u => Member (Time t d) r => u -> Sem r () Source #
Suspend the current computation for the specified time span.
setTime :: forall t d r. Member (Time t d) r => t -> Sem r () Source #
Set the current time, if the interpreter supports it.
adjust :: forall t d u1 u2 r. AddTimeUnit t u1 u2 => Member (Time t d) r => u1 -> Sem r () Source #
Adjust the current time relatively, if the interpreter supports it.
setDate :: forall t d r. Member (Time t d) r => d -> Sem r () Source #
Set the current date, if the interpreter supports it.
Interpreters
interpretTimeGhc :: Member (Embed IO) r => InterpreterFor GhcTime r Source #
interpretTimeGhcAt :: Member (Embed IO) r => UTCTime -> InterpreterFor GhcTime r Source #
interpretTimeGhcConstant :: Member (Embed IO) r => UTCTime -> InterpreterFor GhcTime r Source #
interpretTimeGhcConstantNow :: Member (Embed IO) r => InterpreterFor GhcTime r Source #
Data types
newtype NanoSeconds Source #
Nanoseconds. This is the base unit for all conversions.
Instances
newtype MicroSeconds Source #
Microseconds.
Instances
newtype MilliSeconds Source #
Milliseconds.
Instances
Seconds.
Instances
FromJSON Seconds Source # | |
ToJSON Seconds Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Enum Seconds Source # | |
Generic Seconds Source # | |
Num Seconds Source # | |
Integral Seconds Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Real Seconds Source # | |
Defined in Polysemy.Time.Data.TimeUnit toRational :: Seconds -> Rational # | |
Show Seconds Source # | |
Eq Seconds Source # | |
Ord Seconds Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
TimeUnit Seconds Source # | |
Defined in Polysemy.Time.Data.TimeUnit nanos :: NanoSeconds Source # toNanos :: Seconds -> NanoSeconds Source # fromNanos :: NanoSeconds -> Seconds Source # | |
Additive Seconds Source # | |
type Rep Seconds Source # | |
Defined in Polysemy.Time.Data.TimeUnit |
Minutes.
Instances
FromJSON Minutes Source # | |
ToJSON Minutes Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Enum Minutes Source # | |
Generic Minutes Source # | |
Num Minutes Source # | |
Integral Minutes Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Real Minutes Source # | |
Defined in Polysemy.Time.Data.TimeUnit toRational :: Minutes -> Rational # | |
Show Minutes Source # | |
Eq Minutes Source # | |
Ord Minutes Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
TimeUnit Minutes Source # | |
Defined in Polysemy.Time.Data.TimeUnit nanos :: NanoSeconds Source # toNanos :: Minutes -> NanoSeconds Source # fromNanos :: NanoSeconds -> Minutes Source # | |
Additive Minutes Source # | |
type Rep Minutes Source # | |
Defined in Polysemy.Time.Data.TimeUnit |
Hours.
Instances
FromJSON Hours Source # | |
ToJSON Hours Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Enum Hours Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Generic Hours Source # | |
Num Hours Source # | |
Integral Hours Source # | |
Real Hours Source # | |
Defined in Polysemy.Time.Data.TimeUnit toRational :: Hours -> Rational # | |
Show Hours Source # | |
Eq Hours Source # | |
Ord Hours Source # | |
TimeUnit Hours Source # | |
Defined in Polysemy.Time.Data.TimeUnit nanos :: NanoSeconds Source # toNanos :: Hours -> NanoSeconds Source # fromNanos :: NanoSeconds -> Hours Source # | |
Additive Hours Source # | |
type Rep Hours Source # | |
Defined in Polysemy.Time.Data.TimeUnit |
Days.
Instances
FromJSON Days Source # | |
ToJSON Days Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Enum Days Source # | |
Generic Days Source # | |
Num Days Source # | |
Integral Days Source # | |
Real Days Source # | |
Defined in Polysemy.Time.Data.TimeUnit toRational :: Days -> Rational # | |
Show Days Source # | |
Eq Days Source # | |
Ord Days Source # | |
TimeUnit Days Source # | |
Defined in Polysemy.Time.Data.TimeUnit nanos :: NanoSeconds Source # toNanos :: Days -> NanoSeconds Source # fromNanos :: NanoSeconds -> Days Source # | |
Additive Days Source # | |
type Rep Days Source # | |
Defined in Polysemy.Time.Data.TimeUnit |
Weeks.
Instances
FromJSON Weeks Source # | |
ToJSON Weeks Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Enum Weeks Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Generic Weeks Source # | |
Num Weeks Source # | |
Integral Weeks Source # | |
Real Weeks Source # | |
Defined in Polysemy.Time.Data.TimeUnit toRational :: Weeks -> Rational # | |
Show Weeks Source # | |
Eq Weeks Source # | |
Ord Weeks Source # | |
TimeUnit Weeks Source # | |
Defined in Polysemy.Time.Data.TimeUnit nanos :: NanoSeconds Source # toNanos :: Weeks -> NanoSeconds Source # fromNanos :: NanoSeconds -> Weeks Source # | |
Additive Weeks Source # | |
type Rep Weeks Source # | |
Defined in Polysemy.Time.Data.TimeUnit |
Months.
Instances
FromJSON Months Source # | |
ToJSON Months Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Enum Months Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Generic Months Source # | |
Num Months Source # | |
Integral Months Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Real Months Source # | |
Defined in Polysemy.Time.Data.TimeUnit toRational :: Months -> Rational # | |
Show Months Source # | |
Eq Months Source # | |
Ord Months Source # | |
Additive Months Source # | |
type Rep Months Source # | |
Defined in Polysemy.Time.Data.TimeUnit |
Years.
Instances
FromJSON Years Source # | |
ToJSON Years Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Enum Years Source # | |
Defined in Polysemy.Time.Data.TimeUnit | |
Generic Years Source # | |
Num Years Source # | |
Integral Years Source # | |
Real Years Source # | |
Defined in Polysemy.Time.Data.TimeUnit toRational :: Years -> Rational # | |
Show Years Source # | |
Eq Years Source # | |
Ord Years Source # | |
Additive Years Source # | |
type Rep Years Source # | |
Defined in Polysemy.Time.Data.TimeUnit |
Types that represent an amount of time that can be converted to each other.
The methods are internal, the API function is convert
.
Instances
convert :: TimeUnit a => TimeUnit b => a -> b Source #
Convert between different time spans.
>>>
convert (picosecondsToDiffTime 50000000) :: MicroSeconds
MicroSeconds {unMicroSeconds = 50}
>>>
convert (MilliSeconds 5) :: MicroSeconds
MicroSeconds 5000
class Calendar dt where Source #
Construct datetimes, dates or times from integers.
type CalendarDate dt :: Type Source #
type CalendarTime dt :: Type Source #
mkDate :: Int64 -> Int64 -> Int64 -> CalendarDate dt Source #
mkTime :: Int64 -> Int64 -> Int64 -> CalendarTime dt Source #
mkDatetime :: Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> dt Source #
Instances
Calendar UTCTime Source # | |
Defined in Polysemy.Time.Calendar type CalendarDate UTCTime Source # type CalendarTime UTCTime Source # |
Extract the day component from a date.
class HasNanoSecond t where Source #
Extract the nanosecond component from a datetime or time.
nanoSecond :: t -> NanoSeconds Source #
Instances
HasNanoSecond DiffTime Source # | |
Defined in Polysemy.Time.Calendar nanoSecond :: DiffTime -> NanoSeconds Source # | |
HasNanoSecond TimeOfDay Source # | |
Defined in Polysemy.Time.Calendar nanoSecond :: TimeOfDay -> NanoSeconds Source # |
Combinators
measure :: forall dt t d u r a. TimeUnit u => Torsor dt u => Instant t dt => Member (Time t d) r => Sem r a -> Sem r (u, a) Source #
while :: forall t d u r. Member (Time t d) r => TimeUnit u => u -> Sem r Bool -> Sem r () Source #
Repeatedly run the action
, sleeping for interval
between executions.
Stops when action
returns False
.
loop :: forall t d u a r. Member (Time t d) r => TimeUnit u => u -> a -> (a -> Sem r a) -> Sem r () Source #
Repeatedly run the action
, sleeping for interval
between executions.
The result of action
is passed back to it for the next run, starting with initial
.