Re: Foreign C with pointers

2007-12-19 Thread Luis Cabellos
Thanks to all, that is the example that i need.
I'll test the example.zip right now.

-- 
Luis Cabellos
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Foreign C with pointers

2007-12-19 Thread Lemmih
On Dec 19, 2007 3:05 AM, John Vogel [EMAIL PROTECTED] wrote:

 
 Lol, I am surprised that the library even compiled without the return
 addr;.

 But, this definition is correct:

Well, yeah, for some value of correct. It works in this case but it
will most likely bite you if you use it in any other way.

 The other 2 definitions don't even compile.

I posted two new type-signatures and two new definitions. I'm quite
sure the right combination would work.

-- 
Cheers,
  Lemmih
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Foreign C with pointers

2007-12-18 Thread Luis Cabellos
Hi,

I am creating a binding to an existing library (lib*.a) from Haskell.

How can i bind a function that get a pointer?

e.g: I have in the c library.
int GetData( Data * d );

The steps that i need are:
1 - create the Data in Haskell
2 - create the foreign import sentence in a lib*.hs
3 - use the Data after the call

Where can i get a good tutorial about FFI? I try
http://www.haskell.org/hdirect/ffi.html but it's too general (need i pair of
examples, i think)

-- 
Thanks a lot, Luis Cabellos
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Foreign C with pointers

2007-12-18 Thread Don Stewart
zhen.sydow:
Hi,
 
I am creating a binding to an existing library (lib*.a) from Haskell.
 
How can i bind a function that get a pointer?
 
e.g: I have in the c library.
int GetData( Data * d );
 
The steps that i need are:
1 - create the Data in Haskell
2 - create the foreign import sentence in a lib*.hs
3 - use the Data after the call
 
Where can i get a good tutorial about FFI? I try
[1]http://www.haskell.org/hdirect/ffi.html but it's too general (need i
pair of examples, i think)

Say we have:

 #include string.h

 void *
 memmove(void *dst, const void *src, size_t len);

We can bind to that as:

foreign import unsafe ccall string.h memmove
c_memmove :: Ptr Word8 - Ptr Word8 - CSize - IO (Ptr Word8)

You can use Foreign.Ptr.* and Foreign.ForeignPtr (or even, say,
Data.ByteString) to get at Ptr on the Haskell side.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Foreign C with pointers

2007-12-18 Thread John Vogel
You do realize that the example you gave is just as general as all the
tutorials.

Here is an example I was working, but it gives a *segmentation fault* for
some reason:

example.h

typedef struct
{
unsigned char a;
unsigned char b;
unsigned char c;
unsigned char d;
} IP;

IP* shiftIP(IP* addr);


example.c

#include example.h

IP* shiftIP(IP* addr){
unsigned char t;
t = addr-a;
addr-a = addr-b;
addr-b = addr-c;
addr-c = addr-d;
addr-d = t;
}

Example.hsc

{-# OPTIONS -ffi -fglasgow-exts #-}
module Example where

import Foreign
import Foreign.C.Types
import Control.Monad

#include buzz.h

data MyIP = MyIP
{ a :: CUChar
, b :: CUChar
, c :: CUChar
, d :: CUChar
} deriving (Show)

instance Storable MyIP where
sizeOf _ = #{size IP} -- 4
alignment _ = alignment (undefined :: CUChar) -- 1
peek p = return MyIP
  `ap` (#{peek IP, a} p)
  `ap` (#{peek IP, b} p)
  `ap` (#{peek IP, c} p)
  `ap` (#{peek IP, d} p)
poke p ip = do
  #{poke IP, a} p $ a ip
  #{poke IP, b} p $ b ip
  #{poke IP, c} p $ c ip
  #{poke IP, d} p $ d ip

foreign import ccall safe static buzzlib.h shiftIP
shiftIP :: Ptr MyIP - Ptr MyIP

shiftMyIP :: MyIP - MyIP
shiftMyIP ip = unsafePerformIO . alloca $ \ptr - poke ptr ip  peek
(shiftIP ptr)
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Foreign C with pointers

2007-12-18 Thread Lemmih
On Dec 19, 2007 1:06 AM, John Vogel [EMAIL PROTECTED] wrote:

 You do realize that the example you gave is just as general as all the
 tutorials.

 Here is an example I was working, but it gives a segmentation fault for some
 reason:

 example.h

  typedef struct
 {
  unsigned char a;
  unsigned char b;
  unsigned char c;
  unsigned char d;
 } IP;

 IP* shiftIP(IP* addr);


 example.c

 #include example.h

 IP* shiftIP(IP* addr){
  unsigned char t;
  t = addr-a;
  addr-a = addr-b;
  addr-b = addr-c;
  addr-c = addr-d;
  addr-d = t;
 }

return addr; ?
or rather, void shiftIP.

 Example.hsc

 {-# OPTIONS -ffi -fglasgow-exts #-}
 module Example where

 import Foreign
 import Foreign.C.Types
 import Control.Monad

 #include buzz.h

 data MyIP = MyIP
  { a :: CUChar
  , b :: CUChar
  , c :: CUChar
  , d :: CUChar
  } deriving (Show)

 instance Storable MyIP where
  sizeOf _ = #{size IP} -- 4
  alignment _ = alignment (undefined :: CUChar) -- 1
  peek p = return MyIP
`ap` (#{peek IP, a} p)
`ap` (#{peek IP, b} p)
`ap` (#{peek IP, c} p)
`ap` (#{peek IP, d} p)
  poke p ip = do
#{poke IP, a} p $ a ip
#{poke IP, b} p $ b ip
#{poke IP, c} p $ c ip
#{poke IP, d} p $ d ip

 foreign import ccall safe static buzzlib.h shiftIP
  shiftIP :: Ptr MyIP - Ptr MyIP

shiftIP isn't a pure function.

shiftIP :: Ptr MyIP - IO (Ptr MyIP) or
shiftIP :: Ptr MyIP - IO ()

 shiftMyIP :: MyIP - MyIP
 shiftMyIP ip = unsafePerformIO . alloca $ \ptr - poke ptr ip  peek
 (shiftIP ptr)

shiftMyIP ip = unsafePerformIO . alloca $ \ptr - poke ptr ip  peek
= (shiftIP ptr)  or
shiftMyIP ip = unsafePerformIO . alloca $ \ptr - poke ptr ip 
shiftIP ptr  peek ptr

-- 
Cheers,
  Lemmih
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users