Re: How does one use pass by reference functions using the ffi?

2004-01-25 Thread Glynn Clements

David Sankel wrote:

> Hello FFI experts,
> 
>   Say I have a function somewhere in c land with the following declaration:
> 
> void doStuff( int &a, int &b);

That isn't C. Are you referring to C++ references, or did you mean:

void doStuff(int *a, int *b);

?

>   What would the appropriate Haskell wrapper for this function look like? 
> I'm looking to construct a haskell function of the type: 
> 
> doStuff :: Int -> Int -> IO( (Int,Int) )

The direct translation would be:

Ptr CInt -> Ptr CInt -> IO ()

Higher level interfaces, such as the one which you suggest, could be
built upon that, e.g.:

import Foreign.C(CInt)
import Foreign.Ptr(Ptr)
import Foreign.Marshal.Utils(with)
import Foreign.Storable(peek)

foreign import ccall doStuff :: Ptr CInt -> Ptr CInt -> IO ()

doStuff' :: Int -> Int -> IO (Int,Int)
doStuff' x y = do
 with (fromIntegral x) $ \px ->
  with (fromIntegral y) $ \py -> do
   doStuff px py
   x' <- peek px
   y' <- peek py
   return (fromIntegral x', fromIntegral y')

-- 
Glynn Clements <[EMAIL PROTECTED]>
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: How does one use pass by reference functions using the ffi?

2004-01-25 Thread Alastair Reid

>   Say I have a function somewhere in c land with the following declaration:
>
> void doStuff( int &a, int &b);
>
>   What would the appropriate Haskell wrapper for this function look like?
> I'm looking to construct a haskell function of the type:

The following (untested) Greencard code ought to do the trick.

%fun doStuff :: Int -> Int -> IO (Int,Int)
%code doStuff(&arg1,&arg2)
%return ({*arg1},{*arg2})

--
Alastair Reid

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: How does one use pass by reference functions using the ffi?

2004-01-26 Thread Manuel Chakravarty
David Sankel wrote:

>   Say I have a function somewhere in c land with the following declaration:
> 
> void doStuff( int &a, int &b);
> 
>   What would the appropriate Haskell wrapper for this function look like? 

It'll be

  doStuffC :: Ptr Int -> Ptr Int -> IO ()

which really is a purely syntactic translation of the type
of the C function.  

> I'm looking to construct a haskell function of the type: 
> 
> doStuff :: Int -> Int -> IO( (Int,Int) )

You will need to do the work of allocating temporary storage
and passing pointers to that storage manually unless you use
one of the FFI tools (eg, c2hs
 or
GreenCard).  Doing it manually isn't quite as bad as it
might sound at first, as the FFI libraries contain
convenience functions for this type of situation:

  
http://haskell.org/ghc/docs/latest/html/libraries/base/Foreign.Marshal.Utils.html#v%3Awith

So you get

  doStuff x y =
with x $ \xPtr ->
with y $ \yPtr -> do
  doStuffC xPtr yPtr-- calling into C land
  x' <- peek xPtr
  y' <- peek yPtr
  return (x', y')

(The `with' brackets ensure proper deallocation of the
temporary storage in a stack-like manner.)

Good Luck!
Manuel
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi