
Hi all, Quickly! How fast can you tell me which classes are defined an instantiated in the code below?
class Monad m => MonadPlus m where ...
class Ord a => Ix a where ...
instance Integral a => Eq (Ratio a) where ...
How fast did you do it? And no, the correct answer is not Monad, Ord and Integral. It is MonadPlus, Ix and Eq. Ok, I guess you can see my point. My point is that the placement of class constraints in class definitions, instance declarations and type signatures is bad. Class constraints should *not* come first. It's hard on the eye. It makes your eyes going back and forth looking for the most important thing while trying to avoid the class constraints. Class constraints should come *after* the thing they constrain. This hit me pretty badly some time ago when I was writing a largish library full of class declarations. After a while it became unwieldy to browse through the code. It became overly difficult to find the right class definition. This is one of the things that the Clean people got right. In Clean, my examples from above would look like:
class MonadPlus m | Monad m where ...
class Ix a | Ord a where ..
instance Eq (Ratio a) | Integral a where ...
Much better! I'm not proposing we change this though. I realise that Haskell will have to live with this bad syntax for its entire lifetime. It simply brakes too many programs to change it. And having two alternative syntaxes with the goal of eventually switching to the other would be awfully confusing. But even though I don't propose to change this I had to let it off my chest. I feel much better now. All the best, /Josef

Josef Svenningsson wrote:
This is one of the things that the Clean people got right. In Clean, my examples from above would look like:
class MonadPlus m | Monad m where ...
class Ix a | Ord a where ..
instance Eq (Ratio a) | Integral a where ...
Not quite the same complaint, but I've always been bothered by the inconsistent use of "=>". I would prefer "A => B" to mean "if A, then B". Accordingly: class Monad m <= MonadPlus m class Ord a <= Ix a instance Integral a => Eq (Ratio a) foo :: (Monad m) => [m a] -> m [a]

On 2/22/06, Ashley Yakeley
Josef Svenningsson wrote:
This is one of the things that the Clean people got right. In Clean, my examples from above would look like:
class MonadPlus m | Monad m where ...
class Ix a | Ord a where ..
instance Eq (Ratio a) | Integral a where ...
Not quite the same complaint, but I've always been bothered by the inconsistent use of "=>". I would prefer "A => B" to mean "if A, then B". Accordingly:
class Monad m <= MonadPlus m
By your definition, couldn't what we have now (class Monad m => MonadPlus m) be read as "If m is in the Monad class, then the class MonadPlus can be defined for m thusly:...", which seems pretty clear to me. /S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

Sebastian Sylvan wrote:
Not quite the same complaint, but I've always been bothered by the inconsistent use of "=>". I would prefer "A => B" to mean "if A, then B". Accordingly:
class Monad m <= MonadPlus m
By your definition, couldn't what we have now (class Monad m => MonadPlus m) be read as "If m is in the Monad class, then the class MonadPlus can be defined for m thusly:...", which seems pretty clear to me.
Not to me. It's like saying "If f is a piece of furniture, then the set of chairs can be defined for f thusly", which seems equally unclear to me. If m is in the Monad class... then what? It's not necessarily in the MonadPlus class. No useful inference can be drawn this way. What we mean to say instead is "if m is in the MonadPlus class, then it is in the Monad class". -- Ashley Yakeley

On 21/02/06, Ashley Yakeley
Sebastian Sylvan wrote:
Not quite the same complaint, but I've always been bothered by the inconsistent use of "=>". I would prefer "A => B" to mean "if A, then B". Accordingly:
class Monad m <= MonadPlus m
By your definition, couldn't what we have now (class Monad m => MonadPlus m) be read as "If m is in the Monad class, then the class MonadPlus can be defined for m thusly:...", which seems pretty clear to me.
Not to me. It's like saying "If f is a piece of furniture, then the set of chairs can be defined for f thusly", which seems equally unclear to me.
If m is in the Monad class... then what? It's not necessarily in the MonadPlus class. No useful inference can be drawn this way. What we mean to say instead is "if m is in the MonadPlus class, then it is in the Monad class".
I can see both points of view here. I think what Sebastian was trying to say is that it means something along the lines of: "If m is a Monad, then m is a MonadPlus provided that the following are implemented." which is a sensible interpretation. Either way would work. - Cale

Not quite the same complaint, but I've always been bothered by the inconsistent use of "=>". I would prefer "A => B" to mean "if A, then B".
that keeps bugging me, too. but switching the implication is not going to help (although others have proposed the same). here's how I keep my peace with that anomaly: > class Monad m => MonadPlus m if MonadPlus m, then declare Monad m as follows > instance Integral a => Eq (Ratio a) if Integral a, then Eq (Ratio a) > foo :: (Monad m) => [m a] -> m [a] if Monad m, then foo :: [m a] -> m [a] the problem is (methinks) that the superclass implication is interpreted at a different "time/phase" than the others, and classical logic doesn't have that notion: 1. check Monad m, to ensure that MonadPlus m is a valid declaration (here, we _check_ that MonadPlus m => Monad m) 2. handle everything else; and since know that we've done 1 first, we can now _use_ that MonadPlus m => Monad m as well actually, it is worse: constraints in instances and types just affect the validity of the thing that follows them, whereas constraints in classes affect the validity of the whole program. on the basis of which we can reason "backwards": - if the program was invalid, I wouldn't be doing this step - I'm doing this step, so the program is (still) valid - if the program is valid, so must be the Monad m declaration - if MonadPlus m is a valid declaration, there must be Monad m - hence, MonadPlus m => Monad m so, the reasoning for superclass contexts is backwards, not the implications. I once argued that it would be quite natural to interpret the superclass implications in the same way as the other implications (thus relaxing the constraint that 1 has to be checked globally before the program can be assumed valid, hence permitting more programs to be valid).didn't convince the folks I showed it to, so that draft was never even completed.. cheers, claus

Claus Reinke wrote:
class Monad m => MonadPlus m if <..oops..>
if Monad m, then declare MonadPlus m as follows..
This gloss doesn't make sense. The act of declaration is a constant static property of the module, and cannot be conditional on the property of a variable. The module _always_ declares the class. A sensible gloss should begin "Declare MonadPlus to be a class on m such that (Monad m) and..." with the understanding that "m" is quantified by "Declare MonadPlus to be a class on m". -- Ashley Yakeley

class Monad m => MonadPlus m if <..oops..> if Monad m, then declare MonadPlus m as follows..
This gloss doesn't make sense. The act of declaration is a constant static property of the module, and cannot be conditional on the property of a variable. The module _always_ declares the class.
would be nice, wouldn't it? and since section 4.3.1 "Class Declarations" skirts the issue, one might assume that it does (*). but if you look through 4.3.2 "Instance Declarations", you'll find: 1. .. In other words, T must be an instance of each of C's superclasses and the contexts of all superclass instances must be implied by cx'. and If the two instance declarations instead read like this: ... then the program would be invalid. in other words, whether or not the superclass instances exist does not just affect whether or not the subclass instances exist, it affects whether or not the instance declaration, and hence the whole program, is valid. if you don't have any ms for which Monad m holds, you won't be able to declare any instances of MonadPlus m. it doesn't matter whether you never use those instances. this program is simply not valid (but adding an A Int instance makes so): class A x class A x => B x instance B Int (*) granted, the class declaration alone might still be considered valid, but you couldn't actually use it for anything, so I'm not sure that makes a difference. and whether or not the instance declaration is statically valid _is_ conditional on the existence of other instances. it is this early/eager checking of superclass constraints that I find odd, and different from all other constraint handling. it means that I can't use superclass constraints to lift out common method constraints, because class <ctxt> => B x where {m1 :: <t1>;..; mn :: <tn>} is not equivalent to class B x where {m1 :: <ctxt> => <t1>;..; mn :: <ctxt> => <tn>} [even if the conditions for variables in contexts would not rule that out] whereas such lifting is possible for common constraints in instances. it also means that I have to provide superclass instances at the _point of declaration_ of subclass instances - I can not defer that obligation to the _point of use_. cheers, claus

Ashley Yakeley
Josef Svenningsson wrote:
This is one of the things that the Clean people got right. In Clean, my examples from above would look like:
class MonadPlus m | Monad m where ...
class Ix a | Ord a where ..
instance Eq (Ratio a) | Integral a where ...
Not quite the same complaint, but I've always been bothered by the inconsistent use of "=>". I would prefer "A => B" to mean "if A, then B". Accordingly:
class Monad m <= MonadPlus m class Ord a <= Ix a instance Integral a => Eq (Ratio a) foo :: (Monad m) => [m a] -> m [a]
It may be useful to keep in mind how this would translate into the module language of OCaml (remember that in *ML, type application is written argument-first): module type MonadPlus = functor (M: Monad) -> sig type m 'a = 'a M.m val mzero : 'a m val mplus : 'a m -> 'a m -> 'a m end;; module type Eq = sig type t val (==) : t -> t -> bool val (/=) : t -> t -> bool end;; module IntegralRatioEq :: Eq functor (I: Integral) -> struct type t = I.t ratio let (==) = ... end; I am not claiming that all aspects of the syntax are more elegant, but I think it makes the semantics clearer. (Of course, OCaml does not have implicit module arguments, so ``foo :: (Monad m) => [m a] -> m [a]'' has no direct translation.) <plug>See also ``Named Instances for Haskell Type Classes'': http://www.cas.mcmaster.ca/~kahl/Publications/Conf/Kahl-Scheffczyk-2001.html </plug>
instance Eq (Ratio a) | Integral a
Those who think of type classes as a medium for logic programming might indeed prefer instance Eq (Ratio a) :- Integral a ;-) Wolfram

Ashley Yakeley wrote:
foo :: (Monad m) => [m a] -> m [a] instance Integral a => Eq (Ratio a) class Monad m <= MonadPlus m
I think the most consistent (not most convenient!) syntax would be foo :: forall m a. (Monad m) => [m a] -> m [a] instance forall a. (Integral a) => Eq (Ratio a) where {...} class MonadPlus m. (Monad m) && {...} There's implicit forall quantification in instance declarations. It's currently never necessary to make it explicit because there are never type variables in scope at an instance declaration, but there's no theoretical reason that there couldn't be. There's no implicit quantification in class declarations---if you added a quantifier, it would always introduce exactly the type variables that follow the class name. I think it's better to treat the class itself as the quantifier. (And it's more like existential quantification than universal, hence the && instead of =>.) As far as syntax goes, I like foo :: forall m a | Monad m. [m a] -> m [a] class MonadPlus m | Monad m where {...} but I'm not sure what to do about the instance case, since I agree with the OP that the interesting part ought to come first instead of last. -- Ben

On 2/22/06, Claus Reinke
class Monad m => MonadPlus m where ...
class Ord a => Ix a where ...
instance Integral a => Eq (Ratio a) where ...
still difficult?-) works just as well when the constraint lists get longer.
This is the style I've adopted and it makes things a little better but not much. I still found it difficult to browse through my library even with this kind of layout. ps. I like that its the same way as for type signatures.
Well, it's good that the class contraint syntax for type signatures is consistent with that of class and instance declarations. But it is still the wrong syntax. Cheers, /Josef

Am Mittwoch, 22. Februar 2006 01:25 schrieb Claus Reinke:
class Monad m => MonadPlus m where ...
class Ord a => Ix a where ...
instance Integral a => Eq (Ratio a) where ...
still difficult?-) works just as well when the constraint lists get longer.
claus
I do something similar now (use a monospace font): class Monad m => MonadPlus m where [...] Using a line break has also the advantage that changes before the => cannot introduce the necessity for a linebreak in the part after the =>. So the formatting of the part after the => is not affected. This is especially useful if you want to use darcs replace. Best wishes, Wolfgang
participants (8)
-
Ashley Yakeley
-
Ben Rudiak-Gould
-
Cale Gibbard
-
Claus Reinke
-
Josef Svenningsson
-
kahl@cas.mcmaster.ca
-
Sebastian Sylvan
-
Wolfgang Jeltsch