{-# LINE 1 "libraries/unix/System/Posix/Directory/Common.hsc" #-}
{-# LANGUAGE CPP, Safe, CApiFFI, MultiWayIf, PatternSynonyms #-}
#include "HsUnixConfig.h"
module System.Posix.Directory.Common (
       DirStream(..),
       CDir,
       CDirent,
       DirStreamOffset(..),
       DirStreamWithPath(..),
       fromDirStreamWithPath,
       toDirStreamWithPath,
       DirEnt(..),
       dirEntName,
       dirEntType,
       DirType( DirType
              , UnknownType
              , NamedPipeType
              , CharacterDeviceType
              , DirectoryType
              , BlockDeviceType
              , RegularFileType
              , SymbolicLinkType
              , SocketType
              , WhiteoutType
              ),
       isUnknownType,
       isNamedPipeType,
       isCharacterDeviceType,
       isDirectoryType,
       isBlockDeviceType,
       isRegularFileType,
       isSymbolicLinkType,
       isSocketType,
       isWhiteoutType,
       getRealDirType,
       unsafeOpenDirStreamFd,
       readDirStreamWith,
       readDirStreamWithPtr,
       rewindDirStream,
       closeDirStream,
{-# LINE 61 "libraries/unix/System/Posix/Directory/Common.hsc" #-}
       seekDirStream,
{-# LINE 63 "libraries/unix/System/Posix/Directory/Common.hsc" #-}
{-# LINE 64 "libraries/unix/System/Posix/Directory/Common.hsc" #-}
       tellDirStream,
{-# LINE 66 "libraries/unix/System/Posix/Directory/Common.hsc" #-}
       changeWorkingDirectoryFd,
  ) where
import Control.Exception (mask_)
import Control.Monad (void, when)
import System.Posix.Types
import Foreign hiding (void)
import Foreign.C
{-# LINE 79 "libraries/unix/System/Posix/Directory/Common.hsc" #-}
import System.Posix.Files.Common
newtype DirStream = DirStream (Ptr CDir)
newtype DirStreamWithPath a = DirStreamWithPath (a, Ptr CDir)
fromDirStreamWithPath :: DirStreamWithPath a -> DirStream
fromDirStreamWithPath (DirStreamWithPath (_, ptr)) = DirStream ptr
toDirStreamWithPath :: a -> DirStream -> DirStreamWithPath a
toDirStreamWithPath path (DirStream ptr) = DirStreamWithPath (path, ptr)
newtype DirEnt = DirEnt (Ptr CDirent)
instance Storable DirEnt where
  sizeOf _ = sizeOf (undefined :: Ptr CDirent)
  {-# INLINE sizeOf #-}
  alignment _ = alignment (undefined :: Ptr CDirent)
  {-# INLINE alignment #-}
  peek ptr = DirEnt <$> peek (castPtr ptr)
  {-# INLINE peek #-}
  poke ptr (DirEnt dEnt) = poke (castPtr ptr) dEnt
  {-# INLINE poke#-}
data {-# CTYPE "DIR" #-} CDir
data {-# CTYPE "struct dirent" #-} CDirent
newtype DirType = DirType CChar
    deriving (Eq, Ord, Show)
pattern UnknownType :: DirType
pattern UnknownType = DirType (CONST_DT_UNKNOWN)
pattern NamedPipeType :: DirType
pattern NamedPipeType = DirType (CONST_DT_FIFO)
pattern CharacterDeviceType :: DirType
pattern CharacterDeviceType = DirType (CONST_DT_CHR)
pattern DirectoryType :: DirType
pattern DirectoryType = DirType (CONST_DT_DIR)
pattern BlockDeviceType :: DirType
pattern BlockDeviceType = DirType (CONST_DT_BLK)
pattern RegularFileType :: DirType
pattern RegularFileType = DirType (CONST_DT_REG)
pattern SymbolicLinkType :: DirType
pattern SymbolicLinkType = DirType (CONST_DT_LNK)
pattern SocketType :: DirType
pattern SocketType = DirType (CONST_DT_SOCK)
pattern WhiteoutType :: DirType
pattern WhiteoutType = DirType (CONST_DT_WHT)
isUnknownType         :: DirType -> Bool
isBlockDeviceType     :: DirType -> Bool
isCharacterDeviceType :: DirType -> Bool
isNamedPipeType       :: DirType -> Bool
isRegularFileType     :: DirType -> Bool
isDirectoryType       :: DirType -> Bool
isSymbolicLinkType    :: DirType -> Bool
isSocketType          :: DirType -> Bool
isWhiteoutType        :: DirType -> Bool
isUnknownType dtype = dtype == UnknownType
isBlockDeviceType dtype = dtype == BlockDeviceType
isCharacterDeviceType dtype = dtype == CharacterDeviceType
isNamedPipeType dtype = dtype == NamedPipeType
isRegularFileType dtype = dtype == RegularFileType
isDirectoryType dtype = dtype == DirectoryType
isSymbolicLinkType dtype = dtype == SymbolicLinkType
isSocketType dtype = dtype == SocketType
isWhiteoutType dtype = dtype == WhiteoutType
getRealDirType :: IO FileStatus -> DirType -> IO DirType
getRealDirType _ BlockDeviceType = return BlockDeviceType
getRealDirType _ CharacterDeviceType = return CharacterDeviceType
getRealDirType _ NamedPipeType = return NamedPipeType
getRealDirType _ RegularFileType = return RegularFileType
getRealDirType _ DirectoryType = return DirectoryType
getRealDirType _ SymbolicLinkType = return SymbolicLinkType
getRealDirType _ SocketType = return SocketType
getRealDirType _ WhiteoutType = return WhiteoutType
getRealDirType getFileStatus _ = do
    stat <- getFileStatus
    return $ if | isRegularFile stat -> RegularFileType
                | isDirectory stat -> DirectoryType
                | isSymbolicLink stat -> SymbolicLinkType
                | isBlockDevice stat -> BlockDeviceType
                | isCharacterDevice stat -> CharacterDeviceType
                | isNamedPipe stat -> NamedPipeType
                | isSocket stat -> SocketType
                | otherwise -> UnknownType
unsafeOpenDirStreamFd :: Fd -> IO DirStream
unsafeOpenDirStreamFd (Fd fd) = mask_ $ do
    ptr <- c_fdopendir fd
    when (ptr == nullPtr) $ do
        errno <- getErrno
        void $ c_close fd
        ioError (errnoToIOError "openDirStreamFd" errno Nothing Nothing)
    return $ DirStream ptr
foreign import ccall unsafe "HsUnix.h close"
   c_close :: CInt -> IO CInt
foreign import capi unsafe "dirent.h fdopendir"
    c_fdopendir :: CInt -> IO (Ptr CDir)
readDirStreamWith :: (DirEnt -> IO a) -> DirStream -> IO (Maybe a)
readDirStreamWith f dstream = alloca
  (\ptr_dEnt  -> readDirStreamWithPtr ptr_dEnt f dstream)
readDirStreamWithPtr :: Ptr DirEnt -> (DirEnt -> IO a) -> DirStream -> IO (Maybe a)
readDirStreamWithPtr ptr_dEnt f dstream@(DirStream dirp) = do
  resetErrno
  r <- c_readdir dirp (castPtr ptr_dEnt)
  if (r == 0)
       then do dEnt@(DirEnt dEntPtr) <- peek ptr_dEnt
               if (dEntPtr == nullPtr)
                  then return Nothing
                  else do
                   res <- f dEnt
                   c_freeDirEnt dEntPtr
                   return (Just res)
       else do errno <- getErrno
               if (errno == eINTR)
                  then readDirStreamWithPtr ptr_dEnt f dstream
                  else do
                   let (Errno eo) = errno
                   if (eo == 0)
                      then return Nothing
                      else throwErrno "readDirStream"
dirEntName :: DirEnt -> IO CString
dirEntName (DirEnt dEntPtr) = d_name dEntPtr
foreign import ccall unsafe "__hscore_d_name"
  d_name :: Ptr CDirent -> IO CString
dirEntType :: DirEnt -> IO DirType
dirEntType (DirEnt dEntPtr) = DirType <$> d_type dEntPtr
foreign import ccall unsafe "__hscore_d_type"
  d_type :: Ptr CDirent -> IO CChar
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 ()
rewindDirStream :: DirStream -> IO ()
rewindDirStream (DirStream dirp) = c_rewinddir dirp
foreign import ccall unsafe "rewinddir"
   c_rewinddir :: Ptr CDir -> IO ()
closeDirStream :: DirStream -> IO ()
closeDirStream (DirStream dirp) = do
  throwErrnoIfMinus1Retry_ "closeDirStream" (c_closedir dirp)
foreign import ccall unsafe "closedir"
   c_closedir :: Ptr CDir -> IO CInt
newtype DirStreamOffset = DirStreamOffset COff
{-# LINE 375 "libraries/unix/System/Posix/Directory/Common.hsc" #-}
seekDirStream :: DirStream -> DirStreamOffset -> IO ()
seekDirStream (DirStream dirp) (DirStreamOffset off) =
  c_seekdir dirp (fromIntegral off) 
foreign import ccall unsafe "seekdir"
  c_seekdir :: Ptr CDir -> CLong -> IO ()
{-# LINE 382 "libraries/unix/System/Posix/Directory/Common.hsc" #-}
{-# LINE 384 "libraries/unix/System/Posix/Directory/Common.hsc" #-}
tellDirStream :: DirStream -> IO DirStreamOffset
tellDirStream (DirStream dirp) = do
  off <- c_telldir dirp
  return (DirStreamOffset (fromIntegral off)) 
foreign import ccall unsafe "telldir"
  c_telldir :: Ptr CDir -> IO CLong
{-# LINE 392 "libraries/unix/System/Posix/Directory/Common.hsc" #-}
{-# LINE 394 "libraries/unix/System/Posix/Directory/Common.hsc" #-}
changeWorkingDirectoryFd :: Fd -> IO ()
changeWorkingDirectoryFd (Fd fd) =
  throwErrnoIfMinus1Retry_ "changeWorkingDirectoryFd" (c_fchdir fd)
foreign import ccall unsafe "fchdir"
  c_fchdir :: CInt -> IO CInt
{-# LINE 409 "libraries/unix/System/Posix/Directory/Common.hsc" #-}