machinecell-3.1.0: Arrow based stream transducers

Safe HaskellSafe
LanguageHaskell2010

Control.Arrow.Machine.Misc.Discrete

Contents

Synopsis

Discrete type

This module should be imported manually. Qualified import is recommended.

This module provides an abstraction that continuous values with finite number of changing points.

>>> import qualified Control.Arrow.Machine.Misc.Discrete as D
>>> run (D.hold "apple" >>> D.arr reverse >>> D.edge) ["orange", "grape"]
["elppa", "egnaro", "eparg"]

In above example, input data of "reverse" is continuous. But the "D.edge" transducer extracts changing points without calling string comparison.

This is possible because the intermediate type T has the information of changes together with the value information.

data T a Source

The discrete signal type.

updates :: T a -> Event () Source

value :: T a -> a Source

arr :: ArrowApply a => (b -> c) -> ProcessA a (T b) (T c) Source

arr2 :: ArrowApply a => (b1 -> b2 -> c) -> ProcessA a (T b1, T b2) (T c) Source

arr3 :: ArrowApply a => (b1 -> b2 -> b3 -> c) -> ProcessA a (T b1, T b2, T b3) (T c) Source

arr4 :: ArrowApply a => (b1 -> b2 -> b3 -> b4 -> c) -> ProcessA a (T b1, T b2, T b3, T b4) (T c) Source

arr5 :: ArrowApply a => (b1 -> b2 -> b3 -> b4 -> b5 -> c) -> ProcessA a (T b1, T b2, T b3, T b4, T b5) (T c) Source

constant :: ArrowApply a => c -> ProcessA a b (T c) Source

hold :: ArrowApply a => b -> ProcessA a (Event b) (T b) Source

accum :: ArrowApply a => b -> ProcessA a (Event (b -> b)) (T b) Source

fromEq :: (ArrowApply a, Eq b) => ProcessA a b (T b) Source

edge :: ArrowApply a => ProcessA a (T b) (Event b) Source

asUpdater :: ArrowApply a => a b c -> ProcessA a (T b) (Event c) Source

kSwitch :: ArrowApply a => ProcessA a b (T c) -> ProcessA a (b, T c) (Event t) -> (ProcessA a b (T c) -> t -> ProcessA a b (T c)) -> ProcessA a b (T c) Source

dkSwitch :: ArrowApply a => ProcessA a b (T c) -> ProcessA a (b, T c) (Event t) -> (ProcessA a b (T c) -> t -> ProcessA a b (T c)) -> ProcessA a b (T c) Source

Discrete algebra

Calculations between discrete types.

An example is below.

holdAdd ::
    (ArrowApply a, Num b) =>
    ProcessA a (Event b, Event b) (Discrete b)
holdAdd = proc (evx, evy) ->
  do
    x <- D.hold 0 -< evx
    y <- D.hold 0 -< evy
    D.eval (refer fst + refer snd) -< (x, y)

The last line is equivalent to "arr2 (+) -< (x, y)". Using Alg, you can construct more complex calculations between discrete signals.

newtype Alg a i o Source

Discrete algebra type.

Constructors

Alg 

Fields

eval :: ProcessA a i (T o)
 

Instances

ArrowApply a => Functor (Alg a i) Source 
ArrowApply a => Applicative (Alg a i) Source 
(ArrowApply a, Num o) => Num (Alg a i o) Source 

refer :: ArrowApply a => (e -> T b) -> Alg a e b Source