[Haskell-cafe] Trouble with [in,string]char* with hdirect
Vincenzo aka Nick Name
vincenzo_mlRE.MOVE at yahoo.it
Wed Mar 3 03:04:43 EST 2004
Hi all,
I am experimenting with hdirect for the first time, and I can't figure
out how to call an haskell function of type String -> IO Int from C. I
already can compile and use a function of type Char -> IO Int, so I
assume to be using the right command line arguments.
I have, in Math.idl
----
module Math {
int munlink([in,string]char *s);
};
----
in Math.hs
----
module Math where
munlink :: String -> IO Int
munlink s = putStr ("Hey!" ++ s ++ "\n") >> return (-1)
----
This is the generated .hs file:
module MathProxy where
import Prelude (fromEnum, toEnum)
import qualified Prelude
import qualified Foreign.Ptr (Ptr)
import qualified HDirect (unmarshallString)
import qualified Math (munlink)
munlink_proxy :: Prelude.String
-> Prelude.IO Prelude.Int
munlink_proxy = wrap_munlink Math.munlink
foreign export ccall "munlink" munlink_proxy :: Foreign.Ptr.Ptr
Prelude.String -> Prelude.IO Prelude.Int
wrap_munlink :: (Prelude.String -> Prelude.IO Prelude.Int)
-> Foreign.Ptr.Ptr Prelude.String
-> Prelude.IO Prelude.Int
wrap_munlink munlink_meth s =
do
s <- HDirect.unmarshallString s
munlink_meth s
I get a type error when compiling MathProxy.hs, and the strange thing is
that commenting out the type declaration for "munlink_proxy" makes my
program work like a charm.
Errors from the compiler follow, any help will be highly appreciated.
Vincenzo Ciancia
ghc -O2 -fglasgow-exts Math.hs -c
ihc -fshow-idl-in-comments -s -fhs-to-c --gen-headers
-fuse-ints-everywhere -c Math.idl
ghc -O2 -c main.c -o main.o
ghc -O2 -fglasgow-exts -package hdirect MathProxy.hs -c
MathProxy.hs:15:
Couldn't match
`GHC.Ptr.Ptr GHC.Base.String' against `GHC.Base.String'
Expected type: GHC.Base.String -> GHC.IOBase.IO GHC.Base.Int
Inferred type: GHC.Ptr.Ptr GHC.Base.String
-> GHC.IOBase.IO GHC.Base.Int
In the application `wrap_munlink Math.munlink'
In the definition of `munlink_proxy':
munlink_proxy = wrap_munlink Math.munlink
MathProxy.hs:17:
Couldn't match
`GHC.Base.String' against `GHC.Ptr.Ptr GHC.Base.String'
Expected type: GHC.Ptr.Ptr GHC.Base.String
-> GHC.IOBase.IO GHC.Base.Int
Inferred type: GHC.Base.String -> GHC.IOBase.IO GHC.Base.Int
When checking declaration:
foreign export ccall "munlink" munlink_proxy :: GHC.Ptr.Ptr
GHC.Base.String
-> GHC.IOBase.IO
GHC.Base.Int
More information about the Haskell-Cafe
mailing list