standalone binary deriving
Simon Peyton-Jones
simonpj at microsoft.com
Wed May 5 17:39:32 EDT 2010
It's a bug, but it's been fixed
http://hackage.haskell.org/trac/ghc/ticket/3833
Thakns
Simon
| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-
| users-bounces at haskell.org] On Behalf Of Ben
| Sent: 04 May 2010 06:55
| To: glasgow-haskell-users at haskell.org
| Subject: standalone binary deriving
|
| compiling the following fragment in ghci
|
| {-# LANGUAGE StandaloneDeriving #-}
|
| import Data.Binary (Binary)
|
| newtype Pair a b = Pair (a,b)
| deriving instance (Binary a, Binary b) => Binary (Pair a b)
|
| results in the following message:
|
| Prelude> :load "/Users/catbee/Documents/dev/haskell/savestream/foo.hs"
| [1 of 1] Compiling Main (
| /Users/catbee/Documents/dev/haskell/savestream/foo.hs, interpreted )
| ghc: panic! (the 'impossible' happened)
| (GHC version 6.12.1 for i386-apple-darwin):
| genDerivBinds: bad derived class
| binary-0.5.0.2:Data.Binary.Binary{tc rkt}
|
| Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
|
| should i file a bug report?
|
| b
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list