time-warp-1.1.1.2: Distributed systems execution emulation

Copyright(c) Serokell 2016
LicenseGPL-3 (see the file LICENSE)
MaintainerSerokell <hi@serokell.io>
Stabilityexperimental
PortabilityPOSIX, GHC
Safe HaskellNone
LanguageHaskell2010

Control.TimeWarp.Timed.MonadTimed

Contents

Description

This module defines typeclass MonadTimed with basic functions to manipulate time and threads.

Synopsis

Typeclass with basic functions

class MonadThrow m => MonadTimed m where Source #

Allows time management. Time is specified in microseconds passed from launch point (origin), this time is further called virtual time.

Instance of MonadTimed should satisfy the following law:

  • when defining instance of MonadTrans for a monad, information stored inside the transformer should be tied to thread, and get cloned on forks.

For example, instance MonadTimed m => MonadTimed (StateT s m) is declared such that:

example :: (MonadTimed m, MonadIO m) => StateT Int m ()
example = do
    put 1
    fork $ put 10     -- main thread won't be touched
    wait $ for 1 sec  -- wait for forked thread to execute
    liftIO . print =<< get
>>> runTimedT $ runStateT undefined example
1

When implement instance of this typeclass, don't forget to define ThreadId first.

Methods

virtualTime :: m Microsecond Source #

Acquires virtual time.

currentTime :: m Microsecond Source #

Acquires (pseudo-)real time.

wait :: RelativeToNow -> m () Source #

Waits for specified amount of time.

Use for to specify relative virtual time (counting from now), and till for absolute one.

>>> runTimedT $ wait (for 1 sec) >> wait (for 5 sec) >> timestamp "now"
[6000000µs] now
>>> runTimedT $ wait (for 1 sec) >> wait (till 5 sec) >> timestamp "now"
[5000000µs] now
>>> runTimedT $ wait (for 10 minute 34 sec 52 ms) >> timestamp "now"
[634052000µs] now

fork :: m () -> m (ThreadId m) Source #

Creates another thread of execution, with same point of origin.

myThreadId :: m (ThreadId m) Source #

Acquires current thread id.

throwTo :: Exception e => ThreadId m -> e -> m () Source #

Arises specified exception in specified thread.

timeout :: TimeUnit t => t -> m a -> m a Source #

Throws a MTTimeoutError exception if running action exceeds specified time.

forkSlave :: m () -> m (ThreadId m) Source #

From `slave-thread` library.

Instances

MonadTimed TimedIO Source # 
MonadTimed m => MonadTimed (LoggerNameBox m) Source # 
(CanLog m, MonadIO m, MonadThrow m, MonadCatch m) => MonadTimed (TimedT m) Source # 
MonadTimed (Transfer s) Source # 
MonadTimed m => MonadTimed (StateT s m) Source # 

Methods

virtualTime :: StateT s m Microsecond Source #

currentTime :: StateT s m Microsecond Source #

wait :: RelativeToNow -> StateT s m () Source #

fork :: StateT s m () -> StateT s m (ThreadId (StateT s m)) Source #

myThreadId :: StateT s m (ThreadId (StateT s m)) Source #

throwTo :: Exception e => ThreadId (StateT s m) -> e -> StateT s m () Source #

timeout :: TimeUnit t => t -> StateT s m a -> StateT s m a Source #

forkSlave :: StateT s m () -> StateT s m (ThreadId (StateT s m)) Source #

MonadTimed m => MonadTimed (ResponseT s m) Source # 
MonadTimed m => MonadTimed (Dialog p m) Source # 

Methods

virtualTime :: Dialog p m Microsecond Source #

currentTime :: Dialog p m Microsecond Source #

wait :: RelativeToNow -> Dialog p m () Source #

fork :: Dialog p m () -> Dialog p m (ThreadId (Dialog p m)) Source #

myThreadId :: Dialog p m (ThreadId (Dialog p m)) Source #

throwTo :: Exception e => ThreadId (Dialog p m) -> e -> Dialog p m () Source #

timeout :: TimeUnit t => t -> Dialog p m a -> Dialog p m a Source #

forkSlave :: Dialog p m () -> Dialog p m (ThreadId (Dialog p m)) Source #

MonadTimed m => MonadTimed (ReaderT * r m) Source # 

type family ThreadId (m :: * -> *) :: * Source #

Type of thread identifier.

Instances

type RelativeToNow = Microsecond -> Microsecond Source #

Defines some time point basing on current virtual time.

Helper functions

schedule :: MonadTimed m => RelativeToNow -> m () -> m () Source #

Executes an action somewhere in future in another thread. Use after to specify relative virtual time (counting from now), and at for absolute one.

schedule time action ≡ fork_ $ wait time >> action
example :: (MonadTimed m, MonadIO m) => m ()
example = do
    wait (for 10 sec)
    schedule (after 3 sec) $ timestamp "This would happen at 13 sec"
    schedule (at 15 sec)   $ timestamp "This would happen at 15 sec"
    timestamp "And this happens immediately after start"

invoke :: MonadTimed m => RelativeToNow -> m a -> m a Source #

Executes an action at specified time in current thread. Use after to specify relative virtual time (counting from now), and at for absolute one.

invoke time action ≡ wait time >> action
example :: (MonadTimed m, MonadIO m) => m ()
example = do
    wait (for 10 sec)
    invoke (after 3 sec) $ timestamp "This would happen at 13 sec"
    invoke (after 3 sec) $ timestamp "This would happen at 16 sec"
    invoke (at 20 sec)   $ timestamp "This would happen at 20 sec"
    timestamp "This also happens at 20 sec"

timestamp :: (MonadTimed m, MonadIO m) => String -> m () Source #

Prints current virtual time. For debug purposes.

>>> runTimedT $ wait (for 1 mcs) >> timestamp "Look current time here"
[1µs] Look current time here

fork_ :: MonadTimed m => m () -> m () Source #

Similar to fork, but doesn't return a result.

work :: MonadTimed m => RelativeToNow -> m () -> m () Source #

Creates a thread, which works for specified amount of time, and then gets killThreaded. Use for to specify relative virtual time (counting from now), and till for absolute one.

killThread :: MonadTimed m => ThreadId m -> m () Source #

Arises ThreadKilled exception in specified thread

startTimer :: MonadTimed m => m (m Microsecond) Source #

Counts time since outer monad layer was unwrapped.

example :: (MonadTimed m, MonadIO m) => m ()
example = do
    wait (for 10 sec)
    timer <- startTimer
    wait (for 5 ms)
    passedTime <- timer
    liftIO . print $ passedTime
>>> runTimedT example
5000µs

Time measures

hour :: Int -> Microsecond Source #

Converts a specified time to Microsecond.

minute :: Int -> Microsecond Source #

Converts a specified time to Microsecond.

sec :: Int -> Microsecond Source #

Converts a specified time to Microsecond.

ms :: Int -> Microsecond Source #

Converts a specified time to Microsecond.

mcs :: Int -> Microsecond Source #

Converts a specified time to Microsecond.

hour' :: Double -> Microsecond Source #

Converts a specified fractional time to Microsecond.

minute' :: Double -> Microsecond Source #

Converts a specified fractional time to Microsecond.

sec' :: Double -> Microsecond Source #

Converts a specified fractional time to Microsecond.

ms' :: Double -> Microsecond Source #

Converts a specified fractional time to Microsecond.

mcs' :: Double -> Microsecond Source #

Converts a specified fractional time to Microsecond.

Time specifiers

Following functions are used together with time-controlling functions (wait, invoke and others) and serve for two reasons:

  1. Defines, whether time is counted from origin point or current time point.
  2. Allow different ways to specify time (see Time accumulators)

for :: TimeAccR t => t Source #

Defines RelativeToNow, which refers to time point in specified time after current time point. Supposed to be used with wait and work.

after :: TimeAccR t => t Source #

Synonym to for. Supposed to be used with invoke and schedule.

till :: TimeAccR t => t Source #

Defines RelativeToNow, which refers to time point determined by specified virtual time. Supposed to be used with wait and work.

at :: TimeAccR t => t Source #

Synonym to till. Supposed to be used with invoke and schedule.

now :: RelativeToNow Source #

Refers to current time point.

>>> runTimedT $ invoke now $ timestamp ""
[0µs]

interval :: TimeAccM t => t Source #

Returns a time in microseconds.

>>> print $ interval 1 sec
1000000µs

timepoint :: TimeAccM t => t Source #

Synonym to interval. May be more preferable in some situations.

Time types

Re-export of Data.Time.Units.Microsecond

data Microsecond :: * #

Instances

Enum Microsecond 
Eq Microsecond 
Integral Microsecond 
Data Microsecond 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Microsecond -> c Microsecond #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Microsecond #

toConstr :: Microsecond -> Constr #

dataTypeOf :: Microsecond -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Microsecond) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Microsecond) #

gmapT :: (forall b. Data b => b -> b) -> Microsecond -> Microsecond #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Microsecond -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Microsecond -> r #

gmapQ :: (forall d. Data d => d -> u) -> Microsecond -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Microsecond -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Microsecond -> m Microsecond #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Microsecond -> m Microsecond #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Microsecond -> m Microsecond #

Num Microsecond 
Ord Microsecond 
Read Microsecond 
Real Microsecond 
Show Microsecond 
Ix Microsecond 
TimeUnit Microsecond 
TimeAccM Microsecond Source # 
TimeAccR RelativeToNow Source # 
((~) * a b, TimeAccM t) => TimeAccM (a -> (b -> Microsecond) -> t) Source # 

Methods

interval' :: Microsecond -> a -> (b -> Microsecond) -> t

TimeUnit t => TimeAccR (t -> RelativeToNow) Source # 
((~) * a b, TimeAccR t) => TimeAccR (a -> (b -> Microsecond) -> t) Source # 

Methods

till' :: Microsecond -> a -> (b -> Microsecond) -> t

for' :: Microsecond -> a -> (b -> Microsecond) -> t

Re-export of Data.Time.Units.Millisecond

data Millisecond :: * #

Instances

Enum Millisecond 
Eq Millisecond 
Integral Millisecond 
Data Millisecond 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Millisecond -> c Millisecond #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Millisecond #

toConstr :: Millisecond -> Constr #

dataTypeOf :: Millisecond -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Millisecond) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Millisecond) #

gmapT :: (forall b. Data b => b -> b) -> Millisecond -> Millisecond #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Millisecond -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Millisecond -> r #

gmapQ :: (forall d. Data d => d -> u) -> Millisecond -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Millisecond -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Millisecond -> m Millisecond #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Millisecond -> m Millisecond #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Millisecond -> m Millisecond #

Num Millisecond 
Ord Millisecond 
Read Millisecond 
Real Millisecond 
Show Millisecond 
Ix Millisecond 
TimeUnit Millisecond 

Re-export of Data.Time.Units.Second

data Second :: * #

Instances

Enum Second 
Eq Second 

Methods

(==) :: Second -> Second -> Bool #

(/=) :: Second -> Second -> Bool #

Integral Second 
Data Second 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Second -> c Second #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Second #

toConstr :: Second -> Constr #

dataTypeOf :: Second -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Second) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Second) #

gmapT :: (forall b. Data b => b -> b) -> Second -> Second #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Second -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Second -> r #

gmapQ :: (forall d. Data d => d -> u) -> Second -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Second -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Second -> m Second #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Second -> m Second #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Second -> m Second #

Num Second 
Ord Second 
Read Second 
Real Second 
Show Second 
Ix Second 
TimeUnit Second 

Re-export of Data.Time.Units.Minute

data Minute :: * #

Instances

Enum Minute 
Eq Minute 

Methods

(==) :: Minute -> Minute -> Bool #

(/=) :: Minute -> Minute -> Bool #

Integral Minute 
Data Minute 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Minute -> c Minute #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Minute #

toConstr :: Minute -> Constr #

dataTypeOf :: Minute -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Minute) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Minute) #

gmapT :: (forall b. Data b => b -> b) -> Minute -> Minute #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Minute -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Minute -> r #

gmapQ :: (forall d. Data d => d -> u) -> Minute -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Minute -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Minute -> m Minute #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Minute -> m Minute #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Minute -> m Minute #

Num Minute 
Ord Minute 
Read Minute 
Real Minute 
Show Minute 
Ix Minute 
TimeUnit Minute 

Time accumulators

Time accumulators allow to specify time in pretty complicated ways.

  • Some of them can accept TimeUnit, which fully defines result.
for (5 :: Minute)
  • They can accept several numbers with time measures, which would be sumarized.
for 1 minute 15 sec 10 mcs
for 1.2 minute'

class TimeAccR t Source #

Time accumulator, which evaluates to RelativeToNow. It's implementation is intentionally not visible from this module.

Minimal complete definition

till', for'

Instances

TimeAccR RelativeToNow Source # 
TimeUnit t => TimeAccR (t -> RelativeToNow) Source # 
((~) * a b, TimeAccR t) => TimeAccR (a -> (b -> Microsecond) -> t) Source # 

Methods

till' :: Microsecond -> a -> (b -> Microsecond) -> t

for' :: Microsecond -> a -> (b -> Microsecond) -> t

class TimeAccM t Source #

Time accumulator, which evaluates to Microsecond. It's implementation is intentionally not visible from this module.

Minimal complete definition

interval'

Instances

TimeAccM Microsecond Source # 
((~) * a b, TimeAccM t) => TimeAccM (a -> (b -> Microsecond) -> t) Source # 

Methods

interval' :: Microsecond -> a -> (b -> Microsecond) -> t

Exceptions