[Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault
Vagif Verdi
vagif.verdi at gmail.com
Sun Mar 16 06:45:55 UTC 2014
I do not think i can help you, but my FFi to functions with similar
signature looks like this:
C definition:
PDFLIB_API int PDFLIB_CALL
PDF_begin_document(PDF *p, const char *filename, int len, const char
*optlist);
haskell FFI:
c_beginDocument :: Pdf -> String -> String -> IO Int
c_beginDocument pdf a2 a3 =
withCString a2 $ \a2' ->
withCString a3 $ c_beginDocument'_ pdf a2' 0
foreign import ccall safe "Pdflib.chs.h PDF_begin_document"
c_beginDocument'_ :: Pdf -> Ptr CChar -> CInt -> Ptr CChar -> IO Int
The difference as you see, i'm using withCString to convert from ahskell to
C and i'm passing 0 as the string size.
On Friday, March 14, 2014 3:24:23 PM UTC-7, Miroslav Karpis wrote:
>
> Hi, please can you help me with following?
>
> I have a call to an external dll (via ffi) which if executed from ghci
> works fine.
> If I compile my code with 'ghc -o fm Mycode.hs -L. -lextdll' and run it I
> get 'Segmentation fault/access violation in generated code'.
>
>
>
> main = do
> let param = "FilePath"
> let value = "C:/dev/misc/haskell/services/FM"
> result <- liftIO $ FM.setmodulestring param value
> return "done"
>
> setmodulestring :: String -> String -> IO CInt
> setmodulestring param value = do
> let cParamLength = fromIntegral $ length param ::CInt
> cValueLength = fromIntegral $ length value ::CInt
> setVarInArray = (-1)::CInt
> alloca $ \cParam -> do
> alloca $ \cValue -> do
> result <- c_setmodulestring cParam cParamLength cValue cValueLength
> setVarInArray
> return result
>
> If I try also with following, the behaviour is the same:
>
> setmodulestring2 :: String -> String -> IO CInt
> setmodulestring2 param value = do
> cParam <- newCWString param
> cValue <- newCWString value
> let cParamLength = fromIntegral $ length param ::CInt
> cValueLength = fromIntegral $ length value ::CInt
> setVarInArray = (-1)::CInt
> result <- c_setmodulestring cParam cParamLength cValue cValueLength
> setVarInArray
> free cParam
> free cValue
> return res
>
>
> Any comments/ideas more than appreciated.
>
> Cheers,
> Miro
>
>
>
>
>
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140315/cb4596eb/attachment.html>
More information about the Haskell-Cafe
mailing list