#2701: Cannot derive Data for structures containing unboxed values
---------------------------------+------------------------------------------
    Reporter:  batterseapower    |       Owner:                  
        Type:  bug               |      Status:  new             
    Priority:  normal            |   Component:  Compiler        
     Version:  6.10.1            |    Severity:  normal          
    Keywords:                    |    Testcase:                  
Architecture:  Unknown/Multiple  |          Os:  Unknown/Multiple
---------------------------------+------------------------------------------
 Trying to compile this:

 {{{
 {-# LANGUAGE MagicHash, DeriveDataTypeable #-}
 module Test where

 import GHC.Prim

 import Data.Data
 import Data.Typeable

 data Foo = MkFoo Int#
          deriving (Typeable, Data)
 }}}

 Results in an error:

 {{{
 $ ghc/stage1-inplace/ghc --make ~/DerivingUnboxed.hs
 [1 of 1] Compiling Test             (
 /Users/mbolingbroke/DerivingUnboxed.hs,
 /Users/mbolingbroke/DerivingUnboxed.o )

 /Users/mbolingbroke/DerivingUnboxed.hs:10:29:
     Couldn't match kind `#' against `*'
     When matching the kinds of `Int# :: #' and `d :: *'
       Expected type: d
       Inferred type: Int#
     In the first argument of `z', namely `MkFoo'

 /Users/mbolingbroke/DerivingUnboxed.hs:10:29:
     Couldn't match kind `#' against `*'
     When matching the kinds of `Int# :: #' and `b :: *'
       Expected type: b
       Inferred type: Int#
     In the first argument of `z', namely `MkFoo'
 }}}

 I'm not sure if this is really a bug or not. It might be nice if deriving
 Data handled this case by reboxing Int#, or alternatively if it gave a
 clear error messages about not being able to handle unboxed values.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2701>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to