| Comments to me directly ([EMAIL PROTECTED]), or the Haskell mailing
| list.

Here we are ... (comments are marked with `]')

----------------------------------------------------------------------------

Typing of do expressions

[...]

  2. Nuke MonadZero altogether. Instead, augment the Monad class with

             class Monad a where
               ...as before..
               mfail :: m a

     Now all do expressions are in class Monad. You can interpret mfail as a
     zero if you like. Two reasons for liking this:
        o It simplifies the typing of do expressions.

        o Pretty much every monad will have to be in MonadZero in order to
          do something sensible with do expressions that include patterns.
          If that's the case, why not simplify and combine the classes?

        o No known Haskell monad obeys the laws for a zero:

            m >> zero = m

          (e.g. Take m to be bottom.) So calling it a zero is a bit of a
          misnomer.


] I prefer the second option simply because all `do' expressions are then
] in the basic Monad class. One could even add a default definition for
] `mfail'
]
]       class Monad a where
]           ...as before..
]            mfail :: m a
]            mfail =  error "computation failed"
]
] Then no changes to existing instances of Monad are required. 
]
] BTW I guess the law should read as
]
]       m >> zero = zero .

----------------------------------------------------------------------------

The simple-context restriction

The question here is whether

        f :: Eq (h a) => ...
        g :: Eq [a]   => ...

should be legal types. In Haskell 1.4 both are illegal; the constraints in a
context must take the form (Class tyvar). There are three possibilities:

  1. Status quo. Accept that we don't have principal types, and that
     occasionally hurts.
  2. Allow constraints of the form (Class (tyvar types)). This would make
     f's type signature legal, but still exclude g's. It still permits eager
     context reduction (as Haskell currently has). It has principal types.
     But Haskell 2 is going to go further.
  3. Allow arbitrary types in contexts. This would make both f and g's type
     signature legal. This is where Haskell 2 is going; it is sound and
     implementable. But it forces lazy context reduction, which is a big
     change, perhaps all the more so because it is largely hidden.
     Furthermore, it is a change that hbc and nhc might find it hard to
     track.


] Don't stick to the status quo!!! Types like `Eq (h a)' just occur too
] often (as a rule of thumb they always show up if you mix classes and
] constructor classes). So if (3) is a problem because of lazy context
] reduction adopt (2), but not (1).

----------------------------------------------------------------------------

                        Lexical and syntactic matters

VarIds can begin with "_".

The ICFP meeting didn't like this change. Partly because '_' on its own is
not a normal identifier, in a pattern at least: it's a wild card.

The change was apparently originally motivated by noting that

        ___

(three consequtive underscores) would lex as _ _ _, clearly a Bad Thing. We
agreed to fix it thus:

   * make '_' lexically a valid identifier character anywhere
   * but disallow identifiers starting with '_'

Thus '___' would lex as '___' but then be rejected. '_' on its own remains a
wild-card pattern, and illegal in expressions.


] `_' is a special case whatever option one chooses. So I can see no real
] advantage in disallowing identifiers starting with '_'.


Maximal munch rule for '---'

Modified. Yes, use the maximal munch rule, but any lexeme consisting of two
or more hyphens begins a comment.

So '---' is not a valid operator symbol, but '-->' is. A line of hyphens of
any length introduces a comment.


] I do not understand the example: if every lexeme consisting of two
] or more hyphens begins a comment, `-->' begins a comment!


Allow a type and a class to have the same name

Rejected. It's an un-forced change, and it allows even more obscure programs
than now. Data constructors and type constructors can share the same name,
but data constructors appear only in expressions, and type constructors only
in types, so there's no confusion. But classes appear in types too.

] No, no, no! Why on earth should Haskell 98 dictate the choice of names?
] Nobody is forced to use the same names for types and classes, if she or he
] does not like it. But there may be a situation where this is pretty useful.
] The next step is probably to ban the indiscriminate use of recursion
] because one can use recursion to write very obscure programs.
] Sorry for my passionate words but I do not like the tendency here :-(.


Allow import decls anywhere in a file

Rejected. Most people wanted them to stay at the top.

] The same comment applies here ;-).


Remove concept of "special identifier"

The idea was to make hiding and qualified into keywords, and change the
syntax of module imports so that it no longer used the special identifier as

While this is undoubtedly a clean-up, it adds two new keywords and changes
the syntax of the language for a gain that will not be discernable to most
programmers. We didn't discuss this much at the ICFP meeting, but it does
look like an un-forced change with noticeable disadvantages.

] But the change simplifies the language and after all this was one of
] the motivations for Standard Haskell, now Haskell 98.

----------------------------------------------------------------------------

                               Module matters

Allow infix decls anywhere

[..]


] Good idea! We should adopt this one.

----------------------------------------------------------------------------

                               Prelude matters

Un-overload list comprehensions, ++, map, filter, concat

] Well, I'm not particularly fond of the names: `Monad' isn't a beauty spot
] though it is well established (what about `Computation'?), but `MonadZero'
] and `MonadPlus' are really debatable. In the section about `do'-expressions
] Simon suggests to replace `mzero' by `mfail' which I think is a good idea.
] Likewise `mplus' could be replaced by `alt' or `choose' ...

Default default

However, I think it does make sense to make the default-default types
(Integer,Double) rather than their present (Int,Float). These defaults are
used only when resolving an ambiguous type, and can be overridden with a
default declaration.

] Good idea.

Add insert to List

Bjarte Østvold also suggests adding

insert :: Ord a => a -> [a] -> [a]

to module List. This is consistent with the other `By' functions, which all
have a non-By version., so I propose to do this.

] Good idea.


Cheers, Ralf


Reply via email to