Proposal #2: marshalling utilites

Simon Marlow simonmar at microsoft.com
Fri Dec 1 08:56:33 EST 2000


The C strings stuff is still up in the air, so I'll leave that for the
time being.

The main concern as far as adding functionality to the marshalling
libraries seems to be the need to separate the compiler-dependent
primitives from the rest of the library.  With that in mind, I'll
propose the following changes:

	* Deprecate everything in Storable except the class itself 
	  and its instances.

      * Add the Marshal module below (the names are of course all
        up for discussion, including the name of the module itself).

The implementation of Marshal is compiler independent, except there's a
requirement for a way to convert an errno value into an IOError.  As
noted below, perhaps the error processing, or at least the
compiler-dependent portion, should be farmed off into another module.

I omitted some of the generic utilities from Marcin's proposal, since
while obviously useful they don't seem to belong here.

Note that this isn't supposed to be the "higher-level marshalling
library" we've been talking about, it's just s small step from what we
have now, but an important step in that it puts the FFI into a usable
state (at least for interfacing to C libraries, modulo the C strings
support).  That's important for us in the GHC team at least because it
means we can start using this in  GHC's libraries.

My take on the C strings stuff: we can, and should, provide a
portable-ish implementation of poke/peekCString which uses a
(fictitious?) conversion library to do the character conversions, and
uses standard marshalling to get to/from [CChar].  The point is that
we'll probably need to optimise this at least in GHC, both to avoid
writing our own conversion code and to speed things up, so it makes
sense to place it all behind a specialised set of C string marshalling
calls.

Cheers,
	Simon

  module Marshal (

 
------------------------------------------------------------------------
    -- Allocation, deallocation and marshalling for objects and arrays

    malloc,       -- :: Storable a =>        IO (Ptr a)
    mallocArray,  -- :: Storable a => Int -> IO (Ptr a)
    mallocBytes,  -- ::               Int -> IO (Ptr a)

    alloca,       -- :: Storable a =>        (Ptr a -> IO b) -> IO b
    allocaArray,  -- :: Storable a => Int -> (Ptr a -> IO b) -> IO b
    allocaBytes,  -- ::               Int -> (Ptr a -> IO b) -> IO b

    reallocArray, -- :: Storable a => Ptr a -> Int -> IO (Ptr a)
    reallocBytes, -- ::               Ptr a -> Int -> IO (Ptr a)

    free          -- :: Ptr a -> IO ()

    pokeArray,  	-- :: Storable a => Ptr a -> [a] -> IO ()
    pokeArray0, 	-- :: Storable a => a -> Ptr a -> [a] -> IO ()

    peekArray,  	-- :: Storable a => Ptr a -> Int -> IO [a]
    peekArray0, 	-- :: (Storable a, Eq a) => a -> Ptr a -> IO [a]

    withObject,	-- :: Storable a => a -> (Ptr a -> IO b) -> IO b
    withArray, 	-- :: Storable a => [a] -> (Ptr a -> IO b) -> IO b
    withArray0,	-- :: Storable a => a -> [a] -> (Ptr a -> IO b) -> IO b

    new,		-- :: Storable a => a -> IO (Ptr a)
    newArray, 	-- :: Storable a => [a] -> IO (Ptr a)
    newArray0,	-- :: Storable a => a -> [a] -> IO (Ptr a)

    ----------------------------------------------------------------
    -- Haskellish interface to memcpy and memmove.

    copyArray,	-- :: Storable a => Ptr a -> Ptr a -> Int -> IO ()
    copyBytes,	-- :: Ptr a -> Ptr a -> Int -> IO ()

    moveArray,	-- :: Storable a => Ptr a -> Ptr a -> Int -> IO ()
    moveBytes,	-- :: Ptr a -> Ptr a -> Int -> IO ()

   ------------------------------------------------------------------
   -- Error handling.

   -- Perhaps these should be moved to another module (PosixError?)

   getErrno,		-- :: IO Int
   throwIf,			-- :: (a -> Bool) -> String -> IO a ->
IO a
   throwIf_EINTR, 	-- :: (a -> Bool) -> String -> IO a -> IO a
   throwIfNull, 		-- :: String -> IO (Ptr a) -> IO (Ptr a)
   throwIfNull_EINTR,  	-- :: String -> IO (Ptr a) -> IO (Ptr a)
   throwIfMinus1,		-- :: Num a => String -> IO a -> IO a
   throwIfMinus1_EINTR,	-- :: Num a => String -> IO a -> IO a
   throwCError, 		-- :: String -> Int -> IO a
   throwErrno,  		-- :: String -> IO a

 
------------------------------------------------------------------------
-----
   -- Misc
   indexPtr     -- :: Storable a => Ptr a -> Int -> Ptr a
 )








More information about the FFI mailing list