[Haskell-cafe] FRP, arrows and loops
Christopher Lane Hinson
lane at downstairspeople.org
Fri Apr 2 14:51:45 EDT 2010
On Fri, 2 Apr 2010, Maciej Piechotka wrote:
> 1. How to interpret ArrowLoop? I have two possible implementations:
>
> type RunSF a = a Dynamic ()
>
> data SF a b c =
> SF (a (Dynamic, b, RunSF, Set Unique) (c, Set Unique, SF a b c))
>
> (...)
>
> instance ArrowLoop (SF a) where
> loop (SF f) = loop' f undefined
> where loop' g d = proc (dyn, b, r, s) -> do
> ((c, d'), s, g') <- g <- (dyn, (b, d), r, s)
> returnA -< (c, s, loop' g' d')
>
> instance ArrowLoop a => ArrowLoop (SF a) where
> loop (SF f) = SF $! proc (d, b, r, s) -> do
> rec ((c, d), s, f') <- f -< (d, (b, d), r, s)
> returnA -< (c, s, loop f')
Neither of these compile through my eyeball, but I don't think it should
be possible for SF to be an Arrow-anything unless 'a' is also.
> 2. Why there is no ArrowIO in arrows? I.e.
>
> class Arrow a => ArrowIO a where
> liftAIO :: Kleisli IO b c -> a b c
>
> (possibly
>
> class Arrow a => ArrowST a where
> liftAST :: Kleisli ST b c -> a b c
> )
>
It would only be a convenience typeclass, and in that case why not just
have a generic ArrowKleisli with: (i -> m o) -> a i o
> 3. Why switch is needed? How to interpret switch with current
> continuation?
>
> I think switch is equivalent to ArrowChoice but do I miss something?
They are not equivalent. A switch, roughly, provides a way to
persistently replace a running segment of a program with a different
program.
ArrowChoice is just a way of implementing if-then-else flow control in an
Arrow, which might be useful, but is not the point of FRP.
Imagine a light switch that remains on or off after you toggle it,
compared to a pressure switch that requires constant supervision.
Friendly,
--Lane
More information about the Haskell-Cafe
mailing list