> but it works only for Ptrs, not for ForeignObjs! There is no good way
> to peek ForeignObj contents from Haskell. It would be nice to avoid
> C wrappers in such cases.

Well, there's readXXXOffForeignObj and friends.  We need a way to
incorporate ForeignObjs into the Storable framework.  A first attempt is the
code below, but it seems like overkill (and doesn't work because there's no
equivalent of plusAddr for ForeignObj, but we could probably work around
this).

class Address a where
   ptrPlus :: a -> Int -> a
   pokeInt :: a -> Int -> Int -> IO ()
   peekInt :: a -> Int        -> IO Int
   ...

instance Address Addr where
   ptrPlus a i = a `plusAddr` fromIntegral i
   pokeInt = writeIntOffAddr
   peekInt = readIntOffAddr
   ...

instance Address ForeignObj where
   ptrPlus a i = a `plusFO` fromIntegral i  -- can't do this
   pokeInt = writeIntOffForeignObj
   peekInt = readIntOffForeignObj
   ...

class Storable a where

   -- sizeOf/alignment *never* use their first argument
   sizeOf      :: a -> Int
   alignment   :: a -> Int

   -- replacement for read-/write???OffAddr
   peekElemOff :: Address p => p -> Int          -> IO a
   pokeElemOff :: Address p => p -> Int     -> a -> IO ()

   -- the same with *byte* offsets
   peekByteOff :: Address p => p -> AddrOff      -> IO a
   pokeByteOff :: Address p => p -> AddrOff -> a -> IO ()

   -- ... and with no offsets at all
   peek        :: Address p => p      -> IO a
   poke        :: Address p => p -> a -> IO ()


instance Storable Int where
   peekElemOff = peekInt
   pokeElemOff = pokeInt
   ...

> What should we do?

I don't know :)

> Maybe there should be an operation that prevents an object from
> being freed for some time, as if using StablePtr, with an interface
> similar to
>     hold :: a -> IO b -> IO b
> implemented such that in most common uses (where the action is
> simple and inlined) a compiler can determine that physical locking is
> really unnecessary because GC cannot happen? It would allow efficient
> definitions of ForeignObj operations in terms of Ptr operations.

You could certainly do this, but I'm not sure how it would help.  It would
let you write readXXXOffForeignObj safely in Haskell, but this still has to
be incorporated into Storable somehow.

Cheers,
        Simon

Reply via email to