rsagl-frp-0.6.0.0: The RogueStar Animation and Graphics Library: Functional Reactive Programming

RSAGL.FRP.FRP

Synopsis

Documentation

data FRP e m j p Source

A switchable automata with timewise numerical methods.

Instances

StateOf m ~ s => ArrowState s (FRP e m) 
Arrow (FRP e m) 
Category (FRP e m) 
Functor (FRP e m j) 
Applicative (FRP e m j) 

switchContinue :: FRP e m (Maybe (FRP e m (SwitchInputOf m) (SwitchOutputOf m)), SwitchInputOf m) (SwitchInputOf m)Source

Whenever a value is provided, change the presently running switch (or thread) to the specified new value, and execute that switch before continuing. This destroys all state local to the currently running switch (or thread). This function acts as if the switch were performed at frame begin.

switchTerminate :: FRP e m (Maybe (FRP e m (SwitchInputOf m) (SwitchOutputOf m)), SwitchOutputOf m) (SwitchOutputOf m)Source

Whenever a value is provided, change the presently running switch (or thread) to the specified new value, and execute that switch before continuing. This destroys all state local to the currently running switch (or thread). This function acts as if the switch were performed at frame end.

spawnThreads :: ThreadingOf m ~ Enabled => FRP e m [(ThreadIDOf m, FRP e m (SwitchInputOf m) (SwitchOutputOf m))] ()Source

Spawn new threads once per frame.

killThreadIf :: ThreadingOf m ~ Enabled => FRP e m Bool ()Source

Kill the current thread, only when the given parameter is true.

threadIdentity :: FRP e m () (ThreadIDOf m)Source

Get the current thread's identity.

withThreadIdentity :: (ThreadIDOf m -> FRP e m j p) -> FRP e m j pSource

Construct an arrow from its thread identity.

frpTest :: (forall e. [FRP e (FRPX () () i o) i o]) -> [i] -> IO [[o]]Source

type FRPProgram s i o = FRPInit s () i oSource

newFRPProgram :: (RecombinantState s, Eq t) => ThreadIdentityRule t -> (forall e. [(t, FRP e (FRPX t s i o) i o)]) -> IO (FRPProgram s i [(t, o)])Source

Construct a multi-threaded FRPProgram.

newFRP1Program :: (forall e. FRP e (FRP1 s i o) i o) -> IO (FRPProgram s i o)Source

Construct a single-threaded FRPProgram.

updateFRPProgram :: Maybe Time -> (i, s) -> FRPProgram s i o -> IO (o, s)Source

Bring an FRPProgram up-to-date with the current time or a specific time.

accumulate :: p -> (j -> p -> p) -> FRP e m j pSource

Framewise accumulation of signals. The embedded function recieves the current input and the previous output.

absoluteTime :: FRP e m () TimeSource

Get the current absolute time.

deltaTime :: FRP e m () TimeSource

Get the change in time since the last update.

type ThreadIdentityRule t = (t -> Bool) -> t -> BoolSource

Should a thread be allowed to spawn? Typical values are nullaryThreadIdentity, forbidDuplicates. The predicate tests whether or not a particular thread is already running.

forbidDuplicates :: Eq t => ThreadIdentityRule tSource

Forbig duplicate threads by equality on the thread identity.

allowAnonymous :: ThreadIdentityRule t -> ThreadIdentityRule (Maybe t)Source

Allow unlimited duplicate Nothing threads, while restricting all other threads according to the specified rule.

nullaryThreadIdentity :: ThreadIdentityRule aSource

Allow unlimited duplicate threads.

frpContext :: (RecombinantState s, s ~ StateOf m, FRPModel m, Eq t) => ThreadIdentityRule t -> [(t, FRP e (FRPContext t j p m) j p)] -> FRP e m j [(t, p)]Source

Embed some threads inside another running thread, as threadGroup.

frp1Context :: FRPModel m => FRP e (FRP1Context j p m) j p -> FRP e m j pSource

Embed a single-threaded, bracketed switch inside another running thread.

frpFix :: FRPModel m => FRP e (FRP1Context (j, x) (p, x) m) (j, x) (p, x) -> FRP e m j pSource

Value recusion (see fix).

whenJust :: FRPModel m => (forall x y. FRP e (FRP1Context x y m) j p) -> FRP e m (Maybe j) (Maybe p)Source

Run a computation only when the input is defined.

ioInit :: InputOutputOf m ~ Enabled => IO p -> FRP e m () pSource

Perform an IO action when a stream is first initialized.

ioAction :: InputOutputOf m ~ Enabled => (j -> IO p) -> FRP e m j pSource

Perform an arbitrary IO action.

outgoingBySource

Arguments

:: (j -> j -> Bool)

Equality predicate as described in newTransmitterBy.

-> FRP e m j (Message j) 

Send tagged information.

outgoing :: Eq j => FRP e m j (Message j)Source

Send tagged information.

incoming :: FRP e m (Message j) jSource

Receive tagged information, with memoization.

class StreamFunctor s whereSource

An FRP-embedded functor.

Methods

streampure :: a -> FRP e m () (s a)Source

streammap :: (a -> b) -> FRP e m (s a) (s b)Source

randomA :: Random a => FRP e m (a, a) aSource

Get a bounded random value, as randomRIO. A new value is pulled for each frame of animation.