Safe Haskell | None |
---|---|
Language | Haskell2010 |
ToDo: Better name for the module is certainly Synthesizer.Generator.Signal
- data T a = Cons !(StateT s Maybe a) !s
- runViewL :: T y -> (forall s. (s -> Maybe (y, s)) -> s -> x) -> x
- runSwitchL :: T y -> (forall s. (forall z. z -> (y -> s -> z) -> s -> z) -> s -> x) -> x
- 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
- fromStrictStorableSignal :: Storable a => Vector a -> T a
- toStorableSignal :: Storable a => ChunkSize -> T a -> T a
- toStrictStorableSignal :: Storable a => Int -> T a -> Vector a
- toStorableSignalVary :: Storable a => LazySize -> T a -> T a
- fromPiecewiseConstant :: (C time, Integral time) => T time 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
- foldL1 :: (x -> x -> x) -> T x -> x
- length :: T a -> Int
- equal :: Eq a => T a -> T a -> Bool
- 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
- liftA2 :: (a -> b -> c) -> T a -> T b -> T c
- 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
- mapAdjacent :: (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
- zipWithTails1 :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2
- zipWithTailsInf :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2
- zipWithAppend :: (y -> y -> y) -> T y -> T y -> T y
- zipStep :: (s -> Maybe (a, s)) -> (t -> Maybe (a, t)) -> (a -> a -> a) -> (s, t) -> Maybe (a, (s, t))
- 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
- catMaybes :: T (Maybe a) -> T a
- flattenPairs :: T (a, a) -> T a
- interleave :: T y -> T y -> T y
- interleaveAlt :: T y -> T y -> T y
Documentation
Cf. StreamFusion Data.Stream
Monad T Source # | |
Functor T Source # | |
Applicative T Source # | |
Foldable T Source # | |
C T Source # | |
Write0 T Source # | |
Transform0 T Source # | |
Read0 T Source # | |
Write T y Source # | |
Transform T y Source # | |
Read T y Source # | |
Write T y Source # | |
C y yv => C y (T yv) Source # | |
Eq y => Eq (T y) Source # | |
Show y => Show (T y) Source # | |
Monoid (T y) Source # | |
C y => C (T y) Source # | |
Transform (T y) Source # | |
NFData y => NormalForm (T y) Source # | |
Read (T y) Source # | |
Storage (T y) Source # | |
Transform (T y) Source # | |
Read (T y) Source # | |
type ProcessOf T Source # | |
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 #
generateInfinite :: (acc -> (y, acc)) -> acc -> T y Source #
iterateAssociative :: (a -> a -> a) -> a -> T a Source #
scanLClip :: (acc -> x -> acc) -> acc -> T x -> T acc Source #
input and output have equal length, that's better for fusion
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.
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.
functions consuming multiple lists
functions based on foldL
functions based on foldR
Other functions
cons :: a -> T a -> T a Source #
This is expensive and should not be used to construct lists iteratively!
extendConstant :: T a -> T a Source #
This implementation requires that the input generator has to check repeatedly whether it is finished.
dropMarginRem :: Int -> Int -> T a -> (Int, T a) Source #
This implementation expects that looking ahead is cheap.
zapWithAlt :: (a -> a -> b) -> T a -> T b Source #
Deprecated: use mapAdjacent
mapAdjacent :: (a -> a -> b) -> 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.
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
zipStep :: (s -> Maybe (a, s)) -> (t -> Maybe (a, t)) -> (a -> a -> a) -> (s, t) -> Maybe (a, (s, t)) Source #
monoidConcatMap :: Monoid m => (a -> m) -> T a -> m Source #
flattenPairs :: T (a, a) -> T a Source #