mellon-core-0.7.0.3: Control physical access devices

Copyright(c) 2016, Drew Hess
LicenseBSD3
MaintainerDrew Hess <src@drewhess.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Mellon.Controller.Async

Contents

Description

This module implements a thread-safe, asynchronous controller. Scheduled locks are run as background threads, which sleep until their events fire.

Exception safety

All the controller actions provided in this module are exception-safe. If an exception occurs in a controller action (e.g., because the device throws an exception), the controller will be restored to its state as it was immediately prior to the execution of the action, and the exception will be re-thrown. After handling the exception, you can continue to execute actions on the controller, if you wish. However, the controller and the device may be out of sync at that point, or the device may continue to throw exceptions until it can be reset.

The safest action to take after an exception occurs in a controller is to reset the device to a known working state; and then to create, from scratch, a new controller for the device.

Synopsis

An asynchronous controller implementation

data Controller d Source #

A concurrent, thread-safe controller type parameterized on its device type.

Note that the type's constructor is not exported. You must use the controller constructor to create a new value of this type; it ensures that the controller is initialized properly.

controller :: MonadIO m => Maybe NominalDiffTime -> Device d -> m (Controller d) Source #

Create a new Controller value to control the given Device.

Controllers created by this constructor are thread-safe and may be passed around and controlled simultaneously on multiple threads. All actions exported by this module which act on a Controller value are thread-safe.

The controller locks and unlocks the given device in response to user commands and expiring unlocks. The controller assumes that this device has already been initialized and is ready for operation. It also assumes that it exclusively owns the device; do not pass the device to any other controllers or otherwise attempt to control the device while the returned Controller value is live.

The controller treats the device as a critical section; only one thread at a time will issue operations to the device.

In order to synchronize the current device state with the state machine, the constructor will lock the device and set the state machine's initial state to StateLocked before returning the new Controller value.

The optional NominalDiffTime argument can be used to prevent the device from too rapidly switching from the locked->unlocked->locked states (glitching). Effectively, it specifies the minimum amount of time that the controller will unlock the device. This is useful for handling delayed unlock commands (for example, if the user is communicating with the controller via a network connection but the unlock command is delayed in transit because connection is down or lagged), extremely short unlock durations that might damage the physical access device, or hacking attempts. When the controller receives an unlock command, it compares the current time to the unlock command's expiration date. If the difference between the two times is less than the minimum unlock duration, or if the expiration date is in the past, then the controller will effectively ignore the unlock request. If the value of this argument is Nothing or is negative, the controller treats it as a 0 value.

minUnlockTime :: Controller d -> NominalDiffTime Source #

Get the controller's minimum unlock time.

lockController :: MonadIO m => Controller d -> m State Source #

Immediately lock the device controlled by the controller.

Returns the new state of the controller.

unlockController :: MonadIO m => UTCTime -> Controller d -> m State Source #

Immediately unlock the device controlled by the controller, and keep it unlocked until the specified UTCTime.

If the specified time is in the past, then the device will unlock briefly, and then lock again after a brief amount of time. (NOTE: this behavior is considered to be a bug and will be fixed in a subsequent release.)

Returns the new state of the controller.

queryController :: MonadIO m => Controller d -> m State Source #

Query the controller's current state.

Re-exported types

data Device d Source #

A parametric device type which provides two "methods," one to lock the device, and the other to unlock it.

The parameter d is the concrete device type and is used during construction to create the two methods by binding them to actions on the specific device.

For example, the implementation of the mockLockDevice function, which wraps a MockLock in a Device d, looks like this:

mockLockDevice :: MockLock -> Device MockLock
mockLockDevice l =
  Device (liftIO $ lockMockLock l)
         (liftIO $ unlockMockLock l)

A program can construct such a device and use it like so:

>>> ml <- mockLock
>>> let mld = mockLockDevice ml
>>> events ml
[]
>>> lockDevice mld
>>> events ml
[LockEvent ... UTC]
>>> unlockDevice mld
>>> events ml
[LockEvent ... UTC,UnlockEvent ... UTC]

Constructors

Device 

Fields

data State Source #

The state machine's states.

Constructors

StateLocked

The state machine is in the locked state

StateUnlocked !UTCTime

The state machine is unlocked until the specified date.

Instances

Eq State Source # 

Methods

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

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

Data State Source # 

Methods

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

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

toConstr :: State -> Constr #

dataTypeOf :: State -> DataType #

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

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

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

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

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

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

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

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

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

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

Read State Source # 
Show State Source # 

Methods

showsPrec :: Int -> State -> ShowS #

show :: State -> String #

showList :: [State] -> ShowS #

Generic State Source # 

Associated Types

type Rep State :: * -> * #

Methods

from :: State -> Rep State x #

to :: Rep State x -> State #

type Rep State Source # 
type Rep State = D1 (MetaData "State" "Mellon.StateMachine" "mellon-core-0.7.0.3-BJdAbL07PyR3pHmNarPAAw" False) ((:+:) (C1 (MetaCons "StateLocked" PrefixI False) U1) (C1 (MetaCons "StateUnlocked" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime))))