[GHC] #8222: CTYPE pragma on newtype is ignored

#8222: CTYPE pragma on newtype is ignored
--------------------------+------------------------------------------------
Reporter: akio | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: | Version: 7.6.3
Compiler | Operating System: Linux
Keywords: | Type of failure: Incorrect result at runtime
Architecture: x86_64 | Test Case:
(amd64) | Blocking:
Difficulty: |
Unknown |
Blocked By: |
Related Tickets: |
--------------------------+------------------------------------------------
User's guide includes an example where a CTYPE pragma is used for a
newtype.
{{{
newtype {-# CTYPE "useconds_t" #-} T = ...
}}}
However, in the following program, the CTYPE pragma seems to be ignored:
{{{
{-# LANGUAGE CApiFFI #-}
import Foreign.Ptr
foreign import capi unsafe "sys/socket.h CMSG_DATA"
c_CMSG_DATA :: Ptr Cmsg -> Ptr a
newtype {-# CTYPE "sys/socket.h" "struct cmsghdr" #-} Cmsg = Cmsg ()
main = return ()
}}}
Save this as {{{capi.hs}}}, then compile it like:
{{{
ghc capi.hs -fforce-recomp -keep-tmp-files -tmpdir .
}}}
Then GHC creates a C file:
{{{
#define IN_STG_CODE 0
#include "Rts.h"
#include "Stg.h"
#ifdef __cplusplus
extern "C" {
#endif
#include

#8222: CTYPE pragma on newtype is ignored -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => infoneeded Comment: akio: this problem seems fixed in 7.8 and later, can you confirm? I see the following line in the generated C file, which looks correct to me: {{{ void* ghczuwrapperZC0ZCmainZCMainZCCMSGzuDATA(struct cmsghdr* a1) {return CMSG_DATA(a1);} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8222#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8222: CTYPE pragma on newtype is ignored -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: worksforme | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | patsyn/should_compile/T9857 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * testcase: => patsyn/should_compile/T9857 * resolution: => worksforme Comment: testsuite/tests/patsyn/should_compile/T9857.hs uses a CTYPE pragma on a newtype: `newtype {-# CTYPE "unsigned short" #-} Half = ...` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8222#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC