[Haskell-cafe] Creating DLLs with GHC

SevenThunders mattcbro at earthlink.net
Wed Sep 27 22:43:51 EDT 2006




SevenThunders wrote:
> 
> I am having some difficulty with creating a dynamic link library using 
> GHC on windows XP.
> 
> 


I need to report some additional strange DLL behavior with ghc.exe
unfortunately.

Although I solved my linking problems and was able to create a .dll and a MS
VC .lib file using  a .def file.
I get a nasty run time error when my program exits.  

Here is a snippet of the  Haskell code:
module ExternLib where

...
import Foreign.C.String
import Foreign.Ptr
import Foreign.C.Types (CInt, CDouble )
import Foreign.Marshal.Array
import Foreign.Storable

foreign export stdcall initNetChan :: CString -> Ptr CInt -> IO ()


-- | initialize network parameters and return an integer array containing
-- indices to the uplink channel, downlink channel
initNetChan :: CString -> Ptr CInt -> IO()
initNetChan simstring cptr = do

-- some processing 
...

	let hup = mkCInt $ hupchan netop
	let hdn = mkCInt $ hdnchan netop
	print $ "hup = " ++ (show hup)
	print $ "hdn = " ++ (show hdn)
	-- write results to the output array
	pokeElemOff cptr 0 hup
	pokeElemOff cptr 1 hdn
	peekElemOff cptr 0 >>= print

Here is the C code that calls it, (test.c)

#include <stdio.h>

extern void initNetChan(char *str, int *iout) ;

int zout[64] ;


int main(int argc, char *argv[])
{
printf("Starting initNetChan\n") ;
initNetChan("SimPrams.in", zout) ;
printf("Done initNetChan.  out: %p\n", zout) ;
printf("out[0] = %d out[1] = %d\n", zout[0], zout[1]) ;
printf("Done") ;
return(1) ;
}


The dll itself uses this template taken from the GHC manual on DLLs
#include <windows.h>
#include <Rts.h>

extern void __stginit_ExternLib(void);

static char* args[] = { "ghcDll", NULL };
                       /* N.B. argv arrays must end with NULL */
BOOL
STDCALL
DllMain
   ( HANDLE hModule
   , DWORD reason
   , void* reserved
   )
{
  if (reason == DLL_PROCESS_ATTACH) {
      /* By now, the RTS DLL should have been hoisted in, but we need to
start it up. */
      startupHaskell(1, args, __stginit_ExternLib);
      return TRUE;
  }
  return TRUE;
}


I link test.c to my dll via a call
cl.exe test.c netsim.lib

Running test.exe yields
Starting initNetChan
"hup = 26"
"hdn = 30"
26
Done initNetChan.  out: 00408960
out[0] = 26 out[1] = 30
Done
D:\Projects\BRPhoenix\NetworkSim\FastSim>test.exe
Starting initNetChan
"hup = 26"
"hdn = 30"
26
Done initNetChan.  out: 00408960
out[0] = 26 out[1] = 30
Done

which is correct, but then the code crashes with a run time error.  It is an
unhandled exception: access violation.
Is it possible that the Haskell code needs to do some kind of finalization
process before terminating?
I haven't seen the documentation for it yet.  Hopefully it's just something
stupid I've done, but again I am baffled.


-- 
View this message in context: http://www.nabble.com/Creating-DLLs-with-GHC-tf2342692.html#a6539263
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.



More information about the Haskell-Cafe mailing list