In opposition of Functor as super-class of Monad

2011-01-04 Thread oleg

I'd like to argue in opposition of making Functor a super-class of
Monad. I would argue that superclass constraints are not the right
tool for expressing mathematical relationship such that all monads are
functors and applicatives.

Then argument is practical. It seems that making Functor a superclass
of Monad makes defining new monad instances more of a chore, leading
to code duplication. To me, code duplication is a sign that an
abstraction is missing or misused.

For the sake of the argument, let us suppose that Functor is a
superclass of Monad. Let us see how to define a new Monad
instance. For the sake of a better illustration, I'll use a complex
monad. I just happen to have an example of that: Iteratee.
The data type Iteratee is defined as follows:

 type ErrMsg = String-- simplifying
 data Stream el = EOF (Maybe ErrMsg) | Chunk [el] deriving Show

 data Iteratee el m a = IE_done a
  | IE_cont (Maybe ErrMsg)
(Stream el - m (Iteratee el m a, Stream el))
   

We wish to define an instance for Monad (Iteratee el m). Since Functor
is a superclass of Monad, we must define a functor instance:

 instance Functor m = Functor (Iteratee el m) where
 fmap f (IE_done a)   = IE_done (f a)
 fmap f (IE_cont e k) = IE_cont e (\s - fmap docase (k s))
  where
  docase (IE_done a,s) = (IE_done (f a), s)
  docase (i, s)= (fmap f i, s)

There are two ways to proceed with the Monad instance -- to be
precise, there are two ways of defining bind.

Method A: just define bind as usual

 instance (Functor (Iteratee el m),Monad m) = Monad (Iteratee el m) where
 return = IE_done

 IE_done a   = f = f a
 IE_cont e k = f = IE_cont e (\s - k s = docase)
  where
  docase (IE_done a, stream)   = case f a of
  IE_cont Nothing k - k stream
  i - return (i,stream)
  docase (i, s)  = return (i = f, s)

Although we must state the constraint (Functor (Iteratee el m)) to
satisfy the super-class constraint, we have not made any use of the
constraint. We defined bind without resorting to fmap. That seems like
a waste. What makes it seem more like a waste is that the code for
fmap and for bind is almost the same. We had to repeat essentially the
same algorithm, analysing Iteratee and the continuation.

Method B: define bind in terms of fmap

Alas, just fmap is not sufficient to define bind. We need join:

 joinIter :: Monad m = Iteratee el m (Iteratee el m a) - Iteratee el m a
 joinIter (IE_done i) = i
 joinIter (IE_cont e k) = IE_cont e (\s - k s = docase)
  where
  docase (IE_done (IE_cont Nothing k), s) = k s
  docase (IE_done i, s)   = return (i, s)
  docase (i, s)   = return (joinIter i, s)

Only after defining join we can write

 bind m f = joinIter $ fmap f m

Again we see code duplication: the code for join resembles the code
for fmap. The code for join follows the same pattern of analysing
Iteratee and the continuation.

In either way, Functor as a super-class of Monad leads to code
duplication. That gives a bad feeling practically -- and
theoretically. The experiment has led me wonder if a superclass
constraint is the right way to state the relationship between Monads
and Functors.

It _almost_ makes me wish the constraint go the other way:

 instance Monad m = Functor m where
   fmap f m = m = (return . f)

That is, we need an instance rather than a superclass constraint, and
in the other direction. The instance constraint says that every monad
is a functor. Moreover,
\f m = m = (return . f)

is a _proof term_ that every monad is a functor. We can state it once
and for all, for all present and future monads.

Alas, the instance ``instance Monad m = Functor m'' above has several
drawbacks (for one, requiring overlapping instances everywhere). This
makes me wonder if something is amiss.

In the meanwhile, there is a practical work-around. Introduce a
TemplateHaskell operation generating an instance such as

 instance Monad (Iteratee el m) = Functor (Iteratee el m) where
   fmap f m = m = (return . f)

(the code for the method remains the same; only the type in the
instance head varies). Alas, that requires undecidable instances. All
the code before was Haskell98.



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: In opposition of Functor as super-class of Monad

2011-01-04 Thread Martijn van Steenbergen

Method C: Define fmap in terms of bind


instance Monad m = Functor (Iteratee el m) where
  fmap = liftM


Now you need to do the inspection of Iteratee only once: in the 
definition of the bind. However, to use liftM as implementation of fmap 
the superclass constraint of the Functor instance has changed from 
Functor to Monad.


Is this a problem? If so, method A seems the way to go: you could argue 
that `Functor m = fmap :: (a - b) - Iteratee el m a - Iteratee el m 
b' is more general than the `Monad m =' version (works for more `m's) 
and therefore deserves to redo the analysis of Iteratee.


Martijn.


On 1/4/11 11:24, o...@okmij.org wrote:

I'd like to argue in opposition of making Functor a super-class of
Monad. I would argue that superclass constraints are not the right
tool for expressing mathematical relationship such that all monads are
functors and applicatives.


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Functor hierarchy proposal and class system extension proposal

2011-01-04 Thread Conor McBride

Hi

On 2 Jan 2011, at 09:29, Malcolm Wallace wrote:


See also
   http://repetae.net/recent/out/classalias.html
   http://www.haskell.org//pipermail/libraries/2005-March/003494.html
   http://www.haskell.org//pipermail/haskell-prime/2006-April/001344.html
   http://www.haskell.org//pipermail/haskell-prime/2006-August/001582.html


A proposal from Jón Fairbairn for how to add default superclass method
definitions gained some traction, and deserves to be revi(v/s)ed now, I
think.

Some superclass relationships are `shallow' interface extensions:  
MonadPlus
does not give you a standard way to implement Monad, just more  
functionality

within a monad. Other superclass relationships `deepen' existing
functionality---if you have Ord, you can certainly make Eq; if you have
Monad, you can certainly make Applicative, etc. The former is currently
well supported, the latter badly.

Jón's proposal was to improve the latter situation by allowing the  
subclass
to specify a default (partial) implementation of a superclass. So we  
might

write

  class Applicative f where
return :: x - f x
(*) :: f (s - t) - f s - f t
instance Functor f where
  fmap = pure . (*)

giving not only a subclass constraint (Functor f =) but also a standard
means to satisfy it. Whenever an Applicative instance is declared, its
Functor sub-instance is unpacked: buy one, get one free.

This, on its own, is not quite enough. For one thing, we need a way to
switch it off. I should certainly be permitted to write something like

  instance Applicative Blah where
return = ...
(*) = ...
hiding instance Functor Blah

to prevent the automatic generation of the superclass instance. The
subclass constraint would still apply, so in order to use the  
Applciative

functionality of Blah, it would have to be a Functor otherwise, e.g., by
being Traversable. This `hiding' option was missing from Jón's proposal,
but it seems crucial to address the potential for conflicts which was
identified in the discussion at the time.

It's also clear that we must be able to override the default behaviour.
When the class declaration has a superclass instance, but not otherwise,
a subclass instance should be entitled to override and extend the  
methods

of the superclass instance thus generated. It seems unambiguous to allow
this to happen without repeating the instance Mutter Something. So
we'd have


  class Monad f where
(=) :: f s - (s - f t) - f t
instance Applicative f where
  ff * fs = ff = \ f - fs = \ s - return (f s)

and we'd still be able to write

  instance Monad Maybe where
return = Just  -- completing the generated Applicative
Just s  = f = f s
Nothing = _ = Nothing

and acquire Monad, Applicative, Functor.

No new instance inference semantics is required. In order to transform
code under this proposal to code acceptable now, one need only keep
track of which methods belong to which class and which classes have
default superclass instances: each compound instance can then be
split into its individual components before compilation under the
current rules.

Is this clear? Does it seem plausible?

All the best

Conor


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: In opposition of Functor as super-class of Monad

2011-01-04 Thread Dan Doel
On Tuesday 04 January 2011 5:24:21 am o...@okmij.org wrote:
 Method A: just define bind as usual
 
  instance (Functor (Iteratee el m),Monad m) = Monad (Iteratee el m) where
  
  return = IE_done
  
  IE_done a   = f = f a
  IE_cont e k = f = IE_cont e (\s - k s = docase)
  
   where
   docase (IE_done a, stream)   = case f a of
   
   IE_cont Nothing k - k stream
   i - return (i,stream)
   
   docase (i, s)  = return (i = f, s)
 
 Although we must state the constraint (Functor (Iteratee el m)) to
 satisfy the super-class constraint, we have not made any use of the
 constraint.

This, at least, is false. If Functor is a superclass of Monad, then Monad m 
implies Functor m, which implies Functor (Iteratee el m). So Monad m is a 
sufficient constraint for the instance.

As for the other concerns, I think the closest fix I've seen is to allow 
subclasses to specify defaults for superclasses, and allow instances for 
subclasses to include methods for superclasses. So:

  class Functor m = Monad m where
return :: a - m a
(=)  :: m a - (a - m b) - m b

fmap f x = x = return . f

This has its own caveats of course. And in this case, it seems to 
overconstrain the functor instance, since presumably we'd end up with:

  instance Monad m = Monad (Iteratee el m) where ...
==
  instance Monad m = Functor (Iterate el m) where ...

I'm not sure what to do about that.

-- Dan

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: In opposition of Functor as super-class of Monad

2011-01-04 Thread Alexey Khudyakov

On 04.01.2011 13:24, o...@okmij.org wrote:


I'd like to argue in opposition of making Functor a super-class of
Monad. I would argue that superclass constraints are not the right
tool for expressing mathematical relationship such that all monads are
functors and applicatives.

Then argument is practical. It seems that making Functor a superclass
of Monad makes defining new monad instances more of a chore, leading
to code duplication. To me, code duplication is a sign that an
abstraction is missing or misused.




I think I understood your point. But it looks like that it's possible to 
use subclass's function in superclass instance. At very least GHC is 
able to do it.


Following example works just fine without any language extensions in 
GHC6.12.3



import Prelude hiding (Monad(..), Functor(..))

class Functor f where
  fmap :: (a - b) - f a - f b

class Functor m = Monad m where
  return :: a - m a
  (=) :: m a - (a - m b) - m b

instance Functor Maybe where
  fmap f m = m = (return . f)
instance Monad Maybe where
  return = Just
  Nothing = _ = Nothing
  Just x  = f = f x

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: In opposition of Functor as super-class of Monad

2011-01-04 Thread Tony Morris
I think you'll find a problem using do-notation with your Monad.

Tony Morris

On 04/01/2011 11:33 PM, Alexey Khudyakov alexey.sklad...@gmail.com
wrote:

On 04.01.2011 13:24, o...@okmij.org wrote:


 I'd like to argue in opposition of making Functor a...
I think I understood your point. But it looks like that it's possible to use
subclass's function in superclass instance. At very least GHC is able to do
it.

Following example works just fine without any language extensions in
GHC6.12.3


import Prelude hiding (Monad(..), Functor(..))

class Functor f where
 fmap :: (a - b) - f a - f b



class Functor m = Monad m where
 return :: a - m a
 (=) :: m a - (a - m b) - m b
instance Functor Maybe where


 fmap f m = m = (return . f)
instance Monad Maybe where
 return = Just
 Nothing = _ = Nothing
 Just x  = f = f x



___
Haskell-prime mailing list
haskell-pr...@haskell.o...
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: In opposition of Functor as super-class of Monad

2011-01-04 Thread kahl
On Tue, Jan 04, 2011 at 02:24:21AM -0800, o...@okmij.org wrote:
  
  I'd like to argue in opposition of making Functor a super-class of
  Monad. I would argue that superclass constraints are not the right
  tool for expressing mathematical relationship such that all monads are
  functors and applicatives.
  
  Then argument is practical. It seems that making Functor a superclass
  of Monad makes defining new monad instances more of a chore, leading
  to code duplication. To me, code duplication is a sign that an
  abstraction is missing or misused.

The argument about code duplication somehow seems to assume that
class member instances need to be defined as part of the instance
declaration. This is not the case, and in fact I am arguing in general
against putting any interesting code into instance declarations,
especially into declarations of instances with constraints
(since, in ML terminology, they are functors, and putting their
definition inside an instance declaration constrains their applicability).

In my opinion, the better approach is to define (generalised versions of)
the functions mentioned in the class interface,
and then just throw together the instances from those functions.
This also makes it easier to adapt to the ``class hierarchy du jour''.

The point for the situation here is that although we eventually need
definitions of all the functions declared as class members,
there is absolutely nothing that constrains the dependency relation
between the definitions of these functions to be conforming in any way
to the class hierarchy.

For a simpler example, assume that I have some arbitrary data type

 data T a = One a | Two a a

and assume that I am interested only in Ord instances, since I want to
use T with Data.Set, and I am not really interested in Eq instances.

Assume that the order will depend on that for |a|,
so I will define a function:

 compareT :: (a - a - Ordering) - T a - T a - Ordering

Then I can thow together the necessary instances from that:

 instance Ord a = Ord (T a) where
   compare = compareT compare
 
 instance Ord a = Eq (T a) where
   (==) = eqFromCompare compare

assuming I have (preferably from the exporter of Eq and Ord):

 eqFromCompare :: (a - a - Ordering) - (a - a - Bool)
 eqFromCompare cmp x y = case cmp x y of
   EQ - True
   _ - False

The same approach works for Oleg's example:

  For the sake of the argument, let us suppose that Functor is a
  superclass of Monad. Let us see how to define a new Monad
  instance. For the sake of a better illustration, I'll use a complex
  monad. I just happen to have an example of that: Iteratee.
  The data type Iteratee is defined as follows:

 type ErrMsg = String-- simplifying
 data Stream el = EOF (Maybe ErrMsg) | Chunk [el] deriving Show

 data Iteratee el m a = IE_done a
  | IE_cont (Maybe ErrMsg)
(Stream el - m (Iteratee el m a, Stream el))

  [...]   
  
  It _almost_ makes me wish the constraint go the other way:
  
   instance Monad m = Functor m where
  fmap f m = m = (return . f)
  
  That is, we need an instance rather than a superclass constraint, and
  in the other direction. The instance constraint says that every monad
  is a functor. Moreover,
   \f m = m = (return . f)
  
  is a _proof term_ that every monad is a functor. We can state it once
  and for all, for all present and future monads.

I would expect that proof term to exported by the package exporting
Functor and Monad; let us define it here:

 fmapFromBind (=) f m = m = (return . f)

Now you can write, no matter which class is a superclass of which:

 bindIt return (=) (IE_done a) f = f a
 bindIt return (=) (IE_cont e k) f = IE_cont e (\s - k s = docase)
   where
 docase (IE_done a, stream)   = case f a of
   IE_cont Nothing k - k stream
   i - return (i,stream)
 docase (i, s)  = return (bindIt return (=) i f, s)
 
 instance Monad m = Monad (Iteratee el m) where
return = IE_done
(=) = bindIt return (=)
 
 instance Monad m = Functor (Iteratee el m) where
   fmap = fmapFromBind (=)

Of course this assumes that you are not actually interested in an
instance of shape: instance (Functor ...) = Functor (Iteratee el m),
but this seems to be a plausible assumption.

Defining the functionality really has nothing to do with declaring an
instance of a type class, and it is normally better to keep the two
separated. And that does not lead to any real code duplication,
only extremely boring instance declarations.


Wolfram



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Functor hierarchy proposal and class system extension proposal

2011-01-04 Thread Ben Millwood
On Tue, Jan 4, 2011 at 1:21 PM, Conor McBride
co...@strictlypositive.org wrote:
 Jón's proposal was to improve the latter situation by allowing the subclass
 to specify a default (partial) implementation of a superclass. So we might
 write

  class Applicative f where
    return :: x - f x
    (*) :: f (s - t) - f s - f t
    instance Functor f where
      fmap = pure . (*)

 giving not only a subclass constraint (Functor f =) but also a standard
 means to satisfy it. Whenever an Applicative instance is declared, its
 Functor sub-instance is unpacked: buy one, get one free.

 This, on its own, is not quite enough. For one thing, we need a way to
 switch it off. I should certainly be permitted to write something like

  instance Applicative Blah where
    return = ...
    (*) = ...
    hiding instance Functor Blah

The use of 'hiding' here I'd object to, as it really isn't a good
description of what's going on. Personally I'd think it more clear to
explicitly opt into an automatic instance:
instance Applicative Blah where
  return = ...
  (*) = ...
  deriving (Functor) -- or something like that

but one of the advantages of John Meachem's original proposal was that
it allowed for example a library author to split up a class without
users changing their instances, which my idea would not do. I suppose
that alone makes it far less useful, but I think there is an argument
to be made about how much of this process we want to be explicit and
how much we want to be implicit.

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Functor hierarchy proposal and class system extension proposal

2011-01-04 Thread Conor McBride

Hi Ben

On 4 Jan 2011, at 19:19, Ben Millwood wrote:


On Tue, Jan 4, 2011 at 1:21 PM, Conor McBride
co...@strictlypositive.org wrote:
Jón's proposal was to improve the latter situation by allowing the  
subclass
to specify a default (partial) implementation of a superclass. So  
we might

write

This, on its own, is not quite enough. For one thing, we need a way  
to
switch it off. I should certainly be permitted to write something  
like


 instance Applicative Blah where
   return = ...
   (*) = ...
   hiding instance Functor Blah


The use of 'hiding' here I'd object to, as it really isn't a good
description of what's going on.


It's perhaps suboptimal. I chose hiding only because it's already
a vaguely keywordy thing. It's only syntax. What's important is...


Personally I'd think it more clear to
explicitly opt into an automatic instance:
instance Applicative Blah where
 return = ...
 (*) = ...
 deriving (Functor) -- or something like that


[..]


but I think there is an argument
to be made about how much of this process we want to be explicit and
how much we want to be implicit.


...the argument about what should be implicit or explicit, opt-in
or opt-out. In this argument, I disagree with you.

I'd much rather it was notationally cheaper to go with the supplied
default, provided deviation from the default is also fairly cheap
(but explicit).

My plan also has the advantage of cheaper backward compatibility
(for this and other (future) class splittings).

Note that in my example, return had moved to Applicative, pure had
been dumped, and a typical Monad instance would look like

instance Monad Maybe where
  Just x = f = f x
  Nothing = _ = Nothing
  return = Just   -- where this implicitly opts into and extends the
  -- Applicative instance
  -- and also implicitly generates Functor

We could not simply have said deriving Applicative here, because
the default instance is incomplete. In general, one might want to
override some but not all of the default instance, just as one
does when default method implementations come from the class.

There's a general engineering concern as well. The refactoring cost
of splitting Applicative off as a lesser version of Monad, taking
return, adding (*) derivable from (=) is much reduced by this
choice. I'm sure it's not the only instance of a class we might
discover is better split: the opt-in default reduces inertia to
such design improvements.

I'd certainly be happy with a different opt-out notation, but I
would be unhappy if opting in (and overriding/extending) were
made more complex than necessary to allow an opt-out default.

All the best

Conor


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Functor hierarchy proposal and class system extension proposal

2011-01-04 Thread Isaac Dupree

On 01/04/11 19:48, Ben Millwood wrote:

There's a fair question in whether we want deviation from the default
at all (although I think the answer is probably yes). I think it's
reasonable that any type that is an instance of Monad be forced to
have ap = (*), for example, so really the only reason I can see we'd
want to be able to override those functions would be for efficiency.


Remember the example
Monad implies Functor (fmap = Control.Monad.liftM)
Traversable implies Functor (fmap = Data.Traversable.fmapDefault)

e.g. [] and Maybe are instances of all these classes.

yes, liftM and fmapDefault probably must *do* the same thing[*], but one 
of those definitions still needs to be picked.


[*probably--I'm haven't convinced myself that it's true in all cases of 
deepening-type class hierarchies though--we are here trying to 
engineer to support all cases of deepening hierarchies.]


-Isaac

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime