{-# LINE 1 "System/Posix/Directory/PosixPath.hsc" #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE NondecreasingIndentation #-}
{-# LINE 24 "System/Posix/Directory/PosixPath.hsc" #-}
module System.Posix.Directory.PosixPath (
   
   createDirectory, removeDirectory,
   
   DirStream,
   openDirStream,
   readDirStream,
   rewindDirStream,
   closeDirStream,
   DirStreamOffset,
{-# LINE 37 "System/Posix/Directory/PosixPath.hsc" #-}
   tellDirStream,
{-# LINE 39 "System/Posix/Directory/PosixPath.hsc" #-}
{-# LINE 40 "System/Posix/Directory/PosixPath.hsc" #-}
   seekDirStream,
{-# LINE 42 "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 name mode =
  withFilePath name $ \s ->
    throwErrnoPathIfMinus1Retry_ "createDirectory" name (c_mkdir s mode)
    
    
foreign import ccall unsafe "mkdir"
  c_mkdir :: CString -> CMode -> IO CInt
openDirStream :: PosixPath -> IO DirStream
openDirStream name =
  withFilePath name $ \s -> do
    dirp <- throwErrnoPathIfNullRetry "openDirStream" name $ c_opendir s
    return (Common.DirStream dirp)
foreign import capi unsafe "HsUnix.h opendir"
   c_opendir :: CString  -> IO (Ptr Common.CDir)
readDirStream :: DirStream -> IO PosixPath
readDirStream (Common.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 mempty
                    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 mempty
                    else throwErrno "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 = go (4096)
{-# LINE 122 "System/Posix/Directory/PosixPath.hsc" #-}
  where
    go bytes = do
        r <- allocaBytes bytes $ \buf -> do
            buf' <- c_getcwd buf (fromIntegral 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 :: PosixPath -> IO ()
changeWorkingDirectory path =
  withFilePath path $ \s ->
     throwErrnoPathIfMinus1Retry_ "changeWorkingDirectory" path (c_chdir s)
foreign import ccall unsafe "chdir"
   c_chdir :: CString -> IO CInt
removeDirectory :: PosixPath -> IO ()
removeDirectory path =
  withFilePath path $ \s ->
     throwErrnoPathIfMinus1Retry_ "removeDirectory" path (c_rmdir s)
foreign import ccall unsafe "rmdir"
   c_rmdir :: CString -> IO CInt