[GHC] #8037: GHC panic when compiling unsafeCoerce

GHC ghc-devs at haskell.org
Sat Sep 21 02:12:41 CEST 2013


#8037: GHC panic when compiling unsafeCoerce
---------------------------------+------------------------------------
        Reporter:  ghc@…         |            Owner:
            Type:  bug           |           Status:  new
        Priority:  normal        |        Milestone:
       Component:  Compiler      |          Version:  7.6.1
      Resolution:                |         Keywords:
Operating System:  MacOS X       |     Architecture:  Unknown/Multiple
 Type of failure:  None/Unknown  |       Difficulty:  Unknown
       Test Case:                |       Blocked By:
        Blocking:                |  Related Tickets:
---------------------------------+------------------------------------
Changes (by monoidal):

 * status:  infoneeded => new


Comment:

 Great, I can now reproduce. I looked into internals of OpenGL and
 OpenGLRaw and here's a version which does not have the dependency. Compile
 with -O to get the panic, both 7.6 and HEAD.

 {{{
 module Test where

 import Unsafe.Coerce
 import Foreign.Ptr
 import Foreign.C.Types
 import System.IO.Unsafe

 data D4 = D4 Double Double Double Double

 crash :: D4 -> IO ()
 crash c = color (invalidCast c)

 invalidCast :: D4 -> Color3 CDouble
 invalidCast = unsafeCoerce

 class Color a where
    color  :: a -> IO ()
    colorv :: [a] -> IO ()

 data Color3 a = Color3 !a !a !a

 instance ColorComponent a => Color (Color3 a) where
    color (Color3 r g b) = color3 r g b

 class ColorComponent a where
    color3 :: a -> a -> a -> IO ()

 instance ColorComponent CDouble where
    color3 = g

 type Invoker a = FunPtr a -> a

 foreign import ccall dyn_g :: Invoker (CDouble -> CDouble -> CDouble -> IO
 ())
 g :: CDouble -> CDouble -> CDouble -> IO ()
 g = dyn_g ptr_g
 ptr_g :: FunPtr a
 ptr_g = unsafePerformIO undefined
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8037#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler



More information about the ghc-tickets mailing list