[GHC] #8588: ForeignImport coercion evaluated before typechecking
GHC
ghc-devs at haskell.org
Sun Dec 1 19:33:47 UTC 2013
#8588: ForeignImport coercion evaluated before typechecking
----------------------------------+----------------------------
Reporter: zcourts | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Keywords: | Operating System: Windows
Architecture: x86_64 (amd64) | Type of failure: Other
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
----------------------------------+----------------------------
I'm fairly new to Haskell by all accounts this could have been caused by
me doing something silly. Following the real world haskell book's
directions on the FFI resulted in:
"Multiple markers at this line: - buildwrapper.exe: panic! (the
'impossible' happened) (GHC version 7.6.3 for i386-unknown-mingw32):
ForeignImport coercion evaluated before typechecking Please report this as
a GHC bug: http://www.haskell.org/ghc/reportabug - 16 changed lines"
I went to the Haskell Wiki to try an example from there to see if the RWH
e.g. was just out dated. All examples I've come across causes this error
inc. those at
http://www.haskell.org/haskellwiki/FFI_complete_examples#Calling_standard_library_functions
and reading https://www.haskell.org/ghc/docs/7.6.3/users_guide.pdf FFI
section didn't help.
The current failing code is
{{{
{-# LANGUAGE ForeignFunctionInterface #-}
module Events.CEvent where
import Prelude hiding (sin)
import Foreign.C -- get the C types
import Foreign.Ptr (Ptr,nullPtr)
-- pure function
foreign import ccall "sin" c_sin :: CDouble -> CDouble
sin :: Double -> Double
sin d = realToFrac (c_sin (realToFrac d))
-- impure function
foreign import ccall "time" c_time :: Ptr a -> IO CTime
getTime :: IO CTime
getTime = c_time nullPtr
}}}
I've also tried this which causes the same error
{{{
{-# LANGUAGE ForeignFunctionInterface #-}
module Events.Event2 where
import Foreign
import Foreign.C.Types
foreign import ccall "math.h sin"
c_sin :: CDouble -> CDouble
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8588>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list