Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread Duncan Coutts

On Thu, 2008-07-17 at 13:36 -0300, Felipe Lessa wrote:

> I am using hsc2hs currently, but googling about #def with Cabal I
> found out that some people were having trouble to make Cabal discover
> that hsc2hs had created a new C file. Specifically, bug #245 [1] which
> says that the milestone is undefined.

Note that a milestone of _|_ doesn't mean we don't want a fix, just that
nobody has said they're going to do it. We would welcome a fix for this
if someone wants to contribute. (Of course we'd like contributions to
fix all our bugs!)

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread Magnus Therning
Felipe Lessa wrote:
> Hi,
>
> I tried googling and searching the haskellwiki about this but wasn't
> lucky enough. My question is: is there a way to send struct arguments
> to C functions via the FFI or do I need to create a C wrapper? I guess
> there isn't, and while I can live without it, I'd like to leave no
> doubt.

You might find this old post of mine useful.

http://therning.org/magnus/archives/315

>
>
> Details:
>
> I have something like
>
> 
> typedef struct vect {
> float x,y;
> } vect;
>
> void func(vect v);
> =
>
> on the C side and
>
> 
> -- Please disregard float /= Float, just an example :)
> data Vector = Vector Float Float
>
> instance Storable Vector where
> ...
> 
>
> on the Haskell side, and I want to call func with Vector as argument.
> Now, Vector isn't a basic FFI type, although it implements Storable.
> So does that mean that I need to create something like
>
> 
> void funcWrapper(vect *v) {
> func(*v);
> }
> 
>
> and then allocate some temporary memory on the Haskell side to use func?
>
> Cheers!
>


-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
magnus@therning.org Jabber: magnus@therning.org
http://therning.org/magnus

Haskell is an even 'redder' pill than Lisp or Scheme.
 -- PaulPotts




signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread Felipe Lessa
On Thu, Jul 17, 2008 at 12:37 PM, Bayley, Alistair
<[EMAIL PROTECTED]> wrote:
> -- inline your *vect->vect wrapper (ends up in generated .c file)
> #def void funcWrapper(vect *v) { func(*v); }
>
> foreign import stdcall funcWr unsafe "funcWrapper" :: VectorC -> IO ()

I am using hsc2hs currently, but googling about #def with Cabal I
found out that some people were having trouble to make Cabal discover
that hsc2hs had created a new C file. Specifically, bug #245 [1] which
says that the milestone is undefined. So for now I'm creating a
wrapper.[ch] myself.

[1] http://hackage.haskell.org/trac/hackage/ticket/245

-- 
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread Felipe Lessa
On Thu, Jul 17, 2008 at 12:08 PM, kyra <[EMAIL PROTECTED]> wrote:
> Yes, but programmer *knows* the structure layout, so she usually can emulate
> it with a sequence of primary ffi type arguments. It's pretty trivial for
> the original example (see my previous post on this subj) and can be extended
> further. For example, in my homebrew COM library I pretty successfully
> marshall 16-byte Variants *by value* by means of two consecutive "legal"
> Word64 arguments.

I am concerned, however, with the portability of the library. I mean,
is the calling convention for both

void func(vect v);
void func(float x, float y);

the same on x86? On x86-64? On Windows? On Linux? I guess it would be
a lot faster to pass the arguments on the stack than alloca'ting,
copying to the new area and then copying from the area to the stack,
but I don't want to sacrifice the portability.

Thanks,

-- 
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread Bayley, Alistair
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of Duncan Coutts
> Sent: 17 July 2008 12:46
> 
> On Wed, 2008-07-16 at 22:45 -0300, Felipe Lessa wrote:
> > Hi,
> > 
> > I tried googling and searching the haskellwiki about this but wasn't
> > lucky enough. My question is: is there a way to send struct 
> arguments
> > to C functions via the FFI or do I need to create a C 
> wrapper? I guess
> > there isn't, and while I can live without it, I'd like to leave no
> > doubt.
> 
> If the struct is passed by reference of course then you're 
> fine, but if
> it's by value then you need a C wrapper. The reason is because it's
> beyond the scope of the FFI to know the structure layout and 
> how to map
> that to haskell types. That's the domain of FFI 
> pre-processors. However
> I don't know of any FFI pre-processors that help in this 
> case. Passing C
> structs by value seems to be pretty rare in exported C APIs.


hsc2hs can help a bit (I haven't used the other FFI tools, so don't take
this as an endorsement of hsc2hs over them). You could create a wrapper
that marshals your Vector to a vector struct like this:

 .hsc file:

#include   -- whatever header contains your C vector struct

data VectorC = Ptr ()  -- opaque data type, like void*

-- your Haskell vector
data Vector = Vector Float Float

vector2cvect :: Vector -> IO VectorC
vector2cvect (Vector x y) = do
  ptr <- mallocBytes #{size vect}
  pokeByteOff #{offset vect, x} x
  pokeByteOff #{offset vect, x} x
  return ptr

cvect2Vector :: VectorC -> IO Vector
cvect2Vector ptr = do
  x <- peekByteOff ptr #{offset vect, x}
  y <- peekByteOff ptr #{offset vect, y}
  return (Vector x y)

-- inline your *vect->vect wrapper (ends up in generated .c file)
#def void funcWrapper(vect *v) { func(*v); }

foreign import stdcall funcWr unsafe "funcWrapper" :: VectorC -> IO ()

main = do
  vc <- vector2cvect (Vector 3 4)
  funcWr vc
  free vc
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread kyra

If the struct is passed by reference of course then you're fine, but if
it's by value then you need a C wrapper. The reason is because it's
beyond the scope of the FFI to know the structure layout and how to map
that to haskell types. That's the domain of FFI pre-processors. However
I don't know of any FFI pre-processors that help in this case. Passing C
structs by value seems to be pretty rare in exported C APIs.


Yes, but programmer *knows* the structure layout, so she usually can 
emulate it with a sequence of primary ffi type arguments. It's pretty 
trivial for the original example (see my previous post on this subj) and 
can be extended further. For example, in my homebrew COM library I 
pretty successfully marshall 16-byte Variants *by value* by means of two 
consecutive "legal" Word64 arguments.


Cheers,
Kyra

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread Duncan Coutts

On Wed, 2008-07-16 at 22:45 -0300, Felipe Lessa wrote:
> Hi,
> 
> I tried googling and searching the haskellwiki about this but wasn't
> lucky enough. My question is: is there a way to send struct arguments
> to C functions via the FFI or do I need to create a C wrapper? I guess
> there isn't, and while I can live without it, I'd like to leave no
> doubt.

Correct. The FFI spec does not support C structs as C function
parameters or results. You'll need a wrapper.

If the struct is passed by reference of course then you're fine, but if
it's by value then you need a C wrapper. The reason is because it's
beyond the scope of the FFI to know the structure layout and how to map
that to haskell types. That's the domain of FFI pre-processors. However
I don't know of any FFI pre-processors that help in this case. Passing C
structs by value seems to be pretty rare in exported C APIs.

Duncan


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI and struct arguments

2008-07-16 Thread kyra

Felipe Lessa wrote:

Hi,

I tried googling and searching the haskellwiki about this but wasn't
lucky enough. My question is: is there a way to send struct arguments
to C functions via the FFI or do I need to create a C wrapper? I guess
there isn't, and while I can live without it, I'd like to leave no
doubt.
  

Sometimes there is such a way. See below.

Details:

I have something like


typedef struct vect {
float x,y;
} vect;

void func(vect v);
  

For most architectures stack layout of

void func(vect v);

and

void func(float x, float y);

is exactly the same, so for FFI purposes this 'func' can be declared as 
something like:


foreign import ccall unsafe :: Float -> Float -> IO ()


Cheers,
Kyra

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe