[Hat] Bug in hat-trans?
Malcolm Wallace
hat@haskell.org
Wed, 28 Aug 2002 11:39:28 +0100
Magnus Carlsson <magnus@cse.ogi.edu> writes:
> module Bug where f = \ ~(a,b) -> 1
>
> $ hmake -hat -nhc98 Bug.hs
> hat-trans Bug.hs
> Wrote TBug.hs
> nhc98 -c -package hat -o TBug.o TBug.hs
> ====== Errors after type inference/checking:
> Type error type clash between Hat.R and Prelude.->
> when trying to apply function at 13:7 to its 4th argument at 14:10.
Ok, yes this is a bug. Line 14 of the generated code has some
missing parentheses:
(\ T.R ~(T.Tuple2 fa fb) _ p ->
should be:
(\ (T.R ~(T.Tuple2 fa fb) _) p ->
The fix is in the code pretty-printer. Patch attached.
Regards,
Malcolm
Index: src/compiler98/PrettySyntax.hs
===================================================================
RCS file: /usr/src/master/nhc/src/compiler98/PrettySyntax.hs,v
retrieving revision 1.23
diff -u -r1.23 PrettySyntax.hs
--- src/compiler98/PrettySyntax.hs 2002/07/18 09:28:17 1.23
+++ src/compiler98/PrettySyntax.hs 2002/08/28 10:38:02
@@ -679,7 +679,7 @@
ppExpPrec info withPar (ExpLambda pos pats e) =
parenExp info pos withPar $
- text "\\ " <> sep fSpace (map (ppExpPrec info False) pats) <>
+ text "\\ " <> sep fSpace (map (ppLambdaPat info) pats) <>
text " ->" <> dSpace <> ppExpPrec info False e
ppExpPrec info withPar (ExpDo pos stmts) =
parenExp info pos withPar $
@@ -776,6 +776,11 @@
ppExpPrec info withPar (PatNplusK pos n n' k _ _) =
parenExp info pos withPar $
ppIdAsVar info n <> fSpace <> text "+" <> fSpace <> ppExpPrec info True k
+
+
+ppLambdaPat :: PPInfo a -> Exp a -> Doc
+ppLambdaPat info pat@(ExpApplication _ _) = ppExpPrec info True pat
+ppLambdaPat info pat = ppExpPrec info False pat
ppField :: PPInfo a -> Field a -> Doc