[Haskell] Composing applicative functors?

Conal Elliott conal at conal.net
Mon Mar 12 20:19:27 EDT 2007


I just added a Cofunctor instance for type composition, but there are two
competing choices:

-- | Often useful for \"acceptors\" (consumers, sinks) of values.
class Cofunctor acc where
  cofmap :: (a -> b) -> (acc b -> acc a)

-- | Composition of type constructors: unary & unary.  Called "g . f"
-- in [1], section 5.
newtype (g :. <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:.>:
f) a = T_T { runT_T :: g (f a) }

instance (Functor
<http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Functor>
g, Cofunctor f) => Cofunctor (g :.
<http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:.>:
f) where
  cofmap h (T_T gf) = T_T (fmap
<http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:fmap>
(cofmap h) gf)

-- Or this alternative.  Having both yields "Duplicate instance
-- declarations".  How to decide between these instances?
-- instance (Cofunctor g, Functor f) => Cofunctor (g :.: f) where
--   cofmap h (T_T gf) = T_T (cofmap (fmap h) gf)

Any comments/suggestions about how or whether to make the choice between
these two instances?

  - Conal


On 3/12/07, Conal Elliott <conal at conal.net> wrote:
>
> I'm still interested in comments composition operators at http://haskell.org/haskellwiki/TypeComposition
> .   Now I see that my ":.::" is what [1] calls "StaticArrow".
>
> Mainly, I'd like to hear thoughts on how to make an arrow out of a functor
> & arrow, with the functor on the inside.  My attempt is called " ::.:" on
> the wiki page.
>
>     newtype ((~>) ::.: f) a b = TT_T { runTT_T :: f a ~> f b }
>
> As mentioned in the comments, my Arrow definition isn't really
> satisfactory.  Is there an arrow that corresponds to this sort of
> composition?
>
> Thanks,  - Conal
>
> On 3/8/07, Conal Elliott <conal at conal.net> wrote:
> >
> > I made a first pass at a module of type compositions with some instances
> > at http://haskell.org/haskellwiki/TypeComposition and would love to get
> > comments & suggestions.
> >
> > Is there an existing process for library proposals & discussions?
> >
> > Cheers,  - Conal
> >
> > On 2/21/07, Ross Paterson < ross at soi.city.ac.uk> wrote:
> > >
> > > [redirecting to libraries]
> > > On Wed, Feb 21, 2007 at 04:23:50PM -0800, Conal Elliott wrote:
> > > > Is the composition instance of Control.Applicative defined
> > > somewhere?  I see
> > > > it in the McBride & Paterson paper [1], but not in the library docs
> > > [2].
> > > > I'd rather pull it in from a library than (re)define it myself.
> > > >
> > > > [1] http://www.soi.city.ac.uk/~ross/papers/Applicative.pdf<http://www.soi.city.ac.uk/%7Eross/papers/Applicative.pdf>
> > > > [2]
> > > > http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Applicative.html
> > >
> > >
> > > It's not defined in the libraries.  The type (and the identity
> > > functor)
> > > should probably go in the module that defines Functor (currently
> > > Control.Monad) with a Functor instance, and an Applicative instance
> > > in Control.Applicative.
> > >
> > > _______________________________________________
> > > Libraries mailing list
> > > Libraries at haskell.org
> > > http://www.haskell.org/mailman/listinfo/libraries
> > >
> >
> >
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/libraries/attachments/20070312/fd989e90/attachment.htm


More information about the Libraries mailing list