synthesizer-0.2.0.1: Audio signal processing coded in HaskellSource codeContentsIndex
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
class Read (sig y) => Read sig y where
toList :: sig y -> [y]
toState :: sig y -> T y
foldL :: (s -> y -> s) -> s -> sig y -> s
viewL :: sig y -> Maybe (y, sig y)
viewR :: sig y -> Maybe (sig y, y)
class (Read sig y, Transform (sig y)) => Transform sig y where
cons :: y -> sig y -> sig y
takeWhile :: (y -> Bool) -> sig y -> sig y
dropWhile :: (y -> Bool) -> sig y -> sig y
span :: (y -> Bool) -> sig y -> (sig y, sig y)
map :: (y -> y) -> sig y -> sig y
scanL :: (y -> y -> y) -> y -> sig y -> sig y
crochetL :: (y -> s -> Maybe (y, s)) -> s -> sig y -> sig y
zipWithAppend :: (y -> y -> y) -> sig y -> sig y -> sig y
newtype LazySize = LazySize Int
defaultLazySize :: LazySize
class Transform sig y => Write sig y where
fromList :: LazySize -> [y] -> sig y
repeat :: LazySize -> y -> sig y
replicate :: LazySize -> Int -> y -> sig y
iterate :: LazySize -> (y -> y) -> y -> sig y
iterateAssociative :: LazySize -> (y -> y -> y) -> y -> sig y
unfoldR :: LazySize -> (s -> Maybe (y, s)) -> s -> sig y
withStorableContext :: (ChunkSize -> a) -> LazySize -> a
switchL :: Read sig y => a -> (y -> sig y -> a) -> sig y -> a
mix :: (C y, Transform sig y) => sig y -> sig y -> sig y
zipWith :: (Read sig a, Transform sig b) => (a -> b -> b) -> sig a -> sig b -> sig b
delay :: Write sig y => LazySize -> y -> Int -> sig y -> sig y
delayLoop :: Transform sig y => (sig y -> sig y) -> sig y -> sig y
delayLoopOverlap :: (C y, Write sig y) => Int -> (sig y -> sig y) -> sig y -> sig y
sum :: (C a, Read sig a) => sig a -> a
tails :: Transform sig y => sig y -> T (sig y)
mapAdjacent :: (Read sig a, Transform sig a) => (a -> a -> a) -> sig a -> sig a
modifyStatic :: Transform sig a => Simple s ctrl a a -> ctrl -> sig a -> sig a
modifyModulated :: (Transform sig a, Read sig ctrl) => Simple s ctrl a a -> sig ctrl -> sig a -> sig a
linearComb :: (C t y, Read sig t, Read sig y) => sig t -> sig y -> y
fromState :: Write sig y => LazySize -> T y -> sig y
extendConstant :: Write sig y => LazySize -> sig y -> sig y
mapTails :: Transform sig a => (sig a -> a) -> sig a -> sig a
mapTailsAlt :: (Read sig a, Write sig b) => LazySize -> (sig a -> b) -> sig a -> sig b
zipWithTails :: (Read sig b, Transform sig a) => (a -> sig b -> a) -> sig a -> sig b -> sig a
null :: Read sig => sig -> Bool
length :: Read sig => sig -> Int
empty :: Monoid sig => sig
cycle :: Monoid sig => sig -> sig
append :: Monoid sig => sig -> sig -> sig
concat :: Monoid sig => [sig] -> sig
take :: Transform sig => Int -> sig -> sig
drop :: Transform sig => Int -> sig -> sig
dropMarginRem :: Transform sig => Int -> Int -> sig -> (Int, sig)
splitAt :: Transform sig => Int -> sig -> (sig, sig)
reverse :: Transform sig => sig -> sig
lengthAtLeast :: Transform sig => Int -> sig -> Bool
lengthAtMost :: Transform sig => Int -> sig -> Bool
sliceVertical :: Transform sig => Int -> sig -> T sig
Documentation
class Read (sig y) => Read sig y whereSource
Methods
toList :: sig y -> [y]Source
toState :: sig y -> T ySource
foldL :: (s -> y -> s) -> s -> sig y -> sSource
viewL :: sig y -> Maybe (y, sig y)Source
viewR :: sig y -> Maybe (sig y, y)Source
show/hide Instances
class (Read sig y, Transform (sig y)) => Transform sig y whereSource
Methods
cons :: y -> sig y -> sig ySource
This function belongs logically to the Write class, but since an empty signal contains no data, the maximum package size is irrelevant. This makes e.g. the definition of mixMulti more general.
takeWhile :: (y -> Bool) -> sig y -> sig ySource
dropWhile :: (y -> Bool) -> sig y -> sig ySource
span :: (y -> Bool) -> sig y -> (sig y, sig y)Source
map :: (y -> y) -> sig y -> sig ySource
scanL :: (y -> y -> y) -> y -> sig y -> sig ySource
crochetL :: (y -> s -> Maybe (y, s)) -> s -> sig y -> sig ySource
zipWithAppend :: (y -> y -> y) -> sig y -> sig y -> sig ySource
show/hide Instances
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.
Constructors
LazySize Int
defaultLazySize :: LazySizeSource
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.
class Transform sig y => Write sig y whereSource
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.
Methods
fromList :: LazySize -> [y] -> sig ySource
repeat :: LazySize -> y -> sig ySource
replicate :: LazySize -> Int -> y -> sig ySource
iterate :: LazySize -> (y -> y) -> y -> sig ySource
iterateAssociative :: LazySize -> (y -> y -> y) -> y -> sig ySource
unfoldR :: LazySize -> (s -> Maybe (y, s)) -> s -> sig ySource
show/hide Instances
withStorableContext :: (ChunkSize -> a) -> LazySize -> aSource
switchL :: Read sig y => a -> (y -> sig y -> a) -> sig y -> aSource
mix :: (C y, Transform sig y) => sig y -> sig y -> sig ySource
zipWith :: (Read sig a, Transform sig b) => (a -> b -> b) -> sig a -> sig b -> sig bSource
delay :: Write sig y => LazySize -> y -> Int -> sig y -> sig ySource
delayLoopSource
:: Transform sig y
=> sig y -> sig yprocessor that shall be run in a feedback loop
-> sig yprefix of the output, its length determines the delay
-> sig y
delayLoopOverlapSource
:: (C y, Write sig y)
=> Int
-> sig y -> sig yProcessor 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 yinput
-> sig youtput has the same length as the input
sum :: (C a, Read sig a) => sig a -> aSource
tails :: Transform sig y => sig y -> T (sig y)Source
mapAdjacent :: (Read sig a, Transform sig a) => (a -> a -> a) -> sig a -> sig aSource
modifyStatic :: Transform sig a => Simple s ctrl a a -> ctrl -> sig a -> sig aSource
modifyModulated :: (Transform sig a, Read sig ctrl) => Simple s ctrl a a -> sig ctrl -> sig a -> sig aSource
Here the control may vary over the time.
linearComb :: (C t y, Read sig t, Read sig y) => sig t -> sig y -> ySource
fromState :: Write sig y => LazySize -> T y -> sig ySource
extendConstant :: Write sig y => LazySize -> sig y -> sig ySource
mapTails :: Transform sig a => (sig a -> a) -> sig a -> sig aSource
mapTailsAlt :: (Read sig a, Write sig b) => LazySize -> (sig a -> b) -> sig a -> sig bSource
zipWithTails :: (Read sig b, Transform sig a) => (a -> sig b -> a) -> sig a -> sig b -> sig aSource

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.

null :: Read sig => sig -> BoolSource
length :: Read sig => sig -> IntSource
empty :: Monoid sig => sigSource
cycle :: Monoid sig => sig -> sigSource
append :: Monoid sig => sig -> sig -> sigSource
concat :: Monoid sig => [sig] -> sigSource
take :: Transform sig => Int -> sig -> sigSource
drop :: Transform sig => Int -> sig -> sigSource
dropMarginRem :: Transform sig => Int -> Int -> sig -> (Int, sig)Source
splitAt :: Transform sig => Int -> sig -> (sig, sig)Source
reverse :: Transform sig => sig -> sigSource
lengthAtLeast :: Transform sig => Int -> sig -> BoolSource
Like lengthAtLeast n xs = length xs >= n, but is more efficient, because it is more lazy.
lengthAtMost :: Transform sig => Int -> sig -> BoolSource
sliceVertical :: Transform sig => Int -> sig -> T sigSource
Produced by Haddock version 2.4.2