aboutsummaryrefslogtreecommitdiffhomepage
path: root/System/Posix/Directory/ByteString.hsc
diff options
context:
space:
mode:
authorGravatar Simon Marlow <marlowsd@gmail.com>2011-11-11 16:18:48 +0000
committerGravatar Simon Marlow <marlowsd@gmail.com>2011-11-22 12:36:48 +0000
commit34c7bf896f19b182cf6fa104e057f1df9df1254a (patch)
treeabdb8264ae52c62263fc0fb4b395906a64acb104 /System/Posix/Directory/ByteString.hsc
parentc213ae2ec6d9c71266aebc8e5b2326a9625fba7a (diff)
Provide a raw ByteString version of FilePath and environment APIs
The new module System.Posix.ByteString provides exactly the same API as System.Posix, except that: - There is a new type: RawFilePath = ByteString - All functions mentioning FilePath in the System.Posix API use RawFilePath in the System.Posix.ByteString API - RawFilePaths are not subject to Unicode locale encoding and decoding, unlike FilePaths. They are the exact bytes passed to and returned from the underlying POSIX API. - Similarly for functions that deal in environment strings (System.Posix.Env): these use untranslated ByteStrings in System.Posix.Environment - There is a new function System.Posix.ByteString.getArgs :: [ByteString] returning the raw untranslated arguments as passed to exec() when the program was started.
Diffstat (limited to 'System/Posix/Directory/ByteString.hsc')
-rw-r--r--System/Posix/Directory/ByteString.hsc155
1 files changed, 155 insertions, 0 deletions
diff --git a/System/Posix/Directory/ByteString.hsc b/System/Posix/Directory/ByteString.hsc
new file mode 100644
index 0000000..9159d05
--- /dev/null
+++ b/System/Posix/Directory/ByteString.hsc
@@ -0,0 +1,155 @@
+{-# LANGUAGE ForeignFunctionInterface #-}
+{-# OPTIONS_GHC -fno-warn-unused-imports #-}
+#if __GLASGOW_HASKELL__ >= 701
+{-# LANGUAGE Trustworthy #-}
+#endif
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : System.Posix.Directory.ByteString
+-- Copyright : (c) The University of Glasgow 2002
+-- License : BSD-style (see the file libraries/base/LICENSE)
+--
+-- Maintainer : libraries@haskell.org
+-- Stability : provisional
+-- Portability : non-portable (requires POSIX)
+--
+-- String-based POSIX directory support
+--
+-----------------------------------------------------------------------------
+
+module System.Posix.Directory.ByteString (
+ -- * Creating and removing directories
+ createDirectory, removeDirectory,
+
+ -- * Reading directories
+ DirStream,
+ openDirStream,
+ readDirStream,
+ rewindDirStream,
+ closeDirStream,
+ DirStreamOffset,
+ tellDirStream,
+ seekDirStream,
+
+ -- * The working dirctory
+ getWorkingDirectory,
+ changeWorkingDirectory,
+ changeWorkingDirectoryFd,
+ ) where
+
+import System.IO.Error
+import System.Posix.Types
+import Foreign
+import Foreign.C
+
+import Data.ByteString.Char8 as BC
+
+import System.Posix.Directory.Common
+import System.Posix.ByteString.FilePath
+
+-- | @createDirectory dir mode@ calls @mkdir@ to
+-- create a new directory, @dir@, with permissions based on
+-- @mode@.
+createDirectory :: RawFilePath -> FileMode -> IO ()
+createDirectory name mode =
+ withFilePath name $ \s ->
+ throwErrnoPathIfMinus1Retry_ "createDirectory" name (c_mkdir s mode)
+ -- POSIX doesn't allow mkdir() to return EINTR, but it does on
+ -- OS X (#5184), so we need the Retry variant here.
+
+foreign import ccall unsafe "mkdir"
+ c_mkdir :: CString -> CMode -> IO CInt
+
+-- | @openDirStream dir@ calls @opendir@ to obtain a
+-- directory stream for @dir@.
+openDirStream :: RawFilePath -> IO DirStream
+openDirStream name =
+ withFilePath name $ \s -> do
+ dirp <- throwErrnoPathIfNullRetry "openDirStream" name $ c_opendir s
+ return (DirStream dirp)
+
+foreign import ccall unsafe "__hsunix_opendir"
+ c_opendir :: CString -> IO (Ptr CDir)
+
+-- | @readDirStream dp@ calls @readdir@ to obtain the
+-- next directory entry (@struct dirent@) for the open directory
+-- stream @dp@, and returns the @d_name@ member of that
+-- structure.
+readDirStream :: DirStream -> IO RawFilePath
+readDirStream (DirStream dirp) =
+ alloca $ \ptr_dEnt -> loop ptr_dEnt
+ where
+ loop ptr_dEnt = do
+ resetErrno
+ r <- c_readdir dirp ptr_dEnt
+ if (r == 0)
+ then do dEnt <- peek ptr_dEnt
+ if (dEnt == nullPtr)
+ then return BC.empty
+ else do
+ entry <- (d_name dEnt >>= peekFilePath)
+ c_freeDirEnt dEnt
+ return entry
+ else do errno <- getErrno
+ if (errno == eINTR) then loop ptr_dEnt else do
+ let (Errno eo) = errno
+ if (eo == 0)
+ then return BC.empty
+ else throwErrno "readDirStream"
+
+-- traversing directories
+foreign import ccall unsafe "__hscore_readdir"
+ c_readdir :: Ptr CDir -> Ptr (Ptr CDirent) -> IO CInt
+
+foreign import ccall unsafe "__hscore_free_dirent"
+ c_freeDirEnt :: Ptr CDirent -> IO ()
+
+foreign import ccall unsafe "__hscore_d_name"
+ d_name :: Ptr CDirent -> IO CString
+
+
+-- | @getWorkingDirectory@ calls @getcwd@ to obtain the name
+-- of the current working directory.
+getWorkingDirectory :: IO RawFilePath
+getWorkingDirectory = do
+ p <- mallocBytes long_path_size
+ go p long_path_size
+ where go p bytes = do
+ p' <- c_getcwd p (fromIntegral bytes)
+ if p' /= nullPtr
+ then do s <- peekFilePath p'
+ free p'
+ return s
+ else do errno <- getErrno
+ if errno == eRANGE
+ then do let bytes' = bytes * 2
+ p'' <- reallocBytes p bytes'
+ go p'' bytes'
+ else throwErrno "getCurrentDirectory"
+
+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 ()
+changeWorkingDirectory path =
+ modifyIOError (`ioeSetFileName` (BC.unpack path)) $
+ withFilePath path $ \s ->
+ throwErrnoIfMinus1Retry_ "changeWorkingDirectory" (c_chdir s)
+
+foreign import ccall unsafe "chdir"
+ c_chdir :: CString -> IO CInt
+
+removeDirectory :: RawFilePath -> IO ()
+removeDirectory path =
+ modifyIOError (`ioeSetFileName` BC.unpack path) $
+ withFilePath path $ \s ->
+ throwErrnoIfMinus1Retry_ "removeDirectory" (c_rmdir s)
+
+foreign import ccall unsafe "rmdir"
+ c_rmdir :: CString -> IO CInt