artery-0.1.1: A simple, arrow-based reactive programming

Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Artery

Synopsis

Documentation

newtype Artery m i o Source

Artery is a device that produces a value from the input every beat.

Constructors

Artery 

Fields

unArtery :: forall r. i -> (o -> Artery m i o -> m r) -> m r
 

Instances

Category * (Artery m) 
Arrow (Artery m) 
ArrowChoice (Artery m) 
Strong (Artery m) 
Choice (Artery m) 
Profunctor (Artery m) 
Functor (Artery m i) 
Applicative (Artery m i) 
Fractional o => Fractional (Artery m i o) 
Num o => Num (Artery m i o) 
Monoid o => Monoid (Artery m i o) 

runArtery :: Monad m => Artery m i o -> i -> m (o, Artery m i o) Source

Pump up the Artery.

effectful :: Monad m => (i -> m o) -> Artery m i o Source

Run the given action every beat.

stateful :: Monad m => (i -> StateT s m o) -> s -> Artery m i o Source

Run the given stateful action every beat.

scan :: (i -> a -> a) -> a -> Artery m i a Source

Produce values by accumulating inputs.

scanM :: Monad m => (i -> a -> m a) -> a -> Artery m i a Source

Analogous to scan, but it allows monadic accumulators.

fromList :: [a] -> Artery m b a Source

runList :: Applicative m => Artery m a b -> [a] -> m [b] Source

feedback :: r -> Artery m (i, r) (o, r) -> Artery m i o Source

Analogous to loop, but the feedback will be delayed a beat.

delay1 :: a -> Artery m a a Source

Delay a beat. The first argument is the default value for the output.

delay :: Int -> a -> Artery m a a Source

'delay n' propagates a signal n beat behind.

cartridge :: MonadIO m => MVar (Artery m i o) -> Artery m i o Source