GHC 6.4.1 and Win32 DLLs: Bug in shutdownHaskell?

SevenThunders mattcbro at earthlink.net
Tue Oct 24 16:16:44 EDT 2006



SevenThunders wrote:
> 
> 
> I just tried it under GHC 6.6 with the same results. If the DLL is loaded
> it crashes when it's unloaded even if no Haskell code is actually
> executed.  
> 
> 

Here is the promised simple example.  This example will cause an exception
when the DLL is unloaded, but it doesn't seem to cause the run time
exception that a more complicated example might cause.  This could be
because of the very small amount of memory it actually uses.

 -------- dllNet.c -----------------------------

#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;
}

-------------------- ExternLib.hs -----------------------------------------

module ExternLib where

foreign export stdcall hinc :: Double -> Double

hinc :: Double -> Double
hinc dval = dval + 1.0

------------------------- matlabinterf.c ---------------------------------

#include <stdlib.h>
#include <string.h>
#include <assert.h>
#include <stdio.h>
#include "mex.h"

#ifndef FFI_H
#define FFI_H

typedef unsigned int HsChar;  // on 32 bit machine
typedef int HsInt;
typedef unsigned int HsWord;

typedef void *HsPtr;
typedef void (*HsFunPtr)(void);
typedef void *HsForeignPtr;
typedef void *HsStablePtr;

typedef double HsDouble ;

#define HS_BOOL_FALSE 0
#define HS_BOOL_TRUE 1
#endif // FFI_H


__declspec(dllimport) HsDouble  __stdcall hinc(HsDouble ival) ;



void mexFunction(int nlhs, mxArray *plhs[], int nrhs, const mxArray *prhs[])
{
HsDouble  *ival, *oval ;
mxArray *mret ;
/* We check the number of input and output arguments*/
if (nrhs != 1) 
  mexErrMsgTxt("Error: this needs 1 input argument") ;
ival = mxGetPr(prhs[0]) ;
/* create a 1 x 1 real matrix for the output */
mret = mxCreateDoubleMatrix(1,1, mxREAL) ;
plhs[0] = mret ;
oval = mxGetPr(plhs[0]) ;
*oval = hinc(*ival) ;

}


Here is the batch file I use to create the Haskell DLL.  It assumes MS VC
tools are in the
search path.

--------------- ghcdll.bat ----------------------------------------------
ghc -O2 -c ExternLib.hs -fglasgow-exts
ghc -c dllNet.c
ghc --mk-dll -fglasgow-exts -o interf.dll ExternLib.o ExternLib_stub.o
dllNet.o -L"." -optdll--def -optdllinterf.def 
lib /def:interf.def /MACHINE:X86



------------------ interf.def ----------------------------------------

LIBRARY    interf.dll
EXPORTS
    hinc at 8                       
    hinc = hinc at 8 


Run the following commands in Matlab to load and unload the Haskell DLL

mex matlabinterf.c interf.lib 
y = matlabinterf(0)
clear matlabinterf

Matlab will crash with an unhandled exception after calling a floating point
division operation.  It is possible to actually make it so that the haskell
code is not called at all but merely linked and thus loaded when the dll is
loaded.  The crash still occurs.  I suspect Matlab must be accessing some
kind of resource used by the DLL that is not shut down properly when the DLL
is unloaded.  However in more complicated examples Matlab will eventually
crash after multiple calls to perfectly good Haskell code, whether or not
the DLL is unloaded.  Next I will try to see if I can duplicate this outside
of a Matlab environment.



-- 
View this message in context: http://www.nabble.com/GHC-6.4.1-and-Win32-DLLs%3A-Bug-in-shutdownHaskell--tf1206938.html#a6980729
Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.



More information about the Glasgow-haskell-users mailing list