Skip to content
Snippets Groups Projects
Commit b495e1d8 authored by Herbert Valerio Riedel's avatar Herbert Valerio Riedel :man_dancing:
Browse files

Use `#const` rather than FFI wrapper for PATH_MAX

This has the side-effect of making two more modules `Safe`-inferred
parent 57d2cb2a
No related branches found
No related tags found
No related merge requests found
{-# 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@.
changeWorkingDirectory :: FilePath -> IO ()
......
{-# 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@.
changeWorkingDirectory :: RawFilePath -> IO ()
......
......@@ -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.
......
......@@ -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
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment