distributed-process-client-server-0.2.0: The Cloud Haskell Application Platform

Copyright(c) Tim Watson 2017
LicenseBSD3 (see the file LICENSE)
MaintainerTim Watson <watson.timothy@gmail.com>
Stabilityexperimental
Portabilitynon-portable (requires concurrency)
Safe HaskellNone
LanguageHaskell98

Control.Distributed.Process.ManagedProcess.Timer

Description

This module provides a wrap around a simple Timer that can be started, stopped, reset, cleared, and read. A convenient function is provided for creating a Match expression for the timer.

Notes

The timers defined in this module are based on a TVar Bool. When the client program is -threaded (i.e. rtsSupportsBoundThreads == True), then the timers are set using registerDelay, which is very efficient and relies only no the RTS IO Manager. When we're not -threaded, we fall back to using Control.Distributed.Process.Extras.Timer to set the TVar, which has much the same effect, but requires us to spawn a process to handle setting the TVar - a process which could theoretically die before setting the variable.

Synopsis

Documentation

data Timer Source #

We hold timers in 2 states, each described by a Delay. isActive = isJust . mtSignal the TimerRef is optional since we only use the Timer module from extras when we're unable to registerDelay (i.e. not running under -threaded)

type TimerKey = Int Source #

A key for storing timers in prioritised process backing state.

delayTimer :: Delay -> Timer Source #

Creates a default Timer which is inactive.

startTimer :: Delay -> Process Timer Source #

Starts a Timer Will use the GHC registerDelay API if rtsSupportsBoundThreads == True

stopTimer :: Timer -> Process Timer Source #

Stops a previously started Timer. Has no effect if the Timer is inactive.

resetTimer :: Timer -> Delay -> Process Timer Source #

Clears and restarts a Timer.

clearTimer :: Maybe TimerRef -> Process () Source #

Clears/cancels a running timer. Has no effect if the Timer is inactive.

matchTimeout :: Timer -> [Match (Either TimedOut Message)] Source #

Creates a Match for a given timer, for use with Cloud Haskell's messaging primitives for selective receives.

matchKey :: TimerKey -> Timer -> [Match (Either TimedOut Message)] Source #

Create a match expression for a given Timer. When the timer expires (i.e. the "TVar Bool" is set to True), the Match will return Yield i, where i is the given TimerKey.

matchRun :: (TimerKey -> Process Message) -> TimerKey -> Timer -> [Match Message] Source #

As "matchKey", but instead of a returning Yield i, the generated Match handler evaluates the first argument - and expression from TimerKey to Process Message - to determine its result.

isActive :: Timer -> Bool Source #

True if a Timer is currently active.

readTimer :: TVar Bool -> STM TimedOut Source #

Reads a given TVar Bool for a timer, and returns STM TimedOut once the variable is set to true. Will retry in the meanwhile.

data TimedOut Source #

Used during STM reads on Timers and to implement blocking. Since timers can be associated with a TimerKey, the second constructor for this type yields a key indicating whic Timer it refers to. Note that the user is responsible for establishing and maintaining the mapping between Timers and their keys.

Constructors

TimedOut 
Yield TimerKey 

Instances

Eq TimedOut Source # 
Show TimedOut Source # 
Generic TimedOut Source # 

Associated Types

type Rep TimedOut :: * -> * #

Methods

from :: TimedOut -> Rep TimedOut x #

to :: Rep TimedOut x -> TimedOut #

Binary TimedOut Source # 

Methods

put :: TimedOut -> Put #

get :: Get TimedOut #

putList :: [TimedOut] -> Put #

type Rep TimedOut Source # 
type Rep TimedOut = D1 (MetaData "TimedOut" "Control.Distributed.Process.ManagedProcess.Timer" "distributed-process-client-server-0.2.0-3Nq2WNrfSap4YYGReBe59H" False) ((:+:) (C1 (MetaCons "TimedOut" PrefixI False) U1) (C1 (MetaCons "Yield" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TimerKey))))