box-0.4.0: boxes

Safe HaskellNone
LanguageHaskell2010

Box.Control

Description

An example of a Box for the command line.

Synopsis

Documentation

data ControlRequest Source #

request ADT

Constructors

Check 
Start 
Stop 
Reset 
Quit 
Instances
Eq ControlRequest Source # 
Instance details

Defined in Box.Control

Data ControlRequest Source # 
Instance details

Defined in Box.Control

Methods

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

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

toConstr :: ControlRequest -> Constr #

dataTypeOf :: ControlRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ControlRequest Source # 
Instance details

Defined in Box.Control

Show ControlRequest Source # 
Instance details

Defined in Box.Control

Generic ControlRequest Source # 
Instance details

Defined in Box.Control

Associated Types

type Rep ControlRequest :: Type -> Type #

type Rep ControlRequest Source # 
Instance details

Defined in Box.Control

type Rep ControlRequest = D1 (MetaData "ControlRequest" "Box.Control" "box-0.4.0-9uzoOHquWyV3T7MIf5USX" False) ((C1 (MetaCons "Check" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Start" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Stop" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Reset" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Quit" PrefixI False) (U1 :: Type -> Type))))

data ControlResponse Source #

response ADT

Constructors

ShuttingDown 
Status (Toggle, Int) 
Info Text 

data Toggle Source #

Constructors

On 
Off 
Instances
Eq Toggle Source # 
Instance details

Defined in Box.Control

Methods

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

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

Read Toggle Source # 
Instance details

Defined in Box.Control

Show Toggle Source # 
Instance details

Defined in Box.Control

Generic Toggle Source # 
Instance details

Defined in Box.Control

Associated Types

type Rep Toggle :: Type -> Type #

Methods

from :: Toggle -> Rep Toggle x #

to :: Rep Toggle x -> Toggle #

type Rep Toggle Source # 
Instance details

Defined in Box.Control

type Rep Toggle = D1 (MetaData "Toggle" "Box.Control" "box-0.4.0-9uzoOHquWyV3T7MIf5USX" False) (C1 (MetaCons "On" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Off" PrefixI False) (U1 :: Type -> Type))

type ControlBox a b m = MonadConc m => Cont m (Box (STM m) (Either ControlResponse a) (Either ControlRequest b)) Source #

A Box that communicates via ControlRequest and ControlResponse or an underlying typed-channel

data ControlConfig Source #

 

Constructors

ControlConfig 

Fields

defaultControlConfig :: ControlConfig Source #

Default is one start, manual start and no autorestart.

consoleControlBox :: ControlBox Text Text IO Source #

a command-line control box.

consoleControlBox_ :: ControlBox_ IO Source #

a command-line control box.

parseControlRequest :: Parser a -> Parser (Either ControlRequest a) Source #

Parse command line requests

controlBox :: ControlConfig -> IO a -> Box (STM IO) ControlResponse ControlRequest -> IO () Source #

an effect that can be started, stopped and restarted (a limited number of times)

controlBoxProcess :: ControlConfig -> ProcessConfig Handle Handle () -> Box (STM IO) (Either ControlResponse Text) (Either ControlRequest Text) -> IO () Source #

an effect that can be started, stopped and restarted (a limited number of times)

testBoxManual :: ControlConfig -> Double -> IO () -> IO () Source #

manual testing > testBoxManual (ControlConfig 1 True (Just 0.5) False) 2.3 (beep 3 1 0.5) Status (On,0) beep 1 beep 2 beep 3 Left ShutDown

testBoxAuto :: ControlConfig -> Double -> [(ControlRequest, Double)] -> IO () -> IO () Source #

auto testing FIXME: Doesn't work with doctest > testBoxAuto (ControlConfig 5 True (Just 0.2) False) 5 [(Check, 0.1), (Start,0.1), (Stop,1), (Start, 0.1), (Check, 0.1), (Reset,0.1)] (beep 2 1 1) Left (Status (On,5)) Left (Status (On,4)) Left (Status (On,4)) beep 1 Left (Status (Off,4)) Left (Status (On,4)) Left (Status (On,3)) Left (Status (On,2)) beep 1 beep 2 beep 1 Left ShuttingDown

testBoxAuto (ControlConfig 1 True (Just 0.5) False) 3 [(Reset,1.1), (Quit, 1)] (beep 3 1 1) Left (Status (On,1)) beep 1 Left ShuttingDown Left (Status (On,-1))

beep :: Int -> Int -> Double -> IO () Source #

action for testing

timeOut :: Double -> ControlBox m a b Source #

A box with a self-destruct timer.

timedRequests :: MonadConc m => [(ControlRequest, Double)] -> Cont m (Emitter (STM m) ControlRequest) Source #

a canned ControlRequest emitter with delays