help with FFI: passing char* to dll function + pointer freeing
 
            Please, I just can not figure this out: I have a method in my C dll: int somemethod(char *param, int length, double array[], int UB1, int UB2, bool isValid); I would like to use this method in Haskell, so I have defined it like: {-# OPTIONS_GHC -fglasgow-exts #-} import Foreign import Foreign.C foreign import stdcall unsafe "somemethod" c_somemethod :: Ptr CString -> Int -> Ptr (Double) -> Int -> Int -> Bool -> IO Int main = do let param = ["input"] let paramLength = length param realTable = [ 1.0, 2.0, 3.0 ] :: [Double] ub1 = 0 ub2 = 2 isValid = False realTablePtr <- newArray realTable x <- c_somemethod param paramLength realTablePtr ub1 ub2 isValid free realTablePtr putStrLn $ "c_somemethod output: " ++ show x putStrLn "Done" When I try to compile this I get error regarding the param string. I have no idea how to define it. Additionally to this, is the freeing of realTablePtr correct? compile error: Couldn't match expected type `Ptr CString' with actual type `[t0]' In the first argument of `c_somemethod', namely `param' Please, how can I ix this? cheers, m.
 
            On Fri, Sep 20, 2013 at 6:53 PM, Miro Karpis 
Please, I just can not figure this out:
I have a method in my C dll: int somemethod(char *param, int length, double array[], int UB1, int UB2, bool isValid);
I would like to use this method in Haskell, so I have defined it like:
foreign import stdcall unsafe "somemethod" c_somemethod :: Ptr CString
You don't want Ptr CString. See: Prelude> :m +Foreign.C.String Prelude Foreign.C.String> :i CString type CString = GHC.Ptr.Ptr Foreign.C.Types.CChar -- Defined in `Foreign.C.String' In other words, CString is an alias for Ptr CChar. Ptr CString corresponds to (char **), not (char *). -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
 
            thanks,.. so far I came to this. I can compile it but not getting the right
values from the method. Most probably some problem with the pointers...
----------------
--int setmoduletable(char *param, int length, double array[], int UB1, int
UB2, bool isValid);
foreign import stdcall unsafe "setmoduletable"  c_setmoduletable :: Ptr
Char
                          -> Int
                          -> Ptr (Double)
                          -> Int
                          -> Int
                          -> Bool
                          -> IO Int
main = do
  let param = "Input_Bit_Nozz"
  let paramLength = length param
      realTable = [ 0.0111125, 0.0111125, 0.009525] :: [Double]
      ub1 = 0
      ub2 = 2
      isValid = False
  realTablePtr <- newArray realTable
  paramPtr <- newArray param
  x <- c_setmoduletable paramPtr paramLength realTablePtr ub1 ub2 isValid
  free realTablePtr
  free paramPtr
  putStrLn $ "c_setmoduletable output: " ++ show x
  putStrLn "Done"
On Sat, Sep 21, 2013 at 1:06 AM, Brandon Allbery 
On Fri, Sep 20, 2013 at 6:53 PM, Miro Karpis
wrote: Please, I just can not figure this out:
I have a method in my C dll: int somemethod(char *param, int length, double array[], int UB1, int UB2, bool isValid);
I would like to use this method in Haskell, so I have defined it like:
foreign import stdcall unsafe "somemethod" c_somemethod :: Ptr CString
You don't want Ptr CString. See:
Prelude> :m +Foreign.C.String Prelude Foreign.C.String> :i CString type CString = GHC.Ptr.Ptr Foreign.C.Types.CChar -- Defined in `Foreign.C.String'
In other words, CString is an alias for Ptr CChar. Ptr CString corresponds to (char **), not (char *).
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
 
            You should use the C variants of all the types, so type CBool = CInt foreign import stdcall unsafe "setmoduletable" c_setmoduletable :: CString -> CInt -> Ptr CDouble -> CInt -> CInt -> CBool -> IO CInt Edward Excerpts from Miro Karpis's message of Sat Sep 21 08:55:58 -0400 2013:
thanks,.. so far I came to this. I can compile it but not getting the right values from the method. Most probably some problem with the pointers...
---------------- --int setmoduletable(char *param, int length, double array[], int UB1, int UB2, bool isValid);
foreign import stdcall unsafe "setmoduletable" c_setmoduletable :: Ptr Char
-> Int
-> Ptr (Double)
-> Int
-> Int
-> Bool
-> IO Int
main = do let param = "Input_Bit_Nozz" let paramLength = length param realTable = [ 0.0111125, 0.0111125, 0.009525] :: [Double] ub1 = 0 ub2 = 2 isValid = False realTablePtr <- newArray realTable paramPtr <- newArray param x <- c_setmoduletable paramPtr paramLength realTablePtr ub1 ub2 isValid free realTablePtr free paramPtr putStrLn $ "c_setmoduletable output: " ++ show x putStrLn "Done"
On Sat, Sep 21, 2013 at 1:06 AM, Brandon Allbery
wrote: On Fri, Sep 20, 2013 at 6:53 PM, Miro Karpis
wrote: Please, I just can not figure this out:
I have a method in my C dll: int somemethod(char *param, int length, double array[], int UB1, int UB2, bool isValid);
I would like to use this method in Haskell, so I have defined it like:
foreign import stdcall unsafe "somemethod" c_somemethod :: Ptr CString
You don't want Ptr CString. See:
Prelude> :m +Foreign.C.String Prelude Foreign.C.String> :i CString type CString = GHC.Ptr.Ptr Foreign.C.Types.CChar -- Defined in `Foreign.C.String'
In other words, CString is an alias for Ptr CChar. Ptr CString corresponds to (char **), not (char *).
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
 
            Thanks so far, but I'm still having troubles with converting String to
CString.... The error I'm getting is:
 Couldn't match type `IO CString' with `Ptr CChar'
 Expected type: CString
   Actual type: IO CString
code:
-------
import Foreign
import Foreign.C
--int somemethod(char *param, int length, double array[], int UB1, int UB2,
bool isValid);
foreign import stdcall unsafe "setmoduletable"  c_setmoduletable ::
   CString -> CInt -> Ptr CDouble -> CInt -> CInt -> CInt -> IO CInt
main = do
  let param = newCString "someString"
  --paramLength = length param
  let realTable = [ 0.0111125, 0.0111125, 0.009525] :: [CDouble]
      ub1 = 0::CInt
      ub2 = 2::CInt
      --isValid = False
  realTablePtr <- newArray realTable
  x <- c_setmoduletable param 14 realTablePtr ub1 ub2 0
  free realTablePtr
  putStrLn $ "c_setmoduletable output: " ++ show x
  putStrLn "Done"
cheers,
m.
On Sat, Sep 21, 2013 at 4:21 PM, Edward Z. Yang 
You should use the C variants of all the types, so
type CBool = CInt foreign import stdcall unsafe "setmoduletable" c_setmoduletable :: CString -> CInt -> Ptr CDouble -> CInt -> CInt -> CBool -> IO CInt
Edward
Excerpts from Miro Karpis's message of Sat Sep 21 08:55:58 -0400 2013:
thanks,.. so far I came to this. I can compile it but not getting the right values from the method. Most probably some problem with the pointers...
---------------- --int setmoduletable(char *param, int length, double array[], int UB1, int UB2, bool isValid);
foreign import stdcall unsafe "setmoduletable" c_setmoduletable :: Ptr Char
-> Int
-> Ptr (Double)
-> Int
-> Int
-> Bool
-> IO Int
main = do let param = "someString" let paramLength = length param realTable = [ 0.0111125, 0.0111125, 0.009525] :: [Double] ub1 = 0 ub2 = 2 isValid = False realTablePtr <- newArray realTable paramPtr <- newArray param x <- c_setmoduletable paramPtr paramLength realTablePtr ub1 ub2 isValid free realTablePtr free paramPtr putStrLn $ "c_setmoduletable output: " ++ show x putStrLn "Done"
On Sat, Sep 21, 2013 at 1:06 AM, Brandon Allbery
On Fri, Sep 20, 2013 at 6:53 PM, Miro Karpis < miroslav.karpis@gmail.com>wrote:
Please, I just can not figure this out:
I have a method in my C dll: int somemethod(char *param, int length, double array[], int UB1, int UB2, bool isValid);
I would like to use this method in Haskell, so I have defined it like:
foreign import stdcall unsafe "somemethod" c_somemethod :: Ptr CString
You don't want Ptr CString. See:
Prelude> :m +Foreign.C.String Prelude Foreign.C.String> :i CString type CString = GHC.Ptr.Ptr Foreign.C.Types.CChar -- Defined in `Foreign.C.String'
In other words, CString is an alias for Ptr CChar. Ptr CString corresponds to (char **), not (char *).
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
 
            On Sat, Sep 21, 2013 at 3:25 PM, Miro Karpis 
Thanks so far, but I'm still having troubles with converting String to CString.... The error I'm getting is:
Couldn't match type `IO CString' with `Ptr CChar' Expected type: CString Actual type: IO CString
(...)
let param = newCString "someString"
Don't use let there; newCString is in IO. param <- newCString "someString" -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
 
            Hello Miro, The immediate problem is that you need to use the bind notation (param <- newCString "foo") rather than let notation, but if the string will not be used beyond the function call, it is preferable to use withCString Edward Excerpts from Miro Karpis's message of Sat Sep 21 15:25:58 -0400 2013:
Thanks so far, but I'm still having troubles with converting String to CString.... The error I'm getting is:
Couldn't match type `IO CString' with `Ptr CChar' Expected type: CString Actual type: IO CString
code:
------- import Foreign import Foreign.C
--int somemethod(char *param, int length, double array[], int UB1, int UB2, bool isValid); foreign import stdcall unsafe "setmoduletable" c_setmoduletable :: CString -> CInt -> Ptr CDouble -> CInt -> CInt -> CInt -> IO CInt
main = do let param = newCString "someString" --paramLength = length param let realTable = [ 0.0111125, 0.0111125, 0.009525] :: [CDouble] ub1 = 0::CInt ub2 = 2::CInt --isValid = False realTablePtr <- newArray realTable x <- c_setmoduletable param 14 realTablePtr ub1 ub2 0 free realTablePtr putStrLn $ "c_setmoduletable output: " ++ show x putStrLn "Done"
cheers, m.
On Sat, Sep 21, 2013 at 4:21 PM, Edward Z. Yang
wrote: You should use the C variants of all the types, so
type CBool = CInt foreign import stdcall unsafe "setmoduletable" c_setmoduletable :: CString -> CInt -> Ptr CDouble -> CInt -> CInt -> CBool -> IO CInt
Edward
Excerpts from Miro Karpis's message of Sat Sep 21 08:55:58 -0400 2013:
thanks,.. so far I came to this. I can compile it but not getting the right values from the method. Most probably some problem with the pointers...
---------------- --int setmoduletable(char *param, int length, double array[], int UB1, int UB2, bool isValid);
foreign import stdcall unsafe "setmoduletable" c_setmoduletable :: Ptr Char
-> Int
-> Ptr (Double)
-> Int
-> Int
-> Bool
-> IO Int
main = do let param = "someString" let paramLength = length param realTable = [ 0.0111125, 0.0111125, 0.009525] :: [Double] ub1 = 0 ub2 = 2 isValid = False realTablePtr <- newArray realTable paramPtr <- newArray param x <- c_setmoduletable paramPtr paramLength realTablePtr ub1 ub2 isValid free realTablePtr free paramPtr putStrLn $ "c_setmoduletable output: " ++ show x putStrLn "Done"
On Sat, Sep 21, 2013 at 1:06 AM, Brandon Allbery
On Fri, Sep 20, 2013 at 6:53 PM, Miro Karpis < miroslav.karpis@gmail.com>wrote:
Please, I just can not figure this out:
I have a method in my C dll: int somemethod(char *param, int length, double array[], int UB1, int UB2, bool isValid);
I would like to use this method in Haskell, so I have defined it like:
foreign import stdcall unsafe "somemethod" c_somemethod :: Ptr CString
You don't want Ptr CString. See:
Prelude> :m +Foreign.C.String Prelude Foreign.C.String> :i CString type CString = GHC.Ptr.Ptr Foreign.C.Types.CChar -- Defined in `Foreign.C.String'
In other words, CString is an alias for Ptr CChar. Ptr CString corresponds to (char **), not (char *).
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
 
            yes, that solved it. millions of thanks everybody ;-)
m.
On Sat, Sep 21, 2013 at 10:10 PM, Edward Z. Yang 
Hello Miro,
The immediate problem is that you need to use the bind notation (param <- newCString "foo") rather than let notation, but if the string will not be used beyond the function call, it is preferable to use withCString
Edward
Thanks so far, but I'm still having troubles with converting String to CString.... The error I'm getting is:
Couldn't match type `IO CString' with `Ptr CChar' Expected type: CString Actual type: IO CString
code:
------- import Foreign import Foreign.C
--int somemethod(char *param, int length, double array[], int UB1, int UB2, bool isValid); foreign import stdcall unsafe "setmoduletable" c_setmoduletable :: CString -> CInt -> Ptr CDouble -> CInt -> CInt -> CInt -> IO CInt
main = do let param = newCString "someString" --paramLength = length param let realTable = [ 0.0111125, 0.0111125, 0.009525] :: [CDouble] ub1 = 0::CInt ub2 = 2::CInt --isValid = False realTablePtr <- newArray realTable x <- c_setmoduletable param 14 realTablePtr ub1 ub2 0 free realTablePtr putStrLn $ "c_setmoduletable output: " ++ show x putStrLn "Done"
cheers, m.
On Sat, Sep 21, 2013 at 4:21 PM, Edward Z. Yang
wrote: You should use the C variants of all the types, so
type CBool = CInt foreign import stdcall unsafe "setmoduletable" c_setmoduletable :: CString -> CInt -> Ptr CDouble -> CInt -> CInt -> CBool -> IO CInt
Edward
Excerpts from Miro Karpis's message of Sat Sep 21 08:55:58 -0400 2013:
thanks,.. so far I came to this. I can compile it but not getting the right values from the method. Most probably some problem with the
---------------- --int setmoduletable(char *param, int length, double array[], int
UB1, int
UB2, bool isValid);
foreign import stdcall unsafe "setmoduletable" c_setmoduletable :: Ptr Char
-> Int
-> Ptr (Double)
-> Int
-> Int
-> Bool
-> IO Int
main = do let param = "someString" let paramLength = length param realTable = [ 0.0111125, 0.0111125, 0.009525] :: [Double] ub1 = 0 ub2 = 2 isValid = False realTablePtr <- newArray realTable paramPtr <- newArray param x <- c_setmoduletable paramPtr paramLength realTablePtr ub1 ub2 isValid free realTablePtr free paramPtr putStrLn $ "c_setmoduletable output: " ++ show x putStrLn "Done"
On Sat, Sep 21, 2013 at 1:06 AM, Brandon Allbery < allbery.b@gmail.com wrote:
On Fri, Sep 20, 2013 at 6:53 PM, Miro Karpis < miroslav.karpis@gmail.com>wrote:
Please, I just can not figure this out:
I have a method in my C dll: int somemethod(char *param, int length, double array[], int UB1, int UB2, bool isValid);
I would like to use this method in Haskell, so I have defined it
Excerpts from Miro Karpis's message of Sat Sep 21 15:25:58 -0400 2013: pointers... like:
foreign import stdcall unsafe "somemethod" c_somemethod :: Ptr
CString
You don't want Ptr CString. See:
Prelude> :m +Foreign.C.String Prelude Foreign.C.String> :i CString type CString = GHC.Ptr.Ptr Foreign.C.Types.CChar -- Defined in `Foreign.C.String'
In other words, CString is an alias for Ptr CChar. Ptr CString corresponds to (char **), not (char *).
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
participants (3)
- 
                 Brandon Allbery Brandon Allbery
- 
                 Edward Z. Yang Edward Z. Yang
- 
                 Miro Karpis Miro Karpis