Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/1bde0e5f0038c30063e02641fda0996d898a06ef

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

commit 1bde0e5f0038c30063e02641fda0996d898a06ef
Author: Ian Lynagh <[email protected]>
Date:   Mon Nov 28 18:58:59 2011 +0000

    Use capi to define the fcntl FFI imports

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

 GHC/Event/Clock.hsc       |    2 +-
 System/CPUTime.hsc        |    2 +-
 System/Posix/Internals.hs |    6 +++---
 include/HsBase.h          |   14 --------------
 4 files changed, 5 insertions(+), 19 deletions(-)

diff --git a/GHC/Event/Clock.hsc b/GHC/Event/Clock.hsc
index 8200d28..4a538f4 100644
--- a/GHC/Event/Clock.hsc
+++ b/GHC/Event/Clock.hsc
@@ -1,5 +1,5 @@
 {-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude, BangPatterns, ForeignFunctionInterface #-}
+{-# LANGUAGE NoImplicitPrelude, BangPatterns, ForeignFunctionInterface, 
CApiFFI #-}
 
 module GHC.Event.Clock (getCurrentTime) where
 
diff --git a/System/CPUTime.hsc b/System/CPUTime.hsc
index e875528..385e0fb 100644
--- a/System/CPUTime.hsc
+++ b/System/CPUTime.hsc
@@ -1,5 +1,5 @@
 {-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NondecreasingIndentation, ForeignFunctionInterface #-}
+{-# LANGUAGE CPP, NondecreasingIndentation, ForeignFunctionInterface, CApiFFI 
#-}
 
 -----------------------------------------------------------------------------
 -- |
diff --git a/System/Posix/Internals.hs b/System/Posix/Internals.hs
index e48ca05..a9c2eab 100644
--- a/System/Posix/Internals.hs
+++ b/System/Posix/Internals.hs
@@ -459,13 +459,13 @@ foreign import ccall unsafe "HsBase.h getpid"
    c_getpid :: IO CPid
 
 #if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
-foreign import ccall unsafe "HsBase.h fcntl_read"
+foreign import capi unsafe "HsBase.h fcntl"
    c_fcntl_read  :: CInt -> CInt -> IO CInt
 
-foreign import ccall unsafe "HsBase.h fcntl_write"
+foreign import capi unsafe "HsBase.h fcntl"
    c_fcntl_write :: CInt -> CInt -> CLong -> IO CInt
 
-foreign import ccall unsafe "HsBase.h fcntl_lock"
+foreign import capi unsafe "HsBase.h fcntl"
    c_fcntl_lock  :: CInt -> CInt -> Ptr CFLock -> IO CInt
 
 foreign import ccall unsafe "HsBase.h fork"
diff --git a/include/HsBase.h b/include/HsBase.h
index c252f2b..bad3a4b 100644
--- a/include/HsBase.h
+++ b/include/HsBase.h
@@ -619,19 +619,5 @@ INLINE intptr_t  __hscore_to_intptr   (void *p)     { 
return (intptr_t)p; }
 void errorBelch2(const char*s, char *t);
 void debugBelch2(const char*s, char *t);
 
-#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
-
-INLINE int fcntl_read(int fd, int cmd) {
-    return fcntl(fd, cmd);
-}
-INLINE int fcntl_write(int fd, int cmd, long arg) {
-    return fcntl(fd, cmd, arg);
-}
-INLINE int fcntl_lock(int fd, int cmd, struct flock *lock) {
-    return fcntl(fd, cmd, lock);
-}
-
-#endif
-
 #endif /* __HSBASE_H__ */
 



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to