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.
- class Read (sig y) => Read sig y where
- 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)
- viewL :: sig y -> Maybe (y, sig y)
- viewR :: sig y -> Maybe (sig y, 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
- withStorableContext :: (ChunkSize -> a) -> LazySize -> a
- switchL :: Transform sig y => a -> (y -> sig y -> a) -> sig y -> a
- switchR :: Transform sig y => a -> (sig y -> y -> a) -> sig y -> a
- runViewL :: Read sig y => sig y -> (forall s. (s -> Maybe (y, s)) -> s -> x) -> x
- runSwitchL :: Read sig y => sig y -> (forall s. (forall z. z -> (y -> s -> z) -> s -> z) -> s -> x) -> x
- 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
- zipWithState :: Transform sig b => (a -> b -> b) -> T a -> sig b -> sig b
- zipWithState3 :: Transform sig c => (a -> b -> c -> c) -> T a -> T b -> sig c -> sig c
- 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
- monoidConcatMap :: (Read sig a, Monoid m) => (a -> m) -> sig a -> m
- tails :: Transform sig y => sig y -> T (sig y)
- laxTail :: Transform sig y => sig y -> 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 :: (Transform sig a, Write sig b) => LazySize -> (sig a -> b) -> sig a -> sig b
- zipWithTails :: (Transform sig b, Transform sig a) => (a -> sig b -> a) -> sig a -> sig b -> sig a
- indexByDrop :: Transform sig a => sig a -> Int -> 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, Transform (sig y)) => Transform sig y whereSource
cons :: y -> sig y -> sig ySource
takeWhile :: (y -> Bool) -> sig y -> sig ySource
dropWhile :: (y -> Bool) -> sig y -> sig ySource
span :: (y -> Bool) -> sig y -> (sig y, sig y)Source
viewL :: sig y -> Maybe (y, sig y)Source
When using viewL
for traversing a signal,
it is certainly better to convert to State signal first,
since this might involve optimized traversing
like in case of Storable signals.
viewR :: sig y -> Maybe (sig y, 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
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.
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.
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
withStorableContext :: (ChunkSize -> a) -> LazySize -> aSource
runSwitchL :: Read sig y => sig y -> (forall s. (forall z. z -> (y -> s -> z) -> s -> z) -> s -> x) -> xSource
zipWithState :: Transform sig b => (a -> b -> b) -> T a -> sig b -> sig bSource
zipWithState3 :: Transform sig c => (a -> b -> c -> c) -> T a -> T b -> sig c -> sig cSource
:: Transform sig y | |
=> (sig y -> sig y) | processor that shall be run in a feedback loop |
-> sig y | prefix of the output, its length determines the delay |
-> sig y |
:: (C y, Write sig y) | |
=> Int | |
-> (sig y -> sig y) | Processor 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 |
-> sig y | input |
-> sig y | output has the same length as the input |
monoidConcatMap :: (Read sig a, Monoid m) => (a -> m) -> sig a -> mSource
laxTail :: Transform sig y => sig y -> sig ySource
Like tail
, but for an empty signal it simply returns an empty signal.
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
extendConstant :: Write sig y => LazySize -> sig y -> sig ySource
mapTailsAlt :: (Transform sig a, Write sig b) => LazySize -> (sig a -> b) -> sig a -> sig bSource
zipWithTails :: (Transform 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.
indexByDrop :: Transform sig a => sig a -> Int -> aSource
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