goal-core-0.20: Common, non-geometric tools for use with Goal
Safe HaskellSafe-Inferred
LanguageHaskell2010

Goal.Core.Circuit

Description

A set of functions for working with the Arrow known as a Mealy automata, here referred to as Circuits. Circuits are essentialy a way of building composable fold and iterator operations, where some of the values being processed can be hidden.

Synopsis

Circuits

newtype Circuit m a b Source #

An arrow which takes an input, monadically produces an output, and updates an (inaccessable) internal state.

Constructors

Circuit 

Fields

Instances

Instances details
Monad m => Arrow (Circuit m) Source # 
Instance details

Defined in Goal.Core.Circuit

Methods

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

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

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

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

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

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

Defined in Goal.Core.Circuit

Methods

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

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

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

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

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

Defined in Goal.Core.Circuit

Methods

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

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

accumulateFunction :: Monad m => acc -> (a -> acc -> m (b, acc)) -> Circuit m a b Source #

Takes a function from a value and an accumulator (e.g. just a sum value or an evolving set of parameters for some model) to a value and an accumulator. The accumulator is then looped back into the function, returning a Circuit from a to b, which updates the accumulator every step.

accumulateCircuit :: Monad m => acc -> Circuit m (a, acc) (b, acc) -> Circuit m a b Source #

accumulateCircuit takes a Circuit and an inital value and loops it.

streamCircuit :: Monad m => Circuit m a b -> [a] -> m [b] Source #

Feeds a list of inputs into a Circuit and returns the (monadic) list of outputs.

iterateCircuit :: Monad m => Circuit m a b -> [a] -> m b Source #

Feeds a list of inputs into a Circuit automata and returns the final monadic output. Throws an error on the empty list.

loopCircuit :: Monad m => acc -> Circuit m (a, acc) (b, acc) -> Circuit m a (b, acc) Source #

Takes a Circuit and an inital value and loops it, but continues to return both the output and the accumulated value.

loopAccumulator :: Monad m => acc -> Circuit m (a, acc) acc -> Circuit m a acc Source #

Takes a Circuit which only produces an accumulating value, and loops it.

arrM :: Monad m => (a -> m b) -> Circuit m a b Source #

Turn a monadic function into a circuit.

Chains

type Chain m x = Circuit m () x Source #

A Chain is an iterator built on a Circuit. Chain constructors are designed to ensure that the first value returned is the initial value of the iterator (this is not entirely trivial).

chain Source #

Arguments

:: Monad m 
=> x

The initial state

-> (x -> m x)

The transition function

-> Chain m x

The resulting Chain

Creates a Chain from an initial state and a transition function. The first step of the chain returns the initial state, and then continues with generated states.

chainCircuit Source #

Arguments

:: Monad m 
=> x

The initial state

-> Circuit m x x

The transition circuit

-> Chain m x

The resulting Chain

Creates a Chain from an initial state and a transition circuit. The first step of the chain returns the initial state, and then continues with generated states.

streamChain :: Monad m => Int -> Chain m x -> m [x] Source #

Returns the specified number of the given Chains output.

iterateChain :: Monad m => Int -> Chain m x -> m x Source #

Returns the given Chains output at the given index.

skipChain :: Monad m => Int -> Chain m x -> Chain m x Source #

Modify the given Chain so that it returns the initial value, and then skips the specified number of outputs before producing each subsequent output.

skipChain0 :: Monad m => Int -> Chain m x -> Chain m x Source #

Modify the given Chain so that it skips the specified number of outputs before producing each subsequent output (this skips the initial output too).

Recursive Computations

iterateM :: Monad m => Int -> (x -> m x) -> x -> m [x] Source #

Iterate a monadic action the given number of times, returning the complete sequence of values.

iterateM' :: Monad m => Int -> (x -> m x) -> x -> m x Source #

Iterate a monadic action the given number of times, returning the final value.