Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Synopsis
- type Step = EvalNetwork (IO ())
- type EvalNetwork a = Network -> IO (a, Network)
- data Network
- emptyNetwork :: IO Network
- getSize :: Network -> IO Int
- type Build = ReaderWriterIOT BuildR BuildW IO
- liftIOLater :: IO () -> Build ()
- type BuildIO = Build
- liftBuild :: Build a -> BuildIO a
- buildLater :: Build () -> Build ()
- buildLaterReadNow :: Build a -> Build a
- compile :: BuildIO a -> Network -> IO (a, Network)
- module Control.Monad.IO.Class
- module Reactive.Banana.Prim.High.Cached
- interpret :: (Pulse a -> BuildIO (Pulse b)) -> [Maybe a] -> IO [Maybe b]
- mapAccumM :: Monad m => (a -> s -> m (b, s)) -> s -> [a] -> m ([b], s)
- mapAccumM_ :: Monad m => (a -> s -> m (b, s)) -> s -> [a] -> m ()
- runSpaceProfile :: Show b => (Pulse a -> BuildIO (Pulse b)) -> [a] -> IO ()
- newInput :: forall 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 = IO
- tagFuture :: Latch a -> Pulse b -> Build (Pulse (Future a))
- unsafeMapIOP :: forall a b. (a -> IO b) -> Pulse a -> Build (Pulse b)
- filterJustP :: Pulse (Maybe a) -> Build (Pulse a)
- mergeWithP :: (a -> Maybe c) -> (b -> Maybe c) -> (a -> b -> Maybe c) -> Pulse a -> Pulse b -> Build (Pulse c)
- type Latch a = Ref (LatchD 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 :: forall a b. Pulse (b -> Build a) -> b -> Build (Pulse a)
- switchP :: Pulse a -> Pulse (Pulse a) -> Build (Pulse a)
- printDot :: Network -> IO String
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
type Step = EvalNetwork (IO ()) Source #
emptyNetwork :: IO Network Source #
Build FRP networks
liftIOLater :: IO () -> Build () Source #
buildLater :: Build () -> Build () Source #
buildLaterReadNow :: Build a -> Build a Source #
Pretend to return a value right now, but do not actually calculate it until later.
NOTE: Accessing the value before it's written leads to an error.
FIXME: Is there a way to have the value calculate on demand?
module Control.Monad.IO.Class
Caching
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 ([b], s) Source #
mapAccum
for a monad.
mapAccumM_ :: Monad m => (a -> s -> m (b, s)) -> s -> [a] -> m () Source #
Strict mapAccum
for a monad. Discards results.
runSpaceProfile :: Show b => (Pulse a -> BuildIO (Pulse b)) -> [a] -> IO () Source #
Execute an FRP network with a sequence of inputs. Make sure that outputs are evaluated, but don't display their values.
Mainly useful for testing whether there are space leaks.
IO
newInput :: forall 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.
Pulse
mergeWithP :: (a -> Maybe c) -> (b -> Maybe c) -> (a -> b -> Maybe c) -> Pulse a -> Pulse b -> Build (Pulse c) Source #
Latch
Dynamic event switching
Notes
The Build
monad is an instance of MonadFix
and supports value recursion.
However, it is built on top of the IO
monad, so the recursion is
somewhat limited.
The main rule for value recursion in the IO
monad is that the action
to be performed must be known in advance. For instance, the following snippet
will not work, because putStrLn
cannot complete its action without
inspecting x
, which is not defined until later.
mdo putStrLn x let x = "Hello recursion"
On the other hand, whenever the sequence of IO
actions can be known
before inspecting any later arguments, the recursion works.
For instance the snippet
mdo p1 <- mapP p2 p2 <- neverP return p1
works because mapP
does not inspect its argument. In other words,
a call p1 <- mapP undefined
would perform the same sequence of IO
actions.
(Internally, it essentially calls newIORef
.)
With this issue in mind, almost all operations that build Latch
and Pulse
values have been carefully implemented to not inspect
their arguments.
In conjunction with the Cached
mechanism for observable sharing,
this allows us to build combinators that can be used recursively.
One notable exception is the readLatch
function, which must
inspect its argument in order to be able to read its value.