Extension to the FFI to allow macro expansions to be avoided

Fergus Henderson fjh at cs.mu.oz.au
Wed Apr 14 14:13:12 EDT 2004


On 08-Apr-2004, Ian Lynagh <igloo at earth.li> wrote:
> 
> The problem
> ===========
> 
> Some C libraries (curses is the one I have to hand) provide macros in
> addition to functions in some cases for efficiency reasons.

That is a feature, not a problem.  And it is not just for efficiency reasons.
Macros, enums, and other entities which exist only at the C API level
rather than the ABI level are a fundamental part of the C language which
is used in many C APIs.  Any C interface which does not provide good support
for interfacing with these entitites is IMHO not a good C interface.

> If you use the FFI to import such a function thus:
> 
> -----
> module Q where
> 
> import Foreign.Ptr (Ptr)
> import Foreign.C.Types (CInt)
> 
> foreign import ccall unsafe "static curses.h wstandend" wstandend
>     :: Ptr a -> IO CInt
> -----
> 
> Then GHC fails if not using the NCG

The documented type of wstandend() is 

       int wstandend(WINDOW *win);
        
not

       int wstandend(void *win);

So if you declare this with the Haskell type "Ptr a -> IO CInt",
in general the Haskell implementation doesn't have enough information
about the argument type to know how to call the function.
On any C implementation which uses name mangling or the equivalent,
e.g. the GNU Portable.NET C compiler that compiles to the .NET CLR,
the argument types will have a real effect on the ABI.
And as you have observed, the arguments types also have a real
effect on the C API.

> (there was some disagreement over whether such a macro was poorly
> written for not casting its argument;

I would strongly disagree with anyone who said that the macro should
cast its argument; that could hide type errors.  This macro is an
ordinary, reasonably-written C macro, and a good FFI should support
interfacing with it.


I the right way to solve this is to support some way for the Haskell
user to tell the Haskell implementation what the right type is, for example
perhaps something along the lines of

	data WINDOW

	foreign import ccall unsafe "static curses.h wstandend" wstandend
	     :: Ptr WINDOW -> IO CInt

or perhaps the above plus a new declaration to associate the Haskell name
"WINDOW" with the C type name "WINDOW":

	foreign type "curses.h WINDOW" WINDOW

Then ghc could generate C code which uses "WINDOW *" rather than "void *",
and there would be no need to use parentheses or #undef to stop the macro
being invoked.

-- 
Fergus Henderson                    |  "I have always known that the pursuit
                                    |  of excellence is a lethal habit"
WWW: <http://www.cs.mu.oz.au/~fjh>  |     -- the last words of T. S. Garp.


More information about the FFI mailing list