{-# LINE 1 "libraries/unix/System/Posix/Directory/ByteString.hsc" #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE NondecreasingIndentation #-}
{-# LANGUAGE Safe #-}
{-# LINE 25 "libraries/unix/System/Posix/Directory/ByteString.hsc" #-}
module System.Posix.Directory.ByteString (
createDirectory, removeDirectory,
DirStream,
openDirStream,
readDirStream,
readDirStreamMaybe,
rewindDirStream,
closeDirStream,
DirStreamOffset,
{-# LINE 39 "libraries/unix/System/Posix/Directory/ByteString.hsc" #-}
tellDirStream,
{-# LINE 41 "libraries/unix/System/Posix/Directory/ByteString.hsc" #-}
{-# LINE 42 "libraries/unix/System/Posix/Directory/ByteString.hsc" #-}
seekDirStream,
{-# LINE 44 "libraries/unix/System/Posix/Directory/ByteString.hsc" #-}
getWorkingDirectory,
changeWorkingDirectory,
changeWorkingDirectoryFd,
) where
import Data.Maybe
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 :: RawFilePath -> FileMode -> IO ()
createDirectory :: RawFilePath -> FileMode -> IO ()
createDirectory RawFilePath
name FileMode
mode =
RawFilePath -> (CString -> IO ()) -> IO ()
forall a. RawFilePath -> (CString -> IO a) -> IO a
withFilePath RawFilePath
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
String -> RawFilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
"createDirectory" RawFilePath
name (CString -> FileMode -> IO CInt
c_mkdir CString
s FileMode
mode)
foreign import ccall unsafe "mkdir"
c_mkdir :: CString -> CMode -> IO CInt
openDirStream :: RawFilePath -> IO DirStream
openDirStream :: RawFilePath -> IO DirStream
openDirStream RawFilePath
name =
RawFilePath -> (CString -> IO DirStream) -> IO DirStream
forall a. RawFilePath -> (CString -> IO a) -> IO a
withFilePath RawFilePath
name ((CString -> IO DirStream) -> IO DirStream)
-> (CString -> IO DirStream) -> IO DirStream
forall a b. (a -> b) -> a -> b
$ \CString
s -> do
dirp <- String -> RawFilePath -> IO (Ptr CDir) -> IO (Ptr CDir)
forall a. String -> RawFilePath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoPathIfNullRetry String
"openDirStream" RawFilePath
name (IO (Ptr CDir) -> IO (Ptr CDir)) -> IO (Ptr CDir) -> IO (Ptr CDir)
forall a b. (a -> b) -> a -> b
$ CString -> IO (Ptr CDir)
c_opendir CString
s
return (DirStream dirp)
foreign import capi unsafe "HsUnix.h opendir"
c_opendir :: CString -> IO (Ptr CDir)
readDirStream :: DirStream -> IO RawFilePath
readDirStream :: DirStream -> IO RawFilePath
readDirStream = (Maybe RawFilePath -> RawFilePath)
-> IO (Maybe RawFilePath) -> IO RawFilePath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (RawFilePath -> Maybe RawFilePath -> RawFilePath
forall a. a -> Maybe a -> a
fromMaybe RawFilePath
BC.empty) (IO (Maybe RawFilePath) -> IO RawFilePath)
-> (DirStream -> IO (Maybe RawFilePath))
-> DirStream
-> IO RawFilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DirStream -> IO (Maybe RawFilePath)
readDirStreamMaybe
readDirStreamMaybe :: DirStream -> IO (Maybe RawFilePath)
readDirStreamMaybe :: DirStream -> IO (Maybe RawFilePath)
readDirStreamMaybe (DirStream Ptr CDir
dirp) =
(Ptr (Ptr CDirent) -> IO (Maybe RawFilePath))
-> IO (Maybe RawFilePath)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr (Ptr CDirent) -> IO (Maybe RawFilePath))
-> IO (Maybe RawFilePath))
-> (Ptr (Ptr CDirent) -> IO (Maybe RawFilePath))
-> IO (Maybe RawFilePath)
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr CDirent)
ptr_dEnt -> Ptr (Ptr CDirent) -> IO (Maybe RawFilePath)
loop Ptr (Ptr CDirent)
ptr_dEnt
where
loop :: Ptr (Ptr CDirent) -> IO (Maybe RawFilePath)
loop Ptr (Ptr CDirent)
ptr_dEnt = do
IO ()
resetErrno
r <- Ptr CDir -> Ptr (Ptr CDirent) -> IO CInt
c_readdir Ptr CDir
dirp Ptr (Ptr CDirent)
ptr_dEnt
if (r == 0)
then do dEnt <- peek ptr_dEnt
if (dEnt == nullPtr)
then return Nothing
else do
entry <- (d_name dEnt >>= peekFilePath)
c_freeDirEnt dEnt
return $ Just entry
else do errno <- getErrno
if (errno == eINTR) then loop ptr_dEnt else do
let (Errno eo) = errno
if (eo == 0)
then return Nothing
else throwErrno "readDirStream"
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 :: IO RawFilePath
getWorkingDirectory :: IO RawFilePath
getWorkingDirectory = Int -> IO RawFilePath
go (Int
4096)
{-# LINE 138 "libraries/unix/System/Posix/Directory/ByteString.hsc" #-}
where
go :: Int -> IO RawFilePath
go Int
bytes = do
r <- Int
-> (CString -> IO (Maybe RawFilePath)) -> IO (Maybe RawFilePath)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
bytes ((CString -> IO (Maybe RawFilePath)) -> IO (Maybe RawFilePath))
-> (CString -> IO (Maybe RawFilePath)) -> IO (Maybe RawFilePath)
forall a b. (a -> b) -> a -> b
$ \CString
buf -> do
buf' <- CString -> CSize -> IO CString
c_getcwd CString
buf (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bytes)
if buf' /= nullPtr
then do s <- peekFilePath buf
return (Just s)
else do errno <- getErrno
if errno == eRANGE
then return Nothing
else throwErrno "getWorkingDirectory"
maybe (go (2 * bytes)) return r
foreign import ccall unsafe "getcwd"
c_getcwd :: Ptr CChar -> CSize -> IO (Ptr CChar)
changeWorkingDirectory :: RawFilePath -> IO ()
changeWorkingDirectory :: RawFilePath -> IO ()
changeWorkingDirectory RawFilePath
path =
RawFilePath -> (CString -> IO ()) -> IO ()
forall a. RawFilePath -> (CString -> IO a) -> IO a
withFilePath RawFilePath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
String -> RawFilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
"changeWorkingDirectory" RawFilePath
path (CString -> IO CInt
c_chdir CString
s)
foreign import ccall unsafe "chdir"
c_chdir :: CString -> IO CInt
removeDirectory :: RawFilePath -> IO ()
removeDirectory :: RawFilePath -> IO ()
removeDirectory RawFilePath
path =
RawFilePath -> (CString -> IO ()) -> IO ()
forall a. RawFilePath -> (CString -> IO a) -> IO a
withFilePath RawFilePath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
String -> RawFilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
"removeDirectory" RawFilePath
path (CString -> IO CInt
c_rmdir CString
s)
foreign import ccall unsafe "rmdir"
c_rmdir :: CString -> IO CInt