[C2hs] Pointers to structs without typedef

Jelmer Vernooij jelmer at samba.org
Wed Nov 9 09:07:45 EST 2005


On Thu, Nov 10, 2005 at 12:29:02AM +1100, Manuel M T Chakravarty wrote about 'Re: [C2hs] Pointers to structs without typedef':
> Jelmer Vernooij:
> > c2hs appears to have trouble with pointers to structs when not using
> > typedefs. A simple that shows this behaviour:

> > module Foo
> > where

> > #c

> > struct foo { char x; };

> > void bar(struct foo *x);

> > #endc

> > {#pointer *'struct foo' as Foo newtype#}

> I think you meant

>   {#pointer *foo as Foo newtype#}

That's what I tried initially, but that doesn't appear to work; c2hs will
generate "Ptr ()" as the first argument of bar. It does work correctly 
if I make foo a typdef.

If I try this:

module Foo
where

#c

typedef struct foo {
	char x;
} foo_typedef;

void bar1(struct foo *x);
void bar2(foo_typedef *x);

#endc

{#pointer *foo as Foo newtype#}
{#pointer *foo_typedef as FooTypedef newtype#}

test1 = {#call bar1#}
test2 = {#call bar2#}

c2hs generates the following stub for `bar1':

foreign import ccall safe "c2hstest.h bar1"
  bar1 :: ((Ptr ()) -> (IO ()))

whereas I would expect the `Ptr ()' to be `Foo' instead.

the stub for `bar2' is correct:

foreign import ccall safe "c2hstest.h bar2"
  bar2 :: ((FooTypedef) -> (IO ()))

Cheers,

	Jelmer
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org//pipermail/c2hs/attachments/20051109/55fbcfa8/attachment.bin


More information about the C2hs mailing list