
Hi all, I think there's a problem with the external core generation. Suppose we have the following module: ----- module Test where data Bool = True | False data Maybe a = Just a | Nothing class Eq a where (==) :: a -> a -> Bool instance Eq Bool where (==) True True = True (==) False False = True (==) _ _ = False instance Eq a => Eq (Maybe a) where (==) Nothing Nothing = True (==) (Just a) (Just b) = (==) a b (==) _ _ = False ----- We compile this using: ghc -fext-core -fno-code test.hs -fno-implicit-prelude 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): Test.zdfEqMaybe = \ 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 Now, the problem is that "Test.ZCDEq" isn't defined anywhere in the core file produced and neither is Test.zeze. 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). - Hal p.s., the full core output reads: %module Test %data Test.Bool = {Test.True; Test.False}; %data Test.Maybe a = {Test.Just a; Test.Nothing}; %newtype Test.ZCTEq a = GHCziPrim.ZLzmzgZR a (GHCziPrim.ZLzmzgZR a Test.Bool); Test.zdfEqBool :: GHCziPrim.ZLzmzgZR Test.Bool (GHCziPrim.ZLzmzgZR Test.Bool Test.Bool) = \ (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)) = %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}}); -- Hal Daume III "Computer science is no more about computers | hdaume@isi.edu than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
participants (1)
-
Hal Daume III