5 Commits

Author SHA1 Message Date
d2f89df9b1 Fix build on GHC-7.10.3 2020-05-09 00:50:08 +02:00
5c1d8ed455 Fix build with older GHCs 2020-05-09 00:33:37 +02:00
270d007e40 Use streamly-posix for dircontents wrt #34
Also add getDirsFilesStream.
2020-05-08 23:46:39 +02:00
ae21dbc7fa Improve documentation 2020-04-17 12:48:44 +02:00
014d78e055 Bump hpath-directory to 0.13.3 2020-04-14 23:49:39 +02:00
7 changed files with 52 additions and 14 deletions

View File

@@ -1,5 +1,13 @@
# Revision history for hpath-directory # Revision history for hpath-directory
## 0.13.4 -- 2020-05-08
* Add getDirsFilesStream and use streamly-posix for dircontents (#34)
## 0.13.3 -- 2020-04-14
* Fix tests on mac
## 0.13.2 -- 2020-02-17 ## 0.13.2 -- 2020-02-17
* Fix bug in `createDirRecursive` with trailing path separators * Fix bug in `createDirRecursive` with trailing path separators

View File

@@ -1,7 +1,7 @@
cabal-version: >=1.10 cabal-version: >=1.10
name: hpath-directory name: hpath-directory
version: 0.13.2 version: 0.13.4
synopsis: Alternative to 'directory' package with ByteString based filepaths synopsis: Alternative to 'directory' package with ByteString based filepaths
description: This provides a safer alternative to the 'directory' description: This provides a safer alternative to the 'directory'
package. FilePaths are ByteString based, so this package. FilePaths are ByteString based, so this
@@ -44,7 +44,9 @@ library
, safe-exceptions >= 0.1 , safe-exceptions >= 0.1
, streamly >= 0.7 , streamly >= 0.7
, streamly-bytestring >= 0.1.2 , streamly-bytestring >= 0.1.2
, streamly-posix >= 0.1.0.1
, time >= 1.8 , time >= 1.8
, transformers
, unix >= 2.5 , unix >= 2.5
, unix-bytestring >= 0.3 , unix-bytestring >= 0.3
, utf8-string , utf8-string

View File

@@ -27,7 +27,8 @@
-- Import as: -- Import as:
-- > import System.Posix.RawFilePath.Directory -- > import System.Posix.RawFilePath.Directory
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-} -- streamly
module System.Posix.RawFilePath.Directory module System.Posix.RawFilePath.Directory
( (
@@ -82,6 +83,7 @@ module System.Posix.RawFilePath.Directory
-- * Directory reading -- * Directory reading
, getDirsFiles , getDirsFiles
, getDirsFiles' , getDirsFiles'
, getDirsFilesStream
-- * Filetype operations -- * Filetype operations
, getFileType , getFileType
-- * Others -- * Others
@@ -93,8 +95,11 @@ where
import Control.Applicative ( (<$>) ) import Control.Applicative ( (<$>) )
import Control.Exception.Safe ( IOException import Control.Exception.Safe ( IOException
, MonadCatch
, MonadMask
, bracket , bracket
, bracketOnError , bracketOnError
, onException
, throwIO , throwIO
, finally , finally
) )
@@ -105,6 +110,7 @@ import Control.Monad ( unless
import Control.Monad.Catch ( MonadThrow(..) ) import Control.Monad.Catch ( MonadThrow(..) )
import Control.Monad.Fail ( MonadFail ) import Control.Monad.Fail ( MonadFail )
import Control.Monad.IfElse ( unlessM ) import Control.Monad.IfElse ( unlessM )
import Control.Monad.IO.Class ( liftIO )
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import Data.ByteString ( ByteString ) import Data.ByteString ( ByteString )
import Data.Traversable ( for ) import Data.Traversable ( for )
@@ -155,6 +161,8 @@ import Streamly
import Streamly.External.ByteString import Streamly.External.ByteString
import qualified Streamly.External.ByteString.Lazy import qualified Streamly.External.ByteString.Lazy
as SL as SL
import qualified Streamly.External.Posix.DirStream
as SD
import qualified Streamly.Data.Fold as FL import qualified Streamly.Data.Fold as FL
import Streamly.Memory.Array import Streamly.Memory.Array
import qualified Streamly.FileSystem.Handle as FH import qualified Streamly.FileSystem.Handle as FH
@@ -1147,11 +1155,17 @@ getDirsFiles p = do
-- of prepending the base path. -- of prepending the base path.
getDirsFiles' :: RawFilePath -- ^ dir to read getDirsFiles' :: RawFilePath -- ^ dir to read
-> IO [RawFilePath] -> IO [RawFilePath]
getDirsFiles' fp = do getDirsFiles' fp = getDirsFilesStream fp >>= S.toList
fd <- openFd fp SPI.ReadOnly [SPDF.oNofollow] Nothing
rawContents <- getDirectoryContents' fd
fmap catMaybes $ for rawContents $ \(_, f) -> -- | Like 'getDirsFiles'', except returning a Stream.
if FP.isSpecialDirectoryEntry f then pure Nothing else pure $ Just f getDirsFilesStream :: (MonadCatch m, MonadAsync m, MonadMask m)
=> RawFilePath
-> IO (SerialT m RawFilePath)
getDirsFilesStream fp = do
fd <- openFd fp SPI.ReadOnly [SPDF.oNofollow] Nothing
ds <- SPDT.fdOpendir fd `onException` SPI.closeFd fd
pure $ fmap snd $ SD.dirContentsStream ds

View File

@@ -1,5 +1,9 @@
# Revision history for hpath-io # Revision history for hpath-io
## 0.13.2 -- 2020-05-08
* Add getDirsFilesStream and use streamly-posix for dircontents (#34)
## 0.13.0 -- 2020-01-26 ## 0.13.0 -- 2020-01-26
* switch to using 'hpath-bytestring' for the implementation (this is now just a wrapper module, mostly) * switch to using 'hpath-bytestring' for the implementation (this is now just a wrapper module, mostly)

View File

@@ -1,5 +1,5 @@
name: hpath-io name: hpath-io
version: 0.13.1 version: 0.13.2
synopsis: High-level IO operations on files/directories synopsis: High-level IO operations on files/directories
description: High-level IO operations on files/directories, utilizing type-safe Paths description: High-level IO operations on files/directories, utilizing type-safe Paths
-- bug-reports: -- bug-reports:

View File

@@ -27,7 +27,8 @@
-- For other functions (like `copyFile`), the behavior on these file types is -- For other functions (like `copyFile`), the behavior on these file types is
-- unreliable/unsafe. Check the documentation of those functions for details. -- unreliable/unsafe. Check the documentation of those functions for details.
{-# LANGUAGE PackageImports #-} {-# LANGUAGE FlexibleContexts #-} -- streamly
{-# LANGUAGE PackageImports #-}
module HPath.IO module HPath.IO
( (
@@ -82,6 +83,7 @@ module HPath.IO
-- * Directory reading -- * Directory reading
, getDirsFiles , getDirsFiles
, getDirsFiles' , getDirsFiles'
, getDirsFilesStream
-- * Filetype operations -- * Filetype operations
, getFileType , getFileType
-- * Others -- * Others
@@ -94,7 +96,9 @@ module HPath.IO
where where
import Control.Exception.Safe ( bracketOnError import Control.Exception.Safe ( MonadMask
, MonadCatch
, bracketOnError
, finally , finally
) )
import Control.Monad.Catch ( MonadThrow(..) ) import Control.Monad.Catch ( MonadThrow(..) )
@@ -761,6 +765,15 @@ getDirsFiles' (Path fp) = do
for rawContents $ \r -> parseRel r for rawContents $ \r -> parseRel r
-- | Like 'getDirsFiles'', except returning a Stream.
getDirsFilesStream :: (MonadCatch m, MonadAsync m, MonadMask m)
=> Path b
-> IO (SerialT m (Path Rel))
getDirsFilesStream (Path fp) = do
s <- RD.getDirsFilesStream fp
pure (s >>= parseRel)
--------------------------- ---------------------------

View File

@@ -186,11 +186,8 @@ parseRel filepath =
-- | Parses a path, whether it's relative or absolute. Will lose -- | Parses a path, whether it's relative or absolute.
-- information on whether it's relative or absolute. If you need to know,
-- reparse it.
-- --
-- Filenames must not contain slashes.
-- Excludes '.' and '..'. -- Excludes '.' and '..'.
-- --
-- Throws: 'PathParseException' -- Throws: 'PathParseException'