Things and limitations...

Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl
17 May 2001 07:31:23 GMT


Mon, 14 May 2001 20:26:21 -0700, Juan Carlos Arevalo Baeza <jcab@roningames.com> pisze:

> class (MonadPlus (p s v)) => Parser p where
>      item :: p s v v
>      force :: p s v a -> p s v a
>      first :: p s v a -> p s v a
>      papply :: p s v a -> s -> [(a,s)]

This MonadPlus superclass can't be written. The Parser class is
overloaded only on p and must work uniformly on s and v, which can
be expressed for functions (by using s and v as here: type variables
not mentioned elsewhere), but can't for superclasses. What you want
here is this:

  class (forall s v. MonadPlus (p s v)) => Parser p where

which is not supported by any Haskell implementation (but I hope it
will: it's not the first case when it would be useful).


This should work on implementations supporting multiparameter type
classes (ghc and Hugs):

  class (MonadPlus (p s v)) => Parser p s v where
       item :: p s v v
       force :: p s v a -> p s v a
       first :: p s v a -> p s v a
       papply :: p s v a -> s -> [(a,s)]

Well, having (p s v) in an argument of a superclass context is not
standard too :-(  Haskell98 requires types here to be type variables.

It requires that each parser type is parametrized by s and v; a
concrete parser type with hardwired String can't be made an instance of
this class, unless wrapped in a type which provides these parameters.


The best IMHO solution uses yet another extension: functional dependencies.

  class (MonadPlus p) => Parser p s v | p -> s v where
       item :: p v
       force :: p a -> p a
       first :: p a -> p a
       papply :: p a -> s -> [(a,s)]

Having a fundep allows to have methods which don't have v and s in
their types. The fundep states that a single parser parses only
one type of input and only one type of tokens, so the type will
be implicitly deduced from the type of parser itself, basing on
available instances.

Well, I think that s will always be [v], so it can be simplified thus:

  class (MonadPlus p) => Parser p v | p -> v where
       item :: p v
       force :: p a -> p a
       first :: p a -> p a
       papply :: p a -> [v] -> [(a,[v])]


Without fundeps it could be split into classes depending on which
methods require v:

  class (MonadPlus p) => BasicParser p where
       force :: p a -> p a
       first :: p a -> p a

  class (BasicParser p) => Parser p v where
       item   :: p v
       papply :: p a -> [v] -> [(a,[v])]

This differs from the fundep solution that sometimes an explicit type
constraint must be used to disambiguate the type of v, because the
declaration states that the same parser could parse different types
of values. Well, perhaps this is what you want and
    item :: SomeConcreteParser Char
could give one character where
    item :: SomeConcreteParser (Char,Char)
gives two? In any case using item in a way which doesn't tell which
item type to use is an error.


>     Ok, last, I wanted to alias a constructor. So:

There is no such thing. A constructor can't be renamed. You would
have to wrap the type inside the constructor in a new constructor.

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK