Foreign C with pointers
Lemmih
lemmih at gmail.com
Tue Dec 18 20:01:59 EST 2007
On Dec 19, 2007 1:06 AM, John Vogel <jpvogel1 at gmail.com> 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
More information about the Glasgow-haskell-users
mailing list