[commit: packages/unix] master: Replace `__hscore_mk{dtemp, stemp, stemps}` wrappers with CApiFFI (3e32e39)
git at git.haskell.org
git at git.haskell.org
Tue Apr 19 21:38:01 UTC 2016
Repository : ssh://git@git.haskell.org/unix
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/3e32e3912254b5b13ce27715cbd369e5e4b33241/unix
>---------------------------------------------------------------
commit 3e32e3912254b5b13ce27715cbd369e5e4b33241
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Sun Jan 31 00:15:23 2016 +0100
Replace `__hscore_mk{dtemp,stemp,stemps}` wrappers with CApiFFI
>---------------------------------------------------------------
3e32e3912254b5b13ce27715cbd369e5e4b33241
System/Posix/Temp.hsc | 7 ++++---
System/Posix/Temp/ByteString.hsc | 7 ++++---
cbits/HsUnix.c | 16 ----------------
include/HsUnix.h | 10 ----------
4 files changed, 8 insertions(+), 32 deletions(-)
diff --git a/System/Posix/Temp.hsc b/System/Posix/Temp.hsc
index 473364c..3984144 100644
--- a/System/Posix/Temp.hsc
+++ b/System/Posix/Temp.hsc
@@ -1,3 +1,4 @@
+{-# LANGUAGE CApiFFI #-}
#if __GLASGOW_HASKELL__ >= 709
{-# LANGUAGE Safe #-}
#else
@@ -33,7 +34,7 @@ import System.Posix.IO
import System.Posix.Types
import System.Posix.Internals (withFilePath, peekFilePath)
-foreign import ccall unsafe "HsUnix.h __hscore_mkstemp"
+foreign import capi unsafe "HsUnix.h mkstemp"
c_mkstemp :: CString -> IO CInt
-- | Make a unique filename and open it for reading\/writing. The returned
@@ -53,7 +54,7 @@ mkstemp template' = do
return (name, h)
#if HAVE_MKSTEMPS
-foreign import ccall unsafe "HsUnix.h __hscore_mkstemps"
+foreign import capi unsafe "HsUnix.h mkstemps"
c_mkstemps :: CString -> CInt -> IO CInt
#endif
@@ -81,7 +82,7 @@ mkstemps = error "System.Posix.Temp.mkstemps: not available on this platform"
#endif
#if HAVE_MKDTEMP
-foreign import ccall unsafe "HsUnix.h __hscore_mkdtemp"
+foreign import capi unsafe "HsUnix.h mkdtemp"
c_mkdtemp :: CString -> IO CString
#endif
diff --git a/System/Posix/Temp/ByteString.hsc b/System/Posix/Temp/ByteString.hsc
index 67442fc..0e30c6f 100644
--- a/System/Posix/Temp/ByteString.hsc
+++ b/System/Posix/Temp/ByteString.hsc
@@ -1,3 +1,4 @@
+{-# LANGUAGE CApiFFI #-}
#if __GLASGOW_HASKELL__ >= 709
{-# LANGUAGE Safe #-}
#else
@@ -38,7 +39,7 @@ import System.Posix.Directory (createDirectory)
import System.Posix.IO
import System.Posix.Types
-foreign import ccall unsafe "HsUnix.h __hscore_mkstemp"
+foreign import capi unsafe "HsUnix.h mkstemp"
c_mkstemp :: CString -> IO CInt
-- | Make a unique filename and open it for reading\/writing. The returned
@@ -58,7 +59,7 @@ mkstemp template' = do
return (name, h)
#if HAVE_MKSTEMPS
-foreign import ccall unsafe "HsUnix.h __hscore_mkstemps"
+foreign import capi unsafe "HsUnix.h mkstemps"
c_mkstemps :: CString -> CInt -> IO CInt
#endif
@@ -82,7 +83,7 @@ mkstemps = error "System.Posix.Temp.mkstemps: not available on this platform"
#endif
#if HAVE_MKDTEMP
-foreign import ccall unsafe "HsUnix.h __hscore_mkdtemp"
+foreign import capi unsafe "HsUnix.h mkdtemp"
c_mkdtemp :: CString -> IO CString
#endif
diff --git a/cbits/HsUnix.c b/cbits/HsUnix.c
index 55f9679..aec5368 100644
--- a/cbits/HsUnix.c
+++ b/cbits/HsUnix.c
@@ -65,22 +65,6 @@ int __hsunix_push_module(int fd, const char *module)
#endif
}
-int __hscore_mkstemp(char *filetemplate) {
- return (mkstemp(filetemplate));
-}
-
-#if HAVE_MKSTEMPS
-int __hscore_mkstemps(char *filetemplate, int suffixlen) {
- return (mkstemps(filetemplate, suffixlen));
-}
-#endif
-
-#if HAVE_MKDTEMP
-char *__hscore_mkdtemp(char *filetemplate) {
- return (mkdtemp(filetemplate));
-}
-#endif
-
#ifdef HAVE_UNSETENV
int __hsunix_unsetenv(const char *name)
{
diff --git a/include/HsUnix.h b/include/HsUnix.h
index 093c9e3..5daff0c 100644
--- a/include/HsUnix.h
+++ b/include/HsUnix.h
@@ -134,16 +134,6 @@ int __hsunix_unlockpt(int fd);
// push a SVR4 STREAMS module; do nothing if STREAMS not available
int __hsunix_push_module(int fd, const char *module);
-int __hscore_mkstemp(char *filetemplate);
-
-#if HAVE_MKSTEMPS
-int __hscore_mkstemps(char *filetemplate, int suffixlen);
-#endif
-
-#if HAVE_MKDTEMP
-char *__hscore_mkdtemp(char *filetemplate);
-#endif
-
int __hsunix_unsetenv(const char *name);
/* A size that will contain many path names, but not necessarily all
More information about the ghc-commits
mailing list