| Copyright | (c) Tim Watson Jeff Epstein Alan Zimmerman |
|---|---|
| License | BSD3 (see the file LICENSE) |
| Maintainer | Tim Watson |
| Stability | experimental |
| Portability | non-portable (requires concurrency) |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Control.Distributed.Process.Extras.Time
Description
This module provides facilities for working with time delays and timeouts.
The type Timeout and the timeout family of functions provide mechanisms
for working with threadDelay-like behaviour that operates on microsecond
values.
The TimeInterval and TimeUnit related functions provide an abstraction
for working with various time intervals, whilst the Delay type provides a
corrolary to timeout that works with these.
Synopsis
- microSeconds :: Int -> TimeInterval
- milliSeconds :: Int -> TimeInterval
- seconds :: Int -> TimeInterval
- minutes :: Int -> TimeInterval
- hours :: Int -> TimeInterval
- asTimeout :: TimeInterval -> Int
- after :: Int -> TimeUnit -> Int
- within :: Int -> TimeUnit -> TimeInterval
- timeToMicros :: TimeUnit -> Int -> Int
- data TimeInterval
- data TimeUnit
- data Delay
- timeIntervalToDiffTime :: TimeInterval -> NominalDiffTime
- diffTimeToTimeInterval :: NominalDiffTime -> TimeInterval
- diffTimeToDelay :: NominalDiffTime -> Delay
- delayToDiffTime :: Delay -> NominalDiffTime
- microsecondsToNominalDiffTime :: Integer -> NominalDiffTime
- type Timeout = Maybe Int
- data TimeoutNotification = TimeoutNotification Tag
- timeout :: Int -> Tag -> ProcessId -> Process ()
- infiniteWait :: Timeout
- noWait :: Timeout
Time interval handling
microSeconds :: Int -> TimeInterval Source #
given a number, produces a TimeInterval of microseconds
milliSeconds :: Int -> TimeInterval Source #
given a number, produces a TimeInterval of milliseconds
seconds :: Int -> TimeInterval Source #
given a number, produces a TimeInterval of seconds
minutes :: Int -> TimeInterval Source #
given a number, produces a TimeInterval of minutes
hours :: Int -> TimeInterval Source #
given a number, produces a TimeInterval of hours
asTimeout :: TimeInterval -> Int Source #
converts the supplied TimeInterval to microseconds
after :: Int -> TimeUnit -> Int Source #
Convenience for making timeouts; e.g.,
receiveTimeout (after 3 Seconds) [ match (\"ok" -> return ()) ]
within :: Int -> TimeUnit -> TimeInterval Source #
Convenience for making TimeInterval; e.g.,
let ti = within 5 Seconds in .....
data TimeInterval Source #
A time interval.
Instances
Defines the time unit for a Timeout value
Instances
| Generic TimeUnit Source # | |
| Show TimeUnit Source # | |
| Binary TimeUnit Source # | |
| NFData TimeUnit Source # | |
Defined in Control.Distributed.Process.Extras.Time | |
| Eq TimeUnit Source # | |
| type Rep TimeUnit Source # | |
Defined in Control.Distributed.Process.Extras.Time type Rep TimeUnit = D1 ('MetaData "TimeUnit" "Control.Distributed.Process.Extras.Time" "distributed-process-extras-0.3.9-3PIUq7kIBoQKuBft1CeSET" 'False) ((C1 ('MetaCons "Days" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Hours" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Minutes" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Seconds" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Millis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Micros" 'PrefixI 'False) (U1 :: Type -> Type)))) | |
Represents either a delay of TimeInterval, an infinite wait or no delay
(i.e., non-blocking).
Constructors
| Delay TimeInterval | |
| Infinity | |
| NoDelay |
Instances
| Generic Delay Source # | |
| Num Delay Source # | Allow |
| Show Delay Source # | |
| Binary Delay Source # | |
| NFData Delay Source # | |
Defined in Control.Distributed.Process.Extras.Time | |
| Eq Delay Source # | |
| type Rep Delay Source # | |
Defined in Control.Distributed.Process.Extras.Time type Rep Delay = D1 ('MetaData "Delay" "Control.Distributed.Process.Extras.Time" "distributed-process-extras-0.3.9-3PIUq7kIBoQKuBft1CeSET" 'False) (C1 ('MetaCons "Delay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeInterval)) :+: (C1 ('MetaCons "Infinity" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoDelay" 'PrefixI 'False) (U1 :: Type -> Type))) | |
Conversion To/From NominalDiffTime
timeIntervalToDiffTime :: TimeInterval -> NominalDiffTime Source #
given a TimeInterval, provide an equivalent NominalDiffTim
diffTimeToTimeInterval :: NominalDiffTime -> TimeInterval Source #
given a NominalDiffTim, provide an equivalent TimeInterval@
diffTimeToDelay :: NominalDiffTime -> Delay Source #
given a NominalDiffTim, provide an equivalent Delay@
delayToDiffTime :: Delay -> NominalDiffTime Source #
given a Delay, provide an equivalent NominalDiffTim
microsecondsToNominalDiffTime :: Integer -> NominalDiffTime Source #
Create a NominalDiffTime from a number of microseconds.
(Legacy) Timeout Handling
type Timeout = Maybe Int Source #
Represents a timeout in terms of microseconds, where Nothing stands for
infinity and Just 0, no-delay.
data TimeoutNotification Source #
Send to a process when a timeout expires.
Constructors
| TimeoutNotification Tag |
Instances
| Binary TimeoutNotification Source # | |
Defined in Control.Distributed.Process.Extras.Time Methods put :: TimeoutNotification -> Put # get :: Get TimeoutNotification # putList :: [TimeoutNotification] -> Put # | |
timeout :: Int -> Tag -> ProcessId -> Process () Source #
Sends the calling process TimeoutNotification tag after time microseconds
infiniteWait :: Timeout Source #
Constructs an inifinite Timeout.