FFI and GHC

Manuel M T Chakravarty chak@cse.unsw.edu.au
Mon, 21 Oct 2002 11:48:08 +1000 (EST)


Hal Daume III <hdaume@ISI.EDU> wrote,

> Two things.  First, you need a module name.  So prefix your code with=

> 'module Foo where'.  Secondly, the call to ghc needs -fglasgow-exts t=
o
> pick up the necessary extensions.

For the FFI, better use -ffi (instead of the all
encompassing -fglasgow-exts) - this is, from GHC 5.04
onwards.

Manuel

> On 19 Oct 2002, [ISO-8859-1] Jo=E3o Ferreira wrote:
> =

> > Hello all,
> > =

> > I am trying to learn how to use FFI with GHC. I've tried the exampl=
e in
> > GHC's user's guide but it didn't worked. Here it is:
> > =

> > =

> > 1) The haskell code
> > =3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D
> > =

> > [bracaman@tucano hib]$ cat foo.hs
> > foreign export ccall foo :: Int -> IO Int
> > =

> > foo :: Int -> IO Int
> > foo n =3D return (length (f n))
> > =

> > f :: Int -> [Int]
> > f 0 =3D []
> > f n =3D n:(f (n-1))
> > =

> > 2) The error
> > =3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D
> > =

> > [bracaman@tucano hib]$ ghc -c foo.hs
> > foo.hs:3: Type signature given for an expression
> > [bracaman@tucano hib]$
> > =

> > =

> > I just can't understand why this is happening... can someone, pleas=
e,
> > help?
> > =

> > Thank you in advance,
> > Jo=E3o Ferreira