
#32: #get generated code doesn't work on bitfields --------------------+------------------------------------------------------- Reporter: guest | Type: defect Status: new | Priority: normal Milestone: | Component: general Version: 0.16.2 | Keywords: --------------------+------------------------------------------------------- Consider the following source files: {{{ /* bitfield.c */ #include "bitfield.h" static testStruct makeItFrom; testStruct* makeIt() { makeItFrom.a = 0; makeItFrom.b = 1; return &makeItFrom; } }}} {{{ /* bitfield.h */ typedef struct testStruct_ testStruct; struct testStruct_ { unsigned a : 31; unsigned b : 1; }; testStruct* makeIt(); }}} {{{ {-# LANGUAGE ForeignFunctionInterface #-} #include "bitfield.h" import C2HS {#pointer *testStruct as TestStructPtr #} main = do x <- {#call makeIt #} print =<< ({#get testStruct->b #} x) }}} Compile as follows: {{{ ezyang@javelin:~/Dev/haskell/c2hs-bitfield$ gcc -c -o bitfield.o bitfield.c ezyang@javelin:~/Dev/haskell/c2hs-bitfield$ c2hs Bitfield.chs ezyang@javelin:~/Dev/haskell/c2hs-bitfield$ ghc --make Bitfield.hs bitfield.o [2 of 2] Compiling Main ( Bitfield.hs, Bitfield.o ) Linking Bitfield ... }}} When you run the resulting executable, the expected output is 1, but the actual output is 0. Looking at the generated HS: {{{ main = do x <- makeIt {-# LINE 10 "Bitfield.chs" #-} print =<< ((\ptr -> do {val <- peekByteOff ptr 4 ::IO CUInt{-:1-}; return $ (val `shiftL` (32 - 1)) `shiftR` (32 - 1)}) x) }}} The byte offset is obviously bogus (the important information must be in offsets 0, 1, 2 or 3). Less obvious is what the correct behavior in all cases is: the bitfield arrangement appears to be compiler dependent. Maybe C2HS should just bug out and say that bitfields are not supported. -- Ticket URL: http://hackage.haskell.org/trac/c2hs/ticket/32 c2hs http://www.cse.unsw.edu.au/~chak/haskell/c2hs/ C->Haskell, An Interface Generator for Haskell