[Haskell-beginners] FFI and Cabal

Jeffrey Drake iaefai at me.com
Mon Nov 23 02:35:00 EST 2009


I am trying to use FFI to access some windows console functions via two simple C functions I created.

Essentially my module looks like is this: 

{-# CFILES mouse.c #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Mouse where 
-- import Foreign
import Foreign.C.Types


foreign import ccall unsafe "mouse.h SetupConsole" c_setupConsole :: IO CInt
foreign import ccall unsafe "mouse.h MouseEvent" c_mouseEvent :: IO CInt

setupConsole :: IO Bool
setupConsole = do   c <- c_setupConsole
                    return $ if c == 0
                        then True
                        else False

mouseEvent :: IO (Maybe (Int, Int))
mouseEvent = do	c <- c_mouseEvent
                let d = toInteger c
                let e = (fromInteger d)::Int
                
                return $ if e < 0
                    then Nothing
                    else Just (e `mod` 256, e `div` 256)


It seems to compile fine. The problem comes when I need to link.
Linking dist\build\BoardGames\BoardGames.exe ...
dist\build\BoardGames\BoardGames-tmp\Mouse.o:fake:(.text+0x15): undefined reference to `SetupConsole'
dist\build\BoardGames\BoardGames-tmp\Mouse.o:fake:(.text+0x11d): undefined reference to `MouseEvent'
collect2: ld returned 1 exit status

The problem seems obvious - it isn't compiling OR linking mouse.c which is this:

#include <windows.h>

int SetupConsole()
{
    HANDLE hStdin; 
    DWORD fdwMode, fdwSaveOldMode; 
    int counter=0;
 
    
    hStdin = GetStdHandle(((DWORD)-10)); 
    if (hStdin == ((HANDLE)(LONG_PTR)-1)) 
        return -3; 
 
    
 
    if (! GetConsoleMode(hStdin, &fdwSaveOldMode) ) 
        return -2;
 
    
 
    fdwMode = 0x0010; 
    if (! SetConsoleMode(hStdin, fdwMode) ) 
        return -1;
	return 0;
}

int MouseEvent()
{
	HANDLE hStdin;
	INPUT_RECORD irInBuf[128];
	short x, y;
	unsigned i;
	DWORD cNumRead;

	static int ignoreNext = 0;


	hStdin = GetStdHandle(((DWORD)-10)); 
    if (hStdin == ((HANDLE)(LONG_PTR)-1)) 
		return -2;

	if (!ReadConsoleInputW( 
              hStdin,      
                irInBuf,     
                128,         
                &cNumRead) ) 
            return -1;

   for (i = 0; i < cNumRead; i++) 
        {
			if (irInBuf[i].EventType == 0x0002 && irInBuf[i].Event.MouseEvent.dwEventFlags == 0)
			{
				if (ignoreNext == 1)
				{
					ignoreNext = 0;
					return -1;
				}
				x = irInBuf[i].Event.MouseEvent.dwMousePosition.X;
				y = irInBuf[i].Event.MouseEvent.dwMousePosition.Y;

				ignoreNext = 1;

				return x + (y << 8);
			}
			else
			{
				continue;
			}
   }
   return -1;
}

So far, I have only tested this with MSVC (it works), but not with haskell platform's mingw (which includes windows.h - so I would have to wait for this...)

In my cabal file I have:
 c-sources:		mouse.c

So that basically sums up what I have, I just don't know how to do this. The cabal documentation says for this directive:

c-sources: filename list
A list of C source files to be compiled and linked with the Haskell files.

Which is what I expected it to do - but to no avail.

I should note that when I try to comment out with -- the c-sources line I get this:

Linking dist\build\BoardGames\BoardGames.exe ...
dist\build\BoardGames\BoardGames-tmp\Main.o:fake:(.text+0x27d): undefined reference to `__stginit_Mouse_'
dist\build\BoardGames\BoardGames-tmp\Main.o:fake:(.text+0xb4): undefined reference to `Mouse_a1_info'
dist\build\BoardGames\BoardGames-tmp\Main.o:fake:(.text+0xcc): undefined reference to `Mouse_czusetupConsole_info'
dist\build\BoardGames\BoardGames-tmp\Main.o:fake:(.text+0xf8): undefined reference to `Mouse_a1_info'
dist\build\BoardGames\BoardGames-tmp\Main.o:fake:(.text+0x17a): undefined reference to `Mouse_czusetupConsole_info'
dist\build\BoardGames\BoardGames-tmp\Main.o:fake:(.data+0x14): undefined reference to `Mouse_a1_closure'
collect2: ld returned 1 exit status


Any help that can be offered would be appreciated.

I would tell you where to find the project, but patch-tag is being unavailable for me at this time. It is the 'BoardGames' project, under iaefai.

Thank you again,
iaefai.


More information about the Beginners mailing list