dyna-0.1.0.0: Minimal FRP library
Safe HaskellNone
LanguageHaskell2010

Dyna

Description

Dyna is functional reactive programming library. It describes event streams that are based on callbacks. The event stream can produce something useful with callback that it consumes. Also we have continous signals called Dyn (short for dynamic). The Dyn is sort of observance process of an event stream. For any event that happen on event stream we remember that value and produce it at any time until the next event will happen.

# Events

The event stream is just callback consumer funtion:

newtype Evt m a = Evt {
  runEvt :: (a -> m ()) -> m ()
}

So it tells us: If you give me some callback (a -> m ()) I will apply it to the event when event will occur. But when it will occur we don't know until we run the event. All events happen at the same time. Every event triggers a callback. This has some special nuance to it. That can differ from other FRP libraries. For example monoidal append of two event streams:

evtA <> evtB

In many FRP libraries we choose which element will happen or should we also append the events if they happen "at the same time". For this library we spawn two concurrent processes on background so if two events will happen at the same time callback will be called twice.

# Dynamics

The assumption is that dynamic is a process that evolves in time. And as a human beings we can only ask for current values while process happens. So we assemble the dynamics with combinators an after that we can run it's process:

ref <-runDyn dynamicValue

It produces reference to the process which we can use to sample the current value in real time:

readDyn ref
 10
readDyn ref  -- 5 seconds later
 10
readDyn ref  -- 5 seconds later
 3

This reminds us of the notion of present moment. Take for example a weather temperature. We can claim to build a model of weather and have an assumption of which value will happen tomorrow but the exact value for it we can only measure at the moment when it will actually happen.

So the library is based on simple assumptions:

  • Event stream is a callback processor
  • Event stream happen at the same time as concurrent process
  • Dynamic is a process and we can only query the current value for it
  • Dynamics are based on event streams. The dynamic is an observation of some underlying event streams. We just remember the last event and keep producing it until the next one wil arrive.
Synopsis

Pipe

(|>) :: a -> (a -> b) -> b infixl 0 Source #

Pipe operator. We often write processors of event streams It makes it convenient write them from first to the last:

evt = proc1 |> proc2 |> ... |> procN

Instead of reversed order with ($):

evt = procN $ ... $ proc2 $ proc1

Class

class (IsRef (Ref m), MonadBaseControl IO m, MonadIO m) => Frp m Source #

Associated Types

type Ref m :: * -> * Source #

Instances

Instances details
Frp IO Source # 
Instance details

Defined in Dyna

Associated Types

type Ref IO :: Type -> Type Source #

Events

newtype Evt m a Source #

Event stream. The meaning of an event is a callback consumer function. If we give callback to it it will do something useful based on it.

The main function is runEvt:

runEvt :: Evt m a -> (a -> m ()) -> m ()
runEvt events callback = ...

Let's look at simple examples of the event streams:

Event that never produce anything:

never = Evt {
   runEvt _ = pure ()
 }

So it just ignores the callback and returns right away.

Event that happens only once:

once :: m a -> Evt m a
once get = Evt {
    runEvt go = go =<< get
 }

It just gets the value right away and applies callback to it. We can try it out in the interpreter:

putStrLns $ fmap ("Your message: " <> ) $ once getLine

We have useful functions to print out the events: putStrLns and prints.

Also we have event streams that happen periodically:

prints $ clock 1  -- prints time every second

## Duplication of the events.

Note that event streams are functions that do side-effects within some monad. We use them as values but it means that two values with the same event stream definition can produce different results. For example:

a = toRandomR (0, 10) $ clock 1
b = a

Note that a and b will each have their own copy of underlying random event stream. So if you use it in the code don't expect values to be the same.

But if we want them to be the same we can copy event from it's definition with function:

newEvt :: Evt m a -> m (Evt m a)

It starts the underying event stream process n background and sends all events to the result by channel. With nice property of when we shut down the result event the background process also shuts down.

a <- newEvt toRandomR (0, 10) $ clock 1
b = a

In this example event streams a and b will have the same events during execution.

Constructors

Evt 

Fields

  • runEvt :: (a -> m ()) -> m ()
     

Instances

Instances details
FunctorM Evt Source # 
Instance details

Defined in Dyna

Methods

fmap' :: Frp m => (a -> m b) -> Evt m a -> Evt m b Source #

Frp m => Monad (Evt m) Source # 
Instance details

Defined in Dyna

Methods

(>>=) :: Evt m a -> (a -> Evt m b) -> Evt m b #

(>>) :: Evt m a -> Evt m b -> Evt m b #

return :: a -> Evt m a #

Functor (Evt m) Source # 
Instance details

Defined in Dyna

Methods

fmap :: (a -> b) -> Evt m a -> Evt m b #

(<$) :: a -> Evt m b -> Evt m a #

Frp m => Applicative (Evt m) Source # 
Instance details

Defined in Dyna

Methods

pure :: a -> Evt m a #

(<*>) :: Evt m (a -> b) -> Evt m a -> Evt m b #

liftA2 :: (a -> b -> c) -> Evt m a -> Evt m b -> Evt m c #

(*>) :: Evt m a -> Evt m b -> Evt m b #

(<*) :: Evt m a -> Evt m b -> Evt m a #

Frp m => Semigroup (Evt m a) Source # 
Instance details

Defined in Dyna

Methods

(<>) :: Evt m a -> Evt m a -> Evt m a #

sconcat :: NonEmpty (Evt m a) -> Evt m a #

stimes :: Integral b => b -> Evt m a -> Evt m a #

Frp m => Monoid (Evt m a) Source # 
Instance details

Defined in Dyna

Methods

mempty :: Evt m a #

mappend :: Evt m a -> Evt m a -> Evt m a #

mconcat :: [Evt m a] -> Evt m a #

Frp m => Melody (Evt m a) Source # 
Instance details

Defined in Dyna

Methods

mel :: [Evt m a] -> Evt m a #

(+:+) :: Evt m a -> Evt m a -> Evt m a #

Frp m => Harmony (Evt m a) Source # 
Instance details

Defined in Dyna

Methods

har :: [Evt m a] -> Evt m a #

(=:=) :: Evt m a -> Evt m a -> Evt m a #

Frp m => Compose (Evt m a) Source # 
Instance details

Defined in Dyna

Frp m => Limit (Evt m a) Source # 
Instance details

Defined in Dyna

Methods

lim :: DurOf (Evt m a) -> Evt m a -> Evt m a #

Frp m => Loop (Evt m a) Source # 
Instance details

Defined in Dyna

Methods

loop :: Evt m a -> Evt m a #

type DurOf (Evt m a) Source # 
Instance details

Defined in Dyna

once :: Frp m => m a -> Evt m a Source #

Event that happens only once and happens right away.

never :: Frp m => Evt m a Source #

Event that never happens. Callback function is ignored.

Dynamics

data Dyn m a Source #

Dynamics are step-wise constant effectful functions each step transition is driven by underlying stream of events.

Meaning of the Dyn is a process that evolves in time. We can start the process by running runDyn. It produces a reference to the process that runs in background.

runDyn :: Frp m => Dyn m a -> DynRef m a

When reference is initialized we can query current value of it:

readDyn :: DynRef m a -> m a

When we are done with observations we should shut down the background process with:

cancelDyn :: DynRef m a -> m ()

It kills the background process and triggers the release function of underlying event stream.

Constructors

forall s. Dyn

event based dynamic

Fields

ConstDyn a

Constant value

Instances

Instances details
FunctorM Dyn Source # 
Instance details

Defined in Dyna

Methods

fmap' :: Frp m => (a -> m b) -> Dyn m a -> Dyn m b Source #

Functor m => Functor (Dyn m) Source # 
Instance details

Defined in Dyna

Methods

fmap :: (a -> b) -> Dyn m a -> Dyn m b #

(<$) :: a -> Dyn m b -> Dyn m a #

Frp m => Applicative (Dyn m) Source # 
Instance details

Defined in Dyna

Methods

pure :: a -> Dyn m a #

(<*>) :: Dyn m (a -> b) -> Dyn m a -> Dyn m b #

liftA2 :: (a -> b -> c) -> Dyn m a -> Dyn m b -> Dyn m c #

(*>) :: Dyn m a -> Dyn m b -> Dyn m b #

(<*) :: Dyn m a -> Dyn m b -> Dyn m a #

(Frp m, Fractional a) => Fractional (Dyn m a) Source # 
Instance details

Defined in Dyna

Methods

(/) :: Dyn m a -> Dyn m a -> Dyn m a #

recip :: Dyn m a -> Dyn m a #

fromRational :: Rational -> Dyn m a #

(Frp m, Num a) => Num (Dyn m a) Source # 
Instance details

Defined in Dyna

Methods

(+) :: Dyn m a -> Dyn m a -> Dyn m a #

(-) :: Dyn m a -> Dyn m a -> Dyn m a #

(*) :: Dyn m a -> Dyn m a -> Dyn m a #

negate :: Dyn m a -> Dyn m a #

abs :: Dyn m a -> Dyn m a #

signum :: Dyn m a -> Dyn m a #

fromInteger :: Integer -> Dyn m a #

(Frp m, IsString a) => IsString (Dyn m a) Source # 
Instance details

Defined in Dyna

Methods

fromString :: String -> Dyn m a #

(Frp m, Semigroup a) => Semigroup (Dyn m a) Source # 
Instance details

Defined in Dyna

Methods

(<>) :: Dyn m a -> Dyn m a -> Dyn m a #

sconcat :: NonEmpty (Dyn m a) -> Dyn m a #

stimes :: Integral b => b -> Dyn m a -> Dyn m a #

(Frp m, Monoid a) => Monoid (Dyn m a) Source # 
Instance details

Defined in Dyna

Methods

mempty :: Dyn m a #

mappend :: Dyn m a -> Dyn m a -> Dyn m a #

mconcat :: [Dyn m a] -> Dyn m a #

(Boolean b, Frp m) => Boolean (Dyn m b) Source # 
Instance details

Defined in Dyna

Methods

true :: Dyn m b #

false :: Dyn m b #

notB :: Dyn m b -> Dyn m b #

(&&*) :: Dyn m b -> Dyn m b -> Dyn m b #

(||*) :: Dyn m b -> Dyn m b -> Dyn m b #

(Frp m, IfB a) => IfB (Dyn m a) Source # 
Instance details

Defined in Dyna

Methods

ifB :: bool ~ BooleanOf (Dyn m a) => bool -> Dyn m a -> Dyn m a -> Dyn m a #

(EqB a, Frp m) => EqB (Dyn m a) Source # 
Instance details

Defined in Dyna

Methods

(==*) :: bool ~ BooleanOf (Dyn m a) => Dyn m a -> Dyn m a -> bool #

(/=*) :: bool ~ BooleanOf (Dyn m a) => Dyn m a -> Dyn m a -> bool #

(OrdB a, Frp m) => OrdB (Dyn m a) Source # 
Instance details

Defined in Dyna

Methods

(<*) :: bool ~ BooleanOf (Dyn m a) => Dyn m a -> Dyn m a -> bool #

(<=*) :: bool ~ BooleanOf (Dyn m a) => Dyn m a -> Dyn m a -> bool #

(>*) :: bool ~ BooleanOf (Dyn m a) => Dyn m a -> Dyn m a -> bool #

(>=*) :: bool ~ BooleanOf (Dyn m a) => Dyn m a -> Dyn m a -> bool #

(HasNormal v, Frp m) => HasNormal (Dyn m v) Source # 
Instance details

Defined in Dyna

Methods

normalVec :: Dyn m v -> Dyn m v #

(HasCross2 v, Frp m) => HasCross2 (Dyn m v) Source # 
Instance details

Defined in Dyna

Methods

cross2 :: Dyn m v -> Dyn m v #

(HasCross3 v, Frp m) => HasCross3 (Dyn m v) Source # 
Instance details

Defined in Dyna

Methods

cross3 :: Dyn m v -> Dyn m v -> Dyn m v #

(AffineSpace p, Frp m) => AffineSpace (Dyn m p) Source # 
Instance details

Defined in Dyna

Associated Types

type Diff (Dyn m p) #

Methods

(.-.) :: Dyn m p -> Dyn m p -> Diff (Dyn m p) #

(.+^) :: Dyn m p -> Diff (Dyn m p) -> Dyn m p #

(BasisArity v, HasBasis v, Frp m) => HasBasis (Dyn m v) Source # 
Instance details

Defined in Dyna

Associated Types

type Basis (Dyn m v) #

Methods

basisValue :: Basis (Dyn m v) -> Dyn m v #

decompose :: Dyn m v -> [(Basis (Dyn m v), Scalar (Dyn m v))] #

decompose' :: Dyn m v -> Basis (Dyn m v) -> Scalar (Dyn m v) #

(VectorSpace a, Frp m) => VectorSpace (Dyn m a) Source # 
Instance details

Defined in Dyna

Associated Types

type Scalar (Dyn m a) #

Methods

(*^) :: Scalar (Dyn m a) -> Dyn m a -> Dyn m a #

(AdditiveGroup a, Frp m) => AdditiveGroup (Dyn m a) Source # 
Instance details

Defined in Dyna

Methods

zeroV :: Dyn m a #

(^+^) :: Dyn m a -> Dyn m a -> Dyn m a #

negateV :: Dyn m a -> Dyn m a #

(^-^) :: Dyn m a -> Dyn m a -> Dyn m a #

(Frp m, BasisArity v) => BasisArity (Dyn m v) Source # 
Instance details

Defined in Dyna

Methods

basisArity :: Dyn m v -> Int Source #

type BooleanOf (Dyn m a) Source # 
Instance details

Defined in Dyna

type BooleanOf (Dyn m a) = Dyn m (BooleanOf a)
type Diff (Dyn m p) Source # 
Instance details

Defined in Dyna

type Diff (Dyn m p) = Dyn m (Diff p)
type Basis (Dyn m v) Source # 
Instance details

Defined in Dyna

type Basis (Dyn m v) = Dyn m (Basis v)
type Scalar (Dyn m a) Source # 
Instance details

Defined in Dyna

type Scalar (Dyn m a) = Dyn m (Scalar a)

constDyn :: Frp m => m a -> Dyn m a Source #

Dyn that is constructed from effectful callback.

runDyn :: Frp m => Dyn m a -> m (DynRef m a) Source #

Executes dynamic for observation. The dynamic is step-wise constant function that is driven by some event stream. The function runs the event stream process in background and samples the updated state.

We can observe the value with readDyn. We need to shut down the stream when we no longer need it with cancelDyn function.

data DynRef m a Source #

Reference to running dynamic process by which we can query values (readDyn). Also note that we no longer need the reference we should release the resources by calling cancelDyn.

Constructors

forall s. DynRef (s -> m a) (Ref m s) ThreadId (m ()) 
ConstRef a 

readDyn :: Frp m => DynRef m a -> m a Source #

Reads current dynamic value.

cancelDyn :: Frp m => DynRef m a -> m () Source #

Shuts down the background process for dynamic and releases resulrces for event stream that drives the dynamic.

Control

newEvt :: Frp m => Evt m a -> m (Evt m a) Source #

Runs the argument event stream as background process and produces event stream that is fed with events over channel (unagi-channel package). When result event stream shuts down the background process also shuts down.

newDyn :: Frp m => Dyn m a -> m (Dyn m a) Source #

Runs the dynamic process in background and returns dynamic that just samples the background proces with readDyn.

withDyn :: Frp m => Dyn m a -> (m a -> m b) -> m b Source #

Runs dynamic within the scope of the function. It provides a callback with dyn getter as argument and after callback finishes it shutdowns the dyn process.

API

Event API

scan :: Frp m => (a -> b -> b) -> b -> Evt m a -> Evt m b Source #

scan over event stream. Example:

naturals = scan (+) 0 pulse

scanMay :: Frp m => (a -> b -> Maybe b) -> b -> Evt m a -> Evt m b Source #

scan combined with filter. If accumulator function produces Nothing on event then that event is ignored and state is kept to previous state.

mapMay :: Frp m => (a -> Maybe b) -> Evt m a -> Evt m b Source #

Map with filtering. When Nothing is produced event is omitted from the stream.

accum :: Frp m => (a -> s -> (b, s)) -> s -> Evt m a -> Evt m b Source #

Accumulate over event stream.

accumB :: Frp m => a -> Evt m (a -> a) -> Dyn m a Source #

Accumulates the values with event stream that produce functions.

accumMay :: Frp m => (a -> s -> Maybe (b, s)) -> s -> Evt m a -> Evt m b Source #

Accumulate over event stream.

filters :: Frp m => (a -> Bool) -> Evt m a -> Evt m a Source #

Filtering of the event strewams. Only events that produce True remain in the stream.

filterJust :: Frp m => Evt m (Maybe a) -> Evt m a Source #

Filters based on Maybe. If Nothing is produced forthe event it is omitted from the stream.

whens :: Frp m => Dyn m Bool -> Evt m a -> Evt m a Source #

Filters with dynamic. When dynamic is true events pass through and when it's false events are omitted.

splits :: Frp m => Evt m (Either a b) -> (Evt m a, Evt m b) Source #

Splits the either event stream.

lefts :: Frp m => Evt m (Either a b) -> Evt m a Source #

Gets all left events from the stream

rights :: Frp m => Evt m (Either a b) -> Evt m b Source #

Gets all right events from the stream

iterates :: Frp m => (a -> a) -> a -> Evt m b -> Evt m a Source #

Iterates over event stream. It's like scan but it ignores the values of underying stream and starts with initial value as first element.

withIterates :: Frp m => (a -> a) -> a -> Evt m b -> Evt m (a, b) Source #

fix1 :: Frp m => (Evt m a -> m (Evt m a)) -> Evt m a Source #

Recursion on event streams. As event streams are functions we can not use normal recursion that haskell provides. It will stuck the execution. But we can use fix1 to create event stream that feeds back the events to itself.

Note that any sort of recursion can be implemented with fix1. For example if we need 3-recursive event stream:

fix3 ::
     (Evt m a -> Evt m b -> Evt m c -> m (Evt m a, Evt m b, Evt m c))
  -> (Evt m a, Evt m b, Evt m c)

we can use sum tpye tags to join it to single stream:

data Tag a b c = TagA a | TagB b | TagC c
fix3 f = unwrap $ fix1 g
  where
     g x = wrap <$> f (unwrapA x) (unwrapB x) (unwrapC x)

     wrap a b c = mconcat [TagA <$> a, TagB <$> b, TagC <$> c]
     unwrap evt = (unwrapA evt, unwrapB evt, unwrapC evt)

     unwrapA = flip mapMay $ \x -> case x of
                                 TagA a -> Just a
                                 _      -> Nothing

We can use this trck with any number of streams. There are helper functions: fix2, fix3, fix4

fix2 :: Frp m => (Evt m a -> Evt m b -> m (Evt m a, Evt m b)) -> (Evt m a, Evt m b) Source #

Recursion for binary functions

fix3 :: Frp m => (Evt m a -> Evt m b -> Evt m c -> m (Evt m a, Evt m b, Evt m c)) -> (Evt m a, Evt m b, Evt m c) Source #

Recursion for ternary functions

fix4 :: Frp m => (Evt m a -> Evt m b -> Evt m c -> Evt m d -> m (Evt m a, Evt m b, Evt m c, Evt m d)) -> (Evt m a, Evt m b, Evt m c, Evt m d) Source #

Recursion for functions of four arguments

switch :: Frp m => Evt m (Evt m a) -> Evt m a Source #

Flattens event stream producer by switching between event streams. When next event stream happens it shuts down the previous one.

joins :: Frp m => Evt m (Evt m a) -> Evt m a Source #

Joins event stream of streams. If stream is started it runs until the end.

delay :: Frp m => NominalDiffTime -> Evt m a -> Evt m a Source #

Delays in the thread of execution. Note that it can interfere and screw up functions like clock, timer, pulse, ticks

delayFork :: Frp m => NominalDiffTime -> Evt m a -> Evt m a Source #

Delays in background by forking on each event. Note tht if delayed event was put into background prior to stopping of the main event stream it will fire anyway. There is no way to stop it.

sums :: (Frp m, Num a) => Evt m a -> Evt m a Source #

Sums all the elements in the event stream

sumD :: (Frp m, Num a) => NominalDiffTime -> Dyn m a -> Dyn m a Source #

Sums all points in the signal with given time step

integrate :: (Frp m, VectorSpace v, Real (Scalar v), Fractional (Scalar v)) => Scalar v -> Dyn m v -> Dyn m v Source #

Integrates signal of vectors with given time step

integrate2 :: (Frp m, VectorSpace v, Real (Scalar v), Fractional (Scalar v)) => Scalar v -> Dyn m v -> Dyn m v Source #

More accurate integration of signal of vectors with given time step

products :: (Frp m, Num a) => Evt m a -> Evt m a Source #

Finds the product of all elements in the event stream.

count :: Frp m => Evt m a -> Evt m Int Source #

Counts how many events accured so far on the stream.

withCount :: Frp m => Evt m a -> Evt m (Int, a) Source #

appends :: (Frp m, Monoid a) => Evt m a -> Evt m a Source #

Monoidal append of all elements in the stream

foldMaps :: (Frp m, Monoid b) => (a -> b) -> Evt m a -> Evt m b Source #

Same as foldMap only for streams.

takes :: Frp m => Int -> Evt m a -> Evt m a Source #

Takes only so many events from the stream

drops :: Frp m => Int -> Evt m a -> Evt m a Source #

Drops first so many events from the stream

takesWhile :: Frp m => (a -> Bool) -> Evt m a -> Evt m a Source #

Takes events only while predicate is true.

dropsWhile :: Frp m => (a -> Bool) -> Evt m a -> Evt m a Source #

Drops events while predicate is true.

cycles :: Frp m => [a] -> Evt m b -> Evt m a Source #

Cycles the values in the list over event sream.

listAt :: Frp m => [a] -> Evt m Int -> Evt m a Source #

Takes elements from the list by index. If index is out of bounds the event is omitted.

toToggle :: Frp m => Evt m a -> Evt m Bool Source #

Turns event stream to toggle stream. It produce cyclic sequence of [True, False]

forevers :: Frp m => Evt m a -> Evt m a Source #

Takes an event and repeats it all the time.

races :: Frp m => Evt m a -> Evt m a -> Evt m a Source #

Shutdown the remaining event if one of the events close up early.

forks :: Frp m => Evt m a -> Evt m a Source #

Execute each callback in separate thread

Render streams

heads :: Frp m => Evt m a -> m a Source #

prints :: (Frp m, Show a) => Evt m a -> m () Source #

Starts event stream process and as callback prints it values.

putStrLns :: Frp m => Evt m String -> m () Source #

Starts event stream process and as callback prints it values.

folds :: (Frp m, Monoid a) => Evt m a -> m a Source #

Monoidal fold for event streams, note that stream have to be finite for the function to complete

foldls :: Frp m => (b -> a -> b) -> b -> Evt m a -> m b Source #

Left fold for event streams, note that stream have to be finite for the function to complete

foldls' :: Frp m => (b -> a -> m b) -> b -> Evt m a -> m b Source #

Effectful left fold

foldrs :: Frp m => (a -> b -> b) -> b -> Evt m a -> m b Source #

Right fold for event streams, note that stream have to be finite for the function to complete

foldrs' :: Frp m => (a -> b -> m b) -> b -> Evt m a -> m b Source #

Effectful right fold

data Parser m a b Source #

Instances

Instances details
Frp m => Functor (Parser m a) Source # 
Instance details

Defined in Dyna

Methods

fmap :: (a0 -> b) -> Parser m a a0 -> Parser m a b #

(<$) :: a0 -> Parser m a b -> Parser m a a0 #

Frp m => Applicative (Parser m a) Source # 
Instance details

Defined in Dyna

Methods

pure :: a0 -> Parser m a a0 #

(<*>) :: Parser m a (a0 -> b) -> Parser m a a0 -> Parser m a b #

liftA2 :: (a0 -> b -> c) -> Parser m a a0 -> Parser m a b -> Parser m a c #

(*>) :: Parser m a a0 -> Parser m a b -> Parser m a b #

(<*) :: Parser m a a0 -> Parser m a b -> Parser m a a0 #

runParser :: Frp m => Parser m a b -> Evt m a -> m (Maybe b) Source #

takeP :: Frp m => Parser m a b -> Evt m a -> Evt m b Source #

Reads single event

cycleP :: Frp m => Parser m a b -> Evt m a -> Evt m b Source #

headP :: Frp m => Parser m a a Source #

Takes first element of the event stream and shuts the stream down.

maybeP :: Frp m => (a -> Maybe b) -> Parser m a b Source #

Event/Dynamic interaction

hold :: Frp m => a -> Evt m a -> Dyn m a Source #

Turns event stream to dynamic. It holds the values of events until the next event happen. It starts with initial value.

hold initVal events = ...

unhold :: Frp m => Dyn m a -> Evt m a Source #

Turns dynamic into event stream of underlying events that trigger dynamic updates.

scanD :: Frp m => (a -> b -> b) -> b -> Evt m a -> Dyn m b Source #

scans over event stream and converts it to dynamic.

scanMayD :: Frp m => (a -> b -> Maybe b) -> b -> Evt m a -> Dyn m b Source #

Dynamic scan that can also filter out events. If Nothing is produced then the event is skipped.

switchD :: Frp m => Dyn m a -> Evt m (Dyn m a) -> Dyn m a Source #

Switches between dynamic producers.

switchDyn :: Frp m => Dyn m (Evt m a) -> Evt m a Source #

Queries the event stream form dynamic and runs it all next event streams are ignored.

apply :: Frp m => Dyn m (a -> b) -> Evt m a -> Evt m b Source #

Applies a function to event stream value. The function is sampled from dynamic process.

applyMay :: Frp m => Dyn m (a -> Maybe b) -> Evt m a -> Evt m b Source #

Apply combined with filter.

snap :: Frp m => Dyn m a -> Evt m b -> Evt m a Source #

Snapshot of dynamic process with event stream. All values in the event stream are substituted with current value of dynamic.

attach :: Frp m => Dyn m a -> Evt m b -> Evt m (a, b) Source #

Attach element from dyn to event stream.

attachWith :: Frp m => (a -> b -> c) -> Dyn m a -> Evt m b -> Evt m c Source #

Kind of zipWith function for dynamics and event streams.

attachWithMay :: Frp m => (a -> b -> Maybe c) -> Dyn m a -> Evt m b -> Evt m c Source #

Attach with filtering. When Nothing is produced event is omitted from the stream.

(<@>) :: Frp m => Dyn m (a -> b) -> Evt m a -> Evt m b infixl 4 Source #

Infix variant of apply

(<@) :: Frp m => Dyn m a -> Evt m b -> Evt m a infixl 4 Source #

Infix variant of snap.

Effectful API

class FunctorM f where Source #

Methods

fmap' :: Frp m => (a -> m b) -> f m a -> f m b Source #

Instances

Instances details
FunctorM Evt Source # 
Instance details

Defined in Dyna

Methods

fmap' :: Frp m => (a -> m b) -> Evt m a -> Evt m b Source #

FunctorM Dyn Source # 
Instance details

Defined in Dyna

Methods

fmap' :: Frp m => (a -> m b) -> Dyn m a -> Dyn m b Source #

foreach :: Frp m => (a -> m ()) -> Evt m a -> Evt m a Source #

Adds some procedure to callback. Procedure is called prior to callback execution.

posteach :: Frp m => (a -> m ()) -> Evt m a -> Evt m a Source #

Adds some procedure to callback. Procedure is called after callback execution.

iterates' :: Frp m => (a -> m a) -> a -> Evt m b -> Evt m a Source #

Effectful version for iterates.

scan' :: Frp m => (a -> b -> m b) -> b -> Evt m a -> Evt m b Source #

scan over event stream with effectful function.

scanMay' :: Frp m => (a -> b -> m (Maybe b)) -> b -> Evt m a -> Evt m b Source #

scan combined with filter for effectful function. See scanMay for details.

accum' :: Frp m => (a -> s -> m (b, s)) -> s -> Evt m a -> Evt m b Source #

Accumulate over event stream.

accumMay' :: Frp m => (a -> s -> m (Maybe (b, s))) -> s -> Evt m a -> Evt m b Source #

Accumulate over event stream.

filters' :: Frp m => (a -> m Bool) -> Evt m a -> Evt m a Source #

Effectful filtering for event streams.

mapMay' :: Frp m => (a -> m (Maybe b)) -> Evt m a -> Evt m b Source #

Effectful mapMay

apply' :: Frp m => Dyn m (a -> m b) -> Evt m a -> Evt m b Source #

Effectful variant of apply.

applyMay' :: Frp m => Dyn m (a -> m (Maybe b)) -> Evt m a -> Evt m b Source #

Effectful applyMay.

Utilities

Channels (interaction with the world)

mchanEvt :: Frp m => Chan a -> Evt m a Source #

Creates the event stream that listens to MVar based channel. If any value is put chan the event stream fires the callback.

tchanEvt :: Frp m => TChan a -> Evt m a Source #

Creates the event stream that listens to TChan based channel. If any value is put chan the event stream fires the callback.

uchanEvt :: Frp m => InChan a -> Evt m a Source #

Creates the event stream that listens to unagi channel (package unagi-chan). If any value is put chan the event stream fires the callback.

type UChan a = (InChan a, OutChan a) Source #

newTriggerEvt :: (Frp m, MonadIO io) => m (Evt m a, a -> io ()) Source #

Create a new Event and a function that will cause the Event to fire

IO

getLines :: Frp m => Evt m String Source #

Stream of user inputs

Clock

clock :: Frp m => NominalDiffTime -> Evt m UTCTime Source #

Queries current time periodically with given period in seconds.

pulse :: Frp m => NominalDiffTime -> Evt m () Source #

Produces pulse events with given period in seconds.

ticks :: Frp m => NominalDiffTime -> Evt m NominalDiffTime Source #

Produces pulse events with given period in seconds and also tells how many seconds exactly has passed. It can be useful for simulations of models that are based on differential equations. As event streams carries how much time has passed between simulation steps.

timer :: Frp m => NominalDiffTime -> Evt m NominalDiffTime Source #

Timer behaves like tocks only it produces accumulated time since beginning of the process. It calculates them by querying current time and suntracting start time from it.

It can be though of as:

sums ticks

timerD :: Frp m => NominalDiffTime -> Dyn m NominalDiffTime Source #

Timer as dynamic signal.

Random

toRandom :: forall m a b. (Frp m, Random b) => Evt m a -> Evt m b Source #

Substitutes values in event stream with random values.

toRandomR :: forall m a b. (Frp m, Random b) => (b, b) -> Evt m a -> Evt m b Source #

Substitutes values in event stream with random values from the given range.

withRandom :: forall m a b. (Frp m, Random b) => Evt m a -> Evt m (b, a) Source #

Substitutes values in event stream with random values.

withRandomR :: forall m a b. (Frp m, Random b) => (b, b) -> Evt m a -> Evt m (b, a) Source #

Substitutes values in event stream with random values from the given range.

oneOf :: Frp m => [a] -> Evt m b -> Evt m a Source #

Picks at random one element from the list

withOneOf :: Frp m => [a] -> Evt m b -> Evt m (a, b) Source #

Picks at random one element from the list

freqOf :: (MonadRandom m, Frp m) => Dyn m [(a, Rational)] -> Evt m b -> Evt m a Source #

Picks at random one element from the list. We also provide distribution of events. Probability to pick up the element. Sum of probabilities should equal to 1.

withFreqOf :: (MonadRandom m, Frp m) => Dyn m [(a, Rational)] -> Evt m b -> Evt m (a, b) Source #

Picks at random one element from the list. We also provide distribution of events. Probability to pick up the element. Sum of probabilities should equal to 1.

randSkip :: Frp m => Dyn m Double -> Evt m a -> Evt m a Source #

Skips at random elements from the list. We provide frequency to skip events with dynamic first argument.

randSkipBy :: Frp m => Dyn m (a -> Double) -> Evt m a -> Evt m a Source #

Skips elements at random. The probability to skip element depends on the element itself.

Re-exports

liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c #

Lift a binary function to actions.

Some functors support an implementation of liftA2 that is more efficient than the default one. In particular, if fmap is an expensive operation, it is likely better to use liftA2 than to fmap over the structure and then use <*>.

This became a typeclass method in 4.10.0.0. Prior to that, it was a function defined in terms of <*> and fmap.

Using ApplicativeDo: 'liftA2 f as bs' can be understood as the do expression

do a <- as
   b <- bs
   pure (f a b)

liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d #

Lift a ternary function to actions.

Using ApplicativeDo: 'liftA3 f as bs cs' can be understood as the do expression

do a <- as
   b <- bs
   c <- cs
   pure (f a b c)

class BasisArity v where Source #

Methods

basisArity :: v -> Int Source #

Instances

Instances details
BasisArity Double Source # 
Instance details

Defined in Dyna

BasisArity Float Source # 
Instance details

Defined in Dyna

Methods

basisArity :: Float -> Int Source #

(BasisArity a, BasisArity b) => BasisArity (a, b) Source # 
Instance details

Defined in Dyna

Methods

basisArity :: (a, b) -> Int Source #

(Frp m, BasisArity v) => BasisArity (Dyn m v) Source # 
Instance details

Defined in Dyna

Methods

basisArity :: Dyn m v -> Int Source #

(BasisArity a, BasisArity b, BasisArity c) => BasisArity (a, b, c) Source # 
Instance details

Defined in Dyna

Methods

basisArity :: (a, b, c) -> Int Source #

module Data.Cross