[Haskell-cafe] A very nontrivial parser

Jonathan Cast jcast at ou.edu
Fri Jul 6 13:43:47 EDT 2007


On Friday 06 July 2007, Andrew Coppin wrote:
> Donald Bruce Stewart wrote:
> > andrewcoppin:
> >> Personally, I just try to avoid *all* language extensions - mainly
> >> because most of them are utterly incomprehensible. (But then, perhaps
> >> that's just because they all cover extremely rare edge cases?)
> >
> > Some cover edge cases, some are just useful.  What about:
> >
> >     * the FFI
> >     * bang patterns
> >     * pattern guards
> >     * newtype deriving
> >
> > Surely, fairly simple, useful. Used a lot? :-)
>
> * The FFI - isn't that now officially "in" the language? (I thought
> there was an official report amendment.) Either way, I can't do C, so...
> it looks pretty incomprehensible from here. ;-)

It's in Haskell, but not Haskell 98:

> The benefit of a H98 Addendum over any random language extension provided by
> some Haskell implementation is that a H98 Addendum is a standardised 
> design, and programs coded against such an addendum can be expected to be
> portable across implementations that support this standard.  
> Generally, implementations of H98 are not required to implement all H98
  ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> Addenda,
  ^^^^^^^
> but if such an implementation does provide a feature that is covered by an
> addendum, it is expected that this extension conforms to that addendum (in
> the same way as it is expected to abide by the H98 language definition).  

http://haskell.org/haskellwiki/Language_and_library_specification

> * Bang patterns - what's that?

If you stick a ! in front of a variable in a pattern, or in front of a pattern 
in a let-binding, whatever that variable is getting bound to, or whatever 
that pattern is getting matched against, is evaluated before the binding 
takes place (rather than being suspended in a thunk, as normal).  So if you 
say

foldl' f z [] = z
foldl' f !z (x:xn) = foldl' f (f z x) xn

foldl' is always strict in its second argument (which produces a tremendous 
speed-up; compare foldl (+) 0 with foldl' (+) 0 as definitions of sum).

> * Pattern guards - that's not in the language?

Nope.  Not even a candidate extension.  (I assume you know that pattern guards 
are guards of the form

-- | Cut-off subtraction function
cutOffSub :: Integegral alpha => alpha -> alpha -> Maybe alpha
cutOffSub x y = do
  let d = x - y
  guard $ d >= 0
  return d

genericDrop :: Integral int => int -> [alpha] -> [alpha]
genericDrop _ [] = []
genericDrop 0 xn = []
genericDrop n (x:xn) | Just n' <- cutOffSub n 1 = genericDrop n' xn
                       ^^^^^^^^^^^^^^^^^^^^^^^^
                       pattern guard

Guards on case expression patterns /are/ part of the language, but isn't what 
is meant by `pattern guards'.)

> * Newtype deriving - what's that?

Given that C is a (well-behaved) type class, and T is an instance of that 
class,

newtype S = S T deriving C

will always make S and T isomorphic in C in GHC.  Exceptions: classes too 
funky for GHC to figure out what the class methods for S should be, and Read 
and Show, which by the definition of deriving (and the expectations of 90% of 
the classes' users) lack isomorphic instances entirely.

So, we can define the RWS monad as

newtype RWS r w s alpha = RWS (ReaderT r (WriterT w (State s)) alpha)
  deriving Monad

for example.

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


More information about the Haskell-Cafe mailing list