automaton-1.3: Effectful streams and automata in initial encoding
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Automaton

Synopsis

Constructing automata

newtype Automaton m a b Source #

An effectful automaton in initial encoding.

  • m: The monad in which the automaton performs side effects.
  • a: The type of inputs the automaton constantly consumes.
  • b: The type of outputs the automaton constantly produces.

An effectful automaton with input a is the same as an effectful stream with the additional effect of reading an input value a on every step. This is why automata are defined here as streams.

The API of automata follows that of streams (StreamT and OptimizedStreamT) closely. The prominent addition in automata is now that they are instances of the Category, Arrow, Profunctor, and related type classes. This allows for more ways of creating or composing them.

For example, you can sequentially and parallely compose two automata: @ automaton1 :: Automaton m a b automaton2 :: Automaton m b c

sequentially :: Automaton m a c sequentially = automaton1 >>> automaton2

parallely :: Automaton m (a, b) (b, c) parallely = automaton1 *** automaton2 @ In sequential composition, the output of the first automaton is passed as input to the second one. In parallel composition, both automata receive input simulataneously and process it independently.

Through the Arrow type class, you can use arr to create an automaton from a pure function, and more generally use the arrow syntax extension to define automata.

Constructors

Automaton 

Instances

Instances details
Monad m => Category (Automaton m :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Automaton

Methods

id :: forall (a :: k). Automaton m a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Automaton m b c -> Automaton m a b -> Automaton m a c #

Monad m => Arrow (Automaton m) Source # 
Instance details

Defined in Data.Automaton

Methods

arr :: (b -> c) -> Automaton m b c #

first :: Automaton m b c -> Automaton m (b, d) (c, d) #

second :: Automaton m b c -> Automaton m (d, b) (d, c) #

(***) :: Automaton m b c -> Automaton m b' c' -> Automaton m (b, b') (c, c') #

(&&&) :: Automaton m b c -> Automaton m b c' -> Automaton m b (c, c') #

Monad m => ArrowChoice (Automaton m) Source # 
Instance details

Defined in Data.Automaton

Methods

left :: Automaton m b c -> Automaton m (Either b d) (Either c d) #

right :: Automaton m b c -> Automaton m (Either d b) (Either d c) #

(+++) :: Automaton m b c -> Automaton m b' c' -> Automaton m (Either b b') (Either c c') #

(|||) :: Automaton m b d -> Automaton m c d -> Automaton m (Either b c) d #

MonadFix m => ArrowLoop (Automaton m) Source #

Caution, this can make your program hang. Try to use feedback or unfold where possible, or combine loop with delay.

Instance details

Defined in Data.Automaton

Methods

loop :: Automaton m (b, d) (c, d) -> Automaton m b c #

(Monad m, Alternative m) => ArrowPlus (Automaton m) Source # 
Instance details

Defined in Data.Automaton

Methods

(<+>) :: Automaton m b c -> Automaton m b c -> Automaton m b c #

(Monad m, Alternative m) => ArrowZero (Automaton m) Source # 
Instance details

Defined in Data.Automaton

Methods

zeroArrow :: Automaton m b c #

Monad m => Choice (Automaton m) Source # 
Instance details

Defined in Data.Automaton

Methods

left' :: Automaton m a b -> Automaton m (Either a c) (Either b c) #

right' :: Automaton m a b -> Automaton m (Either c a) (Either c b) #

Monad m => Strong (Automaton m) Source # 
Instance details

Defined in Data.Automaton

Methods

first' :: Automaton m a b -> Automaton m (a, c) (b, c) #

second' :: Automaton m a b -> Automaton m (c, a) (c, b) #

Monad m => Traversing (Automaton m) Source #

Step an automaton several steps at once, depending on how long the input is.

Instance details

Defined in Data.Automaton

Methods

traverse' :: Traversable f => Automaton m a b -> Automaton m (f a) (f b) #

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> Automaton m a b -> Automaton m s t #

Monad m => Profunctor (Automaton m) Source # 
Instance details

Defined in Data.Automaton

Methods

dimap :: (a -> b) -> (c -> d) -> Automaton m b c -> Automaton m a d #

lmap :: (a -> b) -> Automaton m b c -> Automaton m a c #

rmap :: (b -> c) -> Automaton m a b -> Automaton m a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Automaton m a b -> Automaton m a c #

(.#) :: forall a b c q. Coercible b a => Automaton m b c -> q a b -> Automaton m a c #

Alternative m => Alternative (Automaton m a) Source # 
Instance details

Defined in Data.Automaton

Methods

empty :: Automaton m a a0 #

(<|>) :: Automaton m a a0 -> Automaton m a a0 -> Automaton m a a0 #

some :: Automaton m a a0 -> Automaton m a [a0] #

many :: Automaton m a a0 -> Automaton m a [a0] #

Applicative m => Applicative (Automaton m a) Source # 
Instance details

Defined in Data.Automaton

Methods

pure :: a0 -> Automaton m a a0 #

(<*>) :: Automaton m a (a0 -> b) -> Automaton m a a0 -> Automaton m a b #

liftA2 :: (a0 -> b -> c) -> Automaton m a a0 -> Automaton m a b -> Automaton m a c #

(*>) :: Automaton m a a0 -> Automaton m a b -> Automaton m a b #

(<*) :: Automaton m a a0 -> Automaton m a b -> Automaton m a a0 #

Functor m => Functor (Automaton m a) Source # 
Instance details

Defined in Data.Automaton

Methods

fmap :: (a0 -> b) -> Automaton m a a0 -> Automaton m a b #

(<$) :: a0 -> Automaton m a b -> Automaton m a a0 #

Selective m => Selective (Automaton m a) Source # 
Instance details

Defined in Data.Automaton

Methods

select :: Automaton m a (Either a0 b) -> Automaton m a (a0 -> b) -> Automaton m a b #

Align m => Align (Automaton m a) Source # 
Instance details

Defined in Data.Automaton

Methods

nil :: Automaton m a a0 #

Semialign m => Semialign (Automaton m a) Source # 
Instance details

Defined in Data.Automaton

Methods

align :: Automaton m a a0 -> Automaton m a b -> Automaton m a (These a0 b) #

alignWith :: (These a0 b -> c) -> Automaton m a a0 -> Automaton m a b -> Automaton m a c #

(Applicative m, Floating b) => Floating (Automaton m a b) Source # 
Instance details

Defined in Data.Automaton

Methods

pi :: Automaton m a b #

exp :: Automaton m a b -> Automaton m a b #

log :: Automaton m a b -> Automaton m a b #

sqrt :: Automaton m a b -> Automaton m a b #

(**) :: Automaton m a b -> Automaton m a b -> Automaton m a b #

logBase :: Automaton m a b -> Automaton m a b -> Automaton m a b #

sin :: Automaton m a b -> Automaton m a b #

cos :: Automaton m a b -> Automaton m a b #

tan :: Automaton m a b -> Automaton m a b #

asin :: Automaton m a b -> Automaton m a b #

acos :: Automaton m a b -> Automaton m a b #

atan :: Automaton m a b -> Automaton m a b #

sinh :: Automaton m a b -> Automaton m a b #

cosh :: Automaton m a b -> Automaton m a b #

tanh :: Automaton m a b -> Automaton m a b #

asinh :: Automaton m a b -> Automaton m a b #

acosh :: Automaton m a b -> Automaton m a b #

atanh :: Automaton m a b -> Automaton m a b #

log1p :: Automaton m a b -> Automaton m a b #

expm1 :: Automaton m a b -> Automaton m a b #

log1pexp :: Automaton m a b -> Automaton m a b #

log1mexp :: Automaton m a b -> Automaton m a b #

(Applicative m, Num b) => Num (Automaton m a b) Source # 
Instance details

Defined in Data.Automaton

Methods

(+) :: Automaton m a b -> Automaton m a b -> Automaton m a b #

(-) :: Automaton m a b -> Automaton m a b -> Automaton m a b #

(*) :: Automaton m a b -> Automaton m a b -> Automaton m a b #

negate :: Automaton m a b -> Automaton m a b #

abs :: Automaton m a b -> Automaton m a b #

signum :: Automaton m a b -> Automaton m a b #

fromInteger :: Integer -> Automaton m a b #

(Applicative m, Fractional b) => Fractional (Automaton m a b) Source # 
Instance details

Defined in Data.Automaton

Methods

(/) :: Automaton m a b -> Automaton m a b -> Automaton m a b #

recip :: Automaton m a b -> Automaton m a b #

fromRational :: Rational -> Automaton m a b #

(Eq s, Floating s, VectorSpace v s, Applicative m) => VectorSpace (Automaton m a v) (Automaton m a s) Source # 
Instance details

Defined in Data.Automaton

Methods

zeroVector :: Automaton m a v #

(*^) :: Automaton m a s -> Automaton m a v -> Automaton m a v #

(^/) :: Automaton m a v -> Automaton m a s -> Automaton m a v #

(^+^) :: Automaton m a v -> Automaton m a v -> Automaton m a v #

(^-^) :: Automaton m a v -> Automaton m a v -> Automaton m a v #

negateVector :: Automaton m a v -> Automaton m a v #

dot :: Automaton m a v -> Automaton m a v -> Automaton m a s #

norm :: Automaton m a v -> Automaton m a s #

normalize :: Automaton m a v -> Automaton m a v #

unfold Source #

Arguments

:: Applicative m 
=> s

The initial state

-> (a -> s -> Result s b)

The step function

-> Automaton m a b 

Create an Automaton from a state and a pure step function.

unfoldM Source #

Arguments

:: s

The initial state

-> (a -> s -> m (Result s b))

The step function

-> Automaton m a b 

Create an Automaton from a state and an effectful step function.

arrM :: Functor m => (a -> m b) -> Automaton m a b Source #

Consume an input and produce output effectfully, without keeping internal state

constM :: Functor m => m b -> Automaton m a b Source #

Produce output effectfully, without keeping internal state

hoistS :: Monad m => (forall x. m x -> n x) -> Automaton m a b -> Automaton n a b Source #

Apply an arbitrary monad morphism to an automaton.

liftS :: (MonadTrans t, Monad m, Functor (t m)) => Automaton m a b -> Automaton (t m) a b Source #

Lift the monad of an automaton to a transformer.

feedback Source #

Arguments

:: Functor m 
=> c

The additional internal state

-> Automaton m (a, c) (b, c)

The original automaton

-> Automaton m a b 

Extend the internal state and feed back part of the output to the next input.

This is one of the fundamental ways to incorporate recursive dataflow in automata. Given an automaton which consumes an additional input and produces an additional output, the state of the automaton is extended by a further value. This value is used as the additional input, and the resulting additional output is stored in the internal state for the next step.

Running automata

stepAutomaton :: Functor m => Automaton m a b -> a -> m (Result (Automaton m a b) b) Source #

Run one step of an automaton.

This consumes an input value, performs a side effect, and returns an updated automaton together with an output value.

reactimate :: Monad m => Automaton m () () -> m void Source #

Run an automaton with trivial input and output indefinitely.

If the input and output of an automaton does not contain information, all of its meaning is in its effects. This function runs the automaton indefinitely. Since it will never return with a value, this function also has no output (its output is void). The only way it can return is if m includes some effect of termination, e.g. Maybe or Either could terminate with a Nothing or Left value, or IO can raise an exception.

embed Source #

Arguments

:: Monad m 
=> Automaton m a b

The automaton to run

-> [a]

The input values

-> m [b] 

Run an automaton with given input, for a given number of steps.

Especially for tests and batch processing, it is useful to step an automaton with given input.

Modifying automata

withAutomaton :: (Functor m1, Functor m2) => (forall s. (a1 -> m1 (Result s b1)) -> a2 -> m2 (Result s b2)) -> Automaton m1 a1 b1 -> Automaton m2 a2 b2 Source #

Change the output type and effect of an automaton without changing its state type.

mapMaybeS :: Monad m => Automaton m a b -> Automaton m (Maybe a) (Maybe b) Source #

Only step the automaton if the input is Just.

traverseS :: (Monad m, Traversable f) => Automaton m a b -> Automaton m (f a) (f b) Source #

Use an Automaton with a variable amount of input.

traverseS_ :: (Monad m, Traversable f) => Automaton m a b -> Automaton m (f a) () Source #

Like traverseS, discarding the output.

parallely :: Applicative m => Automaton m a b -> Automaton m [a] [b] Source #

Launch arbitrarily many copies of the automaton in parallel.

  • The copies of the automaton are launched on demand as the input lists grow.
  • The n-th copy will always receive the n-th input.
  • If the input list has length n, the n+1-th automaton copy will not be stepped.

Caution: Uses memory of the order of the largest list that was ever input during runtime.

handleAutomaton_ :: Monad m => (forall m. Monad m => StreamT m a -> StreamT m b) -> Automaton m i a -> Automaton m i b Source #

Given a transformation of streams, apply it to an automaton, without changing the input.

handleAutomaton :: Monad m => (StreamT (ReaderT a m) b -> StreamT (ReaderT c n) d) -> Automaton m a b -> Automaton n c d Source #

Given a transformation of streams, apply it to an automaton. The input can be accessed through the ReaderT effect.

concatS :: Monad m => Automaton m () [b] -> Automaton m () b Source #

Buffer the output of an automaton. See concatS.

Examples

withSideEffect Source #

Arguments

:: Monad m 
=> (a -> m b)

For every value passing through the automaton, this function is called and the resulting side effect performed.

-> Automaton m a a 

Pass through a value unchanged, and perform a side effect depending on it

accumulateWith Source #

Arguments

:: Monad m 
=> (a -> b -> b)

The accumulation function

-> b

The initial accumulator

-> Automaton m a b 

Accumulate the input, output the accumulator.

mappendFrom :: (Monoid w, Monad m) => w -> Automaton m w w Source #

Like accumulateWith, with mappend as the accumulation function.

delay Source #

Arguments

:: Applicative m 
=> a

The value to output on the first step

-> Automaton m a a 

Delay the input by one step.

prepend :: Monad m => b -> Automaton m a b -> Automaton m a b Source #

Delay an automaton by one step by prepending one value to the output.

On the first step, the given initial output is returned. On all subsequent steps, the automaton is stepped with the previous input.

mappendS :: (Monoid w, Monad m) => Automaton m w w Source #

Like mappendFrom, initialised at mempty.

sumFrom :: (VectorSpace v s, Monad m) => v -> Automaton m v v Source #

Sum up all inputs so far, with an explicit initial value.

sumS :: (Monad m, VectorSpace v s) => Automaton m v v Source #

Like sumFrom, initialised at 0.

sumN :: (Monad m, Num a) => Automaton m a a Source #

Sum up all inputs so far, initialised at 0.

count :: (Num n, Monad m) => Automaton m a n Source #

Count the natural numbers, beginning at 1.

lastS :: Monad m => a -> Automaton m (Maybe a) a Source #

Remembers the last Just value, defaulting to the given initialisation value.