-- | `Automation` examples. View source for the code. -- -- These examples are tested by doctest when building this library. -- -- Patches adding examples welcomed! module Reactive.Banana.Automation.Examples where import Reactive.Banana import Reactive.Banana.Frameworks import Reactive.Banana.Automation import Data.Time.Clock.POSIX -- | We'll use a single Sensors type containing all the sensors -- used by the examples below. data Sensors = Sensors { fridgeTemperature :: EventSource (Sensed Double) , motionSensor :: EventSource (Sensed (Timestamped POSIXTime Bool)) } -- | And a single Actuators type containing all the actuators used by the -- examples below. data Actuators = FridgePower PowerChange | LightSwitch PowerChange deriving (Show) -- | For running the examples, you'll need this, to construct a `Sensors` mkSensors :: IO Sensors mkSensors = Sensors <$> newAddHandler <*> newAddHandler -- | A fridge, containing the `fridgeTemperature` sensor and with -- its power controlled by the `FridgePower` actuator. -- -- The fridge starts running when its temperature exceeds a maximum -- safe value. Once the temperature falls below a minimim value, the fridge -- stops running. Note that opening the door of this fridge for a minute -- typically won't cause it to run, unless it was already close to being -- too warm. This behavior was chosen to minimise starts of the compressor, -- but of course other fridge behaviors are also possible; this is only an -- example. -- -- To give this example a try, import this module in ghci and run: -- -- >>> runner <- observeAutomation fridge mkSensors -- >>> runner $ \sensors -> fridgeTemperature sensors =: 6 -- [FridgePower PowerOn] -- >>> runner $ \sensors -> fridgeTemperature sensors =: 3 -- [] -- >>> runner $ \sensors -> fridgeTemperature sensors =: 0.5 -- [FridgePower PowerOff] fridge :: Automation Sensors Actuators fridge sensors actuators = do -- Create a Behavior that reflects the most recently reported -- temperature of the fridge. btemperature <- sensedBehavior (fridgeTemperature sensors) -- Calculate when the fridge should turn on and off. let bpowerchange = calcpowerchange <$> btemperature onBehaviorChangeMaybe bpowerchange (actuators . FridgePower) where calcpowerchange (Sensed temp) | temp `belowRange` allowedtemp = Just PowerOff | temp `aboveRange` allowedtemp = Just PowerOn | otherwise = Nothing calcpowerchange SensorUnavailable = Nothing allowedtemp = Range 1 4 -- | A light that comes on when the `motionSensor` detects movement, -- and remains on for 5 minutes after the last movement. -- -- If this were run in real code, the motion sensor would be triggered -- by running `sensedNow`. -- -- But, for testing, it's useful to specify the time that the sensor -- is triggered, using `sensedAt`. Import this module in ghci and run: -- -- >>> runner <- observeAutomation motionActivatedLight mkSensors -- >>> runner $ \sensors -> sensedAt 0 (motionSensor sensors) True -- [LightSwitch PowerOn] -- >>> runner $ \sensors -> sensedAt 30 (motionSensor sensors) False -- [] -- >>> runner $ \sensors -> sensedAt 60 (motionSensor sensors) True -- [LightSwitch PowerOn] -- >>> runner $ \sensors -> sensedAt 120 (motionSensor sensors) False -- [] -- >>> runner $ \sensors -> sensedAt 400 (motionSensor sensors) False -- [LightSwitch PowerOff] motionActivatedLight :: Automation Sensors Actuators motionActivatedLight sensors actuators = do -- Make an Event that contains the time elapsed since the last -- detected motion. timesincemotion <- elapsedTimeSince (== True) =<< sensedEvent (motionSensor sensors) -- Make a Behavior for the light switch. lightchange <- stepper Nothing $ calcchange <$> timesincemotion onBehaviorChangeMaybe lightchange (actuators . LightSwitch) where calcchange t | t == 0 = Just PowerOn -- motion was just detected | t > 300 = Just PowerOff -- 5 minutes since last motion | otherwise = Nothing