
#8281: The impossible happened: primRepToFFIType ---------------------------------------+----------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by errge): I met this today and came up with the following temporary workaround: {{{#!haskell {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnliftedFFITypes #-} {-# LANGUAGE ForeignFunctionInterface #-} import Control.Concurrent import GHC.Conc.Sync import Foreign.C import GHC.Base foreign import ccall unsafe "rts_getThreadId" getThreadId# :: Addr# -> CInt getThreadId :: ThreadId -> CInt {-# INLINE getThreadId #-} getThreadId (ThreadId tid) = getThreadId# (unsafeCoerce# tid) threadId :: IO Int {-# INLINE threadId #-} threadId = do mtid <- myThreadId return $ fromIntegral $ getThreadId mtid main = do print =<< threadId forkIO $ print =<< threadId threadDelay 10000 }}} Seems to work with ghci and 32/64-bit compiled and 32/64-bit optimized code. Total noob in this area, please tell me if this is dangerous somehow. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler