[Haskell-cafe] C++ interface with Haskell

Alfonso Acosta alfonso.acosta at gmail.com
Fri Apr 18 09:33:19 EDT 2008


Although you could use gcc to link the code I wouldn't recommend it
(mainly for the problems you are currently having)

SImply call GHC to compile both the C and Haskell code. It will take
care of finding the headers and supplying the necessary linker
arguments.

ghc -ffi -c   foo.hs myfoo_c.c

BTW, you don't need to compile viaC

2008/4/17 Miguel Lordelo <miguellordelo at gmail.com>:
> Well Isaac...I became now a little bit smarter then yesterday!!!
>
> I show you the example that I found and on which I´m working with.
>
> File: foo.hs
> module Foo where
>
> foreign export ccall foo :: Int -> IO Int
>
> foo :: Int -> IO Int
> foo n = return (length (f n))
>
> f :: Int -> [Int]
> f 0 = []
> f n = n:(f (n-1))
>
> To get the C wrapper you insert the following command:
> ghc -ffi -fvia-C -C foo.hs
>
>  After execution you will have these following additional files:
>
> foo.hc
> foo.hi
> foo_stub.c
> foo_stub.h
> foo_stub.o
>
> What I did next was to create a file named: myfoo_c.c, where I will call the
> foo function (implemented in Haskell).
>  (you can see this example on
> http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi-ghc.html )
> But the problem is to compile with gcc (must I put any flag or whatever set
> something)
>
> The gcc output is:
> myfoo_c.c:2:19: error: HsFFI.h: No such file or directory
>
> I downloaded this header file from: (I know that is not the correct way, but
> it was the only idea that occurs at the moment)
> http://www.koders.com/c/fidD0593B84C41CA71319BB079EFD0A2C80211C9337.aspx
>
> I compiled again and the following return error appears:
> myfoo_c.c:(.text+0x1c): undefined reference to `hs_init'
> myfoo_c.c:(.text+0x31): undefined reference to `foo'
> myfoo_c.c:(.text+0x50): undefined reference to `hs_exit'
>  collect2: ld returned 1 exit status
>
> These functions are necessary to setup GHC runtime (see:
> http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi-ghc.html )
>
> What I want to know is how to compile myfoo_c.c?! Is it with GCC or GHC?!
>
> Chears,
> Miguel Lordelo.
>
>
>
>
> On Wed, Apr 16, 2008 at 9:16 PM, Isaac Dupree <isaacdupree at charter.net>
> wrote:
>
> > perhaps
> >
> > haskell:
> > foreign export "foo_func" foo :: Int -> IO Int
> > -- I forget the rest of the syntax here
> >
> > C++:
> >
> > extern "C" {
> > int foo_func(int i);
> > }
> >
> > int some_cplusplus_function() {
> >  int bat = 3;
> >  int blah = foo_func(bat);
> >  return blah;
> > }
> >
> >
> > Is that all you need to do?
> >
> >
> > Miguel Lordelo wrote:
> >
> > >
> > >
> > >
> > > Hi all,
> > >
> > > Well...somehow I'm a beginner in Haskell. But actually my interest in
> > > Haskell will increase if it is possible to call a haskell function in
> C++.
> > > Something like GreenCard ( http://www.haskell.org/greencard/ )
> simplifying
> > > the task of interfacing Haskell programs to external libraries
> (usually).
> > > But is there also a task to interface a foreign language with Haskell,
> but
> > > calling Haskell functions. Or c2hs which is an interface generator that
> > > simplifies the development of Haskell bindings to C libraries.
> > >
> > > I want to know this, because in my company some guys are doing some
> testing
> > > with Frotran and MatLab and I want to show them the power of haskell and
> the
> > > software which we are using is implemented in C++ (there is the reason
> to
> > > make Haskel -> C++).
> > >
> > > I read somewhere that the only way for C++ calling a haskell function is
> to
> > > create a binding between Haskell and C and from C to C++, but a easy
> "Hello
> > > World" example was not there.
> > > Unfortunatelly I couldn't found anything usefull, like an complete
> example,
> > > or how to compile the code from haskell to C to C++.
> > >
> > > Can sombody help me, please :P
> > >
> > > Chears,
> > > Miguel Lordelo.
> > >
> > >
> > >
> > > ------------------------------------------------------------------------
> > >
> > >
> > > _______________________________________________
> > > Haskell-Cafe mailing list
> > > Haskell-Cafe at haskell.org
> > > http://www.haskell.org/mailman/listinfo/haskell-cafe
> > >
> >
> >
>
>
> _______________________________________________
>  Haskell-Cafe mailing list
>  Haskell-Cafe at haskell.org
>  http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


More information about the Haskell-Cafe mailing list