Safe Haskell | None |
---|
- type Step = EvalNetwork (IO ())
- data Network
- emptyNetwork :: Network
- type Build = BuildT Identity
- liftIOLater :: IO () -> Build ()
- type BuildIO = BuildT IO
- type BuildT = RWST () BuildConf Network
- liftBuild :: Monad m => Build a -> BuildT m a
- compile :: BuildIO a -> Network -> IO (a, Network)
- module Control.Monad.IO.Class
- interpret :: (Pulse a -> BuildIO (Pulse b)) -> [Maybe a] -> IO [Maybe b]
- mapAccumM :: Monad m => (a -> s -> m (b, s)) -> s -> [a] -> m [b]
- mapAccumM_ :: Monad m => (a -> s -> m (b, s)) -> s -> [a] -> m ()
- runSpaceProfile :: (Pulse a -> BuildIO void) -> [a] -> IO ()
- newInput :: Key a -> Build (Pulse a, a -> Step)
- addHandler :: Pulse (Future a) -> (a -> IO ()) -> Build ()
- readLatch :: Latch a -> Build a
- data Pulse a
- neverP :: Build (Pulse a)
- alwaysP :: Build (Pulse ())
- mapP :: (a -> b) -> Pulse a -> Build (Pulse b)
- type Future = Dated
- tagFuture :: Latch a -> Pulse b -> Build (Pulse (Future a))
- unsafeMapIOP :: (a -> IO b) -> Pulse a -> Build (Pulse b)
- filterJustP :: Pulse (Maybe a) -> Build (Pulse a)
- unionWithP :: (a -> a -> a) -> Pulse a -> Pulse a -> Build (Pulse a)
- data Latch a
- pureL :: a -> Latch a
- mapL :: (a -> b) -> Latch a -> Latch b
- applyL :: Latch (a -> b) -> Latch a -> Latch b
- accumL :: a -> Pulse (a -> a) -> Build (Latch a, Pulse a)
- applyP :: Latch (a -> b) -> Pulse a -> Build (Pulse b)
- switchL :: Latch a -> Pulse (Latch a) -> Build (Latch a)
- executeP :: Pulse (b -> BuildIO a) -> b -> Build (Pulse a)
- switchP :: Pulse (Pulse a) -> Build (Pulse a)
Synopsis
This is an internal module, useful if you want to implemented your own FRP library. If you just want to use FRP in your project, have a look at Reactive.Banana instead.
Evaluation
A Network
represents the state of a pulse/latch network,
which consists of a Graph
and the values of all accumulated latches
in the network.
The Network
that contains no pulses or latches.
Build FRP networks
liftIOLater :: IO () -> Build ()Source
module Control.Monad.IO.Class
Testing
interpret :: (Pulse a -> BuildIO (Pulse b)) -> [Maybe a] -> IO [Maybe b]Source
Simple interpreter for pulse/latch networks.
Mainly useful for testing functionality
Note: The result is not computed lazily, for similar reasons
that the sequence
function does not compute its result lazily.
mapAccumM_ :: Monad m => (a -> s -> m (b, s)) -> s -> [a] -> m ()Source
Strict mapAccum
for a monad. Discards results.
runSpaceProfile :: (Pulse a -> BuildIO void) -> [a] -> IO ()Source
Execute an FRP network with a sequence of inputs, but discard results.
Mainly useful for testing whether there are space leaks.
IO
newInput :: Key a -> Build (Pulse a, a -> Step)Source
Create a new pulse in the network and a function to trigger it.
Together with addHandler
, this function can be used to operate with
pulses as with standard callback-based events.
addHandler :: Pulse (Future a) -> (a -> IO ()) -> Build ()Source
Register a handler to be executed whenever a pulse occurs.
The pulse may refer to future latch values.