[Template-haskell] Calling foreign functions in a splice doesn't work

André Pang andrep@cse.unsw.edu.au
Tue, 13 May 2003 01:14:11 +1000


Hi all,

I've been trying to call a foreign function (i.e. via the FFI) inside a 
splice, which doesn't seem to work.

As an example, I'll attach a small program which does work, and then 
modify it so it doesn't work.  So, here's a program which does work:

Splicer.hs:

> module Main where
>
> import Templates
>
> main :: IO ()
> main = do
>    putStrLn (show ($(doubleWrapper) 5))

Templates.hs:

> module Templates where
>
> import Language.Haskell.THSyntax
>
> doubleWrapper :: Expr
> doubleWrapper = [| \x -> myDouble x |]
>
> myDouble :: Int -> Int
> myDouble x = x * 2

Pretty simple: the program splices in an Expr named doubleWrapper; 
doubleWrapper in turn calls myDouble, which is a simple function of 
type Int -> Int.  Execution:

> 20:10 ~/th/ffi-bug % ghc -fglasgow-exts --make Splicer.hs
> ...
> 20:10 ~/th/ffi-bug % ./a.out
> 10

So that works.

Here's a version of the program which modifies the 'myDouble' function 
so that it's now a foreign C function rather than a Haskell function.  
(Note that the main function and doubleWrapper functions are exactly 
the same):

SplicerFFI.hs:

> module Main where
>
> import TemplatesFFI
>
> main :: IO ()
> main = do
>    putStrLn (show ($(doubleWrapper) 5))

TemplatesFFI.hs:

> module TemplatesFFI where
>
> import Language.Haskell.THSyntax
>
> doubleWrapper :: Expr
> doubleWrapper = [| \x -> myDouble x |]
>
> foreign import ccall safe "c_double.h myDouble"
>   myDouble :: Int -> Int

c_double.h:

> int myDouble (int x);

c_double.c:

> int myDouble (int x)
> {
>    return x * 2;
> }

Compiling the FFI version of this small program doesn't work:

> 20:20 ~/th/ffi-bug % gcc -c c_double.c
> 20:20 ~/th/ffi-bug % ghc -fglasgow-exts --make c_double.o 
> SplicerFFI.hs c_double.o
> Chasing modules from: SplicerFFI.hs
> Compiling TemplatesFFI     ( TemplatesFFI.hs, ./TemplatesFFI.o )
> Compiling Main             ( SplicerFFI.hs, ./SplicerFFI.o )
> Loading package base ... linking ... done.
> Loading package haskell98 ... linking ... done.
> Loading package haskell-src ... linking ... done.
>
> TemplatesFFI.o: unknown symbol `_myDouble'
>
> SplicerFFI.hs:7:
>     Exception when trying to run compile-time code:
>         Code: doubleWrapper
>         Exn:
>     In the first argument of `show', namely
>         `($[splice]doubleWrapper 5)'
>     In the first argument of `putStrLn', namely
>         `(show ($[splice]doubleWrapper 5))'
>     In the result of a 'do' expression:
>         putStrLn (show ($[splice]doubleWrapper 5))

I suspect the compilation isn't working because the 'myDouble' symbol 
in c_double.o isn't being loaded _at splice time_ into the list of 
symbols that GHC knows about -- which is also why the exception occurs. 
  I've tried all sorts of kludges to convince GHC to load the symbol 
from the foreign object file, like doing "ar rcs libcdouble.a 
c_double.o" and then putting -L. -lcdouble on the commandline, passing 
additional linker/compiler flags with -optl and -optc, etc, and none of 
them have worked so far.

This was tested with GHC on Mac OS X built from CVS 9 March 2003; my 
apologies for a fairly out-of-date GHC build, but I'm having trouble 
building the recent GHCs on Mac OS X.  Can somebody verify that this 
also occurs on Linux with a recent build of GHC, and hopefully fix it 
or give me a clue on where to start looking for the bug?

Thanks very much!


-- 
% Andre Pang : just.your.average.bounty.hunter