Skip to content

Commit

Permalink
Moved changes to System.Posix.Directory.Internals
Browse files Browse the repository at this point in the history
  • Loading branch information
mmhat authored and hasufell committed Jun 24, 2024
1 parent 51f072c commit c011c2f
Show file tree
Hide file tree
Showing 7 changed files with 66 additions and 194 deletions.
54 changes: 3 additions & 51 deletions System/Posix/Directory.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -28,26 +28,10 @@ module System.Posix.Directory (
createDirectory, removeDirectory,

-- * Reading directories
DirStream, DirStreamWithPath,
fromDirStreamWithPath,
DirType( UnknownType
, NamedPipeType
, CharacterDeviceType
, DirectoryType
, BlockDeviceType
, RegularFileType
, SymbolicLinkType
, SocketType
, WhiteoutType
),
isUnknownType, isBlockDeviceType, isCharacterDeviceType, isNamedPipeType,
isRegularFileType, isDirectoryType, isSymbolicLinkType, isSocketType,
isWhiteoutType,
DirStream,
openDirStream,
openDirStreamWithPath,
readDirStream,
readDirStreamMaybe,
readDirStreamWithType,
rewindDirStream,
closeDirStream,
DirStreamOffset,
Expand All @@ -64,15 +48,14 @@ module System.Posix.Directory (
changeWorkingDirectoryFd,
) where

import Control.Monad ((>=>))
import Data.Maybe
import System.FilePath ((</>))
import System.Posix.Error
import System.Posix.Types
import Foreign
import Foreign.C

import System.Posix.Directory.Common
import System.Posix.Files
import System.Posix.Internals (withFilePath, peekFilePath)

-- | @createDirectory dir mode@ calls @mkdir@ to
Expand All @@ -96,11 +79,6 @@ openDirStream name =
dirp <- throwErrnoPathIfNullRetry "openDirStream" name $ c_opendir s
return (DirStream dirp)

-- | A version of 'openDirStream' where the path of the directory is stored in
-- the returned 'DirStreamWithPath'.
openDirStreamWithPath :: FilePath -> IO (DirStreamWithPath FilePath)
openDirStreamWithPath name = toDirStreamWithPath name <$> openDirStream name

foreign import capi unsafe "HsUnix.h opendir"
c_opendir :: CString -> IO (Ptr CDir)

Expand All @@ -121,33 +99,7 @@ readDirStream = fmap (fromMaybe "") . readDirStreamMaybe
-- structure wrapped in a @Just d_name@ if an entry was read and @Nothing@ if
-- the end of the directory stream was reached.
readDirStreamMaybe :: DirStream -> IO (Maybe FilePath)
readDirStreamMaybe = readDirStreamWith
(\(DirEnt dEnt) -> d_name dEnt >>= peekFilePath)

-- | @readDirStreamWithType dp@ calls @readdir@ to obtain the
-- next directory entry (@struct dirent@) for the open directory
-- stream @dp@. It returns the @d_name@ member of that
-- structure together with the entry's type (@d_type@) wrapped in a
-- @Just (d_name, d_type)@ if an entry was read and @Nothing@ if
-- the end of the directory stream was reached.
--
-- __Note__: The returned 'DirType' has some limitations; Please see its
-- documentation.
readDirStreamWithType :: DirStreamWithPath FilePath -> IO (Maybe (FilePath, DirType))
readDirStreamWithType (DirStreamWithPath (base, ptr)) = readDirStreamWith
(\(DirEnt dEnt) -> do
name <- d_name dEnt >>= peekFilePath
let getStat = getFileStatus (base </> name)
dtype <- d_type dEnt >>= getRealDirType getStat . DirType
return (name, dtype)
)
(DirStream ptr)

foreign import ccall unsafe "__hscore_d_name"
d_name :: Ptr CDirent -> IO CString

foreign import ccall unsafe "__hscore_d_type"
d_type :: Ptr CDirent -> IO CChar
readDirStreamMaybe = readDirStreamWith (dirEntName >=> peekFilePath)


-- | @getWorkingDirectory@ calls @getcwd@ to obtain the name
Expand Down
57 changes: 3 additions & 54 deletions System/Posix/Directory/ByteString.hsc
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE NondecreasingIndentation #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Safe #-}

-----------------------------------------------------------------------------
Expand Down Expand Up @@ -29,26 +28,10 @@ module System.Posix.Directory.ByteString (
createDirectory, removeDirectory,

-- * Reading directories
DirStream, DirStreamWithPath,
fromDirStreamWithPath,
DirType( UnknownType
, NamedPipeType
, CharacterDeviceType
, DirectoryType
, BlockDeviceType
, RegularFileType
, SymbolicLinkType
, SocketType
, WhiteoutType
),
isUnknownType, isBlockDeviceType, isCharacterDeviceType, isNamedPipeType,
isRegularFileType, isDirectoryType, isSymbolicLinkType, isSocketType,
isWhiteoutType,
DirStream,
openDirStream,
openDirStreamWithPath,
readDirStream,
readDirStreamMaybe,
readDirStreamWithType,
rewindDirStream,
closeDirStream,
DirStreamOffset,
Expand All @@ -65,18 +48,15 @@ module System.Posix.Directory.ByteString (
changeWorkingDirectoryFd,
) where

import Control.Monad ((>=>))
import Data.Maybe
import System.Posix.Types
import Foreign
import Foreign.C

import Data.ByteString.Char8 as BC
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid ((<>))
#endif

import System.Posix.Directory.Common
import System.Posix.Files.ByteString
import System.Posix.ByteString.FilePath

-- | @createDirectory dir mode@ calls @mkdir@ to
Expand All @@ -100,11 +80,6 @@ openDirStream name =
dirp <- throwErrnoPathIfNullRetry "openDirStream" name $ c_opendir s
return (DirStream dirp)

-- | A version of 'openDirStream' where the path of the directory is stored in
-- the returned 'DirStreamWithPath'.
openDirStreamWithPath :: RawFilePath -> IO (DirStreamWithPath RawFilePath)
openDirStreamWithPath name = toDirStreamWithPath name <$> openDirStream name

foreign import capi unsafe "HsUnix.h opendir"
c_opendir :: CString -> IO (Ptr CDir)

Expand All @@ -125,33 +100,7 @@ readDirStream = fmap (fromMaybe BC.empty) . readDirStreamMaybe
-- structure wrapped in a @Just d_name@ if an entry was read and @Nothing@ if
-- the end of the directory stream was reached.
readDirStreamMaybe :: DirStream -> IO (Maybe RawFilePath)
readDirStreamMaybe = readDirStreamWith
(\(DirEnt dEnt) -> d_name dEnt >>= peekFilePath)

-- | @readDirStreamWithType dp@ calls @readdir@ to obtain the
-- next directory entry (@struct dirent@) for the open directory
-- stream @dp@. It returns the @d_name@ member of that
-- structure together with the entry's type (@d_type@) wrapped in a
-- @Just (d_name, d_type)@ if an entry was read and @Nothing@ if
-- the end of the directory stream was reached.
--
-- __Note__: The returned 'DirType' has some limitations; Please see its
-- documentation.
readDirStreamWithType :: DirStreamWithPath RawFilePath -> IO (Maybe (RawFilePath, DirType))
readDirStreamWithType (DirStreamWithPath (base, ptr)) = readDirStreamWith
(\(DirEnt dEnt) -> do
name <- d_name dEnt >>= peekFilePath
let getStat = getFileStatus (base <> "/" <> name)
dtype <- d_type dEnt >>= getRealDirType getStat . DirType
return (name, dtype)
)
(DirStream ptr)

foreign import ccall unsafe "__hscore_d_name"
d_name :: Ptr CDirent -> IO CString

foreign import ccall unsafe "__hscore_d_type"
d_type :: Ptr CDirent -> IO CChar
readDirStreamMaybe = readDirStreamWith (dirEntName >=> peekFilePath)


-- | @getWorkingDirectory@ calls @getcwd@ to obtain the name
Expand Down
27 changes: 24 additions & 3 deletions System/Posix/Directory/Common.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -19,9 +19,16 @@
##include "HsUnixConfig.h"

module System.Posix.Directory.Common (
DirStream(..), DirStreamWithPath(..),
fromDirStreamWithPath, toDirStreamWithPath,
DirEnt(..), CDir, CDirent, DirStreamOffset(..),
DirStream(..),
CDir,
DirStreamWithPath(..),
fromDirStreamWithPath,
toDirStreamWithPath,

DirEnt(..),
CDirent,
dirEntName,
dirEntType,
DirType( DirType
, UnknownType
, NamedPipeType
Expand All @@ -40,6 +47,8 @@ module System.Posix.Directory.Common (
unsafeOpenDirStreamFd,
readDirStreamWith,
readDirStreamWithPtr,

DirStreamOffset(..),
rewindDirStream,
closeDirStream,
#ifdef HAVE_SEEKDIR
Expand Down Expand Up @@ -282,6 +291,18 @@ readDirStreamWithPtr ptr_dEnt f dstream@(DirStream dirp) = do
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

-- traversing directories
foreign import ccall unsafe "__hscore_readdir"
c_readdir :: Ptr CDir -> Ptr (Ptr CDirent) -> IO CInt
Expand Down
36 changes: 33 additions & 3 deletions System/Posix/Directory/Internals.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -13,9 +13,39 @@
-----------------------------------------------------------------------------

module System.Posix.Directory.Internals (
DirStream(..), DirEnt(..), DirType(..), CDir, CDirent, DirStreamOffset(..),
readDirStreamWith,
readDirStreamWithPtr,
DirStream(..),
CDir,
DirStreamWithPath(..),
fromDirStreamWithPath,
toDirStreamWithPath,
DirEnt(..),
CDirent,
dirEntName,
dirEntType,
DirType( DirType
, UnknownType
, NamedPipeType
, CharacterDeviceType
, DirectoryType
, BlockDeviceType
, RegularFileType
, SymbolicLinkType
, SocketType
, WhiteoutType
),
isUnknownType,
isNamedPipeType,
isCharacterDeviceType,
isDirectoryType,
isBlockDeviceType,
isRegularFileType,
isSymbolicLinkType,
isSocketType,
isWhiteoutType,
getRealDirType,
readDirStreamWith,
readDirStreamWithPtr,
DirStreamOffset(..),
) where

import System.Posix.Directory.Common
52 changes: 3 additions & 49 deletions System/Posix/Directory/PosixPath.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -27,26 +27,10 @@ module System.Posix.Directory.PosixPath (
createDirectory, removeDirectory,

-- * Reading directories
Common.DirStream, Common.DirStreamWithPath,
Common.fromDirStreamWithPath,
Common.DirType( UnknownType
, NamedPipeType
, CharacterDeviceType
, DirectoryType
, BlockDeviceType
, RegularFileType
, SymbolicLinkType
, SocketType
, WhiteoutType
),
Common.isUnknownType, Common.isBlockDeviceType, Common.isCharacterDeviceType,
Common.isNamedPipeType, Common.isRegularFileType, Common.isDirectoryType,
Common.isSymbolicLinkType, Common.isSocketType, Common.isWhiteoutType,
Common.DirStream,
openDirStream,
openDirStreamWithPath,
readDirStream,
readDirStreamMaybe,
readDirStreamWithType,
Common.rewindDirStream,
Common.closeDirStream,
Common.DirStreamOffset,
Expand All @@ -63,14 +47,14 @@ module System.Posix.Directory.PosixPath (
Common.changeWorkingDirectoryFd,
) where

import Control.Monad ((>=>))
import Data.Maybe
import System.Posix.Types
import Foreign
import Foreign.C

import System.OsPath.Posix
import qualified System.Posix.Directory.Common as Common
import System.Posix.Files.PosixString
import System.Posix.PosixPath.FilePath

-- | @createDirectory dir mode@ calls @mkdir@ to
Expand All @@ -94,11 +78,6 @@ openDirStream name =
dirp <- throwErrnoPathIfNullRetry "openDirStream" name $ c_opendir s
return (Common.DirStream dirp)

-- | A version of 'openDirStream' where the path of the directory is stored in
-- the returned 'DirStreamWithPath'.
openDirStreamWithPath :: PosixPath -> IO (Common.DirStreamWithPath PosixPath)
openDirStreamWithPath name = Common.toDirStreamWithPath name <$> openDirStream name

foreign import capi unsafe "HsUnix.h opendir"
c_opendir :: CString -> IO (Ptr Common.CDir)

Expand All @@ -120,32 +99,7 @@ readDirStream = fmap (fromMaybe mempty) . readDirStreamMaybe
-- the end of the directory stream was reached.
readDirStreamMaybe :: Common.DirStream -> IO (Maybe PosixPath)
readDirStreamMaybe = Common.readDirStreamWith
(\(Common.DirEnt dEnt) -> d_name dEnt >>= peekFilePath)

-- | @readDirStreamWithType dp@ calls @readdir@ to obtain the
-- next directory entry (@struct dirent@) for the open directory
-- stream @dp@. It returns the @d_name@ member of that
-- structure together with the entry's type (@d_type@) wrapped in a
-- @Just (d_name, d_type)@ if an entry was read and @Nothing@ if
-- the end of the directory stream was reached.
--
-- __Note__: The returned 'DirType' has some limitations; Please see its
-- documentation.
readDirStreamWithType :: Common.DirStreamWithPath PosixPath -> IO (Maybe (PosixPath, Common.DirType))
readDirStreamWithType (Common.DirStreamWithPath (base, ptr))= Common.readDirStreamWith
(\(Common.DirEnt dEnt) -> do
name <- d_name dEnt >>= peekFilePath
let getStat = getFileStatus (base </> name)
dtype <- d_type dEnt >>= Common.getRealDirType getStat . Common.DirType
return (name, dtype)
)
(Common.DirStream ptr)

foreign import ccall unsafe "__hscore_d_name"
d_name :: Ptr Common.CDirent -> IO CString

foreign import ccall unsafe "__hscore_d_type"
d_type :: Ptr Common.CDirent -> IO CChar
(Common.dirEntName >=> peekFilePath)


-- | @getWorkingDirectory@ calls @getcwd@ to obtain the name
Expand Down
Loading

0 comments on commit c011c2f

Please sign in to comment.