[commit: packages/unix] master: Replace `__hsunix_unsetenv` wrapper with CApiFFI (57d2cb2)

git at git.haskell.org git at git.haskell.org
Tue Apr 19 21:38:25 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/57d2cb2a613e909829f22be6218e840b2b4602b5/unix

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

commit 57d2cb2a613e909829f22be6218e840b2b4602b5
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sun Jan 31 12:57:23 2016 +0100

    Replace `__hsunix_unsetenv` wrapper with CApiFFI


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

57d2cb2a613e909829f22be6218e840b2b4602b5
 System/Posix/Env.hsc            | 15 ++++++++++++---
 System/Posix/Env/ByteString.hsc | 15 ++++++++++++---
 cbits/HsUnix.c                  | 12 ------------
 include/HsUnix.h                |  2 --
 4 files changed, 24 insertions(+), 20 deletions(-)

diff --git a/System/Posix/Env.hsc b/System/Posix/Env.hsc
index 999daec..6412bae 100644
--- a/System/Posix/Env.hsc
+++ b/System/Posix/Env.hsc
@@ -1,3 +1,4 @@
+{-# LANGUAGE CApiFFI #-}
 #if __GLASGOW_HASKELL__ >= 709
 {-# LANGUAGE Safe #-}
 #else
@@ -116,13 +117,21 @@ setEnvironment env = do
 -- from the environment.
 
 unsetEnv :: String -> IO ()
-#ifdef HAVE_UNSETENV
-
+#if HAVE_UNSETENV
+# if !UNSETENV_RETURNS_VOID
 unsetEnv name = withFilePath name $ \ s ->
   throwErrnoIfMinus1_ "unsetenv" (c_unsetenv s)
 
-foreign import ccall unsafe "__hsunix_unsetenv"
+-- POSIX.1-2001 compliant unsetenv(3)
+foreign import capi unsafe "HsUnix.h unsetenv"
    c_unsetenv :: CString -> IO CInt
+# else
+unsetEnv name = withFilePath name c_unsetenv
+
+-- pre-POSIX unsetenv(3) returning @void@
+foreign import capi unsafe "HsUnix.h unsetenv"
+   c_unsetenv :: CString -> IO ()
+# endif
 #else
 unsetEnv name = putEnv (name ++ "=")
 #endif
diff --git a/System/Posix/Env/ByteString.hsc b/System/Posix/Env/ByteString.hsc
index 0bbcfd8..57b03aa 100644
--- a/System/Posix/Env/ByteString.hsc
+++ b/System/Posix/Env/ByteString.hsc
@@ -1,3 +1,4 @@
+{-# LANGUAGE CApiFFI #-}
 {-# LANGUAGE Trustworthy #-}
 #if __GLASGOW_HASKELL__ >= 709
 {-# OPTIONS_GHC -fno-warn-trustworthy-safe #-}
@@ -98,13 +99,21 @@ getEnvironment = do
 -- from the environment.
 
 unsetEnv :: ByteString -> IO ()
-#ifdef HAVE_UNSETENV
-
+#if HAVE_UNSETENV
+# if !UNSETENV_RETURNS_VOID
 unsetEnv name = B.useAsCString name $ \ s ->
   throwErrnoIfMinus1_ "unsetenv" (c_unsetenv s)
 
-foreign import ccall unsafe "__hsunix_unsetenv"
+-- POSIX.1-2001 compliant unsetenv(3)
+foreign import capi unsafe "HsUnix.h unsetenv"
    c_unsetenv :: CString -> IO CInt
+# else
+unsetEnv name = B.useAsCString name c_unsetenv
+
+-- pre-POSIX unsetenv(3) returning @void@
+foreign import capi unsafe "HsUnix.h unsetenv"
+   c_unsetenv :: CString -> IO ()
+# endif
 #else
 unsetEnv name = putEnv (name ++ "=")
 #endif
diff --git a/cbits/HsUnix.c b/cbits/HsUnix.c
index 5742b49..8e16803 100644
--- a/cbits/HsUnix.c
+++ b/cbits/HsUnix.c
@@ -36,18 +36,6 @@ int __hsunix_push_module(int fd, const char *module)
 #endif
 }
 
-#ifdef HAVE_UNSETENV
-int __hsunix_unsetenv(const char *name)
-{
-#ifdef UNSETENV_RETURNS_VOID
-    unsetenv(name);
-    return 0;
-#else
-    return unsetenv(name);
-#endif
-}
-#endif
-
 /* A size that will contain many path names, but not necessarily all
  * (PATH_MAX is not defined on systems with unlimited path length,
  * e.g. the Hurd).
diff --git a/include/HsUnix.h b/include/HsUnix.h
index fb19f99..dcd0c4a 100644
--- a/include/HsUnix.h
+++ b/include/HsUnix.h
@@ -116,8 +116,6 @@ fall back to O_FSYNC, which should be the same */
 // push a SVR4 STREAMS module; do nothing if STREAMS not available
 int __hsunix_push_module(int fd, const char *module);
 
-int __hsunix_unsetenv(const char *name);
-
 /* A size that will contain many path names, but not necessarily all
  * (PATH_MAX is not defined on systems with unlimited path length,
  * e.g. the Hurd).



More information about the ghc-commits mailing list