[nhc-bugs] Re: Incorrect type clash

Malcolm Wallace Malcolm.Wallace@cs.york.ac.uk
Mon, 10 Dec 2001 14:08:35 +0000


Thanks for the latest bunch of error reports, Ian.  Patches below.

> With this module:
>     data Foo = Foo Int Bar deriving Show
>     data Bar = Bar Int Int deriving Show
>     a `Foo` (b `Bar` c) = 3 `Foo` (4 `Bar` 5)
> 
> I get
>             Error after type deriving/checking:
>     Type error type clash between Prelude.Int and Main.Foo
>     when trying to apply function at 5:15 to its 1:st argument at 5:6.

This was an error in parsing the LHS pattern - the bracketing was lost,
causing it to associate incorrectly as (a `Foo` b) `Bar` c.

> With the module
>     module Foo (,) where
>     foo = 0
> I get
>     2:14 Found Prelude.2 but expected one of _where_ () (
> but the report (and GHC) allows this.

Technically, yes this is legal Haskell'98.  nhc98 is now fixed to
accept a single comma in an export or import list.

> If I have
>     foo = 0 --+ 1
> then nhc tells me
>     Identifier --+ used at 2:11 is not defined.
> while the report (and hugs) believe "--+ 1" is a comment.

Nope, the Report agrees with nhc98 that --+ is an operator.
Hugs is wrong.

Regards,
    Malcolm

Patch for infix pattern decls:

Index: src/compiler98/MkSyntax.hs
===================================================================
RCS file: /usr/src/master/nhc/src/compiler98/MkSyntax.hs,v
retrieving revision 1.3
diff -u -r1.3 MkSyntax.hs
--- src/compiler98/MkSyntax.hs	2000/11/28 18:13:34	1.3
+++ src/compiler98/MkSyntax.hs	2001/12/10 14:00:38
@@ -40,8 +40,8 @@
 
 mkDeclPat :: (Pos,a) -> Exp a -> Exp a -> Rhs a -> Decls a -> Decl a
 
-mkDeclPat (pv,var) op (ExpInfixList pos es) gdexps w =
-	DeclPat (Alt (ExpInfixList pos (ExpVar pv var:op:es)) gdexps w)
+mkDeclPat (pv,var) op e@(ExpInfixList pos es) gdexps w =
+	DeclPat (Alt (ExpInfixList pos [ExpVar pv var,op,e]) gdexps w)
 mkDeclPat (pv,var) op e gdexps w =
 	DeclPat (Alt (ExpInfixList pv [ExpVar pv var,op,e]) gdexps w)
 

Patch for single comma in import/export lists:

Index: src/compiler98/Parse2.hs
===================================================================
RCS file: /usr/src/master/nhc/src/compiler98/Parse2.hs,v
retrieving revision 1.14
diff -u -r1.14 Parse2.hs
--- src/compiler98/Parse2.hs	2001/11/12 14:50:27	1.14
+++ src/compiler98/Parse2.hs	2001/12/10 11:59:47
@@ -20,7 +20,9 @@
     Just `parseChk` lpar `apCut` manySep comma parseExport `chk` 
       optional comma `chk` rpar
         `orelse`
-    parse Nothing `chk` lit (L_ACONID (TupleId 0))
+    parse Nothing `chk` (lit (L_ACONID (TupleId 0))
+                            `orelse`
+                         lit (L_ACONID (TupleId 2)))
         `orelse`
     parse (Just [])
 
@@ -59,7 +61,8 @@
 
 
 parseImpSpec =
-    (NoHiding []) `parseChk` k_unit                  -- fix for import Module()
+    (NoHiding []) `parseChk` (k_unit `orelse` lit (L_ACONID (TupleId 2)))
+			-- fix for  import Module()  and  import Module (,)
         `orelse`
     NoHiding `parseChk` lpar `apCut` manySep comma parseEntity `chk` 
       optional comma `chk` rpar