Allocation & Marshalling Question

Adrian Hey ahey at iee.org
Sun May 11 14:01:01 EDT 2003


Hello,

I wonder if it would be possible to make common FFI utilities more
composable by giving functions with types ending like this:
	.....(Ptr a -> IO b) -> IO b
a type more like this:
	.....(Ptr a -> b) -> b

For example..

 withForeignPtr :: ForeignPtr a -> (Ptr a   -> b) -> b
 allocaBytes    :: Int          -> (Ptr a   -> b) -> b
 alloca         :: (Storable a) => (Ptr a   -> b) -> b
 withCString    :: String       -> (CString -> a) -> a

The reason I ask is that I often find myself writing
code like this:
 f :: String -> String -> IO String
 f s1 s2 =
   withCString s1  $ \s1Ptr ->
   withCString s2  $ \s2Ptr ->
   allocaBytes 256 $ \buffPtr ->
   do ...

But if the type sigs were as I suggested you could define a suitable
left associative reverse application operator like this maybe:
 infixl <+ 0
 (<+) :: a -> (a -> b) -> b
 f <+ alloc = alloc f

Then f could be re-written:
 f s1 s2 =
  f' <+ withCString s1 <+ withCString s2 <+ allocaBytes 256 where
  f'    s1Ptr             s2Ptr             buffPtr         =
         do ...

So the allocation and marshalling bits & bobs just appear in the
same order as the arguments of f'.

Playing about with this idea I came up with a definition of <+
to work with FFI functions as they currently are:

 infixl 0 <+
 (<+) :: (Ptr a -> b) -> ((Ptr a -> IO b) -> IO b) -> b
 f <+ alloc = unsafePerformIO $ alloc $ \p -> return $ f p

Eeek! This actually seems to work on the examples I tried, though
to be honest I have a very hard time imagining what's really
going on at runtime with expressions using <+. Is it likely
to be safe? and efficient?

I'm not really happy with the use of unsafePerformIO and thought
what might happen in reality is that stack space gets allocated,
the pointer applied, then stack space prompty gets deallocated
before the actual call to the f' takes place. I'm not sure about
that though. As far as I can tell using minusPtr the pointers do
seem to have appropriate offsets, so maybe it really does work:-)

Perhaps there's a better way to do tidy marshalling (without all
the deeply nested lambdas or wheres).
Any ideas?

Thanks
--
Adrian Hey










More information about the FFI mailing list