AFSM-0.1.3.1: Arrowized functional state machines

Copyright(c) Hanzhong Xu, Meng Meng 2016,
LicenseMIT License
Maintainerhanzh.xu@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Control.AFSM

Contents

Description

Arrowized functional state machines.

This module is inspired by Yampa and the paper Functional Reactive Programming, Continued* written by Henrik Nilsson, Antony Courtney and John Peterson.

Synopsis

Documentation

data Event a Source #

Event type, there are 4 different events: event a, no event, error event string and exit event.

Instances

Eq a => Eq (Event a) Source # 

Methods

(==) :: Event a -> Event a -> Bool #

(/=) :: Event a -> Event a -> Bool #

Ord a => Ord (Event a) Source # 

Methods

compare :: Event a -> Event a -> Ordering #

(<) :: Event a -> Event a -> Bool #

(<=) :: Event a -> Event a -> Bool #

(>) :: Event a -> Event a -> Bool #

(>=) :: Event a -> Event a -> Bool #

max :: Event a -> Event a -> Event a #

min :: Event a -> Event a -> Event a #

Show a => Show (Event a) Source # 

Methods

showsPrec :: Int -> Event a -> ShowS #

show :: Event a -> String #

showList :: [Event a] -> ShowS #

class SMFunctor f where Source #

Minimal complete definition

smexec

Methods

smexec :: SM s a b -> f a -> (SM s a b, f b) Source #

smfmap :: SM s a b -> f a -> f b Source #

Instances

SMFunctor [] Source # 

Methods

smexec :: SM s a b -> [a] -> (SM s a b, [b]) Source #

smfmap :: SM s a b -> [a] -> [b] Source #

SMFunctor Maybe Source # 

Methods

smexec :: SM s a b -> Maybe a -> (SM s a b, Maybe b) Source #

smfmap :: SM s a b -> Maybe a -> Maybe b Source #

SMFunctor ((->) r) Source # 

Methods

smexec :: SM s a b -> (r -> a) -> (SM s a b, r -> b) Source #

smfmap :: SM s a b -> (r -> a) -> r -> b Source #

SMFunctor (Either a) Source # 

Methods

smexec :: SM s a b -> Either a a -> (SM s a b, Either a b) Source #

smfmap :: SM s a b -> Either a a -> Either a b Source #

SMFunctor ((,) a) Source # 

Methods

smexec :: SM s a b -> (a, a) -> (SM s a b, (a, b)) Source #

smfmap :: SM s a b -> (a, a) -> (a, b) Source #

(SMFunctor f, SMFunctor g) => SMFunctor (Compose * * f g) Source # 

Methods

smexec :: SM s a b -> Compose * * f g a -> (SM s a b, Compose * * f g b) Source #

smfmap :: SM s a b -> Compose * * f g a -> Compose * * f g b Source #

The TF type

newtype TF s a b Source #

TF is a type representing a transition function. s: storage, a: input, b: output Let's explain more about TF. When a state gets an input a, it should do three things base on the storage and input: find the next state, update storage and output b. That's why it looks like this: (storage -> a -> (SM newState newStorage, b)) type TF storage input output = (storage -> input -> (SM storage input output, output)) Also, it is an instance of Arrow, it represents a machine without initial storage. composing two TF represents that two SM shares the same storage

Constructors

TF (s -> a -> (SM s a b, b)) 

transSM2TF :: SM t (s, a) (s, b) -> TF s a b Source #

transform `SM t (s, a) (s, b)` to `TF s a b`

The SM type

data SM s a b Source #

SM is a type representing a state machine. (TF s a b): initial state(transition function), s: initial storage SM storage input output = SM (TF storage input output) storage

Constructors

SM (TF s a b) s 

Instances

Show s => Show (SM s a b) Source # 

Methods

showsPrec :: Int -> SM s a b -> ShowS #

show :: SM s a b -> String #

showList :: [SM s a b] -> ShowS #

SM Constructors

newSM :: (s -> a -> (SM s a b, b)) -> s -> SM s a b Source #

It is the same with the SM constructor.

simpleSM :: (s -> a -> (s, b)) -> s -> SM s a b Source #

build a simple SM which have only one TF.

tf :: SM s a b -> s -> a -> (SM s a b, b) Source #

st :: SM s a b -> s Source #

The SMH type - SM with hidden storage

type SMH a b = SM () a b Source #

SMH is the type of the state machine with hidden or no storage. It is the same type with Circuit a b = Circuit (a -> Circuit a b, b)

newSMH :: (() -> a -> (SMH a b, b)) -> SMH a b Source #

the same constructor with newSM

simpleSMH :: (s -> a -> (s, b)) -> s -> SMH a b Source #

the same constructor with simpleSM

hideStorage :: SM s a b -> SMH a b Source #

hide the Storage type in the transition function.

Source Constructors

buildSrc :: SM s a a -> [a] Source #

Source There are two kinds of source. First one is using the output of `SM s a a` as its input, then it becomes a perpetual motion, :) Second one is a SM which ignore its input, and output something based on its storage. The second one is easier to understand and use.

build a source, for example: buildSrc $ foldlDelaySM (const (+1)) 0 [0..] buildSrc $ foldlDelaySM (+) 1 [1, 2, 4, 8, ...]

simpleSrc :: SM s () a -> [a] Source #

build a simple source, which ignore the inputs fibsSM :: SM (Int, Int) () Int fibsSM = simpleSM ((a, b) () -> ((b, a+b), a)) (0, 1) take 10 $ simpleSrc fibsSM [0,1,1,2,3, ...]simpleSrc :: SM s () a -> [a]

Basic State Machines

constSM :: b -> SM () a b Source #

build a SM which always return b

idSM :: SM () a a Source #

build a SM which just output its input

delaySM :: a -> SM a a a Source #

delay the input with given value. delaySM = foldlDelaySM (const id)

arrSM :: (a -> b) -> SM () a b Source #

build a SM from a function

foldlSM :: (s -> a -> s) -> s -> SM s a s Source #

the same with foldl

foldlDelaySM :: (s -> a -> s) -> s -> SM s a s Source #

the difference from foldlSM is it output the storage first.

Basic SM functions

composeSM :: SM s1 b c -> SM s0 a b -> SM (s0, s1) a c Source #

compose two SM and merge their storage.

(>>>>) :: SM s0 a b -> SM s1 b c -> SM (s0, s1) a c infixr 1 Source #

Left-to-right composition

(<<<<) :: SM s1 b c -> SM s0 a b -> SM (s0, s1) a c infixr 1 Source #

Right-to-left composition

(^>>>) :: (a -> b) -> SM s b c -> SM s a c infixr 1 Source #

(>>>^) :: SM s a b -> (b -> c) -> SM s a c infixr 1 Source #

(^<<<) :: (b -> c) -> SM s a b -> SM s a c infixr 1 Source #

(<<<^) :: SM s b c -> (a -> b) -> SM s a c infixr 1 Source #

firstSM :: SM s a b -> SM s (a, c) (b, c) Source #

secondSM :: SM s a b -> SM s (c, a) (c, b) Source #

(****) :: SM s0 a b -> SM s1 c d -> SM (s0, s1) (a, c) (b, d) infixr 3 Source #

(&&&&) :: SM s0 a b -> SM s1 a c -> SM (s0, s1) a (b, c) infixr 3 Source #

leftSM :: SM s a b -> SM s (Either a c) (Either b c) Source #

rightSM :: SM s a b -> SM s (Either c a) (Either c b) Source #

(++++) :: SM s0 a b -> SM s1 c d -> SM (s0, s1) (Either a c) (Either b d) infixr 2 Source #

(||||) :: SM s0 a c -> SM s1 b c -> SM (s0, s1) (Either a b) c infixr 2 Source #

loopSM :: SM s (a, c) (b, c) -> SM s a b Source #

absorb :: (a1 -> a0) -> (a1 -> b0 -> b1) -> SM s a0 b0 -> SM s a1 b1 Source #

merge :: (a2 -> (a0, a1)) -> (a2 -> b0 -> b1 -> b2) -> SM s0 a0 b0 -> SM s1 a1 b1 -> SM (s0, s1) a2 b2 Source #

High order Machines

execSM :: SM s a b -> SM s [a] [b] Source #

converts SM a b -> SM [a] [b], it is very useful to compose SM a [b] and SM b c to SM a [c].

concatSM :: SM s a [[b]] -> SM s a [b] Source #

Evaluation

step :: SM s a b -> a -> (SM s a b, b) Source #

run SM a b with a.

exec :: SM s a b -> [a] -> (SM s a b, [b]) Source #

execute SM a b with input [a]. Also, it is the map function for SM, perhaps, We should define our own Functor class, the SMFunctor!