[jhc] parse error on where with jhc
J. Garrett Morris
jgmorris at cecs.pdx.edu
Sat Aug 29 16:05:08 EDT 2009
I'm pretty sure GHC has the right behavior here. The first approach
would be to insert a semi and attempt to continue parsing, however,
since this causes a parse error I would expect the rule:
L (t:ts) (m:ms) = } : (L (t:ts) ms) if m /= 0 and parse-error(t)
(Note 5)
(See Section 9.3 in the report)
to be invoked. This is an interesting test case; I'll have to hold
onto it for my Haskell-like parser!
/g
On Sat, Aug 29, 2009 at 9:04 AM, David
Roundy<roundyd at physics.oregonstate.edu> wrote:
> The following code gives a parse error on jhc:
>
> configureFlagWithDefault :: String -> String -> String
> -> C () -> (String -> C ()) -> C FranchiseFlag
> configureFlagWithDefault n argname h defaultaction j =
> do whenC amConfiguring $ addHook n defaultaction
> return $ FF $ Option [] [n] (ReqArg (addHook n . j') argname) h
> where j' v = do putV $ "handling configure flag --"++n++" "++v; j v
>
> Evidently, jhc wants the where to be less indented than the do block.
> I've no idea how this compares with the language standard, but it
> certainly differs from ghc, so I thought it'd be worth mentioning. Of
> course, it's not really a nice way to indent...
> --
> David Roundy
> _______________________________________________
> jhc mailing list
> jhc at haskell.org
> http://www.haskell.org/mailman/listinfo/jhc
>
--
I am in here
More information about the jhc
mailing list