[Haskell-cafe] (Co/Contra)Functor and Comonad

Daniel Peebles pumpkingod at gmail.com
Fri Dec 24 21:00:51 CET 2010


I remember seeing this very discussion about pointed being disjoint from
functor just recently on one of the various haskell mailing lists. But as
for my opinion on it, because there's no real way of specifying any laws for
pointed without functor. With functor and pointed, you can say that you
expect fmap f . point == point . f, but point on its own gives you nothing
to latch onto for behavior expectations.

On Fri, Dec 24, 2010 at 11:08 AM, Mario Blažević <mblazevic at stilo.com>wrote:

> On Fri, Dec 24, 2010 at 7:43 AM, Maciej Piechotka <uzytkownik2 at gmail.com>wrote:
>
>> On Fri, 2010-12-24 at 05:36 -0500, Edward Kmett wrote:
>> >
>> > +1 for adding Comonads. As an aside, since Haskell doesn't have (nor
>> > could it have) coexponential objects, there is no 'missing'
>> > Coapplicative concept that goes with it, so there can be no objection
>> > on the grounds of lack of symmetry even if the Functor => Applicative
>> > => Monad proposal goes through.
>>
>> There is still potentially useful Copointed/CoPointed:
>>
>> class [Functor a =>] CoPointed a where
>>    copoint :: f a -> a
>>
>
>
> Why should Copointed, or Pointed for that matter, be a subclass of Functor?
> I don't see the point of arranging all possible classes into a single
> complete hierarchy. These single-method classes can stand on their own. Once
> you have them, it's easy to declare
>
> > class (Functor f, Pointed f) => Applicative f
>
> and also
>
> > class (Foldable f, Pointed f) => Sequence f
>
> or whatever.
>
>
>
> On Fri, Dec 24, 2010 at 4:51 AM, Stephen Tetley <stephen.tetley at gmail.com>wrote:
>
>> On 24 December 2010 02:16, Mario Blažević <mblazevic at stilo.com> wrote:
>>
>> > To turn the proof obligation around, what could possibly be the downside
>> of
>> > adding a puny Cofunctor class to the base library?
>>
>> Hi Mario
>>
>> For the record I'm personally neutral on Cofunctor and on balance
>> would like to see Comonad added to Base.
>>
>> My reservation is really at the "meta-level" - I suspect there are a
>> lot of candidates for adding to Base if you want to Base to be
>> systematic about "modeling structures".
>
>
>
> There is a limited number of methods with up to N unconstrained arguments,
> combinatorics takes care of that.
>
> class Foo (x :: *) where
>  method1 :: x                    -- default, mempty, minBound, maxBound
>  method2 :: x -> x             -- succ, pred, negate
>  method3 :: x -> x -> x      -- mappend
>  method4 :: (x -> x) -> x    -- fix
>
> class Cons (c :: * -> *) where
>  method1 :: x -> c x           -- return, pure
>  method2 :: c x -> x           -- extract
>  method3 :: c (c x) -> c x    -- join
>  method4 :: c x -> c (c x)    -- duplicate
>  method5 :: c (c x) -> x
>  method6 :: x -> c (c x)
>  method7 :: x -> c x -> c x
>  method8 :: c x -> c x -> x
>  method9 :: (x -> x) -> c x -> c x
>  method10 :: (x -> y) -> c x -> c y  -- fmap
>  method11 :: (x -> y) -> c y -> c x  -- contramap
>  method12 :: x -> c y -> c y
>  method13 :: x -> c y -> c x
>  method14 :: c x -> c y -> x
>  method15 :: c x -> (x -> c x) -> c x
>  method16 :: c x -> (x -> c y) -> c y  -- >>=
>  method17 :: c x -> (c x -> x) -> c x
>  method18 :: c x -> (c x -> y) -> c y  -- extend
>
>
> I may have left something out, but all types above should be inhabited. I
> have omitted methods on constructors that can be defined on a plain type,
> such as mplus :: m a -> m a -> m a, which is a restriction of the type of
> mappend.
>
> If one were to explore the design space systematically with no backward
> compatibility baggage, the best approach might be:
>
> - declare each method in a class of its own, with no laws whatsoever,
> - never declare two methods in a same class,
> - combine the primitive classes into bigger classes,
> - restrict the bigger classes with laws.
>
> The Pointed and Copointed classes above are two examples.
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20101224/69c2e136/attachment.htm>


More information about the Haskell-Cafe mailing list