Hi Duncan and Brandon,

     I am  moving to the ForeignPtr strategy. However, I always try to learn from where I am before going to a new approach. I have discovered by debugging that the AIOCB peek is working; however, passing the "peeked" AIOCB back to the caller(i.e. the test program) is not working .. please let me try to demonstrate below. I have been staring at my Haskell code many, many times .... sigh ...


0)


IN PEEK CODE .. aioErrorCode => 115
IN PEEK CODE .. aioReturnValue => 0
aioWrite after aio_write
IN PEEK CODE .. aioErrorCode => 115
IN PEEK CODE .. aioReturnValue => 0
*************aiocb dump***************
fd => 3
opcode => 1
prio => 0
offset => 0
nbytes => 20
next => 0x00000000
absprio => 0
policy => 0
errocode => 115      <<<< correct ... INPROGRESS errno
return value => 0

<<<<<<<<<<<<<<<<<<<<    return from call of Haskell function aioWrite here ... below "errocode" has changed from 115 to 0 ... somehow my "return AIOCB" is corrupting the "state"/value of AIOCB ....

*****************aioWrite dumpAIOCB
*************aiocb dump***************
fd => 3
opcode => 0
prio => 0
offset => 0
nbytes => 20
next => 0x00000000
absprio => 0
policy => 0
errocode => 0                         <<<< incorrect "Errno" ... should still be IN PROGRESS.
return value => 0

1) aioWrite ... the function marshalling(poke) and unmarshalling(peek) an AIOCB:


aioWrite :: AIOCB -> IO AIOCB
aioWrite aiocb = do
   allocaBytes (#const sizeof(struct aiocb)) $ \ p_aiocb -> do
      poke p_aiocb aiocb

      putStrLn "aioWrite before aio_write"
      aiocb1 <- peek p_aiocb
      dumpAIOCB aiocb1

      throwErrnoIfMinus1 "aioWrite" (c_aio_write  p_aiocb)
      aiocb <- peek p_aiocb

      putStrLn "aioWrite after aio_write"
      aiocb <- peek p_aiocb
      dumpAIOCB aiocb

--      putStrLn "aioWrite after aio_write"
--      aiocb1 <- peek p_aiocb
--      dumpAIOCB aiocb1

      return (aiocb)

foreign import ccall safe "aio.h aio_write"
    c_aio_write :: Ptr AIOCB -> IO CInt


2) an AIOCB:

data LioOps = LioRead | LioWrite | LioNop


data AIOCB = AIOCB {

        aioFd :: Fd,

        aioLioOpcode :: Int,

        aioReqPrio :: Int,

        aioOffset :: FileOffset,

        aioBuf :: Ptr Word8,

        aioBytes :: ByteCount,

        aioSigevent :: Sigevent,


        -- Internal members

        aioNext :: Ptr AIOCB,

        aioAbsPrio :: Int,

        aioPolicy :: Int,

        aioErrorCode :: Int,

        aioReturnValue :: ByteCount
}


3) poke/peek

instance Storable AIOCB where

    sizeOf _ = (#const sizeof (struct aiocb))

    alignment _ = 1

    poke p_AIOCB (AIOCB aioFd aioLioOpcode aioReqPrio aioOffset aioBuf aioBytes aioSigevent aioNext aioAbsPrio aioPolicy aioErrorCode aioReturnValue) = do

       (#poke struct aiocb, aio_fildes) p_AIOCB aioFd

       (#poke struct aiocb, aio_lio_opcode) p_AIOCB aioLioOpcode

       (#poke struct aiocb, aio_reqprio) p_AIOCB aioReqPrio

       (#poke struct aiocb, aio_offset) p_AIOCB aioOffset

       (#poke struct aiocb, aio_buf) p_AIOCB aioBuf

       (#poke struct aiocb, aio_nbytes) p_AIOCB aioBytes

       (#poke struct aiocb, aio_sigevent) p_AIOCB aioSigevent

       (#poke struct aiocb, __next_prio) p_AIOCB aioNext

       (#poke struct aiocb, __abs_prio) p_AIOCB aioAbsPrio

       (#poke struct aiocb, __policy) p_AIOCB aioPolicy

       (#poke struct aiocb, __error_code) p_AIOCB aioErrorCode

       (#poke struct aiocb, __return_value) p_AIOCB aioReturnValue



    peek p_AIOCB = do

       aioFd <- (#peek struct aiocb, aio_fildes) p_AIOCB

       aioLioOpcode <- (#peek struct aiocb, aio_lio_opcode) p_AIOCB

       aioReqPrio <- (#peek struct aiocb, aio_reqprio) p_AIOCB

       aioOffset <- (#peek struct aiocb, aio_offset) p_AIOCB

       aioBuf <- (#peek struct aiocb, aio_buf) p_AIOCB

       aioBytes <- (#peek struct aiocb, aio_nbytes) p_AIOCB

       aioSigevent <- (#peek struct aiocb, aio_sigevent) p_AIOCB

       aioNext <- (#peek struct aiocb, __next_prio) p_AIOCB

       aioAbsPrio <- (#peek struct aiocb, __abs_prio) p_AIOCB

       aioPolicy <- (#peek struct aiocb, __policy) p_AIOCB

       aioErrorCode <- (#peek struct aiocb, __error_code) p_AIOCB
       putStrLn ("IN PEEK CODE .. aioErrorCode => " ++ (show aioErrorCode))

       aioReturnValue <- (#peek struct aiocb, __return_value) p_AIOCB
       putStrLn ("IN PEEK CODE .. aioReturnValue => " ++ (show aioReturnValue))

       return (AIOCB aioFd aioLioOpcode aioReqPrio aioOffset aioBuf aioBytes aioSigevent aioNext aioAbsPrio aioPolicy aioErrorCode aioReturnValue)

Kind regards, Vasili






On Sun, Jul 20, 2008 at 6:51 AM, Duncan Coutts <duncan.coutts@worc.ox.ac.uk> wrote:

On Sat, 2008-07-19 at 23:55 -0500, Galchin, Vasili wrote:
> yes Duncan I am trying to pass-by-value. I am familiar with
> ForeignPtr; however, I don't comprehend what you and Brandon are
> suggesting to do. Could either of you provide a code illustration or
> point at existing code to illustrate your approach?

Take a look at John Meacham's RSA example.

So at the moment you're using using Storable and a Haskell record, say:

data AIOCB = AIOCB {
   ...
 }

and we're suggesting instead:

newtype AIOCB = AIOCB (ForeignPtr AIOCB)

then to access a member use hsc2hs:

getBlah :: AIOCB -> IO Blah
getBlah (AIOCB fptr) =
 withForeignPtr fptr $ \ptr -> {# peek aiocb,blah #} ptr

So you only access the parts you need and keep the aiocb C struct
allocated on the heap (use mallocForeignPtr).

Duncan