Unfortunatly the proposed solutions didn’t work after all (It worked once, I think, but…)
Here again the problem:
glasPng.dll is a Delphi dll with the function getPngVersion in it. Calling convention is stdCall. I want to use this dll. The code:
{-# 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 "getPngVersion" getPngDllVersion :: IO CString
main :: IO ()
main = do
s <- getPngDllVersion
putStrLn (show s)
glasPng.dll is in the Windows path (I’ve checked it).
If I compile with ghc --make testGlasPng.hs –lglasPng I get: ….\ld.exe: cannot find –lglasPng. Collect 2: ld returned 1 exit status.
Ld can’t find lglasPng (with the l in front, does it trim the l?). Why? Okay I try
ghc --make testGlasPng.hs –L<path to glasPng.dll> I get:
testGlasPng.o: fake: (.text + 0x82) :undefined reference to ‘getPngVersion@0’. I think it has found the dll, but it complains the function is not in the dll. But TDump and Dll export viewer say getPngVersion is in the dll.
I run ghc on a 64 bits computer. The dll is 32 bits. Is that the problem?
What can I do?
Kees