synthesizer-0.2: Audio signal processing coded in HaskellSource codeContentsIndex
Synthesizer.State.Signal
Contents
functions consuming multiple lists
functions based on foldL
functions based on foldR
Other functions
Description
ToDo: Better name for the module is certainly Synthesizer.Generator.Signal
Synopsis
data T a = forall s . Cons !(StateT s Maybe a) !s
generate :: (acc -> Maybe (y, acc)) -> acc -> T y
unfoldR :: (acc -> Maybe (y, acc)) -> acc -> T y
generateInfinite :: (acc -> (y, acc)) -> acc -> T y
fromList :: [y] -> T y
toList :: T y -> [y]
fromStorableSignal :: Storable a => T a -> T a
toStorableSignal :: Storable a => ChunkSize -> T a -> T a
toStorableSignalVary :: Storable a => LazySize -> T a -> T a
iterate :: (a -> a) -> a -> T a
iterateAssociative :: (a -> a -> a) -> a -> T a
repeat :: a -> T a
crochetL :: (x -> acc -> Maybe (y, acc)) -> acc -> T x -> T y
scanL :: (acc -> x -> acc) -> acc -> T x -> T acc
scanLClip :: (acc -> x -> acc) -> acc -> T x -> T acc
map :: (a -> b) -> T a -> T b
unzip :: T (a, b) -> (T a, T b)
unzip3 :: T (a, b, c) -> (T a, T b, T c)
delay1 :: a -> T a -> T a
delay :: y -> Int -> T y -> T y
take :: Int -> T a -> T a
takeWhile :: (a -> Bool) -> T a -> T a
replicate :: Int -> a -> T a
zipWith :: (a -> b -> c) -> T a -> T b -> T c
zipWithStorable :: (Storable b, Storable c) => (a -> b -> c) -> T a -> T b -> T c
zipWith3 :: (a -> b -> c -> d) -> T a -> T b -> T c -> T d
zipWith4 :: (a -> b -> c -> d -> e) -> T a -> T b -> T c -> T d -> T e
zip :: T a -> T b -> T (a, b)
zip3 :: T a -> T b -> T c -> T (a, b, c)
zip4 :: T a -> T b -> T c -> T d -> T (a, b, c, d)
foldL' :: (x -> acc -> acc) -> acc -> T x -> acc
foldL :: (acc -> x -> acc) -> acc -> T x -> acc
length :: T a -> Int
foldR :: (x -> acc -> acc) -> acc -> T x -> acc
null :: T a -> Bool
empty :: T a
singleton :: a -> T a
cons :: a -> T a -> T a
viewL :: T a -> Maybe (a, T a)
viewR :: Storable a => T a -> Maybe (T a, a)
viewRSize :: Storable a => ChunkSize -> T a -> Maybe (T a, a)
switchL :: b -> (a -> T a -> b) -> T a -> b
switchR :: Storable a => b -> (T a -> a -> b) -> T a -> b
extendConstant :: T a -> T a
drop :: Int -> T a -> T a
dropMarginRem :: Int -> Int -> T a -> (Int, T a)
dropMargin :: Int -> Int -> T a -> T a
dropMatch :: T b -> T a -> T a
index :: Int -> T a -> a
splitAt :: Storable a => Int -> T a -> (T a, T a)
splitAtSize :: Storable a => ChunkSize -> Int -> T a -> (T a, T a)
dropWhile :: (a -> Bool) -> T a -> T a
span :: Storable a => (a -> Bool) -> T a -> (T a, T a)
spanSize :: Storable a => ChunkSize -> (a -> Bool) -> T a -> (T a, T a)
cycle :: T a -> T a
mix :: C a => T a -> T a -> T a
sub :: C a => T a -> T a -> T a
neg :: C a => T a -> T a
append :: T a -> T a -> T a
appendStored :: Storable a => T a -> T a -> T a
appendStoredSize :: Storable a => ChunkSize -> T a -> T a -> T a
concat :: [T a] -> T a
concatStored :: Storable a => [T a] -> T a
concatStoredSize :: Storable a => ChunkSize -> [T a] -> T a
reverse :: T a -> T a
reverseStored :: Storable a => T a -> T a
reverseStoredSize :: Storable a => ChunkSize -> T a -> T a
sum :: C a => T a -> a
maximum :: Ord a => T a -> a
init :: T y -> T y
sliceVert :: Int -> T y -> [T y]
zapWith :: (a -> a -> b) -> T a -> T b
zapWithAlt :: (a -> a -> b) -> T a -> T b
modifyStatic :: Simple s ctrl a b -> ctrl -> T a -> T b
modifyModulated :: Simple s ctrl a b -> T ctrl -> T a -> T b
linearComb :: C t y => T t -> T y -> y
mapTails :: (T y0 -> y1) -> T y0 -> T y1
zipWithTails :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2
zipWithAppend :: (y -> y -> y) -> T y -> T y -> T y
zipStep :: (a -> a -> a) -> (T a, T a) -> Maybe (a, (T a, T a))
delayLoop :: (T y -> T y) -> T y -> T y
delayLoopOverlap :: C y => Int -> (T y -> T y) -> T y -> T y
sequence_ :: Monad m => T (m a) -> m ()
mapM_ :: Monad m => (a -> m ()) -> T a -> m ()
monoidConcat :: Monoid m => T m -> m
monoidConcatMap :: Monoid m => (a -> m) -> T a -> m
Documentation
data T a Source
Cf. StreamFusion Data.Stream
Constructors
forall s . Cons !(StateT s Maybe a) !s
show/hide Instances
Functor T
C T
C T
Write T y
Transform T y
Read T y
C T y
Transform T y0 y1
C Flat T T
C y yv => C y (T yv)
Show y => Show (T y)
Monoid (T y)
C y => C (T y)
Transform (T y)
Read (T y)
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
fromStorableSignal :: Storable a => T a -> T aSource
toStorableSignal :: Storable a => ChunkSize -> T a -> T aSource
toStorableSignalVary :: Storable a => LazySize -> T 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
length :: T a -> IntSource
functions based on foldR
foldR :: (x -> acc -> acc) -> acc -> T x -> accSource
Other functions
null :: T a -> BoolSource
empty :: T aSource
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
concatStoredSize :: Storable a => ChunkSize -> [T a] -> T aSource
reverse :: T a -> T aSource
reverseStored :: Storable a => T a -> T aSource
reverseStoredSize :: Storable a => ChunkSize -> 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
zapWithAlt :: (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
zipWithAppend :: (y -> y -> y) -> T y -> T y -> T ySource
zipStep :: (a -> a -> a) -> (T a, T a) -> Maybe (a, (T a, T a))Source
delayLoopSource
::
=> T y -> T yprocessor that shall be run in a feedback loop
-> T yprefix of the output, its length determines the delay
-> T y
delayLoopOverlapSource
:: C y
=> Int
-> T y -> T yprocessor that shall be run in a feedback loop
-> T yinput
-> T youtput 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 Data.Monoid.mconcat.
monoidConcatMap :: Monoid m => (a -> m) -> T a -> mSource
Produced by Haddock version 2.4.2