FFI and GHC
Hal Daume III
hdaume@ISI.EDU
Sat, 19 Oct 2002 12:55:45 -0700 (PDT)
Two things. First, you need a module name. So prefix your code with
'module Foo where'. Secondly, the call to ghc needs -fglasgow-exts to
pick up the necessary extensions.
--
Hal Daume III
"Computer science is no more about computers | hdaume@isi.edu
than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
On 19 Oct 2002, [ISO-8859-1] Jo=E3o Ferreira wrote:
> Hello all,
>=20
> I am trying to learn how to use FFI with GHC. I've tried the example in
> GHC's user's guide but it didn't worked. Here it is:
>=20
>=20
> 1) The haskell code
> =3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D
>=20
> [bracaman@tucano hib]$ cat foo.hs
> foreign export ccall foo :: Int -> IO Int
>=20
> foo :: Int -> IO Int
> foo n =3D return (length (f n))
>=20
> f :: Int -> [Int]
> f 0 =3D []
> f n =3D n:(f (n-1))
>=20
> 2) The error
> =3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D
>=20
> [bracaman@tucano hib]$ ghc -c foo.hs
> foo.hs:3: Type signature given for an expression
> [bracaman@tucano hib]$
>=20
>=20
> I just can't understand why this is happening... can someone, please,
> help?
>=20
> Thank you in advance,
> Jo=E3o Ferreira
>=20
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>=20