Safe Haskell | None |
---|---|
Language | Haskell2010 |
Processes that use only the current and past data.
Essentially this is a data type for the crochetL
function.
- data T a b = Cons !(a -> StateT s Maybe b) !s
- fromStateMaybe :: (a -> StateT s Maybe b) -> s -> T a b
- fromState :: (a -> State s b) -> s -> T a b
- fromSimpleModifier :: Simple s ctrl a b -> T (ctrl, a) b
- fromInitializedModifier :: Initialized s init ctrl a b -> init -> T (ctrl, a) b
- id :: T a a
- map :: (a -> b) -> T a b
- first :: Arrow a => forall b c d. a b c -> a (b, d) (c, d)
- second :: Arrow a => forall b c d. a b c -> a (d, b) (d, c)
- compose :: T a b -> T b c -> T a c
- split :: T a b -> T c d -> T (a, c) (b, d)
- fanout :: T a b -> T a c -> T a (b, c)
- loop :: ArrowLoop a => forall b d c. a (b, d) (c, d) -> a b c
- apply :: (Transform sig a, Transform sig b) => T a b -> sig a -> sig b
- applyFst :: Read sig a => T (a, b) c -> sig a -> T b c
- applySnd :: Read sig b => T (a, b) c -> sig b -> T a c
- applySameType :: Transform sig a => T a a -> sig a -> sig a
- applyConst :: T a b -> a -> T b
- apply2 :: (Read sig a, Transform sig b, Transform sig c) => T (a, b) c -> sig a -> sig b -> sig c
- apply3 :: (Read sig a, Read sig b, Transform sig c, Transform sig d) => T (a, b, c) d -> sig a -> sig b -> sig c -> sig d
- applyStorableChunk :: (Storable a, Storable b) => T a b -> T (Vector a) (Vector b)
- feed :: Read sig a => sig a -> T () a
- feedFst :: Read sig a => sig a -> T b (a, b)
- feedSnd :: Read sig a => sig a -> T b (b, a)
- feedGenericFst :: Read sig a => sig a -> T b (a, b)
- feedGenericSnd :: Read sig a => sig a -> T b (b, a)
- feedConstFst :: a -> T b (a, b)
- feedConstSnd :: a -> T b (b, a)
- crochetL :: (x -> acc -> Maybe (y, acc)) -> acc -> T x y
- mapAccumL :: (x -> acc -> (y, acc)) -> acc -> T x y
- scanL :: (acc -> x -> acc) -> acc -> T x acc
- scanL1 :: (x -> x -> x) -> T x x
- zipWith :: Read sig a => (a -> b -> c) -> sig a -> T b c
- consInit :: x -> T x x
- chainControlled :: [T (c, x) x] -> T (c, x) x
- replicateControlled :: Int -> T (c, x) x -> T (c, x) x
- feedback :: T (a, c) b -> T b c -> T a b
- feedbackControlled :: T ((ctrl, a), c) b -> T (ctrl, b) c -> T (ctrl, a) b
- applyFst' :: Read sig a => T (a, b) c -> sig a -> T b c
- applySnd' :: Read sig b => T (a, b) c -> sig b -> T a c
Documentation
Cf. StreamFusion T
Arrow T Source # | |
ArrowLoop T Source # | |
C T Source # | |
C T Source # | |
Functor (T a) Source # | |
Applicative (T a) Source # | |
Category * T Source # | |
Fractional b => Fractional (T a b) Source # | |
Num b => Num (T a b) Source # | |
C b => C (T a b) Source # | |
C b => C (T a b) Source # | |
C b => C (T a b) Source # | |
type SignalOf T Source # | |
fromSimpleModifier :: Simple s ctrl a b -> T (ctrl, a) b Source #
fromInitializedModifier :: Initialized s init ctrl a b -> init -> T (ctrl, a) b Source #
first :: Arrow a => forall b c d. a b c -> a (b, d) (c, d) #
Send the first component of the input through the argument arrow, and copy the rest unchanged to the output.
second :: Arrow a => forall b c d. a b c -> a (d, b) (d, c) #
A mirror image of first
.
The default definition may be overridden with a more efficient version if desired.
applyFst :: Read sig a => T (a, b) c -> sig a -> T b c Source #
I think this function does too much.
Better use feedFst
and (>>>).
applySnd :: Read sig b => T (a, b) c -> sig b -> T a c Source #
I think this function does too much.
Better use feedSnd
and (>>>).
applySameType :: Transform sig a => T a a -> sig a -> sig a Source #
applyConst :: T a b -> a -> T b Source #
applyConst c x == apply c (repeat x)
apply2 :: (Read sig a, Transform sig b, Transform sig c) => T (a, b) c -> sig a -> sig b -> sig c Source #
apply3 :: (Read sig a, Read sig b, Transform sig c, Transform sig d) => T (a, b, c) d -> sig a -> sig b -> sig c -> sig d Source #
feedGenericFst :: Read sig a => sig a -> T b (a, b) Source #
feedGenericSnd :: Read sig a => sig a -> T b (b, a) Source #
feedConstFst :: a -> T b (a, b) Source #
feedConstSnd :: a -> T b (b, a) Source #
consInit :: x -> T x x Source #
Prepend an element to a signal, but keep the signal length, i.e. drop the last element.
chainControlled :: [T (c, x) x] -> T (c, x) x Source #
replicateControlled :: Int -> T (c, x) x -> T (c, x) x Source #
If T
would be the function type ->
then replicateControlled 3 f
computes
(c,x) -> f(c, f(c, f(c, x)))
.