Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- sumFrom :: Monad m => Integer -> Cell m Integer Integer
- count :: Monad m => Cell m a Integer
- foldC :: (Data b, Monad m) => (a -> b -> b) -> b -> Cell m a b
- foldC' :: (Data b, Monad m) => (a -> b -> b) -> b -> Cell m a b
- hold :: (Data a, Monad m) => a -> Cell m (Maybe a) a
- changes :: (Data a, Eq a, Monad m) => Cell m a (Maybe a)
- holdJust :: (Monad m, Data a) => Cell m (Maybe a) (Maybe a)
- holdFirst :: (Data a, Monad m) => Cell m a a
- boundedFIFO :: (Data a, Monad m) => Int -> Cell m (Maybe a) (Seq a)
- fifo :: (Monad m, Data a) => Cell m (Seq a) (Maybe a)
- fifoList :: (Monad m, Data a) => Cell m [a] (Maybe a)
- fifoFoldable :: (Monad m, Data a, Foldable f) => Cell m (f a) (Maybe a)
- edge :: Monad m => Cell m Bool Bool
- printTime :: MonadIO m => String -> m ()
- printTimeC :: MonadIO m => String -> Cell m () ()
- data BufferCommand a
- maybePush :: Maybe a -> [BufferCommand a]
- maybePop :: Maybe a -> [BufferCommand b]
- buffer :: (Monad m, Data a) => Cell m [BufferCommand a] (Maybe a)
- buffered :: (Monad m, Data a) => Cell m (Maybe a) (Maybe b) -> Cell m (Maybe a) (Maybe b)
- onChange :: (Monad m, Data p, Eq p) => p -> (p -> p -> a -> m b) -> Cell m a (Maybe b)
- onChange' :: (Monad m, Data p, Eq p) => (p -> p -> a -> m b) -> Cell m (p, a) (Maybe b)
State accumulation
sumFrom :: Monad m => Integer -> Cell m Integer Integer Source #
Sum all past inputs, starting by the given number
foldC :: (Data b, Monad m) => (a -> b -> b) -> b -> Cell m a b Source #
Accumulate all incoming data,
using the given fold function and start value.
For example, if
receives inputs foldC
f ba0
, a1
,...
it will output b
, f a0 b
, f a1 $ f a0 b
, and so on.
foldC' :: (Data b, Monad m) => (a -> b -> b) -> b -> Cell m a b Source #
Like foldC
, but does not delay the output.
holdFirst :: (Data a, Monad m) => Cell m a a Source #
Hold the first value and output it indefinitely.
boundedFIFO :: (Data a, Monad m) => Int -> Cell m (Maybe a) (Seq a) Source #
boundedFIFO n
keeps the first n
present values.
fifo :: (Monad m, Data a) => Cell m (Seq a) (Maybe a) Source #
Buffers and returns the elements in First-In-First-Out order,
returning Nothing
whenever the buffer is empty.
fifoList :: (Monad m, Data a) => Cell m [a] (Maybe a) Source #
Like fifo
, but accepts lists as input.
Each step is O(n) in the length of the list.
Debugging utilities
printTime :: MonadIO m => String -> m () Source #
Print the current UTC time, prepended with the first 8 characters of the given message.
Buffers
data BufferCommand a Source #
A command to send to buffer
.
buffered :: (Monad m, Data a) => Cell m (Maybe a) (Maybe b) -> Cell m (Maybe a) (Maybe b) Source #
- Whenever
value entersJust
abuffered cell
, it is added to the buffer. - Whenever
cell
emits
, the oldest value is dropped from the buffer.Just
b cell
is always fed withJust
the oldest value from the buffer, except when the buffer is empty, then it is fedNothing
.
This construction guarantees that cell
produces exactly one output for every input value.
Detecting change
:: (Monad m, Data p, Eq p) | |
=> p | This parameter has to change during live coding to trigger an action |
-> (p -> p -> a -> m b) | This action gets passed the old parameter and the new parameter |
-> Cell m a (Maybe b) |
Perform an action whenever the parameter p
changes, and the code is reloaded.
Note that this does not trigger any actions when adding, or removing an onChange
cell.
For this functionality, see LiveCoding.Handle.
Also, when moving such a cell, the action may not be triggered reliably.