standalone binary deriving
Ben
midfield at gmail.com
Tue May 4 01:55:11 EDT 2010
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
More information about the Glasgow-haskell-users
mailing list