| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Control.Monad.Class.MonadTimer.SI
Synopsis
- class (MonadDelay m, MonadMonotonicTime m) => MonadDelay m where- threadDelay :: DiffTime -> m ()
 
- class (MonadTimer m, MonadMonotonicTime m) => MonadTimer m where- registerDelay :: DiffTime -> m (TVar m Bool)
- registerDelayCancellable :: DiffTime -> m (STM m TimeoutState, m ())
- timeout :: DiffTime -> m a -> m (Maybe a)
 
- diffTimeToMicrosecondsAsInt :: DiffTime -> Int
- microsecondsAsIntToDiffTime :: Int -> DiffTime
- data DiffTime
- class MonadThread m => MonadFork (m :: Type -> Type)
- class MonadMonotonicTimeNSec m => MonadMonotonicTime m
- class Monad m => MonadTime (m :: Type -> Type)
- data TimeoutState
- defaultRegisterDelay :: forall m timeout. (MonadFork m, MonadMonotonicTime m, MonadSTM m) => NewTimeout m timeout -> AwaitTimeout m timeout -> DiffTime -> m (TVar m Bool)
- defaultRegisterDelayCancellable :: forall m timeout. (MonadFork m, MonadMonotonicTime m, MonadSTM m) => NewTimeout m timeout -> ReadTimeout m timeout -> CancelTimeout m timeout -> AwaitTimeout m timeout -> DiffTime -> m (STM m TimeoutState, m ())
Type classes
class (MonadDelay m, MonadMonotonicTime m) => MonadDelay m where Source #
Methods
threadDelay :: DiffTime -> m () Source #
Instances
| MonadDelay IO Source # | Thread delay.  When the delay is smaller than what  | 
| Defined in Control.Monad.Class.MonadTimer.SI Methods threadDelay :: DiffTime -> IO () Source # | |
| MonadDelay m => MonadDelay (ReaderT r m) Source # | |
| Defined in Control.Monad.Class.MonadTimer.SI Methods threadDelay :: DiffTime -> ReaderT r m () Source # | |
class (MonadTimer m, MonadMonotonicTime m) => MonadTimer m where Source #
Methods
registerDelay :: DiffTime -> m (TVar m Bool) Source #
A register delay function which safe on 32-bit systems.
registerDelayCancellable :: DiffTime -> m (STM m TimeoutState, m ()) Source #
A cancellable register delay which is safe on 32-bit systems and efficient
 for delays smaller than what Int can represent (especially on systems which
 support native timer manager).
timeout :: DiffTime -> m a -> m (Maybe a) Source #
A timeout function.
TODO: IO instance is not safe on 32-bit systems.
Instances
| MonadTimer IO Source # | Like  TODO:  | 
| MonadTimer m => MonadTimer (ReaderT r m) Source # | |
| Defined in Control.Monad.Class.MonadTimer.SI | |
Auxiliary functions
microsecondsAsIntToDiffTime :: Int -> DiffTime Source #
Convert time in microseconds in DiffTime (measured in seconds).
Re-exports
This is a length of time, as measured by a clock.
 Conversion functions such as fromInteger and realToFrac will treat it as seconds.
 For example, (0.010 :: DiffTime) corresponds to 10 milliseconds.
It has a precision of one picosecond (= 10^-12 s). Enumeration functions will treat it as picoseconds.
Instances
| Data DiffTime | |
| Defined in Data.Time.Clock.Internal.DiffTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DiffTime -> c DiffTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DiffTime # toConstr :: DiffTime -> Constr # dataTypeOf :: DiffTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DiffTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DiffTime) # gmapT :: (forall b. Data b => b -> b) -> DiffTime -> DiffTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DiffTime -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DiffTime -> r # gmapQ :: (forall d. Data d => d -> u) -> DiffTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DiffTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DiffTime -> m DiffTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DiffTime -> m DiffTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DiffTime -> m DiffTime # | |
| Enum DiffTime | |
| Defined in Data.Time.Clock.Internal.DiffTime | |
| Num DiffTime | |
| Defined in Data.Time.Clock.Internal.DiffTime | |
| Read DiffTime | |
| Fractional DiffTime | |
| Real DiffTime | |
| Defined in Data.Time.Clock.Internal.DiffTime Methods toRational :: DiffTime -> Rational # | |
| RealFrac DiffTime | |
| Show DiffTime | |
| NFData DiffTime | |
| Defined in Data.Time.Clock.Internal.DiffTime | |
| Eq DiffTime | |
| Ord DiffTime | |
| Defined in Data.Time.Clock.Internal.DiffTime | |
| NoThunks DiffTime | |
class MonadThread m => MonadFork (m :: Type -> Type) #
Minimal complete definition
Instances
| MonadFork IO | |
| Defined in Control.Monad.Class.MonadFork | |
| MonadFork m => MonadFork (ReaderT e m) | |
| Defined in Control.Monad.Class.MonadFork Methods forkIO :: ReaderT e m () -> ReaderT e m (ThreadId (ReaderT e m)) # forkOn :: Int -> ReaderT e m () -> ReaderT e m (ThreadId (ReaderT e m)) # forkIOWithUnmask :: ((forall a. ReaderT e m a -> ReaderT e m a) -> ReaderT e m ()) -> ReaderT e m (ThreadId (ReaderT e m)) # throwTo :: Exception e0 => ThreadId (ReaderT e m) -> e0 -> ReaderT e m () # killThread :: ThreadId (ReaderT e m) -> ReaderT e m () # | |
class MonadMonotonicTimeNSec m => MonadMonotonicTime m Source #
Instances
| MonadMonotonicTime IO Source # | |
| Defined in Control.Monad.Class.MonadTime.SI Methods | |
| MonadMonotonicTime m => MonadMonotonicTime (ReaderT r m) Source # | |
| Defined in Control.Monad.Class.MonadTime.SI Methods getMonotonicTime :: ReaderT r m Time Source # | |
class Monad m => MonadTime (m :: Type -> Type) #
Minimal complete definition
Instances
| MonadTime IO | |
| Defined in Control.Monad.Class.MonadTime Methods getCurrentTime :: IO UTCTime # | |
| MonadTime m => MonadTime (ReaderT r m) | |
| Defined in Control.Monad.Class.MonadTime Methods getCurrentTime :: ReaderT r m UTCTime # | |
data TimeoutState Source #
State of a timeout: pending, fired or cancelled.
Constructors
| TimeoutPending | |
| TimeoutFired | |
| TimeoutCancelled | 
Instances
| Show TimeoutState Source # | |
| Defined in Control.Monad.Class.MonadTimer.NonStandard Methods showsPrec :: Int -> TimeoutState -> ShowS # show :: TimeoutState -> String # showList :: [TimeoutState] -> ShowS # | |
| Eq TimeoutState Source # | |
| Defined in Control.Monad.Class.MonadTimer.NonStandard | |
| Ord TimeoutState Source # | |
| Defined in Control.Monad.Class.MonadTimer.NonStandard Methods compare :: TimeoutState -> TimeoutState -> Ordering # (<) :: TimeoutState -> TimeoutState -> Bool # (<=) :: TimeoutState -> TimeoutState -> Bool # (>) :: TimeoutState -> TimeoutState -> Bool # (>=) :: TimeoutState -> TimeoutState -> Bool # max :: TimeoutState -> TimeoutState -> TimeoutState # min :: TimeoutState -> TimeoutState -> TimeoutState # | |
Default implementations
defaultRegisterDelay :: forall m timeout. (MonadFork m, MonadMonotonicTime m, MonadSTM m) => NewTimeout m timeout -> AwaitTimeout m timeout -> DiffTime -> m (TVar m Bool) Source #
A default implementation of registerDelay which supports delays longer
 then Int; this is especially important on 32-bit systems where maximum
 delay expressed in microseconds is around 35 minutes.
defaultRegisterDelayCancellable :: forall m timeout. (MonadFork m, MonadMonotonicTime m, MonadSTM m) => NewTimeout m timeout -> ReadTimeout m timeout -> CancelTimeout m timeout -> AwaitTimeout m timeout -> DiffTime -> m (STM m TimeoutState, m ()) Source #
A cancellable register delay which is safe on 32-bit systems and efficient
 for delays smaller than what Int can represent (especially on systems which
 support native timer manager).