synthesizer-core-0.6: Audio signal processing coded in Haskell: Low level part

Safe HaskellNone

Synthesizer.Generic.Signal

Description

Type classes that give a uniform interface to storable signals, stateful signals, lists, fusable lists. Some of the signal types require constraints on the element type. Storable signals require Storable elements. Thus we need multiparameter type classes. In this module we collect functions where the element type is not altered by the function.

Synopsis

Documentation

class Storage signal y whereSource

Associated Types

data Constraints signal y :: *Source

Methods

constraints :: signal y -> Constraints signal ySource

Instances

Storage [] y 
Storable y => Storage Vector y 
Storable y => Storage Vector y 
Storage T y 
Storage (T time) y 

class Read0 sig whereSource

Methods

toList :: Storage sig y => sig y -> [y]Source

toState :: Storage sig y => sig y -> T ySource

foldL :: Storage sig y => (s -> y -> s) -> s -> sig y -> sSource

foldR :: Storage sig y => (y -> s -> s) -> s -> sig y -> sSource

index :: Storage sig y => sig y -> Int -> ySource

Instances

Read0 [] 
Read0 Vector 
Read0 Vector 
Read0 T 
(C time, Integral time) => Read0 (T time) 

class (Read (sig y), Read0 sig, Storage sig y) => Read sig y Source

Instances

Read [] y 
Storable y => Read Vector y 
Storable y => Read Vector y 
Read T y 
(C time, Integral time) => Read (T time) y 

class Read0 sig => Transform0 sig whereSource

Methods

cons :: Storage sig y => y -> sig y -> sig ySource

takeWhile :: Storage sig y => (y -> Bool) -> sig y -> sig ySource

dropWhile :: Storage sig y => (y -> Bool) -> sig y -> sig ySource

span :: Storage sig y => (y -> Bool) -> sig y -> (sig y, sig y)Source

viewL :: Storage sig y => sig y -> Maybe (y, sig y)Source

When using viewL for traversing a signal, it is certainly better to convert to State signal first, since this might involve optimized traversing like in case of Storable signals.

viewR :: Storage sig y => sig y -> Maybe (sig y, y)Source

zipWithAppend :: Storage sig y => (y -> y -> y) -> sig y -> sig y -> sig ySource

map :: (Storage sig y0, Storage sig y1) => (y0 -> y1) -> sig y0 -> sig y1Source

scanL :: (Storage sig y0, Storage sig y1) => (y1 -> y0 -> y1) -> y1 -> sig y0 -> sig y1Source

crochetL :: (Storage sig y0, Storage sig y1) => (y0 -> s -> Maybe (y1, s)) -> s -> sig y0 -> sig y1Source

Instances

class (Transform (sig y), Transform0 sig, Read sig y) => Transform sig y Source

Instances

Transform [] y 
Storable y => Transform Vector y 
Storable y => Transform Vector y 
Transform T y 
(C time, Integral time) => Transform (T time) y 

newtype LazySize Source

This type is used for specification of the maximum size of strict packets. Packets can be smaller, can have different sizes in one signal. In some kinds of streams, like lists and stateful generators, the packet size is always 1. The packet size is not just a burden caused by efficiency, but we need control over packet size in applications with feedback.

ToDo: Make the element type of the corresponding signal a type parameter. This helps to distinguish chunk sizes of scalar and vectorised signals.

Constructors

LazySize Int 

defaultLazySize :: LazySizeSource

This can be used for internal signals that have no observable effect on laziness. E.g. when you construct a list by repeat defaultLazySize zero we assume that zero is defined for all Additive types.

class Transform0 sig => Write0 sig whereSource

We could provide the LazySize by a Reader monad, but we don't do that because we expect that the choice of the lazy size is more local than say the choice of the sample rate. E.g. there is no need to have the same laziness coarseness for multiple signal processors.

Methods

fromList :: Storage sig y => LazySize -> [y] -> sig ySource

repeat :: Storage sig y => LazySize -> y -> sig ySource

replicate :: Storage sig y => LazySize -> Int -> y -> sig ySource

iterate :: Storage sig y => LazySize -> (y -> y) -> y -> sig ySource

iterateAssociative :: Storage sig y => LazySize -> (y -> y -> y) -> y -> sig ySource

unfoldR :: Storage sig y => LazySize -> (s -> Maybe (y, s)) -> s -> sig ySource

Instances

Write0 [] 
Write0 Vector 
Write0 T 
(C time, Integral time) => Write0 (T time) 

class (Write0 sig, Transform sig y) => Write sig y Source

Instances

Write [] y 
Storable y => Write Vector y 
Write T y 
(C time, Integral time) => Write (T time) y 

readSVL :: (Storable a => Vector a -> b) -> Storage Vector a => Vector a -> bSource

readSV :: (Storable a => Vector a -> b) -> Storage Vector a => Vector a -> bSource

switchL :: Transform sig y => a -> (y -> sig y -> a) -> sig y -> aSource

switchR :: Transform sig y => a -> (sig y -> y -> a) -> sig y -> aSource

runViewL :: Read sig y => sig y -> (forall s. (s -> Maybe (y, s)) -> s -> x) -> xSource

runSwitchL :: Read sig y => sig y -> (forall s. (forall z. z -> (y -> s -> z) -> s -> z) -> s -> x) -> xSource

singleton :: Transform sig y => y -> sig ySource

mix :: (C y, Transform sig y) => sig y -> sig y -> sig ySource

zip :: (Read sig a, Transform sig b, Transform sig (a, b)) => sig a -> sig b -> sig (a, b)Source

zipWith :: (Read sig a, Transform sig b, Transform sig c) => (a -> b -> c) -> sig a -> sig b -> sig cSource

zipWith3 :: (Read sig a, Read sig b, Transform sig c) => (a -> b -> c -> c) -> sig a -> sig b -> sig c -> sig cSource

zipWithState :: (Transform sig b, Transform sig c) => (a -> b -> c) -> T a -> sig b -> sig cSource

zipWithState3 :: (Transform sig c, Transform sig d) => (a -> b -> c -> d) -> T a -> T b -> sig c -> sig dSource

unzip :: (Transform sig (a, b), Transform sig a, Transform sig b) => sig (a, b) -> (sig a, sig b)Source

unzip3 :: (Transform sig (a, b, c), Transform sig a, Transform sig b, Transform sig c) => sig (a, b, c) -> (sig a, sig b, sig c)Source

takeStateMatch :: (Transform sig a, Transform sig b) => sig a -> T b -> sig bSource

takeStateMatch len xs keeps a prefix of xs of the same length and block structure as len and stores it in the same type of container as len.

delay :: Write sig y => LazySize -> y -> Int -> sig y -> sig ySource

delayLoopSource

Arguments

:: Transform sig y 
=> (sig y -> sig y)

processor that shall be run in a feedback loop

-> sig y

prefix of the output, its length determines the delay

-> sig y 

delayLoopOverlapSource

Arguments

:: (C y, Write sig y) 
=> Int 
-> (sig y -> sig y)

Processor that shall be run in a feedback loop. It's absolutely necessary that this function preserves the chunk structure and that it does not look a chunk ahead. That's guaranteed for processes that do not look ahead at all, like map, crochetL and all of type Causal.Process.

-> sig y

input

-> sig y

output has the same length as the input

sum :: (C a, Read sig a) => sig a -> aSource

sum1 :: (C a, Read sig a) => sig a -> aSource

monoidConcatMap :: (Read sig a, Monoid m) => (a -> m) -> sig a -> mSource

tails :: Transform sig y => sig y -> T (sig y)Source

laxTail :: Transform sig y => sig y -> sig ySource

Like tail, but for an empty signal it simply returns an empty signal.

mapAdjacent :: (Read sig a, Transform sig a) => (a -> a -> a) -> sig a -> sig aSource

modifyStatic :: Transform sig a => Simple s ctrl a a -> ctrl -> sig a -> sig aSource

modifyModulated :: (Transform sig a, Transform sig b, Read sig ctrl) => Simple s ctrl a b -> sig ctrl -> sig a -> sig bSource

Here the control may vary over the time.

linearComb :: (C t y, Read sig t, Read sig y) => sig t -> sig y -> ySource

fromState :: Write sig y => LazySize -> T y -> sig ySource

extendConstant :: Write sig y => LazySize -> sig y -> sig ySource

mapTails :: Transform sig a => (sig a -> a) -> sig a -> sig aSource

mapTailsAlt :: (Transform sig a, Write sig b) => LazySize -> (sig a -> b) -> sig a -> sig bSource

zipWithTails :: (Transform sig a, Transform sig b, Transform sig c) => (a -> sig b -> c) -> sig a -> sig b -> sig cSource

Only non-empty suffixes are processed. More oftenly we might need

 zipWithTails :: (Read sig b, Transform2 sig a) =>
    (b -> sig a -> a) -> sig b -> sig a -> sig a

this would preserve the chunk structure of sig a, but it is a bit more hassle to implement that.

indexByDrop :: Transform sig a => sig a -> Int -> aSource

null :: Read sig => sig -> BoolSource

length :: Read sig => sig -> IntSource

empty :: Monoid sig => sigSource

cycle :: Monoid sig => sig -> sigSource

append :: Monoid sig => sig -> sig -> sigSource

concat :: Monoid sig => [sig] -> sigSource

take :: Transform sig => Int -> sig -> sigSource

drop :: Transform sig => Int -> sig -> sigSource

dropMarginRem :: Transform sig => Int -> Int -> sig -> (Int, sig)Source

splitAt :: Transform sig => Int -> sig -> (sig, sig)Source

reverse :: Transform sig => sig -> sigSource

lengthAtLeast :: Transform sig => Int -> sig -> BoolSource

Like lengthAtLeast n xs = length xs >= n, but is more efficient, because it is more lazy.

lengthAtMost :: Transform sig => Int -> sig -> BoolSource

sliceVertical :: Transform sig => Int -> sig -> T sigSource