dunai-0.3.0.0: Generalised reactive framework supporting classic, arrowized and monadic FRP.

Safe HaskellSafe
LanguageHaskell2010

Data.MonadicStreamFunction.Util

Contents

Description

Useful auxiliary functions and definitions.

Synopsis

Streams and sinks

type MStream m a = MSF m () a Source #

A stream is an MSF that produces outputs ignoring the input. It can obtain the values from a monadic context.

type MSink m a = MSF m a () Source #

A stream is an MSF that produces outputs producing no output. It can consume the values with side effects.

Lifting

insert :: Monad m => MSF m (m a) a Source #

Deprecated: Don't use this. arrM id instead

Pre-inserts an input sample.

arrM_ :: Monad m => m b -> MSF m a b Source #

Lifts a computation into a Stream.

(^>>>) :: MonadBase m1 m2 => MSF m1 a b -> MSF m2 b c -> MSF m2 a c Source #

Lift the first MSF into the monad of the second.

(>>>^) :: MonadBase m1 m2 => MSF m2 a b -> MSF m1 b c -> MSF m2 a c Source #

Lift the second MSF into the monad of the first.

Analogues of map and fmap

mapMSF :: Monad m => MSF m a b -> MSF m [a] [b] Source #

Apply an MSF to every input.

mapMaybeS :: Monad m => MSF m a b -> MSF m (Maybe a) (Maybe b) Source #

Apply an MSF to every input. Freezes temporarily if the input is Nothing, and continues as soon as a Just is received.

Adding side effects

withSideEffect :: Monad m => (a -> m b) -> MSF m a a Source #

Applies a function to produce an additional side effect and passes the input unchanged.

withSideEffect_ :: Monad m => m b -> MSF m a a Source #

Produces an additional side effect and passes the input unchanged.

Delays

iPost :: Monad m => b -> MSF m a b -> MSF m a b Source #

Preprends a fixed output to an MSF. The first input is completely ignored.

next :: Monad m => b -> MSF m a b -> MSF m a b Source #

Preprends a fixed output to an MSF, shifting the output.

Folding

Folding for VectorSpace instances

count :: (Num n, Monad m) => MSF m a n Source #

Count the number of simulation steps. Produces 1, 2, 3,...

sumS :: (RModule v, Monad m) => MSF m v v Source #

Sums the inputs, starting from zero.

sumFrom :: (RModule v, Monad m) => v -> MSF m v v Source #

Sums the inputs, starting from an initial vector.

Folding for monoids

mappendS :: (Monoid n, Monad m) => MSF m n n Source #

Accumulate the inputs, starting from mempty.

mappendFrom :: (Monoid n, Monad m) => n -> MSF m n n Source #

Accumulate the inputs, starting from an initial monoid value.

Generic folding / accumulation

accumulateWith :: Monad m => (a -> s -> s) -> s -> MSF m a s Source #

Applies a function to the input and an accumulator, outputing the accumulator. Equal to f s0 -> feedback s0 $ arr (uncurry f >>> dup).

Unfolding

unfold :: Monad m => (a -> (b, a)) -> a -> MSF m () b Source #

Generate outputs using a step-wise generation function and an initial value.

repeatedly :: Monad m => (a -> a) -> a -> MSF m () a Source #

Generate outputs using a step-wise generation function and an initial value. Version of unfold in which the output and the new accumulator are the same. Should be equal to f a -> unfold (f >>> dup) a.

Running functions

embed_ :: (Functor m, Monad m) => MSF m a () -> [a] -> m () Source #

Run an MSF fed from a list, discarding results. Useful when one needs to combine effects and streams (i.e., for testing purposes).

Debugging

trace :: Show a => String -> MSF IO a a Source #

Outputs every input sample, with a given message prefix.

traceWith :: (Monad m, Show a) => (String -> m ()) -> String -> MSF m a a Source #

Outputs every input sample, with a given message prefix, using an auxiliary printing function.

traceWhen :: (Monad m, Show a) => (a -> Bool) -> (String -> m ()) -> String -> MSF m a a Source #

Outputs every input sample, with a given message prefix, using an auxiliary printing function, when a condition is met.

pauseOn :: Show a => (a -> Bool) -> String -> MSF IO a a Source #

Outputs every input sample, with a given message prefix, when a condition is met, and waits for some input / enter to continue.