[Haskell-cafe] bizarre syntax error
Geoffrey Irving
irving at naml.us
Sat Jun 27 20:37:00 EDT 2009
I ran into a unfortunate syntax error just now. I figured I'd share
it because it's the weirdest message I've ever gotten out of ghc. The
broken code is
case t of
TyApply tv types -> do
(tvl, cases) <- lookupDatatype prog tv
let tenv = Map.fromList (zip tvl types) -- GHC POINTS HERE
caseType (c,vl,e')
| Just tl <- List.lookup c cases =
if length vl == a then
expr prog global (foldl (\e (v,t) -> Map.insert v
t e) env (zip vl (map (subst tenv) tl))) e'
else
typeError ("arity mismatch in pattern: "++show
(pretty c)++" expected "++show a++" argument"++(if a == 1 then "" else
"s")
++" but got ["++concat (intersperse ", " (map
(show . pretty) vl))++"]")
where a = length tl -- THIS IS THE PROBLEM
| otherwise = typeError ("datatype "++show (pretty
tv)++" has no constructor "++show (pretty c))
defaultType Nothing = return []
defaultType (Just (v,e')) = expr prog global (Map.insert v
t env) e' >>=. \t -> [t]
join t1 t2 | Just t <- unifyS t1 t2 = return t
| otherwise = typeError ("failed to unify types
"++show (pretty t1)++" and "++show (pretty t2)++" from different case
branches")
caseResults <- mapM caseType pl
defaultResults <- defaultType def
foldM1 join (caseResults ++ defaultResults)
_ -> typeError ("expected datatype, got "++show (pretty t))
ghc complains that
"The last statement in a 'do' construct must be an expression"
and points to the line declaring "tenv". The actual problem is that
you can't put a "where" block in between two pattern guards. :)
Geoffrey
More information about the Haskell-Cafe
mailing list