distributed-process-extras-0.3.5: Cloud Haskell Extras

Copyright(c) Tim Watson Jeff Epstein Alan Zimmerman
LicenseBSD3 (see the file LICENSE)
MaintainerTim Watson
Stabilityexperimental
Portabilitynon-portable (requires concurrency)
Safe HaskellNone
LanguageHaskell98

Control.Distributed.Process.Extras.Time

Contents

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

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 .....

timeToMicros :: TimeUnit -> Int -> Int Source #

converts the supplied TimeUnit to microseconds

data TimeInterval Source #

A time interval.

data TimeUnit Source #

Defines the time unit for a Timeout value

Constructors

Days 
Hours 
Minutes 
Seconds 
Millis 
Micros 

Instances

Eq TimeUnit Source # 
Show TimeUnit Source # 
Generic TimeUnit Source # 

Associated Types

type Rep TimeUnit :: * -> * #

Methods

from :: TimeUnit -> Rep TimeUnit x #

to :: Rep TimeUnit x -> TimeUnit #

Binary TimeUnit Source # 

Methods

put :: TimeUnit -> Put #

get :: Get TimeUnit #

putList :: [TimeUnit] -> Put #

NFData TimeUnit Source # 

Methods

rnf :: TimeUnit -> () #

type Rep TimeUnit Source # 
type Rep TimeUnit = D1 * (MetaData "TimeUnit" "Control.Distributed.Process.Extras.Time" "distributed-process-extras-0.3.5-7qzKH0dWmcLBNm6JMkdrjz" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Days" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Hours" PrefixI False) (U1 *)) (C1 * (MetaCons "Minutes" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "Seconds" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Millis" PrefixI False) (U1 *)) (C1 * (MetaCons "Micros" PrefixI False) (U1 *)))))

data Delay Source #

Represents either a delay of TimeInterval, an infinite wait or no delay (i.e., non-blocking).

Instances

Eq Delay Source # 

Methods

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

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

Num Delay Source #

Allow (+) and (-) operations on Delays

Show Delay Source # 

Methods

showsPrec :: Int -> Delay -> ShowS #

show :: Delay -> String #

showList :: [Delay] -> ShowS #

Generic Delay Source # 

Associated Types

type Rep Delay :: * -> * #

Methods

from :: Delay -> Rep Delay x #

to :: Rep Delay x -> Delay #

Binary Delay Source # 

Methods

put :: Delay -> Put #

get :: Get Delay #

putList :: [Delay] -> Put #

NFData Delay Source # 

Methods

rnf :: Delay -> () #

type Rep Delay Source # 
type Rep Delay = D1 * (MetaData "Delay" "Control.Distributed.Process.Extras.Time" "distributed-process-extras-0.3.5-7qzKH0dWmcLBNm6JMkdrjz" False) ((:+:) * (C1 * (MetaCons "Delay" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TimeInterval))) ((:+:) * (C1 * (MetaCons "Infinity" PrefixI False) (U1 *)) (C1 * (MetaCons "NoDelay" PrefixI False) (U1 *))))

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 

timeout :: Int -> Tag -> ProcessId -> Process () Source #

Sends the calling process TimeoutNotification tag after time microseconds

infiniteWait :: Timeout Source #

Constructs an inifinite Timeout.

noWait :: Timeout Source #

Constructs a no-wait Timeout