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

Safe HaskellNone
LanguageHaskell2010

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 (Write0 sig, Transform sig y) => Write sig y Source #

Instances
Write [] y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Storable y => Write Vector y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Write T y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

(C time, Integral time) => Write (T time) y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

class Transform0 sig => Write0 sig where Source #

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.

Minimal complete definition

fromList, repeat, replicate, iterate, iterateAssociative, unfoldR

Methods

fromList :: Storage (sig y) => LazySize -> [y] -> sig y Source #

repeat :: Storage (sig y) => LazySize -> y -> sig y Source #

replicate :: Storage (sig y) => LazySize -> Int -> y -> sig y Source #

iterate :: Storage (sig y) => LazySize -> (y -> y) -> y -> sig y Source #

iterateAssociative :: Storage (sig y) => LazySize -> (y -> y -> y) -> y -> sig y Source #

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

Instances
Write0 [] Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

fromList :: Storage [y] => LazySize -> [y] -> [y] Source #

repeat :: Storage [y] => LazySize -> y -> [y] Source #

replicate :: Storage [y] => LazySize -> Int -> y -> [y] Source #

iterate :: Storage [y] => LazySize -> (y -> y) -> y -> [y] Source #

iterateAssociative :: Storage [y] => LazySize -> (y -> y -> y) -> y -> [y] Source #

unfoldR :: Storage [y] => LazySize -> (s -> Maybe (y, s)) -> s -> [y] Source #

Write0 Vector Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

fromList :: Storage (Vector y) => LazySize -> [y] -> Vector y Source #

repeat :: Storage (Vector y) => LazySize -> y -> Vector y Source #

replicate :: Storage (Vector y) => LazySize -> Int -> y -> Vector y Source #

iterate :: Storage (Vector y) => LazySize -> (y -> y) -> y -> Vector y Source #

iterateAssociative :: Storage (Vector y) => LazySize -> (y -> y -> y) -> y -> Vector y Source #

unfoldR :: Storage (Vector y) => LazySize -> (s -> Maybe (y, s)) -> s -> Vector y Source #

Write0 T Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

fromList :: Storage (T y) => LazySize -> [y] -> T y Source #

repeat :: Storage (T y) => LazySize -> y -> T y Source #

replicate :: Storage (T y) => LazySize -> Int -> y -> T y Source #

iterate :: Storage (T y) => LazySize -> (y -> y) -> y -> T y Source #

iterateAssociative :: Storage (T y) => LazySize -> (y -> y -> y) -> y -> T y Source #

unfoldR :: Storage (T y) => LazySize -> (s -> Maybe (y, s)) -> s -> T y Source #

(C time, Integral time) => Write0 (T time) Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

fromList :: Storage (T time y) => LazySize -> [y] -> T time y Source #

repeat :: Storage (T time y) => LazySize -> y -> T time y Source #

replicate :: Storage (T time y) => LazySize -> Int -> y -> T time y Source #

iterate :: Storage (T time y) => LazySize -> (y -> y) -> y -> T time y Source #

iterateAssociative :: Storage (T time y) => LazySize -> (y -> y -> y) -> y -> T time y Source #

unfoldR :: Storage (T time y) => LazySize -> (s -> Maybe (y, s)) -> s -> T time y Source #

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 
Instances
Eq LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Ord LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Show LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Semigroup LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Monoid LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Arbitrary LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

C LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

C LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

C LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

C LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

C LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

C LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

split :: LazySize -> LazySize -> (LazySize, (Bool, LazySize)) #

C LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

C LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

C LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

isZero :: LazySize -> Bool #

C LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Transform LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Read LazySize Source # 
Instance details

Defined in Synthesizer.Generic.Signal

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

Instances
Transform [] y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Storable y => Transform Vector y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Storable y => Transform Vector y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Transform T y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

(C time, Integral time) => Transform (T time) y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

class Read0 sig => Transform0 sig where Source #

Minimal complete definition

cons, takeWhile, dropWhile, span, viewL, viewR, zipWithAppend, map, scanL, crochetL

Methods

cons :: Storage (sig y) => y -> sig y -> sig y Source #

takeWhile :: Storage (sig y) => (y -> Bool) -> sig y -> sig y Source #

dropWhile :: Storage (sig y) => (y -> Bool) -> sig y -> sig y Source #

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 y Source #

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

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

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

Instances
Transform0 [] Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

cons :: Storage [y] => y -> [y] -> [y] Source #

takeWhile :: Storage [y] => (y -> Bool) -> [y] -> [y] Source #

dropWhile :: Storage [y] => (y -> Bool) -> [y] -> [y] Source #

span :: Storage [y] => (y -> Bool) -> [y] -> ([y], [y]) Source #

viewL :: Storage [y] => [y] -> Maybe (y, [y]) Source #

viewR :: Storage [y] => [y] -> Maybe ([y], y) Source #

zipWithAppend :: Storage [y] => (y -> y -> y) -> [y] -> [y] -> [y] Source #

map :: (Storage [y0], Storage [y1]) => (y0 -> y1) -> [y0] -> [y1] Source #

scanL :: (Storage [y0], Storage [y1]) => (y1 -> y0 -> y1) -> y1 -> [y0] -> [y1] Source #

crochetL :: (Storage [y0], Storage [y1]) => (y0 -> s -> Maybe (y1, s)) -> s -> [y0] -> [y1] Source #

Transform0 Vector Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

cons :: Storage (Vector y) => y -> Vector y -> Vector y Source #

takeWhile :: Storage (Vector y) => (y -> Bool) -> Vector y -> Vector y Source #

dropWhile :: Storage (Vector y) => (y -> Bool) -> Vector y -> Vector y Source #

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

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

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

zipWithAppend :: Storage (Vector y) => (y -> y -> y) -> Vector y -> Vector y -> Vector y Source #

map :: (Storage (Vector y0), Storage (Vector y1)) => (y0 -> y1) -> Vector y0 -> Vector y1 Source #

scanL :: (Storage (Vector y0), Storage (Vector y1)) => (y1 -> y0 -> y1) -> y1 -> Vector y0 -> Vector y1 Source #

crochetL :: (Storage (Vector y0), Storage (Vector y1)) => (y0 -> s -> Maybe (y1, s)) -> s -> Vector y0 -> Vector y1 Source #

Transform0 Vector Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

cons :: Storage (Vector y) => y -> Vector y -> Vector y Source #

takeWhile :: Storage (Vector y) => (y -> Bool) -> Vector y -> Vector y Source #

dropWhile :: Storage (Vector y) => (y -> Bool) -> Vector y -> Vector y Source #

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

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

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

zipWithAppend :: Storage (Vector y) => (y -> y -> y) -> Vector y -> Vector y -> Vector y Source #

map :: (Storage (Vector y0), Storage (Vector y1)) => (y0 -> y1) -> Vector y0 -> Vector y1 Source #

scanL :: (Storage (Vector y0), Storage (Vector y1)) => (y1 -> y0 -> y1) -> y1 -> Vector y0 -> Vector y1 Source #

crochetL :: (Storage (Vector y0), Storage (Vector y1)) => (y0 -> s -> Maybe (y1, s)) -> s -> Vector y0 -> Vector y1 Source #

Transform0 T Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

cons :: Storage (T y) => y -> T y -> T y Source #

takeWhile :: Storage (T y) => (y -> Bool) -> T y -> T y Source #

dropWhile :: Storage (T y) => (y -> Bool) -> T y -> T y Source #

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

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

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

zipWithAppend :: Storage (T y) => (y -> y -> y) -> T y -> T y -> T y Source #

map :: (Storage (T y0), Storage (T y1)) => (y0 -> y1) -> T y0 -> T y1 Source #

scanL :: (Storage (T y0), Storage (T y1)) => (y1 -> y0 -> y1) -> y1 -> T y0 -> T y1 Source #

crochetL :: (Storage (T y0), Storage (T y1)) => (y0 -> s -> Maybe (y1, s)) -> s -> T y0 -> T y1 Source #

(C time, Integral time) => Transform0 (T time) Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

cons :: Storage (T time y) => y -> T time y -> T time y Source #

takeWhile :: Storage (T time y) => (y -> Bool) -> T time y -> T time y Source #

dropWhile :: Storage (T time y) => (y -> Bool) -> T time y -> T time y Source #

span :: Storage (T time y) => (y -> Bool) -> T time y -> (T time y, T time y) Source #

viewL :: Storage (T time y) => T time y -> Maybe (y, T time y) Source #

viewR :: Storage (T time y) => T time y -> Maybe (T time y, y) Source #

zipWithAppend :: Storage (T time y) => (y -> y -> y) -> T time y -> T time y -> T time y Source #

map :: (Storage (T time y0), Storage (T time y1)) => (y0 -> y1) -> T time y0 -> T time y1 Source #

scanL :: (Storage (T time y0), Storage (T time y1)) => (y1 -> y0 -> y1) -> y1 -> T time y0 -> T time y1 Source #

crochetL :: (Storage (T time y0), Storage (T time y1)) => (y0 -> s -> Maybe (y1, s)) -> s -> T time y0 -> T time y1 Source #

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

Instances
Read [] y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Storable y => Read Vector y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Storable y => Read Vector y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Read T y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

(C time, Integral time) => Read (T time) y Source # 
Instance details

Defined in Synthesizer.Generic.Signal

class Read0 sig where Source #

Minimal complete definition

toList, toState, foldL, foldR, index

Methods

toList :: Storage (sig y) => sig y -> [y] Source #

toState :: Storage (sig y) => sig y -> T y Source #

foldL :: Storage (sig y) => (s -> y -> s) -> s -> sig y -> s Source #

foldR :: Storage (sig y) => (y -> s -> s) -> s -> sig y -> s Source #

index :: Storage (sig y) => sig y -> Int -> y Source #

Instances
Read0 [] Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

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

toState :: Storage [y] => [y] -> T y Source #

foldL :: Storage [y] => (s -> y -> s) -> s -> [y] -> s Source #

foldR :: Storage [y] => (y -> s -> s) -> s -> [y] -> s Source #

index :: Storage [y] => [y] -> Int -> y Source #

Read0 Vector Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

toList :: Storage (Vector y) => Vector y -> [y] Source #

toState :: Storage (Vector y) => Vector y -> T y Source #

foldL :: Storage (Vector y) => (s -> y -> s) -> s -> Vector y -> s Source #

foldR :: Storage (Vector y) => (y -> s -> s) -> s -> Vector y -> s Source #

index :: Storage (Vector y) => Vector y -> Int -> y Source #

Read0 Vector Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

toList :: Storage (Vector y) => Vector y -> [y] Source #

toState :: Storage (Vector y) => Vector y -> T y Source #

foldL :: Storage (Vector y) => (s -> y -> s) -> s -> Vector y -> s Source #

foldR :: Storage (Vector y) => (y -> s -> s) -> s -> Vector y -> s Source #

index :: Storage (Vector y) => Vector y -> Int -> y Source #

Read0 T Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

toList :: Storage (T y) => T y -> [y] Source #

toState :: Storage (T y) => T y -> T y Source #

foldL :: Storage (T y) => (s -> y -> s) -> s -> T y -> s Source #

foldR :: Storage (T y) => (y -> s -> s) -> s -> T y -> s Source #

index :: Storage (T y) => T y -> Int -> y Source #

(C time, Integral time) => Read0 (T time) Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Methods

toList :: Storage (T time y) => T time y -> [y] Source #

toState :: Storage (T time y) => T time y -> T0 y Source #

foldL :: Storage (T time y) => (s -> y -> s) -> s -> T time y -> s Source #

foldR :: Storage (T time y) => (y -> s -> s) -> s -> T time y -> s Source #

index :: Storage (T time y) => T time y -> Int -> y Source #

class Storage signal where Source #

Minimal complete definition

constraints

Associated Types

data Constraints signal :: * Source #

Methods

constraints :: signal -> Constraints signal Source #

Instances
Storage [y] Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Associated Types

data Constraints [y] :: * Source #

Methods

constraints :: [y] -> Constraints [y] Source #

Storable y => Storage (Vector y) Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Associated Types

data Constraints (Vector y) :: * Source #

Storable y => Storage (Vector y) Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Associated Types

data Constraints (Vector y) :: * Source #

Storage (T y) Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Associated Types

data Constraints (T y) :: * Source #

Methods

constraints :: T y -> Constraints (T y) Source #

Storage (T time y) Source # 
Instance details

Defined in Synthesizer.Generic.Signal

Associated Types

data Constraints (T time y) :: * Source #

Methods

constraints :: T time y -> Constraints (T time y) Source #

defaultLazySize :: LazySize Source #

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.

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

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

switchL :: Transform sig y => a -> (y -> sig y -> a) -> sig y -> a Source #

switchR :: Transform sig y => a -> (sig y -> y -> a) -> sig y -> a Source #

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

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

singleton :: Transform sig y => y -> sig y Source #

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

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 c Source #

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

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

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

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 b Source #

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 y Source #

delayLoop Source #

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 

delayLoopOverlap Source #

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 -> a Source #

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

foldMap :: (Read sig a, Monoid m) => (a -> m) -> sig a -> m Source #

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

Deprecated: Use foldMap instead.

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

laxTail :: Transform sig y => sig y -> sig y Source #

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 a Source #

modifyStatic :: Transform sig a => Simple s ctrl a a -> ctrl -> sig a -> sig a Source #

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

Here the control may vary over the time.

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

fromState :: Write sig y => LazySize -> T y -> sig y Source #

extendConstant :: Write sig y => LazySize -> sig y -> sig y Source #

snoc :: Transform sig y => sig y -> y -> sig y Source #

mapTails :: Transform sig a => (sig a -> a) -> sig a -> sig a Source #

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

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

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 -> a Source #

null :: Read sig => sig -> Bool Source #

length :: Read sig => sig -> Int Source #

empty :: Monoid sig => sig Source #

cycle :: Monoid sig => sig -> sig Source #

append :: Monoid sig => sig -> sig -> sig Source #

concat :: Monoid sig => [sig] -> sig Source #

take :: Transform sig => Int -> sig -> sig Source #

drop :: Transform sig => Int -> sig -> sig Source #

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

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

reverse :: Transform sig => sig -> sig Source #

lengthAtLeast :: Transform sig => Int -> sig -> Bool Source #

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

lengthAtMost :: Transform sig => Int -> sig -> Bool Source #

sliceVertical :: Transform sig => Int -> sig -> T sig Source #