[Haskell-cafe] A very nontrivial parser

Jonathan Cast jcast at ou.edu
Thu Jul 5 15:22:40 EDT 2007


On Thursday 05 July 2007, Andrew Coppin wrote:
> Jonathan Cast wrote:
> > On Wednesday 04 July 2007, Andrew Coppin wrote:
> >> Anybody have a solution to this?
> >
> > newtype Parser state x y
> >   = Parser (forall src. Source src => (state, src x) -> (state, src x,
> > y))
>
> ...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.

> > Definition of monad functions, etc, works exactly as for your version.
>
> Not so.
>
> In fact, doing this causes all mannar of malfunctions. First I get lots
> of messages of the form
>
> "Cannot (yet) use update syntax on non-Haskell98 types."
>
> Then I get lots of
>
> "Cannot use function 'foo' as a selector."
>
> And then I get
>
> "My brain has exploded. I can't handle pattern bindings in
> existentially-quantified type constructors."
>
> (?!)
>
> And after that I get
>
> "Type variable 'bar' escapes pattern binding."
>
> And finally, after I correct all of those, I get an error saying that
> the compiler can't match [the hidden type variable] against [some
> suitable type for that variable]. And in a pattern of all things!
> (Surely if it's not the right type at runtime, it should generate an
> exception, just like if you use the wrong constructor...?)

Just a side point but: how would it know?  Leaving aside the 
dictionary-passing used for type classes, Haskell has (and has always had) a 
type-erasure semantics, which rules out runtime type errors.

> In all, the whole thing just malfunctions horribly and I can get no
> useful work done! >_<
>
> So my next plan was to write the code as normal, and then create a
> front-end module which "hides" all the messy types. But then I just get
> a whole bunch of "escaping type variable" errors again.
>
> Basically everything I tried make the code drastically more complicated,
> and even *then* certain parts of it (most especially the stack function)
> wouldn't compile.
>
> 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!  
If you got the answer right, I can't see why you'd be getting unmistakable 
existential-type errors; there are no existential quantifiers in my proposal.  
But I'll try to implement it myself and see what I get.

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


More information about the Haskell-Cafe mailing list