varying-0.8.1.0: FRP through value streams and monadic splines.

Copyright(c) 2015 Schell Scivally
LicenseMIT
MaintainerSchell Scivally <schell@takt.com>
Safe HaskellNone
LanguageHaskell2010

Control.Varying.Spline

Contents

Description

Using splines we can easily create continuous streams from discontinuous streams. A spline is a monadic layer on top of event streams which are only continuous over a certain domain. The idea is that we use a monad to "run a stream switched by events". This means taking two streams - an output stream and an event stream, and combining them into a temporarily producing stream. Once that "stream pair" inhibits, the computation completes and returns a result value. That result value is then used to determine the next spline in the sequence.

Synopsis

Spline

type Spline a b c = SplineT a b Identity c Source #

A SplineT monad parameterized with Identity that takes input of type a, output of type b and a result value of type c.

Spline Transformer

newtype SplineT a b m c Source #

SplineT shares all the types of VarT and adds a result value. Its monad, input and output types (m, a and b, respectively) represent the same parameters in VarT. A spline adds a result type which represents the monadic computation's result value.

A spline either concludes in a result or it produces an output value and another spline. This makes it a stream that eventually ends. We can use this to set up our streams in a monadic fashion, where the end result of one spline can be used to determine the next spline to run. Using outputStream we can then fuse these piecewise continuous (but otherwise discontinuous) streams into one continuous stream of type VarT m a b. Alternatively you can simply poll the network until it ends using runSplineT.

Constructors

SplineT 

Fields

Instances
MonadTrans (SplineT a b) Source #

A spline is a transformer by running the effect and immediately concluding, using the effect's result as the result value.

>>> :{
let s = do () <- lift $ print "Hello"
           step 2
    v = outputStream s 0
in testVarOver v [()]
>>> :}
"Hello"
2
Instance details

Defined in Control.Varying.Spline

Methods

lift :: Monad m => m a0 -> SplineT a b m a0 #

Monad m => Monad (SplineT a b m) Source #

A spline responds to bind by running until it concludes in a value, then uses that value to run the next spline.

Note - checkout the proofs

Instance details

Defined in Control.Varying.Spline

Methods

(>>=) :: SplineT a b m a0 -> (a0 -> SplineT a b m b0) -> SplineT a b m b0 #

(>>) :: SplineT a b m a0 -> SplineT a b m b0 -> SplineT a b m b0 #

return :: a0 -> SplineT a b m a0 #

fail :: String -> SplineT a b m a0 #

Monad m => Functor (SplineT a b m) Source #

A spline is a functor by applying the function to the result of the spline. This does just what you would expect of other Monads such as StateT or Maybe.

>>> :{
let s0 = pure "first" `untilEvent` (1 >>> after 2)
    s = do str <- fmap show s0
           step str
    v = outputStream s ""
in testVarOver v [(),()]
>>> :}
"first"
"(\"first\",2)"
Instance details

Defined in Control.Varying.Spline

Methods

fmap :: (a0 -> b0) -> SplineT a b m a0 -> SplineT a b m b0 #

(<$) :: a0 -> SplineT a b m b0 -> SplineT a b m a0 #

Monad m => Applicative (SplineT a b m) Source #

A spline responds to pure by returning a spline that never produces an output value and immediately returns the argument. It responds to <*> by applying the left arguments result value (the function) to the right arguments result value (the argument), sequencing them both in serial.

pure = return
sf * sx = do
  f <- sf
  x <- sx
  return $ f x
Instance details

Defined in Control.Varying.Spline

Methods

pure :: a0 -> SplineT a b m a0 #

(<*>) :: SplineT a b m (a0 -> b0) -> SplineT a b m a0 -> SplineT a b m b0 #

liftA2 :: (a0 -> b0 -> c) -> SplineT a b m a0 -> SplineT a b m b0 -> SplineT a b m c #

(*>) :: SplineT a b m a0 -> SplineT a b m b0 -> SplineT a b m b0 #

(<*) :: SplineT a b m a0 -> SplineT a b m b0 -> SplineT a b m a0 #

(Monad m, MonadIO m) => MonadIO (SplineT a b m) Source #

A spline can do IO if its underlying monad has a MonadIO instance. It takes the result of the IO action as its immediate return value.

Instance details

Defined in Control.Varying.Spline

Methods

liftIO :: IO a0 -> SplineT a b m a0 #

Creating streams from splines

outputStream :: Monad m => SplineT a b m c -> b -> VarT m a b Source #

Permute a spline into one continuous stream. Since a spline is not guaranteed to be defined over any domain (specifically on its edges), this function takes a default value to use as the "last known value".

>>> :{
let s :: SplineT () String IO ()
    s = do first <- pure "accumulating until 3" `_untilEvent` (1 >>> after 3)
           secnd <- pure "accumulating until 4" `_untilEvent` (1 >>> after 4)
           if first + secnd == 7
             then step "done"
             else step "something went wrong!"
    v = outputStream s ""
in testVarOver v $ replicate 6 ()
>>> :}
"accumulating until 3"
"accumulating until 3"
"accumulating until 4"
"accumulating until 4"
"accumulating until 4"
"done"

Creating splines from streams

fromEvent :: Monad m => VarT m a (Event b) -> SplineT a (Event b) m b Source #

Create a spline from an event stream.

untilProc :: Monad m => VarT m a (Event b) -> SplineT a (Event b) m b Source #

Create a spline from an event stream. Outputs noevent until the event stream procs, at which point the spline concludes with the event value.

whileProc :: Monad m => VarT m a (Event b) -> SplineT a b m () Source #

Create a spline from an event stream. Outputs b until the event stream inhibits, at which point the spline concludes with ().

untilEvent :: Monad m => VarT m a b -> VarT m a (Event c) -> SplineT a b m (b, c) Source #

Create a spline from a stream and an event stream. The spline uses the stream's values as its own output values. The spline will run until the event stream produces an event, at that point the last known output value and the event value are tupled and returned as the spline's result.

untilEvent_ :: Monad m => VarT m a b -> VarT m a (Event c) -> SplineT a b m b Source #

A variant of untilEvent that results in the last known output value.

_untilEvent :: Monad m => VarT m a b -> VarT m a (Event c) -> SplineT a b m c Source #

A variant of untilEvent that results in the event steam's event value.

_untilEvent_ :: Monad m => VarT m a b -> VarT m a (Event c) -> SplineT a b m () Source #

A variant of untilEvent that discards both the output and event values.

Other runners

scanSpline :: Monad m => SplineT a b m c -> b -> [a] -> m [b] Source #

Run the spline over the input values, gathering the output values in a list.

Combinators

step :: Monad m => b -> SplineT a b m () Source #

Produce the argument as an output value exactly once.

>>> :{
let s = do step "hi"
           step "there"
           step "friend"
in testVarOver (outputStream s "") [1,2,3,4]
>>> :}
"hi"
"there"
"friend"
"friend"

race :: Monad m => (a -> b -> c) -> SplineT i a m d -> SplineT i b m e -> SplineT i c m (Either d e) Source #

Run two splines in parallel, combining their output. Return the result of the spline that concludes first. If they conclude at the same time the result is taken from the left spline.

>>> :{
let s1 = pure "route "   `_untilEvent` (1 >>> after 2)
    s2 = pure 666     `_untilEvent` (1 >>> after 3)
    s = do winner <- race (\l r -> l ++ show r) s1 s2
           step $ show winner
    v = outputStream s ""
in testVarOver v [(),(),()]
>>> :}
"route 666"
"Left 2"
"Left 2"

raceAny :: (Monad m, Monoid b) => [SplineT a b m c] -> SplineT a b m c Source #

Run many splines in parallel, combining their output with mappend. Returns the result of the spline that concludes first. If any conclude at the same time the leftmost result will be returned.

>>> :{
let ss = [ pure "hey "   `_untilEvent` (1 >>> after 5)
         , pure "there"  `_untilEvent` (1 >>> after 3)
         , pure "!"      `_untilEvent` (1 >>> after 2)
         ]
    s = do winner <- raceAny ss
           step $ show winner
    v = outputStream s ""
in testVarOver v [(),()]
>>> :}
"hey there!"
"2"

merge :: Monad m => (b -> b -> b) -> SplineT a b m c -> SplineT a b m d -> SplineT a b m (c, d) Source #

Run two splines in parallel, combining their output. Once both splines have concluded, return the results of each in a tuple.

>>> :{
let s1 = pure "hey "   `_untilEvent` (1 >>> after 3)
    s2 = pure "there!" `_untilEvent` (1 >>> after 2)
    s  = do tuple <- merge (++) s1 s2
            step $ show tuple
    v  = outputStream s ""
in testVarOver v [(),(),()]
>>> :}
"hey there!"
"hey "
"(3,2)"

capture :: Monad m => SplineT a b m c -> SplineT a b m (Maybe b, c) Source #

Capture the spline's last output value and tuple it with the spline's result. This is helpful when you want to sample the last output value in order to determine the next spline to sequence.

The tupled value is returned in as a 'Maybe b' since it is not guaranteed that an output value is produced before a Spline concludes.

>>> :{
let
  s :: MonadIO m => SplineT () Int m String
  s = do
    (mayX, boomStr) <-
      capture
        $ do
          step 0
          step 1
          step 2
          return "boom"
    -- x is 2, but 'capture' can't be sure of that
    maybe
      (return "Failure")
      ( (>> return boomStr)
        . step
        . (+1)
      )
      mayX
in
  testVarOver (outputStream s 666) [(),(),(),()]
>>> :}
0
1
2
3

mapOutput :: Monad m => VarT m a (b -> t) -> SplineT a b m c -> SplineT a t m c Source #

Map the output value of a spline.

>>> :{
let s = mapOutput (pure show) $ step 1 >> step 2 >> step 3
in testVarOver (outputStream s "") [(),(),()]
>>> :}
"1"
"2"
"3"

adjustInput :: Monad m => VarT m a (a -> r) -> SplineT r b m c -> SplineT a b m c Source #

Map the input value of a spline.

Hand Proofs of the Monad laws

Left Identity

k =<< return c = k c
-- Definition of =<<
fix (\f s ->
  SplineT (\a ->
    runSplineT s a >>= \case
      Left c -> runSplineT (k c) a
      Right s' -> return (Right (fmap f s')))) (return c)
-- Definition of fix
(\s ->
  SplineT (\a ->
    runSplineT s a >>= \case
      Left c -> runSplineT (k c) a
      Right s' -> return (Right (fmap (k =<<) s')))) (return c)
-- Application
SplineT (\a ->
  runSplineT (return c) a >>= \case
    Left c -> runSplineT (k c) a
    Right s' -> return (Right (fmap (k =<<) s')))
-- Definition of return
SplineT (\a ->
  runSplineT (SplineT (\_ -> return (Left c))) a >>= \case
    Left c -> runSplineT (k c) a
    Right s' -> return (Right (fmap (k =<<) s')))
-- Newtype
SplineT (\a ->
  (\_ -> return (Left c)) a >>= \case
    Left c -> runSplineT (k c) a
    Right s' -> return (Right (fmap (k =<<) s')))
-- Application
SplineT (\a ->
  return (Left c) >>= \case
    Left c -> runSplineT (k c) a
    Right s' -> return (Right (fmap (k =<<) s')))
-- return x >>= f = f x
SplineT (\a ->
  case (Left c) of
    Left c -> runSplineT (k c) a
    Right s' -> return (Right (fmap (k =<<) s')))
-- Case evaluation
SplineT (\a -> runSplineT (k c) a)
-- Eta reduction
SplineT (runSplineT (k c))
-- Newtype
k c

Right Identity

return =<< m = m
-- Definition of =<<
fix (\f s ->
  SplineT (\a ->
    runSplineT s a >>= \case
      Left c -> runSplineT (return c) a
      Right s' -> return (Right (fmap f s')))) m
-- Definition of fix
(\s ->
  SplineT (\a ->
    runSplineT s a >>= \case
      Left c -> runSplineT (return c) a
      Right s' -> return (Right (fmap (return =<<) s')))) m
-- Application
SplineT (\a ->
  runSplineT m a >>= \case
    Left c -> runSplineT (return c) a
    Right s' -> return (Right (fmap (return =<<) s')))
-- Definition of return
SplineT (\a ->
  runSplineT m a >>= \case
    Left c -> runSplineT (SplineT (\_ -> return (Left c))) a
    Right s' -> return (Right (fmap (return =<<) s')))
-- Newtype
SplineT (\a ->
  runSplineT m a >>= \case
    Left c -> (\_ -> return (Left c)) a
    Right s' -> return (Right (fmap (return =<<) s')))
-- Application
SplineT (\a ->
  runSplineT m a >>= \case
    Left c -> return (Left c)
    Right s' -> return (Right (fmap (return =<<) s')))
-- m >>= return . f = fmap f m
SplineT (\a -> fmap (either id (fmap (return =<<))) (runSplineT m a))
-- Coinduction
SplineT (\a -> fmap (either id (fmap id)) (runSplineT m a))
-- fmap id = id
SplineT (\a -> fmap (either id id) (runSplineT m a))
-- either id id = id
SplineT (\a -> fmap id (runSplineT m a))
-- fmap id = id
SplineT (\a -> runSplineT m a)
-- Eta reduction
SplineT (runSplineT m)
-- Newtype
m

Application

(m >>= f) >>= g = m >>= (\x -> f x >>= g)