[Haskell-cafe] A very nontrivial parser

Jonathan Cast jcast at ou.edu
Thu Jul 5 17:13:54 EDT 2007


On Thursday 05 July 2007, Andrew Coppin wrote:
> Jonathan Cast wrote:
> > On Thursday 05 July 2007, Andrew Coppin wrote:
> >> ...OK, anybody have a solution that works in Haskell 98?
> >
> > Rank-2 types are perhaps /the/ most common, widely accepted extension to
> > Haskell 98, after the approved addendum for FFI and the draft addendum
> > for hierarchical modules.  I would really be concerned about using them
> > (it's certainly not like they're going to just disappear on you one day,
> > like say functional dependencies almost certainly will).  But that's just
> > me.
>
> Personally, I just try to avoid *all* language extensions - mainly
> because most of them are utterly incomprehensible.

Ah, there's your problem :)

> (But then, perhaps 
> that's just because they all cover extremely rare edge cases?)

I wouldn't call rank-2 types extremely rare . . .

<snip>

> >> So *neeer* :-P
> >
> > My first thought is that surely you must have said
> >
> > newtype Parser state x y
> >   = forall src. Source src => Parser ((state, src x) -> (state, src x,
> > y))
> >
> > when you meant
> >
> > newtype Parser state x y
> >   = Parser (forall src. Source src => (state, src x) -> (state, src x,
> > y))
> >
> > The relative order of the constructor name and the forall is very
> > important!
>
> Care to explain what's different about these apparently identical
> declarations?

Sure.  Given

newtype Parser0 state x y
  = forall src. Source src => Parser0 ((state, src x) -> (state, src x, y))

we get

Parser0 :: forall src. Source src
        => ((state, src x) -> (state, src x, y)) -> Parser0 state x y

which type assignment is isomorphic to (note: not legal Haskell!)

Parser0 :: (exists src. Source src => (state, src x) -> (state, src x, y))
        -> Parser0 state x y

Given

newtype Parser1 state x y
  = Parser1 (forall src. Source src => (state, src x) -> (state, src x, y))

we get

Parser1 :: (forall src. Source src => (state, src x) -> (state, src x, y))
        -> Parser state x y

The key difference is in the quantifier in the type of the constructor's 
argument.  The exists quantifier (on types) is a tupling operator; Parser0 
takes three arguments: a type (elided at run time!), an instance for the 
Source class (not elided at run time!), and a function implementing the 
parser.

The forall quantifier is a function-forming operator; Parser1 takes one 
argument, which is a function on a type (elided at run time!) and an instance 
for the Source class (not elided at run time!), yielding a function 
implementing the parser.

Using a (thoroughly invalid Haskell) record syntax, we could write the two 
versions

Parser0 :: { type src :: *,
             dict :: Source src,
             fun :: (state, src x) -> (state, src x, y)}
        -> Parser0 state x y

Parser1 :: ({ type src :: *, dict :: Source src, input :: (state, src x)} ->
            (state, src x, y))
        -> Parser1 state x y

which may make the distinction a bit clearer (or not).

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs


More information about the Haskell-Cafe mailing list