[Haskell-cafe] FRP, arrows and loops

Maciej Piechotka uzytkownik2 at gmail.com
Tue Apr 6 08:39:43 EDT 2010


On Fri, 2010-04-02 at 14:51 -0400, Christopher Lane Hinson wrote:
> 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,

What I meant was:

> instance ArrowLoop a => ArrowLoop (SF a) where
>   loop (SF f) =  SF $! proc (dyn, b, r, s) -> do
>     rec ((c, d), s, f') <- f -< (dyn, (b, d), r, s)
>     returnA -< (c, s, loop f')


> > 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
> 

Hmm. I guess to avoid (some) problems:

> class (Monad m, Arrow a) => ArrowKleisli m a where
>     liftMonad ∷  (b -> m c) -> a c
>     liftMonad = liftKleisli . Kleisli
>     liftKleisli ∷  Kleisli m b c -> a b c
>     liftKleisli = liftMonad . runKleisli


Given:

> instance ArrowKleisli CHP (Kleisli CHP)
> instance ArrowKleisli IO (Kleisli CHP)

And:

> someFunc = liftIO . print :: (Show b, MonadIO m) => b -> m ()

Which liftIO is run in:

> liftMonad someFunc :: Kleisli CHP String ()

ghci> :t liftMonad (someFunc) :: Kleisli CHP String ()

<interactive>:1:0:
    No instance for (ArrowKleisli m (Kleisli CHP))
      arising from a use of `liftMonad' at <interactive>:1:0-19
    Possible fix:
      add an instance declaration for (ArrowKleisli m (Kleisli CHP))
    In the expression: liftMonad (someFunc) :: Kleisli CHP String ()


As IO is popular it is particularly likely to run into this problem.

Adding:

> class Arrow a ⇒  ArrowIO a where
>     liftAIO ∷  (b →  IO c) →  a b c
>
> instance ArrowKleisli IO a ⇒  ArrowIO a where
>     liftAIO = liftMonad

Solves problem:
ghci> :t liftAIO someFunc :: Kleisli CHP String ()
liftAIO someFunc :: Kleisli CHP String () :: Kleisli CHP String ()

Regards
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 836 bytes
Desc: This is a digitally signed message part
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20100406/55cf053c/attachment.bin


More information about the Haskell-Cafe mailing list