
Hello all, 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: 1) The haskell code =================== [bracaman@tucano hib]$ cat foo.hs 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)) 2) The error ============ [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, please, help? Thank you in advance, João Ferreira

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�o Ferreira wrote:
Hello all,
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:
1) The haskell code ===================
[bracaman@tucano hib]$ cat foo.hs 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))
2) The error ============
[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, please, help?
Thank you in advance, Jo�o Ferreira
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hal Daume III
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.
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ão Ferreira wrote:
Hello all,
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:
1) The haskell code ===================
[bracaman@tucano hib]$ cat foo.hs 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))
2) The error ============
[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, please, help?
Thank you in advance, João Ferreira
participants (3)
-
Hal Daume III
-
João Ferreira
-
Manuel M T Chakravarty