[Haskell-cafe] using a win32 dll

Krzysztof Skrzętnicki gtener at gmail.com
Wed May 29 10:14:01 CEST 2013


My first guess would be missing -l parameter. The examples you have linked
read:

ghc --make compname.hs -lkernel32


Best regards,
Krzysztof Skrzętnicki

On Wed, May 29, 2013 at 9:13 AM, Kees Bleijenberg <
k.bleijenberg at lijbrandt.nl> wrote:

> I made a Delphi dll (32 bits windows). This dll exports a function named
> getPngVersion. This is a function with no arguments that returns a pointer
> to a array of chars.****
>
> If I examine the dll with a tools like tdump, I can see the function
> getPngVersion on index 1.****
>
> Now I want to use this dll in Haskell:****
>
> ** **
>
> {-# LANGUAGE ForeignFunctionInterface #-}****
>
> module Main(****
>
> main****
>
> )****
>
> ** **
>
> where****
>
> import Control.Monad****
>
> import Foreign.C****
>
> import Foreign.Marshal.Alloc****
>
> import Foreign.Marshal.Array****
>
> import System.Win32.Types****
>
> ** **
>
> foreign import stdcall "glasPng getPngVersion"  getPngDllVersion :: IO
> CString****
>
> ** **
>
> main :: IO ()****
>
> main = do ****
>
>          s <- getPngDllVersion****
>
>          putStrLn (show s)****
>
> ** **
>
> Compiling this with ghc --make glasPng.hs gives:****
>
> GlasPng.o: fake: (.text +0x82): undefined reference to  ‘getPngVersion at 0> collect2 : Id returned 1 exit status ****
>
> ** **
>
> I wonder what went wrong. In the foreign import line I use “glasPng…. “ to
> tell ghc, it has to searh in glasPng.dll (changing glasPng to glasPng.dll
> doesn’t help). I’ve changed the name of the function in  the dll to
> getPngVersion at 0 but no luck.  I’ve read and tested the last example at
> http://stackoverflow.com/questions/1027246/haskell-foreign-import-stdcall-on-dll-function
> (win32_getComputername,  this works!). I wonder how  haskell knows which
> dll to use in this example?)****
>
> Probably I’am doing something wrong with the way I tell ghc which dll to
> link or….****
>
> ** **
>
> Any ideas?****
>
> ** **
>
> Kees****
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130529/be8d5595/attachment.htm>


More information about the Haskell-Cafe mailing list