ghc puzzling behaviour
Simon Peyton-Jones
simonpj@microsoft.com
Tue, 8 Apr 2003 12:01:21 +0100
Thank you. A palpable bug. Fixed.
Simon
| -----Original Message-----
| From: glasgow-haskell-users-admin@haskell.org
[mailto:glasgow-haskell-users-
| admin@haskell.org] On Behalf Of Ketil Z. Malde
| Sent: 07 April 2003 13:33
| To: glasgow-haskell-users@haskell.org
| =20
| =20
| Hi,
| =20
| 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.
| =20
| Is this intentional? I'll get by by dropping -funbox, or explicitly
| declaring the instance, so it's no big deal -- just slightly
| surprising.
| =20
| --T1.hs--
| =20
| > module T1 where
| >
| > data Foo =3D Foo Int String
| > data Bar =3D Bar Int Foo
| >
| > instance Ord Bar where
| > compare (Bar i _) (Bar j _) =3D compare i j
| >
| > instance Eq Bar where
| > (Bar i _) =3D=3D (Bar j _) =3D i =3D=3D j
| =20
| --T2.hs--
| =20
| > module Main where
| >
| > import T1
| >
| > data Zot =3D Zot !Bar !String deriving (Ord,Eq)
| >
| > main =3D putStrLn "Success"
| =20
| -kzm
| --
| If I haven't seen further, it is by standing in the footprints of
giants
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users