problem generating Core with no-implicit-prelude

Simon Peyton-Jones simonpj@microsoft.com
Thu, 31 Oct 2002 14:11:37 -0000


It is a bug... we weren't printing enough in -fext-core.

I think it's fixed now.  (I'm away till Monday.)

Simon

| -----Original Message-----
| From: Hal Daume III [mailto:hdaume@ISI.EDU]
| Sent: 29 October 2002 17:57
| To: GHC Users Mailing List
| Subject: problem generating Core with no-implicit-prelude
|=20
| Hi all,
|=20
| I think there's a problem with the external core generation.  Suppose
we
| have the following module:
|=20
| -----
| module Test where
|=20
| data Bool =3D True | False
| data Maybe a =3D Just a | Nothing
|=20
| class Eq a where
|     (=3D=3D) :: a -> a -> Bool
|=20
| instance Eq Bool where
|     (=3D=3D) True  True  =3D True
|     (=3D=3D) False False =3D True
|     (=3D=3D) _     _     =3D False
|=20
| instance Eq a =3D> Eq (Maybe a) where
|     (=3D=3D) Nothing  Nothing  =3D True
|     (=3D=3D) (Just a) (Just b) =3D (=3D=3D) a b
|     (=3D=3D) _        _        =3D False
| -----
|=20
| We compile this using:
|   ghc -fext-core -fno-code test.hs -fno-implicit-prelude
|=20
| Now, if we look at the core, inside the definition of Test.zdfEqMaybe
(the
| eq function for Maybe a), it essentially looks like (glossing over
some of
| the extraneous stuff):
|=20
|   Test.zdfEqMaybe =3D \ zddEq -> Test.ZCDEq
|                     \ ds ds1 ->
|          case ds of
|            Nothing -> case ds1 of
|                         Test.Just a1 -> Test.zdwFalse
|                         Test.Nothing -> Test.zdwTrue
|            Just a1 -> case ds1 of
|                         Test.Nothing -> Test.zdwFalse
|                         Test.Just b  -> Test.zeze zddEq a1 b
|=20
| Now, the problem is that "Test.ZCDEq" isn't defined anywhere in the
core
| file produced and neither is Test.zeze.
|=20
| If this is indeed a bug, could someone fix it?  If not, could someone
tell
| me what I'm doing wrong (I could be misreading the Core, but I don't
think
| so).
|=20
|  - Hal
|=20
| p.s., the full core output reads:
|=20
| %module Test
|   %data Test.Bool =3D
|     {Test.True;
|      Test.False};
|   %data Test.Maybe a =3D
|     {Test.Just a;
|      Test.Nothing};
|   %newtype Test.ZCTEq a =3D GHCziPrim.ZLzmzgZR
| 			  a
| 			  (GHCziPrim.ZLzmzgZR a Test.Bool);
|   Test.zdfEqBool :: GHCziPrim.ZLzmzgZR
| 		    Test.Bool
| 		    (GHCziPrim.ZLzmzgZR Test.Bool Test.Bool) =3D
|     \ (ds::Test.Bool) (ds1::Test.Bool) ->
| 	%case ds %of (wild::Test.Bool)
| 	  {Test.False ->
| 	     %case ds1 %of (wild1::Test.Bool)
| 	       {Test.True ->
| 		  Test.zdwFalse;
| 		Test.False ->
| 		  Test.zdwTrue};
| 	   Test.True ->
| 	     ds1};
|   Test.zdfEqMaybe :: %forall a . GHCziPrim.ZLzmzgZR
| 				 (GHCziPrim.ZLzmzgZR a
(GHCziPrim.ZLzmzgZR
| a Test.Bool))
| 				 (GHCziPrim.ZLzmzgZR
| 				  (Test.Maybe a)
| 				  (GHCziPrim.ZLzmzgZR (Test.Maybe
| a) Test.Bool)) =3D
|     %note "InlineMe"
|     \ @ a
|       (zddEq::GHCziPrim.ZLzmzgZR a (GHCziPrim.ZLzmzgZR a Test.Bool))
->
| 	Test.ZCDEq @ (Test.Maybe a)
| 	(\ (ds::Test.Maybe a) (ds1::Test.Maybe a) ->
| 	     %case ds %of (wild::Test.Maybe a)
| 	       {Test.Nothing ->
| 		  %case ds1 %of (wild1::Test.Maybe a)
| 		    {Test.Just (a1::a) ->
| 		       Test.zdwFalse;
| 		     Test.Nothing ->
| 		       Test.zdwTrue};
| 		Test.Just (a1::a) ->
| 		  %case ds1 %of (wild1::Test.Maybe a)
| 		    {Test.Nothing ->
| 		       Test.zdwFalse;
| 		     Test.Just (b::a) ->
| 		       Test.zeze @ a zddEq a1 b}});
|=20
| --
| Hal Daume III
|=20
|  "Computer science is no more about computers    | hdaume@isi.edu
|   than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
|=20
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users