ghc puzzling behaviour

Ketil Z. Malde ketil@ii.uib.no
07 Apr 2003 14:33:27 +0200


Hi,

When compiling with -funbox-strict-fields, the supplied code doesn't
seem to compile, requiring 'Ord Foo' to derive 'Ord Zot', even if 'Ord
Bar' is explicitly declared.  Without the flag, it works as expected.

Is this intentional?  I'll get by by dropping -funbox, or explicitly
declaring the instance, so it's no big deal -- just slightly
surprising. 

--T1.hs--

> module T1 where
> 
> data Foo = Foo Int String
> data Bar = Bar Int Foo
> 
> instance Ord Bar where 
>     compare (Bar i _) (Bar j _) = compare i j
> 
> instance Eq Bar where
>     (Bar i _) == (Bar j _) = i == j
 
--T2.hs--    
 
> module Main where
> 
> import T1
> 
> data Zot = Zot !Bar !String deriving (Ord,Eq)
> 
> main = putStrLn "Success"

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants