#7506: adding extra arguments to a foreign import statement can cause ghc to 
panic
-------------------------------+--------------------------------------------
Reporter:  jwlato              |          Owner:                  
    Type:  bug                 |         Status:  new             
Priority:  normal              |      Component:  Compiler (FFI)  
 Version:  7.6.1               |       Keywords:                  
      Os:  Unknown/Multiple    |   Architecture:  Unknown/Multiple
 Failure:  Compile-time crash  |      Blockedby:                  
Blocking:                      |        Related:                  
-------------------------------+--------------------------------------------
 When defining a "FunPtr" of a C import, adding extra arguments outside the
 "FunPtr" causes ghc to panic.

 {{{
 {-# LANGUAGE ForeignFunctionInterface #-}

 module Foo where

 import Foreign.Ptr
 foreign import ccall "stdio.h &putchar" c_putchar :: () -> FunPtr (Char ->
 IO ())
 }}}

 compiling results in

 {{{

 [1 of 1] Compiling Foo              ( foo.hs, foo.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.1.20121207 for x86_64-unknown-linux):
         resultWrapper
     ghc-prim:GHC.Tuple.(){(w) tc 40}
     -> base:GHC.Ptr.FunPtr{tc 33D}
          (ghc-prim:GHC.Types.Char{(w) tc 3o}
           -> ghc-prim:GHC.Types.IO{tc 32I} ghc-prim:GHC.Tuple.(){(w) tc
 40})

 }}}

 Ideally, a solution to this would allow for partially applying a value
 that would be accessed within the FunPtr, although that's probably not
 trivial to support.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7506>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to