On 02.04.2009, at 09:42, Mark Wassell wrote:
Hello,

I have the following:
...
typedef struct tagINPUT {
DWORD type;
union {MOUSEINPUT mi;
          KEYBDINPUT ki;
          HARDWAREINPUT hi;
         };
}INPUT, *PINPUT;
Hi Marc,

this is probably because c2hs does not (yet) support the 'Unnamed fields' extension (http://gcc.gnu.org/onlinedocs/gcc-4.3.3/gcc/Unnamed-Fields.html ).

This works fine:

> module Test where
> #c
> typedef struct {
>   union { int x;  } u;
> } S1;
> #endc
> test  = {#set S1.u.x #}

but this won't work:

> module Test where
> #c
> typedef struct {
>   union { int x;  };
> } S2;
> #endc
> test  = {#set S2.x #}

If you care about a fix, please file a bug at 
http://hackage.haskell.org/trac/c2hs/wiki

cheers, benedikt



and in a chs file:

sendChar :: HWND -> Char -> IO ()
sendChar win ch = do
                    allocaBytes ( {#sizeof INPUT#}) $ \ptr ->
                      {#set INPUT.type #} ptr 0
                      {#set INPUT.ki.wVk #} ptr 0
                      {#set INPUT.ki.dwFlags #} ptr 0

c2hs comes up with


Test1.chs:27: (column 37) [ERROR]  >>> error
Unknown member name!
The structure has no member called `ki'.  The structure is defined at
("sendinput.h",35,9).
Test1.chs:26: (column 37) [ERROR]  >>> error
Unknown member name!
The structure has no member called `ki'.  The structure is defined at
("sendinput.h",35,9).

How do I address fields inside the union?

Cheers

Mark

_______________________________________________
C2hs mailing list
C2hs@haskell.org
http://www.haskell.org/mailman/listinfo/c2hs

_______________________________________________
C2hs mailing list
C2hs@haskell.org
http://www.haskell.org/mailman/listinfo/c2hs

Reply via email to