The native code generator only handles 'foreign import's with a
static target, which is why you're seeing this (HEAD handles
this situation a little bit more gracefully).

Use -fvia-C (or -O, which implicitly does the same thing).

--sigbjorn

----- Original Message -----
From: "Volker Stolz" <[EMAIL PROTECTED]>
To: <[EMAIL PROTECTED]>
Sent: Friday, November 16, 2001 10:18
Subject: AbsCStixGen.gencode panic


> Beware, to reproduce you need c2hs & gtk+hs!
> Luckily, I can use the "-O" switch (does that option mean "turn errors
OFF"?)
> to get a perfectly working binary!
>
> ghc -c Get.lhs -o Get.o `c2hs-config --cflags`  -fglasgow-exts -package
lang
>
> ghc-5.02.1: panic! (the `impossible' happened, GHC version 5.02.1):
>         AbsCStixGen.gencode
>     typedef void ( *_ccall_fun_tys1Cc) (StgAddr, I_);
>
> \begin{code}
>
> module Main where
>
> import IO
> import Maybe
> import Monad
> import Foreign
> import CString
> import GModule
>
> type Fun = CString -> Int -> IO ()
> foreign import dynamic unsafe iterator__ :: FunPtr Fun -> Fun
>
> main :: IO ()
> main = do
>   withModule (Just ".") "simple" ModuleBindOnLoad $ \ mod -> do
>     funptr <- moduleSymbol mod "simple"
>     when (isNothing funptr) $ error "fooooo!"
>     let res = iterator__ (castPtrToFunPtr (fromJust funptr))
>     withCString "hello" $ \ str -> res str 1
>   return ()
>
> \end{code}
> --
> Volker Stolz * [EMAIL PROTECTED] * PGP + S/MIME
>
> _______________________________________________
> Glasgow-haskell-bugs mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to