[commit: packages/unix] master: Add CTYPE annotations to ptr types used for FFI (731f7dd)

git at git.haskell.org git at git.haskell.org
Tue Apr 19 21:37:47 UTC 2016


Repository : ssh://git@git.haskell.org/unix

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/731f7dddcbae3c4332beac742605dade2d4a80ad/unix

>---------------------------------------------------------------

commit 731f7dddcbae3c4332beac742605dade2d4a80ad
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sat Jan 30 19:44:58 2016 +0100

    Add CTYPE annotations to ptr types used for FFI
    
    This avoids incompatible-pointer warnings from the c-compiler when using
    `CApiFFI`


>---------------------------------------------------------------

731f7dddcbae3c4332beac742605dade2d4a80ad
 System/Posix/Directory/Common.hsc | 4 ++--
 System/Posix/IO/Common.hsc        | 6 ++----
 System/Posix/Process/Common.hsc   | 2 +-
 System/Posix/Resource.hsc         | 2 +-
 System/Posix/Terminal/Common.hsc  | 2 +-
 5 files changed, 7 insertions(+), 9 deletions(-)

diff --git a/System/Posix/Directory/Common.hsc b/System/Posix/Directory/Common.hsc
index 4ea8f78..9fb5ac4 100644
--- a/System/Posix/Directory/Common.hsc
+++ b/System/Posix/Directory/Common.hsc
@@ -39,8 +39,8 @@ import Foreign.C
 
 newtype DirStream = DirStream (Ptr CDir)
 
-type CDir       = ()
-type CDirent    = ()
+data {-# CTYPE "DIR" #-} CDir
+data {-# CTYPE "struct dirent" #-} CDirent
 
 -- | @rewindDirStream dp@ calls @rewinddir@ to reposition
 --   the directory stream @dp@ at the beginning of the directory.
diff --git a/System/Posix/IO/Common.hsc b/System/Posix/IO/Common.hsc
index 198b3f1..eb4a721 100644
--- a/System/Posix/IO/Common.hsc
+++ b/System/Posix/IO/Common.hsc
@@ -320,9 +320,7 @@ getLock (Fd fd) lock =
     maybeResult (_, (Unlock, _, _, _)) = Nothing
     maybeResult x = Just x
 
-type CFLock     = ()
-
-allocaLock :: FileLock -> (Ptr CFLock -> IO a) -> IO a
+allocaLock :: FileLock -> (Ptr Base.CFLock -> IO a) -> IO a
 allocaLock (lockreq, mode, start, len) io =
   allocaBytes (#const sizeof(struct flock)) $ \p -> do
     (#poke struct flock, l_type)   p (lockReq2Int lockreq :: CShort)
@@ -336,7 +334,7 @@ lockReq2Int ReadLock  = (#const F_RDLCK)
 lockReq2Int WriteLock = (#const F_WRLCK)
 lockReq2Int Unlock    = (#const F_UNLCK)
 
-bytes2ProcessIDAndLock :: Ptr CFLock -> IO (ProcessID, FileLock)
+bytes2ProcessIDAndLock :: Ptr Base.CFLock -> IO (ProcessID, FileLock)
 bytes2ProcessIDAndLock p = do
   req   <- (#peek struct flock, l_type)   p
   mode  <- (#peek struct flock, l_whence) p
diff --git a/System/Posix/Process/Common.hsc b/System/Posix/Process/Common.hsc
index c13bf5e..ee7310e 100644
--- a/System/Posix/Process/Common.hsc
+++ b/System/Posix/Process/Common.hsc
@@ -212,7 +212,7 @@ getProcessTimes = do
                            childSystemTime = cst
                           })
 
-type CTms = ()
+data {-# CTYPE "struct tms" #-} CTms
 
 foreign import capi unsafe "HsUnix.h times"
   c_times :: Ptr CTms -> IO CClock
diff --git a/System/Posix/Resource.hsc b/System/Posix/Resource.hsc
index 4c5ca48..280c25f 100644
--- a/System/Posix/Resource.hsc
+++ b/System/Posix/Resource.hsc
@@ -55,7 +55,7 @@ data ResourceLimit
   | ResourceLimit Integer
   deriving Eq
 
-type RLimit = ()
+data {-# CTYPE "struct rlimit" #-} RLimit
 
 foreign import ccall unsafe "HsUnix.h __hscore_getrlimit"
   c_getrlimit :: CInt -> Ptr RLimit -> IO CInt
diff --git a/System/Posix/Terminal/Common.hsc b/System/Posix/Terminal/Common.hsc
index 68ce321..5d81ec5 100644
--- a/System/Posix/Terminal/Common.hsc
+++ b/System/Posix/Terminal/Common.hsc
@@ -77,6 +77,7 @@ import Foreign.Ptr ( Ptr, plusPtr )
 import Foreign.Storable ( Storable(..) )
 import System.IO.Unsafe ( unsafePerformIO )
 import System.Posix.Types
+import System.Posix.Internals ( CTermios )
 
 #if !HAVE_TCDRAIN
 import System.IO.Error ( ioeSetLocation )
@@ -86,7 +87,6 @@ import GHC.IO.Exception ( unsupportedOperation )
 -- -----------------------------------------------------------------------------
 -- Terminal attributes
 
-type CTermios = ()
 newtype TerminalAttributes = TerminalAttributes (ForeignPtr CTermios)
 
 makeTerminalAttributes :: ForeignPtr CTermios -> TerminalAttributes



More information about the ghc-commits mailing list