synthesizer-0.2.0.1: Audio signal processing coded in HaskellSource codeContentsIndex
Synthesizer.FusionList.Signal
Contents
functions based on generate
functions based on crochetL
functions consuming multiple lists
functions based on reduceL
Fusion helpers
Other functions
Synopsis
newtype T y = Cons {
decons :: [y]
}
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]
toStorableSignal :: Storable y => ChunkSize -> T y -> Vector y
fromStorableSignal :: Storable y => Vector y -> T y
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
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)
reduceL :: (x -> acc -> Maybe acc) -> acc -> T x -> acc
foldL' :: (x -> acc -> acc) -> acc -> T x -> acc
foldL :: (acc -> x -> acc) -> acc -> T x -> acc
lengthSlow :: T a -> Int
zipWithGenerate :: (a -> b -> c) -> (acc -> Maybe (a, acc)) -> acc -> T b -> T c
zipWithCrochetL :: (a -> b -> c) -> (x -> acc -> Maybe (a, acc)) -> acc -> T x -> T b -> T c
mixGenerate :: C a => (a -> a -> a) -> (acc -> Maybe (a, acc)) -> acc -> T a -> T a
crochetLCons :: (a -> acc -> Maybe (b, acc)) -> acc -> a -> T a -> T b
reduceLCons :: (a -> acc -> Maybe acc) -> acc -> a -> T a -> acc
zipWithCons :: (a -> b -> c) -> a -> T a -> T b -> T c
null :: T a -> Bool
empty :: T a
singleton :: a -> T a
cons :: a -> T a -> T a
length :: T a -> Int
viewL :: T a -> Maybe (a, T a)
viewR :: T a -> Maybe (T a, a)
extendConstant :: T a -> T a
tail :: T a -> T a
head :: T a -> a
drop :: Int -> T a -> T a
dropMarginRem :: Int -> Int -> T a -> (Int, T a)
dropMargin :: Int -> Int -> T a -> T a
index :: Int -> T a -> a
splitAt :: Int -> T a -> (T a, T a)
dropWhile :: (a -> Bool) -> T a -> T a
span :: (a -> Bool) -> T a -> (T a, T a)
mapAccumL :: (acc -> x -> (acc, y)) -> acc -> T x -> (acc, T y)
mapAccumR :: (acc -> x -> (acc, y)) -> acc -> T x -> (acc, T y)
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
concat :: [T a] -> T a
reverse :: T a -> T a
sum :: C a => T a -> a
maximum :: Ord a => T a -> a
tails :: T y -> [T y]
init :: T y -> T y
sliceVert :: Int -> T y -> [T y]
zapWith :: (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
zipWithRest :: (y0 -> y0 -> y1) -> T y0 -> T y0 -> (T y1, (Bool, T y0))
zipWithAppend :: (y -> y -> y) -> T y -> T y -> T y
delayLoop :: (T y -> T y) -> T y -> T y
delayLoopOverlap :: C y => Int -> (T y -> T y) -> T y -> T y
recourse :: (acc -> Maybe acc) -> acc -> acc
Documentation
newtype T y Source
Constructors
Cons
decons :: [y]
show/hide Instances
Functor T
C T
Write T y
Transform T y
Read T y
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)
functions based on generate
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
toStorableSignal :: Storable y => ChunkSize -> T y -> Vector ySource
fromStorableSignal :: Storable y => Vector y -> T ySource
iterate :: (a -> a) -> a -> T aSource
iterateAssociative :: (a -> a -> a) -> a -> T aSource
repeat :: a -> T aSource
functions based on crochetL
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
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
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 reduceL
reduceL :: (x -> acc -> Maybe acc) -> acc -> T x -> accSource
foldL' :: (x -> acc -> acc) -> acc -> T x -> accSource
foldL :: (acc -> x -> acc) -> acc -> T x -> accSource
lengthSlow :: T a -> IntSource
can be used to check against native length implementation
Fusion helpers
zipWithGenerate :: (a -> b -> c) -> (acc -> Maybe (a, acc)) -> acc -> T b -> T cSource
zipWithCrochetL :: (a -> b -> c) -> (x -> acc -> Maybe (a, acc)) -> acc -> T x -> T b -> T cSource
mixGenerate :: C a => (a -> a -> a) -> (acc -> Maybe (a, acc)) -> acc -> T a -> T aSource
crochetLCons :: (a -> acc -> Maybe (b, acc)) -> acc -> a -> T a -> T bSource
reduceLCons :: (a -> acc -> Maybe acc) -> acc -> a -> T a -> accSource
zipWithCons :: (a -> b -> c) -> a -> T a -> T b -> T cSource
Other functions
null :: T a -> BoolSource
empty :: T aSource
singleton :: a -> T aSource
cons :: a -> T a -> T aSource
length :: T a -> IntSource
viewL :: T a -> Maybe (a, T a)Source
viewR :: T a -> Maybe (T a, a)Source
extendConstant :: T a -> T aSource
tail :: T a -> T aSource
head :: T a -> aSource
drop :: Int -> T a -> T aSource
dropMarginRem :: Int -> Int -> T a -> (Int, T a)Source
dropMargin :: Int -> Int -> T a -> T aSource
index :: Int -> T a -> aSource
splitAt :: Int -> T a -> (T a, T a)Source
dropWhile :: (a -> Bool) -> T a -> T aSource
span :: (a -> Bool) -> T a -> (T a, T a)Source
mapAccumL :: (acc -> x -> (acc, y)) -> acc -> T x -> (acc, T y)Source
mapAccumR :: (acc -> x -> (acc, y)) -> acc -> T x -> (acc, T y)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
concat :: [T a] -> T aSource
reverse :: T a -> T aSource
sum :: C a => T a -> aSource
maximum :: Ord a => T a -> aSource
tails :: T y -> [T y]Source
init :: T y -> T ySource
sliceVert :: Int -> T y -> [T y]Source
zapWith :: (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
zipWithRest :: (y0 -> y0 -> y1) -> T y0 -> T y0 -> (T y1, (Bool, T y0))Source
zipWithAppend :: (y -> y -> y) -> T y -> T y -> T ySource
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
recourse :: (acc -> Maybe acc) -> acc -> accSource
Produced by Haddock version 2.4.2