Re: The worst piece of syntax in Haskell

2006-02-22 Thread Ben Rudiak-Gould

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

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


superclass implications (was: The worst piece of syntax in Haskell)

2006-02-21 Thread Claus Reinke
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

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


Re: The worst piece of syntax in Haskell

2006-02-21 Thread Josef Svenningsson
On 2/22/06, Claus Reinke [EMAIL PROTECTED] wrote:
 class Monad m= MonadPlus mwhere ... class Ord a= Ix awhere ... 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
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: The worst piece of syntax in Haskell

2006-02-21 Thread Cale Gibbard
On 21/02/06, Ashley Yakeley [EMAIL PROTECTED] wrote:
 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
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime