[commit: packages/unix] master: Use `#const` rather than FFI wrapper for PATH_MAX (b495e1d)

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


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

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

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

commit b495e1d862411c731bf9374e2db949dfb3442fd4
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sun Jan 31 13:30:15 2016 +0100

    Use `#const` rather than FFI wrapper for PATH_MAX
    
    This has the side-effect of making two more modules `Safe`-inferred


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

b495e1d862411c731bf9374e2db949dfb3442fd4
 System/Posix/Directory.hsc            | 14 ++++++++++----
 System/Posix/Directory/ByteString.hsc | 14 ++++++++++----
 cbits/HsUnix.c                        | 12 ------------
 include/HsUnix.h                      |  6 ------
 4 files changed, 20 insertions(+), 26 deletions(-)

diff --git a/System/Posix/Directory.hsc b/System/Posix/Directory.hsc
index f1caaaf..10dcbb4 100644
--- a/System/Posix/Directory.hsc
+++ b/System/Posix/Directory.hsc
@@ -1,6 +1,10 @@
 {-# LANGUAGE CApiFFI #-}
 {-# LANGUAGE NondecreasingIndentation #-}
+#if __GLASGOW_HASKELL__ >= 709
+{-# LANGUAGE Safe #-}
+#else
 {-# LANGUAGE Trustworthy #-}
+#endif
 
 -----------------------------------------------------------------------------
 -- |
@@ -18,6 +22,11 @@
 
 #include "HsUnix.h"
 
+-- hack copied from System.Posix.Files
+#if !defined(PATH_MAX)
+# define PATH_MAX 4096
+#endif
+
 module System.Posix.Directory (
    -- * Creating and removing directories
    createDirectory, removeDirectory,
@@ -115,7 +124,7 @@ foreign import ccall unsafe "__hscore_d_name"
 -- | @getWorkingDirectory@ calls @getcwd@ to obtain the name
 --   of the current working directory.
 getWorkingDirectory :: IO FilePath
-getWorkingDirectory = go long_path_size
+getWorkingDirectory = go (#const PATH_MAX)
   where
     go bytes = do
         r <- allocaBytes bytes $ \buf -> do
@@ -134,9 +143,6 @@ getWorkingDirectory = go long_path_size
 foreign import ccall unsafe "getcwd"
    c_getcwd   :: Ptr CChar -> CSize -> IO (Ptr CChar)
 
-foreign import ccall unsafe "__hsunix_long_path_size"
-  long_path_size :: Int
-
 -- | @changeWorkingDirectory dir@ calls @chdir@ to change
 --   the current working directory to @dir at .
 changeWorkingDirectory :: FilePath -> IO ()
diff --git a/System/Posix/Directory/ByteString.hsc b/System/Posix/Directory/ByteString.hsc
index 3f96831..b5ea462 100644
--- a/System/Posix/Directory/ByteString.hsc
+++ b/System/Posix/Directory/ByteString.hsc
@@ -1,6 +1,10 @@
 {-# LANGUAGE CApiFFI #-}
 {-# LANGUAGE NondecreasingIndentation #-}
+#if __GLASGOW_HASKELL__ >= 709
+{-# LANGUAGE Safe #-}
+#else
 {-# LANGUAGE Trustworthy #-}
+#endif
 
 -----------------------------------------------------------------------------
 -- |
@@ -18,6 +22,11 @@
 
 #include "HsUnix.h"
 
+-- hack copied from System.Posix.Files
+#if !defined(PATH_MAX)
+# define PATH_MAX 4096
+#endif
+
 module System.Posix.Directory.ByteString (
    -- * Creating and removing directories
    createDirectory, removeDirectory,
@@ -116,7 +125,7 @@ foreign import ccall unsafe "__hscore_d_name"
 -- | @getWorkingDirectory@ calls @getcwd@ to obtain the name
 --   of the current working directory.
 getWorkingDirectory :: IO RawFilePath
-getWorkingDirectory = go long_path_size
+getWorkingDirectory = go (#const PATH_MAX)
   where
     go bytes = do
         r <- allocaBytes bytes $ \buf -> do
@@ -135,9 +144,6 @@ getWorkingDirectory = go long_path_size
 foreign import ccall unsafe "getcwd"
    c_getcwd   :: Ptr CChar -> CSize -> IO (Ptr CChar)
 
-foreign import ccall unsafe "__hsunix_long_path_size"
-  long_path_size :: Int
-
 -- | @changeWorkingDirectory dir@ calls @chdir@ to change
 --   the current working directory to @dir at .
 changeWorkingDirectory :: RawFilePath -> IO ()
diff --git a/cbits/HsUnix.c b/cbits/HsUnix.c
index 8e16803..bdd1e80 100644
--- a/cbits/HsUnix.c
+++ b/cbits/HsUnix.c
@@ -36,18 +36,6 @@ int __hsunix_push_module(int fd, const char *module)
 #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).
- */
-HsInt __hsunix_long_path_size(void) {
-#ifdef PATH_MAX
-    return PATH_MAX;
-#else
-    return 4096;
-#endif
-}
-
 /*
  * read an entry from the directory stream; opt for the
  * re-entrant friendly way of doing this, if available.
diff --git a/include/HsUnix.h b/include/HsUnix.h
index dcd0c4a..1273452 100644
--- a/include/HsUnix.h
+++ b/include/HsUnix.h
@@ -116,10 +116,4 @@ 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);
 
-/* 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).
- */
-HsInt __hsunix_long_path_size();
-
 #endif



More information about the ghc-commits mailing list