Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Home (etc) automation using reactive-banana.
Functional Reactive Programming is a natural fit for home automation, which involves sensor values that vary over time and are used to control actuators.
This library provides a framework and some useful types for using the reactive-banana FRP library for home automation.
Its main abstraction is the Automation
which describes how to process
Event
s from Sensor
s and how to drive actuators such as lights,
and relays in response.
See Reactive.Banana.Automation.Examples for several examples of using this library.
Synopsis
- data Automation sensors actuators a
- runAutomation :: Automation sensors actuators () -> IO sensors -> (actuators -> IO ()) -> (sensors -> IO ()) -> IO ()
- observeAutomation :: Automation sensors actuators () -> IO sensors -> IO ((sensors -> IO ()) -> IO [actuators])
- liftMomentIO :: MomentIO a -> Automation sensors actuators a
- data EventSource a v
- newEventSource :: v -> IO (EventSource a v)
- fromEventSource :: EventSource a v -> v
- gotEvent :: EventSource a v -> a -> IO ()
- getEventFrom :: (sensors -> EventSource a v) -> Automation sensors actuators (Event a)
- data Sensed a
- = SensorUnavailable
- | Sensed a
- sensedEvent :: (sensors -> EventSource (Sensed a) v) -> Automation sensors actuators (Event a)
- sensedBehavior :: (sensors -> EventSource (Sensed a) v) -> Automation sensors actuators (Behavior (Sensed a))
- sensed :: EventSource (Sensed a) v -> a -> IO ()
- (=:) :: EventSource (Sensed a) v -> a -> IO ()
- sensorUnavailable :: EventSource (Sensed a) v -> IO ()
- sensedEventBehavior :: Event (Sensed a) -> Automation sensors actuators (Behavior (Sensed a))
- automationStepper :: a -> Event a -> Automation sensors actuators (Behavior a)
- automationChanges :: Behavior a -> Automation sensors actuators (Event (Future a))
- data Timestamped t a = Timestamped {}
- class Timestamp t where
- getCurrentTimestamp :: IO t
- sensedNow :: Timestamp t => EventSource (Sensed (Timestamped t a)) v -> a -> IO ()
- sensedAt :: Timestamp t => t -> EventSource (Sensed (Timestamped t a)) v -> a -> IO ()
- elapsedTimeSince :: (Num t, Timestamp t) => (a -> Bool) -> Event (Timestamped t a) -> Automation sensors actuators (Event t)
- data ClockSignal a = ClockSignal a
- clockSignal :: Timestamp t => EventSource (ClockSignal t) v -> IO ()
- clockSignalAt :: Timestamp t => t -> EventSource (ClockSignal t) v -> IO ()
- clockSignalBehavior :: Timestamp t => (sensors -> EventSource (ClockSignal t) v) -> Automation sensors actuators (Behavior (Maybe (ClockSignal t)))
- data PowerChange
- actuateEvent :: Event a -> (a -> actuators) -> Automation sensors actuators ()
- actuateFutureEvent :: Event (Future a) -> (a -> actuators) -> Automation sensors actuators ()
- actuateBehavior :: Behavior a -> (a -> actuators) -> Automation sensors actuators ()
- actuateBehaviorMaybe :: Behavior (Maybe a) -> (a -> actuators) -> Automation sensors actuators ()
- data Range t = Range t t
- belowRange :: Ord t => t -> Range t -> Bool
- aboveRange :: Ord t => t -> Range t -> Bool
- inRange :: Ord t => t -> Range t -> Bool
- extendRange :: Ord t => Range t -> t -> Range t
Framework
data Automation sensors actuators a Source #
An Automation receives Event
s from some sensors and decides what
to do, controlling the actuators. It is implemented as a reactive-banana
event network description.
For example, let's make an automation for a fridge, which has a temperature sensor and a relay controlling its power, and should run as needed to keep the temperature in a safe range, while minimizing compressor starts.
data Sensors = Sensors { fridgeTemperature :: EventSource (Sensed Double) () } data Actuators = FridgePower PowerChange deriving (Show) fridge :: Automation Sensors Actuators () fridge = do btemperature <- sensedBehavior fridgeTemperature let bpowerchange = calcpowerchange <$> btemperature actuateBehavior bpowerchange FridgePower where calcpowerchange (Sensed temp) | temp `belowRange` allowedtemp = Just PowerOff | temp `aboveRange` allowedtemp = Just PowerOn | otherwise = Nothing calcpowerchange SensorUnavailable = Nothing allowedtemp = Range 1 4
Automation is a wrapper around reactive-banana's MomentIO
,
but without the MonadIO
instance, so this monad
is limited to using its sensors and actuators for IO. That allows
it to be fully tested using observeAutomation
.
Instances
MonadFix (Automation sensors actuators) Source # | |
Defined in Reactive.Banana.Automation mfix :: (a -> Automation sensors actuators a) -> Automation sensors actuators a # | |
Applicative (Automation sensors actuators) Source # | |
Defined in Reactive.Banana.Automation pure :: a -> Automation sensors actuators a # (<*>) :: Automation sensors actuators (a -> b) -> Automation sensors actuators a -> Automation sensors actuators b # liftA2 :: (a -> b -> c) -> Automation sensors actuators a -> Automation sensors actuators b -> Automation sensors actuators c # (*>) :: Automation sensors actuators a -> Automation sensors actuators b -> Automation sensors actuators b # (<*) :: Automation sensors actuators a -> Automation sensors actuators b -> Automation sensors actuators a # | |
Functor (Automation sensors actuators) Source # | |
Defined in Reactive.Banana.Automation fmap :: (a -> b) -> Automation sensors actuators a -> Automation sensors actuators b # (<$) :: a -> Automation sensors actuators b -> Automation sensors actuators a # | |
Monad (Automation sensors actuators) Source # | |
Defined in Reactive.Banana.Automation (>>=) :: Automation sensors actuators a -> (a -> Automation sensors actuators b) -> Automation sensors actuators b # (>>) :: Automation sensors actuators a -> Automation sensors actuators b -> Automation sensors actuators b # return :: a -> Automation sensors actuators a # | |
MonadMoment (Automation sensors actuators) Source # | All of Reactive.Banana.Combinators can be used with this monad. |
Defined in Reactive.Banana.Automation liftMoment :: Moment a -> Automation sensors actuators a # | |
Monoid (Automation sensors actuators ()) Source # | |
Defined in Reactive.Banana.Automation mempty :: Automation sensors actuators () # mappend :: Automation sensors actuators () -> Automation sensors actuators () -> Automation sensors actuators () # mconcat :: [Automation sensors actuators ()] -> Automation sensors actuators () # | |
Semigroup (Automation sensors actuators ()) Source # | |
Defined in Reactive.Banana.Automation (<>) :: Automation sensors actuators () -> Automation sensors actuators () -> Automation sensors actuators () # sconcat :: NonEmpty (Automation sensors actuators ()) -> Automation sensors actuators () # stimes :: Integral b => b -> Automation sensors actuators () -> Automation sensors actuators () # |
runAutomation :: Automation sensors actuators () -> IO sensors -> (actuators -> IO ()) -> (sensors -> IO ()) -> IO () Source #
Runs an Automation, given a constructor for the sensors, an IO action to drive the actuators, and an IO action that feeds data into the sensors.
Continuing the above example of a fridge, here's how to run it:
mkSensors :: IO Sensors mkSensors = Sensors <$> newEventSource () driveActuators :: Actuators -> IO () driveActuators = print getFridgeTemperature :: IO Double getFridgeTemperature = ... main = runAutomation fridge mkSensors driveActuators $ \sensors -> do getFridgeTemperature >>= sensed (fridgeTemperature sensors)
Note that this function does not return; the sensor feeding action is run in a loop.
observeAutomation :: Automation sensors actuators () -> IO sensors -> IO ((sensors -> IO ()) -> IO [actuators]) Source #
Allows observing what an Automation does. Designed to be especially useful for testing.
The Automation is started, and a runner action is returned. The runner allows updating the sensors, and returns what the Automation wants to do in response.
For example, in ghci:
> runner <- observeAutomation fridge mkSensors > runner $ \sensors -> fridgeTemperature sensors =: 6 [FridgeRelay PowerOn] > runner $ \sensors -> fridgeTemperature sensors =: 3 [] > runner $ \sensors -> fridgeTemperature sensors =: 0.5 [FridgeRelay PowerOff]
Note that internal state is maintained between calls to the runner.
liftMomentIO :: MomentIO a -> Automation sensors actuators a Source #
Allows Reactive.Banana.Framework to be used with this monad.
Events
data EventSource a v Source #
A source of events.
v
is unused by this library, but is provided in case you
need a way to track some extra data about an EventSource such as, for
example, the timestamp of the most recent event.
newEventSource :: v -> IO (EventSource a v) Source #
Construct a new EventSource.
fromEventSource :: EventSource a v -> v Source #
Get extra data from an EventSource.
gotEvent :: EventSource a v -> a -> IO () Source #
Call this to trigger an event.
getEventFrom :: (sensors -> EventSource a v) -> Automation sensors actuators (Event a) Source #
Get an Event from an EventSource.
Sensors
A value read from a sensor.
Sensors are sometimes not available, or have not provided a value yet.
sensedEvent :: (sensors -> EventSource (Sensed a) v) -> Automation sensors actuators (Event a) Source #
Create an Event from sensed values.
The Event only contains values when the sensor provided a reading, not times when it was unavailable.
sensedBehavior :: (sensors -> EventSource (Sensed a) v) -> Automation sensors actuators (Behavior (Sensed a)) Source #
Create a Behavior from sensed values.
sensed :: EventSource (Sensed a) v -> a -> IO () Source #
Call when a sensor has sensed a value.
getFridgeTemperature >>= sensed (fridgeTemperature sensors)
sensorUnavailable :: EventSource (Sensed a) v -> IO () Source #
Call when a sensor is unavailable.
sensedEventBehavior :: Event (Sensed a) -> Automation sensors actuators (Behavior (Sensed a)) Source #
Combinators
automationStepper :: a -> Event a -> Automation sensors actuators (Behavior a) Source #
stepper
lifted into Automation
automationChanges :: Behavior a -> Automation sensors actuators (Event (Future a)) Source #
changes
lifted into Automation
Time
data Timestamped t a Source #
A timestamped value.
In reactive-banana, an Event
is tagged with its time of occurrence,
but that internal representation of time is never exposed. It can be
useful to have an Event
timestamped as occurring at a specific wall
clock time.
See motionActivatedLight
for an example
of using timestamped values, and how to test code that uses them.
Instances
Functor (Timestamped t) Source # | |
Defined in Reactive.Banana.Automation fmap :: (a -> b) -> Timestamped t a -> Timestamped t b # (<$) :: a -> Timestamped t b -> Timestamped t a # | |
(Show t, Show a) => Show (Timestamped t a) Source # | |
Defined in Reactive.Banana.Automation showsPrec :: Int -> Timestamped t a -> ShowS # show :: Timestamped t a -> String # showList :: [Timestamped t a] -> ShowS # |
class Timestamp t where Source #
Class of values that are timestamps.
getCurrentTimestamp :: IO t Source #
Instances
Timestamp POSIXTime Source # | |
Defined in Reactive.Banana.Automation | |
Timestamp UTCTime Source # | |
Defined in Reactive.Banana.Automation | |
Timestamp LocalTime Source # | |
Defined in Reactive.Banana.Automation | |
Timestamp TimeOfDay Source # | |
Defined in Reactive.Banana.Automation | |
Timestamp ZonedTime Source # | |
Defined in Reactive.Banana.Automation |
sensedNow :: Timestamp t => EventSource (Sensed (Timestamped t a)) v -> a -> IO () Source #
Call when a sensor has sensed a value, which will be Timestamped
with
the current time.
sensedAt :: Timestamp t => t -> EventSource (Sensed (Timestamped t a)) v -> a -> IO () Source #
Call when a sensor sensed a value with a particular timestamp.
elapsedTimeSince :: (Num t, Timestamp t) => (a -> Bool) -> Event (Timestamped t a) -> Automation sensors actuators (Event t) Source #
Given a Timestamped
Event
and a function, produces an Event
that contains the elapsed time since the function last matched the
event's value.
motionActivatedLight
has a good example
of using this.
data ClockSignal a Source #
A clock signal.
See nightLight
for an example
of using clock signals, and how to test code that uses them.
It's recommended that any Behavior
that contains a ClockSignal
be constructed to update whenever the clock signals an update.
Instances
Functor ClockSignal Source # | |
Defined in Reactive.Banana.Automation fmap :: (a -> b) -> ClockSignal a -> ClockSignal b # (<$) :: a -> ClockSignal b -> ClockSignal a # | |
Show a => Show (ClockSignal a) Source # | |
Defined in Reactive.Banana.Automation showsPrec :: Int -> ClockSignal a -> ShowS # show :: ClockSignal a -> String # showList :: [ClockSignal a] -> ShowS # | |
Eq a => Eq (ClockSignal a) Source # | |
Defined in Reactive.Banana.Automation (==) :: ClockSignal a -> ClockSignal a -> Bool # (/=) :: ClockSignal a -> ClockSignal a -> Bool # | |
Ord a => Ord (ClockSignal a) Source # | |
Defined in Reactive.Banana.Automation compare :: ClockSignal a -> ClockSignal a -> Ordering # (<) :: ClockSignal a -> ClockSignal a -> Bool # (<=) :: ClockSignal a -> ClockSignal a -> Bool # (>) :: ClockSignal a -> ClockSignal a -> Bool # (>=) :: ClockSignal a -> ClockSignal a -> Bool # max :: ClockSignal a -> ClockSignal a -> ClockSignal a # min :: ClockSignal a -> ClockSignal a -> ClockSignal a # |
clockSignal :: Timestamp t => EventSource (ClockSignal t) v -> IO () Source #
Call repeatedly to feed a clock signal to an Automation
that needs to know what time it is.
clockSignalAt :: Timestamp t => t -> EventSource (ClockSignal t) v -> IO () Source #
Call to feed a particular time to an Automation
.
clockSignalBehavior :: Timestamp t => (sensors -> EventSource (ClockSignal t) v) -> Automation sensors actuators (Behavior (Maybe (ClockSignal t))) Source #
Create a Behavior from a ClockSignal. It will initially be Nothing, and then updates with each incoming clock signal.
Actuators
data PowerChange Source #
For controlling relays and other things that can have their power turned on and off.
Instances
Show PowerChange Source # | |
Defined in Reactive.Banana.Automation showsPrec :: Int -> PowerChange -> ShowS # show :: PowerChange -> String # showList :: [PowerChange] -> ShowS # | |
Eq PowerChange Source # | |
Defined in Reactive.Banana.Automation (==) :: PowerChange -> PowerChange -> Bool # (/=) :: PowerChange -> PowerChange -> Bool # | |
Ord PowerChange Source # | |
Defined in Reactive.Banana.Automation compare :: PowerChange -> PowerChange -> Ordering # (<) :: PowerChange -> PowerChange -> Bool # (<=) :: PowerChange -> PowerChange -> Bool # (>) :: PowerChange -> PowerChange -> Bool # (>=) :: PowerChange -> PowerChange -> Bool # max :: PowerChange -> PowerChange -> PowerChange # min :: PowerChange -> PowerChange -> PowerChange # |
actuateEvent :: Event a -> (a -> actuators) -> Automation sensors actuators () Source #
Makes an Event drive an actuator.
actuateFutureEvent :: Event (Future a) -> (a -> actuators) -> Automation sensors actuators () Source #
Like actuateEvent
but with a Future, as produced by
automationChanges
actuateBehavior :: Behavior a -> (a -> actuators) -> Automation sensors actuators () Source #
Makes a Behavior drive an actuator. This will happen when the Behavior's value changes, but possibly more often as well, depending on how the Behavior is constructed.
actuateBehaviorMaybe :: Behavior (Maybe a) -> (a -> actuators) -> Automation sensors actuators () Source #
Variant of actuateBehavior
that does nothing when a behavior
is Nothing.
Ranges
The range between two values (inclusive).
Note that the position of the two values in the Range constructor is not significant; Range 1 10 == Range 10 1
Range t t |