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

Safe HaskellNone

Synthesizer.State.Signal

Contents

Description

ToDo: Better name for the module is certainly Synthesizer.Generator.Signal

Synopsis

Documentation

data T a Source

Cf. StreamFusion Data.Stream

Constructors

forall s . Cons !(StateT s Maybe a) !s 

Instances

Monad T 
Functor T 
Applicative T 
C T 
Write T y 
Transform T y 
Read T y 
Write T y 
Transform T y0 y1 
C y yv => C y (T yv) 
Eq y => Eq (T y) 
Show y => Show (T y) 
Monoid (T y) 
C y => C (T y) 
Transform (T y) 
NFData y => NormalForm (T y) 
Read (T y) 
Transform (T y) 
Read (T y) 

runViewL :: T y -> (forall s. (s -> Maybe (y, s)) -> s -> x) -> xSource

It is a common pattern to use switchL or viewL in a loop in order to traverse a signal. However this needs repeated packing and unpacking of the viewL function and the state. It seems that GHC is not clever enough to detect, that the view function does not change. With runViewL you can unpack a stream once and use an efficient viewL in the loop.

runSwitchL :: T y -> (forall s. (forall z. z -> (y -> s -> z) -> s -> z) -> s -> x) -> xSource

generate :: (acc -> Maybe (y, acc)) -> acc -> T ySource

unfoldR :: (acc -> Maybe (y, acc)) -> acc -> T ySource

generateInfinite :: (acc -> (y, acc)) -> acc -> T ySource

fromList :: [y] -> T ySource

toList :: T y -> [y]Source

fromPiecewiseConstant :: (C time, Integral time) => T time a -> T aSource

iterate :: (a -> a) -> a -> T aSource

iterateAssociative :: (a -> a -> a) -> a -> T aSource

repeat :: a -> T aSource

crochetL :: (x -> acc -> Maybe (y, acc)) -> acc -> T x -> T ySource

scanL :: (acc -> x -> acc) -> acc -> T x -> T accSource

scanLClip :: (acc -> x -> acc) -> acc -> T x -> T accSource

input and output have equal length, that's better for fusion

map :: (a -> b) -> T a -> T bSource

unzip :: T (a, b) -> (T a, T b)Source

This function will recompute the input lists and is thus probably not what you want. If you want to avoid recomputation please consider Causal.Process.

unzip3 :: T (a, b, c) -> (T a, T b, T c)Source

delay1 :: a -> T a -> T aSource

This is a fusion friendly implementation of delay. However, in order to be a crochetL the output has the same length as the input, that is, the last element is removed - at least for finite input.

delay :: y -> Int -> T y -> T ySource

take :: Int -> T a -> T aSource

takeWhile :: (a -> Bool) -> T a -> T aSource

replicate :: Int -> a -> T aSource

functions consuming multiple lists

zipWith :: (a -> b -> c) -> T a -> T b -> T cSource

zipWithStorable :: (Storable b, Storable c) => (a -> b -> c) -> T a -> T b -> T cSource

zipWith3 :: (a -> b -> c -> d) -> T a -> T b -> T c -> T dSource

zipWith4 :: (a -> b -> c -> d -> e) -> T a -> T b -> T c -> T d -> T eSource

zip :: T a -> T b -> T (a, b)Source

zip3 :: T a -> T b -> T c -> T (a, b, c)Source

zip4 :: T a -> T b -> T c -> T d -> T (a, b, c, d)Source

functions based on foldL

foldL' :: (x -> acc -> acc) -> acc -> T x -> accSource

foldL :: (acc -> x -> acc) -> acc -> T x -> accSource

foldL1 :: (x -> x -> x) -> T x -> xSource

equal :: Eq a => T a -> T a -> BoolSource

functions based on foldR

foldR :: (x -> acc -> acc) -> acc -> T x -> accSource

Other functions

null :: T a -> BoolSource

singleton :: a -> T aSource

cons :: a -> T a -> T aSource

This is expensive and should not be used to construct lists iteratively!

viewL :: T a -> Maybe (a, T a)Source

viewR :: Storable a => T a -> Maybe (T a, a)Source

viewRSize :: Storable a => ChunkSize -> T a -> Maybe (T a, a)Source

switchL :: b -> (a -> T a -> b) -> T a -> bSource

switchR :: Storable a => b -> (T a -> a -> b) -> T a -> bSource

extendConstant :: T a -> T aSource

This implementation requires that the input generator has to check repeatedly whether it is finished.

drop :: Int -> T a -> T aSource

dropMarginRem :: Int -> Int -> T a -> (Int, T a)Source

This implementation expects that looking ahead is cheap.

dropMargin :: Int -> Int -> T a -> T aSource

dropMatch :: T b -> T a -> T aSource

index :: Int -> T a -> aSource

splitAt :: Storable a => Int -> T a -> (T a, T a)Source

splitAtSize :: Storable a => ChunkSize -> Int -> T a -> (T a, T a)Source

dropWhile :: (a -> Bool) -> T a -> T aSource

span :: Storable a => (a -> Bool) -> T a -> (T a, T a)Source

spanSize :: Storable a => ChunkSize -> (a -> Bool) -> T a -> (T a, T a)Source

cycle :: T a -> T aSource

mix :: C a => T a -> T a -> T aSource

sub :: C a => T a -> T a -> T aSource

neg :: C a => T a -> T aSource

append :: T a -> T a -> T aSource

appendStored :: Storable a => T a -> T a -> T aSource

appendStoredSize :: Storable a => ChunkSize -> T a -> T a -> T aSource

concat :: [T a] -> T aSource

certainly inefficient because of frequent list deconstruction

concatStored :: Storable a => [T a] -> T aSource

liftA2 :: (a -> b -> c) -> T a -> T b -> T cSource

reverse :: T a -> T aSource

sum :: C a => T a -> aSource

maximum :: Ord a => T a -> aSource

init :: T y -> T ySource

sliceVert :: Int -> T y -> [T y]Source

zapWith :: (a -> a -> b) -> T a -> T bSource

Deprecated: use mapAdjacent

zapWithAlt :: (a -> a -> b) -> T a -> T bSource

Deprecated: use mapAdjacent

mapAdjacent :: (a -> a -> b) -> T a -> T bSource

modifyStatic :: Simple s ctrl a b -> ctrl -> T a -> T bSource

modifyModulated :: Simple s ctrl a b -> T ctrl -> T a -> T bSource

Here the control may vary over the time.

linearComb :: C t y => T t -> T y -> ySource

mapTails :: (T y0 -> y1) -> T y0 -> T y1Source

zipWithTails :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2Source

only non-empty suffixes are processed

zipWithTails1 :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2Source

in contrast to zipWithTails it also generates the empty suffix (once)

zipWithTailsInf :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2Source

in contrast to zipWithTails it appends infinitely many empty suffixes

zipWithAppend :: (y -> y -> y) -> T y -> T y -> T ySource

zipStep :: (s -> Maybe (a, s)) -> (t -> Maybe (a, t)) -> (a -> a -> a) -> (s, t) -> Maybe (a, (s, t))Source

delayLoopSource

Arguments

:: (T y -> T y)

processor that shall be run in a feedback loop

-> T y

prefix of the output, its length determines the delay

-> T y 

delayLoopOverlapSource

Arguments

:: C y 
=> Int 
-> (T y -> T y)

processor that shall be run in a feedback loop

-> T y

input

-> T y

output has the same length as the input

sequence_ :: Monad m => T (m a) -> m ()Source

mapM_ :: Monad m => (a -> m ()) -> T a -> m ()Source

monoidConcat :: Monoid m => T m -> mSource

Counterpart to mconcat.

monoidConcatMap :: Monoid m => (a -> m) -> T a -> mSource

catMaybes :: T (Maybe a) -> T aSource

flattenPairs :: T (a, a) -> T aSource

interleave :: T y -> T y -> T ySource

interleaveAlt :: T y -> T y -> T ySource