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

Safe HaskellNone
LanguageHaskell2010

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

Cons !(StateT s Maybe a) !s 

Instances

Monad T Source # 

Methods

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

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

return :: a -> T a #

fail :: String -> T a #

Functor T Source # 

Methods

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

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

Applicative T Source # 

Methods

pure :: a -> T a #

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

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

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

Foldable T Source # 

Methods

fold :: Monoid m => T m -> m #

foldMap :: Monoid m => (a -> m) -> T a -> m #

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

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

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

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

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

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

toList :: T a -> [a] #

null :: T a -> Bool #

length :: T a -> Int #

elem :: Eq a => a -> T a -> Bool #

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

minimum :: Ord a => T a -> a #

sum :: Num a => T a -> a #

product :: Num a => T a -> a #

C T Source # 

Methods

format :: Show x => Int -> T x -> ShowS Source #

Write0 T Source # 

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 #

Transform0 T Source # 

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 #

Read0 T Source # 

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 #

Write T y Source # 
Transform T y Source # 
Read T y Source # 
Write T y Source # 

Methods

unfoldRN :: T -> (s -> Maybe (y, s)) -> s -> T y Source #

C y yv => C y (T yv) Source # 

Methods

(*>) :: y -> T yv -> T yv #

Eq y => Eq (T y) Source # 

Methods

(==) :: T y -> T y -> Bool #

(/=) :: T y -> T y -> Bool #

Show y => Show (T y) Source # 

Methods

showsPrec :: Int -> T y -> ShowS #

show :: T y -> String #

showList :: [T y] -> ShowS #

Monoid (T y) Source # 

Methods

mempty :: T y #

mappend :: T y -> T y -> T y #

mconcat :: [T y] -> T y #

C y => C (T y) Source # 

Methods

zero :: T y #

(+) :: T y -> T y -> T y #

(-) :: T y -> T y -> T y #

negate :: T y -> T y #

Transform (T y) Source # 

Methods

take :: Int -> T y -> T y Source #

drop :: Int -> T y -> T y Source #

dropMarginRem :: Int -> Int -> T y -> (Int, T y) Source #

splitAt :: Int -> T y -> (T y, T y) Source #

reverse :: T y -> T y Source #

NFData y => NormalForm (T y) Source # 

Methods

evaluateHead :: T y -> () Source #

Read (T y) Source # 

Methods

null :: T y -> Bool Source #

length :: T y -> Int Source #

Storage (T y) Source # 

Associated Types

data Constraints (T y) :: * Source #

Methods

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

Transform (T y) Source # 

Methods

take :: T -> T y -> T y Source #

drop :: T -> T y -> T y Source #

splitAt :: T -> T y -> (T y, T y) Source #

Read (T y) Source # 

Methods

length :: T y -> T Source #

type ProcessOf T Source # 
type ProcessOf T = T
data Constraints (T y) Source # 

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

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) -> x Source #

generate :: (acc -> Maybe (y, acc)) -> acc -> T y Source #

unfoldR :: (acc -> Maybe (y, acc)) -> acc -> T y Source #

generateInfinite :: (acc -> (y, acc)) -> acc -> T y Source #

fromList :: [y] -> T y Source #

toList :: T y -> [y] Source #

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

iterate :: (a -> a) -> a -> T a Source #

iterateAssociative :: (a -> a -> a) -> a -> T a Source #

repeat :: a -> T a Source #

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

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

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

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

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

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

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

take :: Int -> T a -> T a Source #

takeWhile :: (a -> Bool) -> T a -> T a Source #

replicate :: Int -> a -> T a Source #

functions consuming multiple lists

zipWith :: (a -> b -> c) -> T a -> T b -> T c Source #

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

zipWith3 :: (a -> b -> c -> d) -> T a -> T b -> T c -> T d Source #

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

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

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

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

length :: T a -> Int Source #

equal :: Eq a => T a -> T a -> Bool Source #

functions based on foldR

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

Other functions

null :: T a -> Bool Source #

singleton :: a -> T a Source #

cons :: a -> T a -> T a Source #

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

switchR :: Storable a => b -> (T a -> a -> b) -> T a -> b Source #

extendConstant :: T a -> T a Source #

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

drop :: Int -> T a -> T a Source #

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

This implementation expects that looking ahead is cheap.

dropMargin :: Int -> Int -> T a -> T a Source #

dropMatch :: T b -> T a -> T a Source #

index :: Int -> T a -> a Source #

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

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

mix :: C a => T a -> T a -> T a Source #

sub :: C a => T a -> T a -> T a Source #

neg :: C a => T a -> T a Source #

append :: T a -> T a -> T a infixr 5 Source #

appendStored :: Storable a => T a -> T a -> T a Source #

appendStoredSize :: Storable a => ChunkSize -> T a -> T a -> T a Source #

concat :: [T a] -> T a Source #

certainly inefficient because of frequent list deconstruction

concatStored :: Storable a => [T a] -> T a Source #

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

reverse :: T a -> T a Source #

reverseStored :: Storable a => T a -> T a Source #

sum :: C a => T a -> a Source #

maximum :: Ord a => T a -> a Source #

init :: T y -> T y Source #

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

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

Deprecated: use mapAdjacent

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

Deprecated: use mapAdjacent

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

modifyStatic :: Simple s ctrl a b -> ctrl -> T a -> T b Source #

modifyModulated :: Simple s ctrl a b -> T ctrl -> T a -> T b Source #

Here the control may vary over the time.

linearComb :: C t y => T t -> T y -> y Source #

mapTails :: (T y0 -> y1) -> T y0 -> T y1 Source #

zipWithTails :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2 Source #

only non-empty suffixes are processed

zipWithTails1 :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2 Source #

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

zipWithTailsInf :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2 Source #

in contrast to zipWithTails it appends infinitely many empty suffixes

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

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

delayLoop Source #

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 

delayLoopOverlap Source #

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

Counterpart to mconcat.

monoidConcatMap :: Monoid m => (a -> m) -> T a -> m Source #

catMaybes :: T (Maybe a) -> T a Source #

flattenPairs :: T (a, a) -> T a Source #

interleave :: T y -> T y -> T y Source #

interleaveAlt :: T y -> T y -> T y Source #