synthesizer-core-0.8.3: Audio signal processing coded in Haskell: Low level part
Safe HaskellSafe-Inferred
LanguageHaskell2010

Synthesizer.Causal.Process

Description

Processes that use only the current and past data. Essentially this is a data type for the crochetL function.

Synopsis

Documentation

data T a b Source #

Cf. StreamFusion T

Constructors

forall s. Cons !(a -> StateT s Maybe b) !s 

Instances

Instances details
Arrow T Source # 
Instance details

Defined in Synthesizer.Causal.Process

Methods

arr :: (b -> c) -> T b c #

first :: T b c -> T (b, d) (c, d) #

second :: T b c -> T (d, b) (d, c) #

(***) :: T b c -> T b' c' -> T (b, b') (c, c') #

(&&&) :: T b c -> T b c' -> T b (c, c') #

ArrowLoop T Source # 
Instance details

Defined in Synthesizer.Causal.Process

Methods

loop :: T (b, d) (c, d) -> T b c #

C T Source # 
Instance details

Defined in Synthesizer.Causal.Arrow

Methods

apply :: (Transform sig a, Transform sig b) => T a b -> sig a -> sig b Source #

C T Source # 
Instance details

Defined in Synthesizer.Causal.Process

Associated Types

type SignalOf T :: Type -> Type Source #

Methods

toSignal :: T () a -> SignalOf T a Source #

fromSignal :: SignalOf T b -> T a b Source #

Category T Source # 
Instance details

Defined in Synthesizer.Causal.Process

Methods

id :: forall (a :: k). T a a #

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

Applicative (T a) Source # 
Instance details

Defined in Synthesizer.Causal.Process

Methods

pure :: a0 -> T a a0 #

(<*>) :: T a (a0 -> b) -> T a a0 -> T a b #

liftA2 :: (a0 -> b -> c) -> T a a0 -> T a b -> T a c #

(*>) :: T a a0 -> T a b -> T a b #

(<*) :: T a a0 -> T a b -> T a a0 #

Functor (T a) Source # 
Instance details

Defined in Synthesizer.Causal.Process

Methods

fmap :: (a0 -> b) -> T a a0 -> T a b #

(<$) :: a0 -> T a b -> T a a0 #

Num b => Num (T a b) Source # 
Instance details

Defined in Synthesizer.Causal.Process

Methods

(+) :: T a b -> T a b -> T a b #

(-) :: T a b -> T a b -> T a b #

(*) :: T a b -> T a b -> T a b #

negate :: T a b -> T a b #

abs :: T a b -> T a b #

signum :: T a b -> T a b #

fromInteger :: Integer -> T a b #

Fractional b => Fractional (T a b) Source # 
Instance details

Defined in Synthesizer.Causal.Process

Methods

(/) :: T a b -> T a b -> T a b #

recip :: T a b -> T a b #

fromRational :: Rational -> T a b #

C b => C (T a b) Source # 
Instance details

Defined in Synthesizer.Causal.Process

Methods

zero :: T a b #

(+) :: T a b -> T a b -> T a b #

(-) :: T a b -> T a b -> T a b #

negate :: T a b -> T a b #

C b => C (T a b) Source # 
Instance details

Defined in Synthesizer.Causal.Process

Methods

(/) :: T a b -> T a b -> T a b #

recip :: T a b -> T a b #

fromRational' :: Rational -> T a b #

(^-) :: T a b -> Integer -> T a b #

C b => C (T a b) Source # 
Instance details

Defined in Synthesizer.Causal.Process

Methods

(*) :: T a b -> T a b -> T a b #

one :: T a b #

fromInteger :: Integer -> T a b #

(^) :: T a b -> Integer -> T a b #

type SignalOf T Source # 
Instance details

Defined in Synthesizer.Causal.Process

type SignalOf T = T

fromStateMaybe :: (a -> StateT s Maybe b) -> s -> T a b Source #

fromState :: (a -> State s b) -> s -> T a b 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 #

id :: T a a Source #

map :: (a -> b) -> T a b Source #

first :: Arrow a => 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 => 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.

compose :: T a b -> T b c -> T a c Source #

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 :: ArrowLoop a => a (b, d) (c, d) -> a b c #

apply :: (Transform sig a, Transform sig b) => T a b -> sig a -> sig b Source #

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 #

feed :: Read sig a => sig a -> T () a Source #

feedFst :: Read sig a => sig a -> T b (a, b) Source #

feedSnd :: Read sig a => sig 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 y Source #

mapAccumL :: (x -> acc -> (y, acc)) -> acc -> T x y Source #

scanL :: (acc -> x -> acc) -> acc -> T x acc Source #

scanL1 :: (x -> x -> x) -> T x x Source #

zipWith :: Read sig a => (a -> b -> c) -> sig a -> T b c 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))).

feedback :: T (a, c) b -> T b c -> T a b Source #

feedbackControlled :: T ((ctrl, a), c) b -> T (ctrl, b) c -> T (ctrl, a) b Source #

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 (>>>).