{-# LINE 1 "libraries/unix/System/Posix/Directory/PosixPath.hsc" #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE NondecreasingIndentation #-}
{-# LINE 24 "libraries/unix/System/Posix/Directory/PosixPath.hsc" #-}
module System.Posix.Directory.PosixPath (
createDirectory, removeDirectory,
DirStream,
openDirStream,
readDirStream,
rewindDirStream,
closeDirStream,
DirStreamOffset,
{-# LINE 37 "libraries/unix/System/Posix/Directory/PosixPath.hsc" #-}
tellDirStream,
{-# LINE 39 "libraries/unix/System/Posix/Directory/PosixPath.hsc" #-}
{-# LINE 40 "libraries/unix/System/Posix/Directory/PosixPath.hsc" #-}
seekDirStream,
{-# LINE 42 "libraries/unix/System/Posix/Directory/PosixPath.hsc" #-}
getWorkingDirectory,
changeWorkingDirectory,
changeWorkingDirectoryFd,
) where
import System.Posix.Types
import Foreign
import Foreign.C
import System.OsPath.Types
import System.Posix.Directory hiding (createDirectory, openDirStream, readDirStream, getWorkingDirectory, changeWorkingDirectory, removeDirectory)
import qualified System.Posix.Directory.Common as Common
import System.Posix.PosixPath.FilePath
createDirectory :: PosixPath -> FileMode -> IO ()
createDirectory :: PosixPath -> FileMode -> IO ()
createDirectory PosixPath
name FileMode
mode =
PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
"createDirectory" PosixPath
name (CString -> FileMode -> IO CInt
c_mkdir CString
s FileMode
mode)
foreign import ccall unsafe "mkdir"
c_mkdir :: CString -> CMode -> IO CInt
openDirStream :: PosixPath -> IO DirStream
openDirStream :: PosixPath -> IO DirStream
openDirStream PosixPath
name =
PosixPath -> (CString -> IO DirStream) -> IO DirStream
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO DirStream) -> IO DirStream)
-> (CString -> IO DirStream) -> IO DirStream
forall a b. (a -> b) -> a -> b
$ \CString
s -> do
Ptr CDir
dirp <- String -> PosixPath -> IO (Ptr CDir) -> IO (Ptr CDir)
forall a. String -> PosixPath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoPathIfNullRetry String
"openDirStream" PosixPath
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
DirStream -> IO DirStream
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr CDir -> DirStream
Common.DirStream Ptr CDir
dirp)
foreign import capi unsafe "HsUnix.h opendir"
c_opendir :: CString -> IO (Ptr Common.CDir)
readDirStream :: DirStream -> IO PosixPath
readDirStream :: DirStream -> IO PosixPath
readDirStream (Common.DirStream Ptr CDir
dirp) = (Ptr (Ptr CDirent) -> IO PosixPath) -> IO PosixPath
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr (Ptr CDirent) -> IO PosixPath) -> IO PosixPath)
-> (Ptr (Ptr CDirent) -> IO PosixPath) -> IO PosixPath
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr CDirent)
ptr_dEnt -> Ptr (Ptr CDirent) -> IO PosixPath
loop Ptr (Ptr CDirent)
ptr_dEnt
where
loop :: Ptr (Ptr CDirent) -> IO PosixPath
loop Ptr (Ptr CDirent)
ptr_dEnt = do
IO ()
resetErrno
CInt
r <- Ptr CDir -> Ptr (Ptr CDirent) -> IO CInt
c_readdir Ptr CDir
dirp Ptr (Ptr CDirent)
ptr_dEnt
if (CInt
r CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
0)
then do Ptr CDirent
dEnt <- Ptr (Ptr CDirent) -> IO (Ptr CDirent)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CDirent)
ptr_dEnt
if (Ptr CDirent
dEnt Ptr CDirent -> Ptr CDirent -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr CDirent
forall a. Ptr a
nullPtr)
then PosixPath -> IO PosixPath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PosixPath
forall a. Monoid a => a
mempty
else do
PosixPath
entry <- (Ptr CDirent -> IO CString
d_name Ptr CDirent
dEnt IO CString -> (CString -> IO PosixPath) -> IO PosixPath
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO PosixPath
peekFilePath)
Ptr CDirent -> IO ()
c_freeDirEnt Ptr CDirent
dEnt
PosixPath -> IO PosixPath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PosixPath
entry
else do Errno
errno <- IO Errno
getErrno
if (Errno
errno Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
eINTR) then Ptr (Ptr CDirent) -> IO PosixPath
loop Ptr (Ptr CDirent)
ptr_dEnt else do
let (Errno CInt
eo) = Errno
errno
if (CInt
eo CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
0)
then PosixPath -> IO PosixPath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PosixPath
forall a. Monoid a => a
mempty
else String -> IO PosixPath
forall a. String -> IO a
throwErrno String
"readDirStream"
foreign import ccall unsafe "__hscore_readdir"
c_readdir :: Ptr Common.CDir -> Ptr (Ptr Common.CDirent) -> IO CInt
foreign import ccall unsafe "__hscore_free_dirent"
c_freeDirEnt :: Ptr Common.CDirent -> IO ()
foreign import ccall unsafe "__hscore_d_name"
d_name :: Ptr Common.CDirent -> IO CString
getWorkingDirectory :: IO PosixPath
getWorkingDirectory :: IO PosixPath
getWorkingDirectory = Int -> IO PosixPath
go (Int
4096)
{-# LINE 122 "libraries/unix/System/Posix/Directory/PosixPath.hsc" #-}
where
go :: Int -> IO PosixPath
go Int
bytes = do
Maybe PosixPath
r <- Int -> (CString -> IO (Maybe PosixPath)) -> IO (Maybe PosixPath)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
bytes ((CString -> IO (Maybe PosixPath)) -> IO (Maybe PosixPath))
-> (CString -> IO (Maybe PosixPath)) -> IO (Maybe PosixPath)
forall a b. (a -> b) -> a -> b
$ \CString
buf -> do
CString
buf' <- CString -> CSize -> IO CString
c_getcwd CString
buf (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bytes)
if CString
buf' CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
/= CString
forall a. Ptr a
nullPtr
then do PosixPath
s <- CString -> IO PosixPath
peekFilePath CString
buf
Maybe PosixPath -> IO (Maybe PosixPath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (PosixPath -> Maybe PosixPath
forall a. a -> Maybe a
Just PosixPath
s)
else do Errno
errno <- IO Errno
getErrno
if Errno
errno Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
eRANGE
then Maybe PosixPath -> IO (Maybe PosixPath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PosixPath
forall a. Maybe a
Nothing
else String -> IO (Maybe PosixPath)
forall a. String -> IO a
throwErrno String
"getWorkingDirectory"
IO PosixPath
-> (PosixPath -> IO PosixPath) -> Maybe PosixPath -> IO PosixPath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Int -> IO PosixPath
go (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
bytes)) PosixPath -> IO PosixPath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PosixPath
r
foreign import ccall unsafe "getcwd"
c_getcwd :: Ptr CChar -> CSize -> IO (Ptr CChar)
changeWorkingDirectory :: PosixPath -> IO ()
changeWorkingDirectory :: PosixPath -> IO ()
changeWorkingDirectory PosixPath
path =
PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
"changeWorkingDirectory" PosixPath
path (CString -> IO CInt
c_chdir CString
s)
foreign import ccall unsafe "chdir"
c_chdir :: CString -> IO CInt
removeDirectory :: PosixPath -> IO ()
removeDirectory :: PosixPath -> IO ()
removeDirectory PosixPath
path =
PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
"removeDirectory" PosixPath
path (CString -> IO CInt
c_rmdir CString
s)
foreign import ccall unsafe "rmdir"
c_rmdir :: CString -> IO CInt