synthesizer-core-0.2: Audio signal processing coded in Haskell: Low level partSource codeContentsIndex
Synthesizer.Causal.Process
Description
Processes that use only the current and past data. Essentially this is a data type for the Synthesizer.State.Signal.crochetL function.
Synopsis
data T a b
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
id :: T a a
map :: (a -> b) -> T a b
first
second
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
apply :: T a b -> T a -> T b
applyFst :: T (a, b) c -> T a -> T b c
applySnd :: T (a, b) c -> T b -> T a c
applyGeneric :: Transform sig a b => T a b -> sig a -> sig b
applyGenericSameType :: Transform sig a => T a a -> sig a -> sig a
applyConst :: T a b -> a -> T b
apply2 :: T (a, b) c -> T a -> T b -> T c
apply3 :: T (a, b, c) d -> T a -> T b -> T c -> T d
feed :: T a -> T () a
feedFst :: T a -> T b (a, b)
feedSnd :: T 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
scanL :: (acc -> x -> acc) -> acc -> T x acc
scanL1 :: (x -> x -> x) -> T x x
zipWith :: (a -> b -> c) -> T 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' :: T (a, b) c -> T a -> T b c
applySnd' :: T (a, b) c -> T b -> T a c
Documentation
data T a b Source
Cf. StreamFusion Synthesizer.State.Signal.T
show/hide Instances
fromStateMaybe :: (a -> StateT s Maybe b) -> s -> T a bSource
fromState :: (a -> State s b) -> s -> T a bSource
fromSimpleModifier :: Simple s ctrl a b -> T (ctrl, a) bSource
id :: T a aSource
map :: (a -> b) -> T a bSource
first
second
compose :: T a b -> T b c -> T a cSource
split :: T a b -> T c d -> T (a, c) (b, d)Source
fanout :: T a b -> T a c -> T a (b, c)Source
loop
apply :: T a b -> T a -> T bSource
applyFst :: T (a, b) c -> T a -> T b cSource
applySnd :: T (a, b) c -> T b -> T a cSource
applyGeneric :: Transform sig a b => T a b -> sig a -> sig bSource
applyGenericSameType :: Transform sig a => T a a -> sig a -> sig aSource
applyConst :: T a b -> a -> T bSource
applyConst c x == apply c (repeat x)
apply2 :: T (a, b) c -> T a -> T b -> T cSource
apply3 :: T (a, b, c) d -> T a -> T b -> T c -> T dSource
feed :: T a -> T () aSource
feedFst :: T a -> T b (a, b)Source
feedSnd :: T a -> T b (b, a)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
crochetL :: (x -> acc -> Maybe (y, acc)) -> acc -> T x ySource
scanL :: (acc -> x -> acc) -> acc -> T x accSource
scanL1 :: (x -> x -> x) -> T x xSource
zipWith :: (a -> b -> c) -> T a -> T b cSource
consInit :: x -> T x xSource
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) xSource
replicateControlled :: Int -> T (c, x) x -> T (c, x) xSource
If T would be the function type -> then replicateControlled 3 f computes (c,x) -> f(c, f(c, f(c, x))).
feedback :: T (a, c) b -> T b c -> T a bSource
feedbackControlled :: T ((ctrl, a), c) b -> T (ctrl, b) c -> T (ctrl, a) bSource
applyFst' :: T (a, b) c -> T a -> T b cSource
I think this function does too much. Better use feedFst and (>>>).
applySnd' :: T (a, b) c -> T b -> T a cSource
I think this function does too much. Better use feedSnd and (>>>).
Produced by Haddock version 2.4.2