auto: Denotative, locally stateful programming DSL & platform

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

(Up to date documentation is maintained at https://mstksg.github.com/auto)

Read the README first! https://github.com/mstksg/auto/blob/master/README.md , for motivating examples, and concrete explanations of things described here.

auto is a Haskell DSL and platform providing declarative, compositional, denotative semantics for discrete-step, locally stateful, interactive programs, games, and automations, with implicitly derived serialization. It is suited for any domain where either the input or the output can be described as a stream of values: a stream of input events, output views, etc.

auto works by providing a type that encapsulates "value stream transformers", or locally stateful functions; by specifying your program as a (potentially cyclic) graph of relationships between value streams, you create a way of "declaring" a system based simply on static relationships between quantities.

Instead of a "state monad" type solution, where all functions have access to a rigid global state, auto works by specifying relationships which each exist independently and on their own, without any global state.

A more fuller exposition is in the README.md, in this project directory and also online at https://github.com/mstksg/auto/blob/master/README.md; you can get started by reading the tutorial, which is also in this project directory in the tutorial directory, and also incidentally online at https://github.com/mstksg/auto/blob/master/tutorial/tutorial.md. Also, check out the auto-examples repository on github for plenty of real-world and toy examples to learn from; I've also done a blog series on this library, for examples and full tutorials!

Support available on freenode's #haskell-auto, #haskell-game, and also on the github issue tracker for the source repository.

Import Control.Auto to begin!


[Skip to Readme]

Properties

Versions 0.2.0.2, 0.2.0.3, 0.2.0.4, 0.2.0.5, 0.2.0.6, 0.3.0.0, 0.4.0.0, 0.4.1.0, 0.4.1.0, 0.4.2.0, 0.4.2.1, 0.4.2.2, 0.4.2.3, 0.4.3.0, 0.4.3.1
Change log CHANGELOG.md
Dependencies base (>=4.6 && <4.9), bytestring (>=0.10.4.0 && <0.11), cereal (>=0.4.1.1 && <0.5), containers (>=0.5.5.1 && <0.6), deepseq (>=1.3.0.2 && <2.0), MonadRandom (>=0.3.0.1 && <0.4), profunctors (>=4.3 && <5.0), random (>=1.1 && <2.0), semigroups (>=0.16 && <0.17), transformers (>=0.4.2.0 && <0.5) [details]
License MIT
Copyright (c) Justin Le 2015
Author Justin Le
Maintainer justin@jle.im
Category Control
Home page https://github.com/mstksg/auto
Bug tracker https://github.com/mstksg/issues
Source repo head: git clone git://github.com/mstksg/auto.git
Uploaded by jle at 2015-04-06T08:52:29Z

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for auto-0.4.1.0

[back to package description]

Auto

$ cabal install auto

Check it out!

-- Let's impliement a PID feedback controller over a black box system.

import Control.Auto
import Prelude hiding ((.), id)

-- We represent a system as `System`, an `Auto` that takes stream of `Double`s
-- as input and transforms it into a stream of `Double`s as output.  The `m`
-- means that a `System IO` might do IO in the process of creating its ouputs,
-- for instance.
--
type System m = Auto m Double Double

-- A PID controller adjusts the input to the black box system until the
-- response matches the target.  It does this by adjusting the input based on
-- the current error, the cumulative sum, and the consecutative differences.
--
-- See http://en.wikipedia.org/wiki/PID_controller
--
-- Here, we just lay out the "concepts"/time-varying values in our system as a
-- recursive/cyclic graph of dependencies.  It's a feedback system, after all.
--
pid :: MonadFix m => (Double, Double, Double) -> System m -> System m
pid (kp, ki, kd) blackbox = proc target -> do       -- proc syntax; see tutorial
    rec --  err :: Double
        --  the difference of the response from the target
        let err        = target - response

        -- cumulativeSum :: Double
        -- the cumulative sum of the errs
        cumulativeSum <- sumFrom 0 -< err

        -- changes :: Maybe Double
        -- the consecutive differences of the errors, with 'Nothing' at first.
        changes       <- deltas    -< err

        --  adjustment :: Double
        --  the adjustment term, from the PID algorithm
        let adjustment = kp * err
                       + ki * cumulativeSum
                       + kd * fromMaybe 0 changes

        -- the control input is the cumulative sum of the adjustments
        control  <- sumFromD 0 -< adjustment

        -- the response of the system, feeding the control into the blackbox
        response <- blackbox   -< control

    -- the output of this all is the value of the response
    id -< response

What is it?

Auto is a Haskell DSL and platform providing an API with declarative, compositional, denotative semantics for discrete-step, locally stateful, interactive programs, games, and automations, with implicitly derived serialization.

It is suited for any domain where your program's input or output is a stream of values, input events, or output views. At the high-level, it allows you to describe your interactive program or simulation as a value stream transformer, by composition and transformation of other stream transformers. So, things like:

  1. Chat bots
  2. Turn-based games
  3. GUIs
  4. Numerical simulations
  5. Process controllers
  6. Text-based interfaces
  7. (Value) stream transformers, filters, mergers, processors

It's been called "FRP for discrete time contexts".

Intrigued? Excited? Start at the tutorial!

It's a part of this package directory and also on github at the above link. The current development documentation server is found at https://mstksg.github.io/auto.

From there, you can check out my All About Auto series on my blog, where I break sample projects and show to approach projects in real life. You can also find examples and demonstrations in the auto-examples repo on github.

Buzzwords explained!

Support

The official support and discussion channel is #haskell-auto on freenode. You can also usually find me (the maintainer and developer) as jle` on #haskell-game or #haskell. Also, contributions to documentation and tests are welcome! :D

Why Auto?

Auto is distinct from a "state transformer" (state monad, or explicit state passing) in that it gives you the ability to implicitly compose and isolate state transformers and state.

That is, imagine you have two different state monads with different states, and you can compose them together into one giant loop, and:

  1. You don't have to make a new "composite type"; you can add a new component dealing with its own state without changing the total state type.

  2. You can't write anything cross-talking. You can't write anything that can interfere with the internal state of any components; each one is isolated.

So --- Auto is useful over a state monad/state transformer approach in cases where you like to build your problem out of multiple individual components, and compose them all together at once.

Examples include a multiple-module stateful chat bot, where every module of the chat bot consists of its own internal state.

If you used a state monad approach, every time you added a new module with its own state, you'd have to "add it into" your total state type.

This simply does not scale.

Imagine a large architecture, where every composition adds more and more complexity.

Now, imagine you can just throw in another module with its own state without any other component even "caring". Or be able to limit access implicitly, without explicit "limiting through lifting" with zoom from lens, etc. (Without that, you basically have "global state" --- the very thing that we went to Functional Programming/Haskell to avoid in the first place! And the thing that languages have been trying to prevent in the last twenty years of language development. Why go "backwards"?)

In addition to all of these practical reasons, State imposes a large imperative shift in your design.

State forces you to begin modeling your problem as "this happens, then this happens, then this happens". When you choose to use a State monad or State passing approach, you immediately begin to frame your entire program from an imperative approach.

Auto lets you structure your program denotatively and declaratively. It gives you that awesome style that functional programming promised in the first place.

Instead of saying "do this then that", you say "this is how things...just are. This is the structure of my program, and this is the nature of the relationship between each component".

If you're already using Haskell...I shouldn't have to explain to you the benefits of a high-level declarative style over an imperative one :)

Why not Auto?

That being said, there are cases where Auto is either the wrong tool or not very helpful.

Relation to FRP

Auto borrows a lot of concepts from Functional Reactive Programming --- especially arrowized, locally stateful libraries like netwire. At best, Auto can be said to bring a lot of API ideas and borrows certain aspects of the semantic model of FRP and incorporates them as a part of a broader semantic model more suitable for discrete-time discrete-stel contexts. But, users of such libraries would likely be able to quickly pick up Auto, and the reverse is (hopefully) true too.

Note that this library is not meant to be any sort of meaningful substitution for implementing situations which involve concepts of continuous ("real number-valued", as opposed to "integer valued") time (like real-time games); you can "fake" it using Auto, but in those situations, FRP provides a much superior semantics and set of concepts for working in such contexts. That is, you can "fake" it, but you then lose almost all of the benefits of FRP in the first place.

A chatbot

import qualified Data.Map as M
import Data.Map (Map)
import Control.Auto
import Prelude hiding ((.), id)

-- Let's build a big chat bot by combining small chat bots.
-- A "ChatBot" is going to be an `Auto` taking in a stream of tuples of
-- incoming nick, message, and timestamps; the result is a "blip stream" that
-- emits with messages whenever it wants to respond.

type Message   = String
type Nick      = String
type ChatBot m = Auto m (Nick, Message, UTCTime) (Blip [Message])


-- Keeps track of last time a nick has spoken, and allows queries
seenBot :: Monad m => ChatBot m
seenBot = proc (nick, msg, time) -> do          -- proc syntax; see tutorial
    -- seens :: Map Nick UTCTime
    -- Map containing last time each nick has spoken
    seens <- accum addToMap M.empty -< (nick, time)

    -- query :: Blip Nick
    -- blip stream emits whenever someone queries for a last time seen;
    -- emits with the nick queried for
    query <- emitJusts getRequest -< words msg

        -- a function to get a response from a nick query
    let respond :: Nick -> [Message]
        respond qry = case M.lookup qry seens of
                        Just t  -> [qry ++ " last seen at " ++ show t ++ "."]
                        Nothing -> ["No record of " ++ qry ++ "."]

    -- output is, whenever the `query` stream emits, map `respond` to it.
    id -< respond <$> query
  where
    addToMap :: Map Nick UTCTime -> (Nick, UTCTime) -> Map Nick UTCTime
    addToMap mp (nick, time) = M.insert nick time mp
    getRequest ("@seen":request:_) = Just request
    getRequest _                   = Nothing


-- Users can increase and decrease imaginary internet points for other users
karmaBot :: Monad m => ChatBot m
karmaBot = proc (_, msg, _) -> do
    -- karmaBlip :: Blip (Nick, Int)
    -- blip stream emits when someone modifies karma, with nick and increment
    karmaBlip <- emitJusts getComm -< msg

    -- karmas :: Map Nick Int
    -- keeps track of the total karma for each user by updating with karmaBlip
    karmas    <- scanB updateMap M.empty -< karmaBlip

    -- function to look up a nick, if one is asked for
    let lookupKarma :: Nick -> [Message]
        lookupKarma nick = let karm = M.findWithDefault 0 nick karmas
                           in  [nick ++ " has a karma of " ++ show karm ++ "."]

    -- output is, whenever `karmaBlip` stream emits, look up the result
    id -< lookupKarma . fst <$> karmaBlip
  where
    getComm :: String -> Maybe (Nick, Int)
    getComm msg = case words msg of
                    "@addKarma":nick:_ -> Just (nick, 1 )
                    "@subKarma":nick:_ -> Just (nick, -1)
                    "@karma":nick:_    -> Just (nick, 0)
                    _                  -> Nothing
    updateMap :: Map Nick Int -> (Nick, Int) -> Map Nick Int
    updateMap mp (nick, change) = M.insertWith (+) nick change mp


-- Echos inputs prefaced with "@echo"...unless flood limit has been reached
echoBot :: Monad m => ChatBot m
echoBot = proc (nick, msg, time) -> do
    -- echoBlip :: Blip [Message]
    -- blip stream emits when someone wants an echo, with the message
    echoBlip   <- emitJusts getEcho  -< msg

    -- newDayBlip :: Blip UTCTime
    -- blip stream emits whenever the day changes
    newDayBlip <- onChange           -< utctDay time

    -- echoCounts :: Map Nick Int
    -- `countEchos` counts the number of times each user asks for an echo, and
    -- `resetOn` makes it "reset" itself whenever `newDayBlip` emits.
    echoCounts <- resetOn countEchos -< (nick <$ echoBlip, newDayBlip)

        -- has this user flooded today...?
    let hasFlooded = M.lookup nick echoCounts > Just floodLimit
        -- output :: Blip [Message]
        -- blip stream emits whenever someone asks for an echo, limiting flood
        output | hasFlooded = ["No flooding!"] <$ echoBlip
               | otherwise  = echoBlip

    -- output is the `output` blip stream
    id -< output
  where
    floodLimit = 5
    getEcho msg = case words msg of
                    "@echo":xs -> Just [unwords xs]
                    _          -> Nothing
    countEchos :: Auto m (Blip Nick) (Map Nick Int)
    countEchos = scanB countingFunction M.empty
    countingFunction :: Map Nick Int -> Nick -> Map Nick Int
    countingFunction mp nick = M.insertWith (+) nick 1 mp

-- Our final chat bot is the `mconcat` of all the small ones...it forks the
-- input between all three, and mconcats the outputs.
chatBot :: Monad m => ChatBot m
chatBot = mconcat [seenBot, karmaBot, echoBot]

-- Here, our chatbot will automatically serialize itself to "data.dat"
-- whenever it is run.
chatBotSerialized :: ChatBot IO
chatBotSerialized = serializing' "data.dat" chatBot

Open questions