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.Core

Contents

Description

 

Synopsis

Documentation

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]

idSM :: SM () a a Source #

build a SM which just output its input

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

build a SM which always return b

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.

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

absorb a function. absorbR sm f = absorbRSM sm (arrSM f) absorbL f sm = absorbLSM (arrSM f) sm

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

(^>>>) :: (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 #

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

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

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

compose two SM and merge their storage.

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

Right-to-left composition

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

Left-to-right composition

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

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

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

fanoutSM :: SM s0 a b -> SM s1 a c -> SM (s0, s1) a (b, c) 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 #

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

faninSM :: SM s0 a c -> SM s1 b c -> SM (s0, s1) (Either a b) c 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 #

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].

joinSM :: Monad m => SM s a (m (m b)) -> SM s a (m b) Source #

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

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!

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

fmapSM f sm = sm >>> arr f

Orphan instances

Functor (SM s a) Source # 

Methods

fmap :: (a -> b) -> SM s a a -> SM s a b #

(<$) :: a -> SM s a b -> SM s a a #