[Haskell-cafe] ANNOUNCE: iterIO-0.1 - iteratee-based IO with pipe operators

Maciej Marcin Piechotka uzytkownik2 at gmail.com
Sat May 7 22:50:13 CEST 2011


Sorry for third post but I wonder why the many instances are restricted
by Monad.

Both Functor and Applicative can by constructed without Monad:

> instance (Functor m) => Functor (CtlArg t m) where
>     fmap f (CtlArg arg g c) = CtlArg arg (fmap f . g) c
> 
> instance (Functor m) => Functor (Iter t m) where
>     {-# INLINE fmap #-}
>     fmap f (Iter g) = Iter (fmap f . g
>
> instance (Functor m) => Functor (IterR t m) where
>     fmap f (IterF i) = IterF (fmap f i)
>     fmap f (IterM i) = IterM (fmap (fmap f) i)
>     fmap f (IterC c) = IterC (fmap f c)
>     fmap f (Done a c) = Done (f a) c
>     fmap f (Fail i m mc) = Fail i (fmap f m) mc
>
> instance (Functor m) => Applicative (Iter t m) where
>     {-# INLINE pure #-}
>     pure x = Iter $ Done x
>     {-# INLINE (<*>) #-}
>     Iter a <*> bi@(Iter b) = Iter $ \c -> fix (\f ir -> case ir of
>         IterF cont -> cont <*> bi
>         IterM m -> IterM $ fmap f m
>         IterC (CtlArg a cn ch) ->
>             IterC (CtlArg a (\r -> cn r <*> bi) ch)
>         Done v ch -> fmap v (b ch)
>         Fail f _ ch -> Fail f Nothing ch) a c

Since every monad is applicative (or rather should be) it doesn't loose
generality.

Join is also defined by using only functor:

> joinI :: (Functor m) => Iter t m (Iter t m a) -> Iter t m a
> joinI (Iter i) = Iter $ \c -> fix (\f x -> case x of
>      IterF cont -> IterF (joinI cont)
>      IterM m -> IterM $ fmap f m
>      IterC (CtlArg a cn ch) ->
>          IterC (CtlArg a (\r -> joinI (cn r)) ch)
>      Done v ch -> runIter v ch
>      Fail f _ ch -> Fail f Nothing ch) (i c)

Regards

PS. I haven't tested the code or benchmarked it - but it seems it is
possible.
-------------- 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/20110507/296c5565/attachment.pgp>


More information about the Haskell-Cafe mailing list