Copyright | (c) Sergey Vinokurov 2024 |
---|---|
License | Apache-2.0 (see LICENSE) |
Maintainer | serg.foo@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
System.Directory.OsPath.Streaming
Description
You’ll most likely be interested in either
getDirectoryContentsRecursive
to search directory hierarchy recursivelyDirStream
,openDirStream
,readDirStream
, andcloseDirStream
to traverse single directory efficiently
Synopsis
- data DirStream
- openDirStream :: OsPath -> IO DirStream
- readDirStream :: DirStream -> IO (Maybe (OsPath, FileType))
- readDirStreamFull :: DirStream -> IO (Maybe (OsPath, Basename OsPath, FileType))
- closeDirStream :: DirStream -> IO ()
- data SymlinkType
- data FileType
- newtype Basename a = Basename {
- unBasename :: a
- getFileType :: OsPath -> IO FileType
- getDirectoryContentsRecursive :: OsPath -> IO [(OsPath, FileType)]
- getDirectoryContentsWithFilterRecursive :: (Basename OsPath -> SymlinkType -> Bool) -> (Basename OsPath -> Bool) -> OsPath -> IO [(OsPath, FileType)]
- listContentsRecFold :: forall f a b. (Foldable f, Coercible b OsPath) => Maybe Int -> (forall c. OsPath -> b -> Relative OsPath -> Basename OsPath -> SymlinkType -> (a -> IO c -> IO c) -> (IO c -> IO c) -> IO c -> IO c) -> (OsPath -> b -> Relative OsPath -> Basename OsPath -> FileType -> IO (Maybe a)) -> f b -> IO [a]
- regularFile :: FileType
- regularDirectory :: FileType
- regularOther :: FileType
- symlinkFile :: FileType
- symlinkDirectory :: FileType
- symlinkOther :: FileType
Documentation
Abstract handle to directory contents.
May be closed multiple times and will be automatically closed by GC when it goes out of scope.
readDirStream :: DirStream -> IO (Maybe (OsPath, FileType)) Source #
Returns basename path of the directory entry.
readDirStreamFull :: DirStream -> IO (Maybe (OsPath, Basename OsPath, FileType)) Source #
Returns both basename path and full path of a directory entry relative to the
passed DirStream
root.
For example:
readDirStreamFull =<< openDirStream [osp|.|] Just ("./bar",Basename {unBasename = "foo"},File Regular)
readDirStreamFull =<< openDirStream [osp|foo/|] Just ("foo/bar",Basename {unBasename = "foo"},File Regular)
readDirStreamFull =<< openDirStream [osp|/foo/foo|] Just ("/foo/foo/bar",Basename {unBasename = "foo"},File Regular)
This allows to avoid re-creating the full path on the client side and thus reduce allocations.
closeDirStream :: DirStream -> IO () Source #
Deallocate directory handle. It’s safe to close DirStream
multiple times,
unlike the underlying OS-specific directory stream handle.
File types
data SymlinkType Source #
Instances
Constructors
File !SymlinkType | |
Directory !SymlinkType | |
Other !SymlinkType |
Instances
Generic FileType Source # | |||||
Defined in System.Directory.OsPath.Types Associated Types
| |||||
Read FileType Source # | |||||
Show FileType Source # | |||||
NFData FileType Source # | |||||
Defined in System.Directory.OsPath.Types | |||||
Eq FileType Source # | |||||
Ord FileType Source # | |||||
Defined in System.Directory.OsPath.Types | |||||
type Rep FileType Source # | |||||
Defined in System.Directory.OsPath.Types type Rep FileType = D1 ('MetaData "FileType" "System.Directory.OsPath.Types" "directory-ospath-streaming-0.3-FcpYLoE7KT5C5PlPTFRXlJ" 'False) (C1 ('MetaCons "File" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 SymlinkType)) :+: (C1 ('MetaCons "Directory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 SymlinkType)) :+: C1 ('MetaCons "Other" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 SymlinkType)))) |
Basename part of filename, without directory separators.
Constructors
Basename | |
Fields
|
Instances
Foldable Basename Source # | |||||
Defined in System.Directory.OsPath.Types Methods fold :: Monoid m => Basename m -> m # foldMap :: Monoid m => (a -> m) -> Basename a -> m # foldMap' :: Monoid m => (a -> m) -> Basename a -> m # foldr :: (a -> b -> b) -> b -> Basename a -> b # foldr' :: (a -> b -> b) -> b -> Basename a -> b # foldl :: (b -> a -> b) -> b -> Basename a -> b # foldl' :: (b -> a -> b) -> b -> Basename a -> b # foldr1 :: (a -> a -> a) -> Basename a -> a # foldl1 :: (a -> a -> a) -> Basename a -> a # elem :: Eq a => a -> Basename a -> Bool # maximum :: Ord a => Basename a -> a # minimum :: Ord a => Basename a -> a # | |||||
Traversable Basename Source # | |||||
Defined in System.Directory.OsPath.Types | |||||
Functor Basename Source # | |||||
Generic1 Basename Source # | |||||
Defined in System.Directory.OsPath.Types Associated Types
| |||||
Generic (Basename a) Source # | |||||
Defined in System.Directory.OsPath.Types Associated Types
| |||||
Show a => Show (Basename a) Source # | |||||
NFData a => NFData (Basename a) Source # | |||||
Defined in System.Directory.OsPath.Types | |||||
Eq a => Eq (Basename a) Source # | |||||
Ord a => Ord (Basename a) Source # | |||||
Defined in System.Directory.OsPath.Types | |||||
type Rep1 Basename Source # | |||||
Defined in System.Directory.OsPath.Types | |||||
type Rep (Basename a) Source # | |||||
Defined in System.Directory.OsPath.Types |
Get directory contents
getDirectoryContentsRecursive :: OsPath -> IO [(OsPath, FileType)] Source #
Recursively list all the files and directories in a directory and all subdirectories.
The directory structure is traversed depth-first.
The result is generated lazily so is not well defined if the source directory structure changes before the list is fully consumed.
Symlinks within directory structure may cause result to be infinitely long.
getDirectoryContentsWithFilterRecursive Source #
Arguments
:: (Basename OsPath -> SymlinkType -> Bool) | Whether to visit a directory |
-> (Basename OsPath -> Bool) | Whether to collect given directory element, either file or directory. |
-> OsPath | |
-> IO [(OsPath, FileType)] |
Recursively list all the files and directories that satisfy given predicate in a directory and all subdirectories. Descending into some subdirectories may be avoided by filtering them out with a visiting predicate.
Not visited directory entry may still be reported depending on the collection predicate.
The directory structure is traversed depth-first.
The result is generated lazily so is not well defined if the source directory structure changes before the list is fully consumed.
Symlinks within directory structure may cause result to be infinitely long, but they can be filtered out with a suitable directory visiting predicate.
Arguments
:: forall f a b. (Foldable f, Coercible b OsPath) | |
=> Maybe Int | Depth limit if specified, negative values treated the same as positive ones. |
-> (forall c. OsPath -> b -> Relative OsPath -> Basename OsPath -> SymlinkType -> (a -> IO c -> IO c) -> (IO c -> IO c) -> IO c -> IO c) | Decide how to fold directory and its children given its path. Can do IO actions to plan what to do and typically should derive its
result from last Returns Arguments:
The passed |
-> (OsPath -> b -> Relative OsPath -> Basename OsPath -> FileType -> IO (Maybe a)) | What to do with file |
-> f b | Roots to search in, either absolute or relative |
-> IO [a] |
The most general form of gathering directory contents.
Treats symlinks the same as regular files and directories. Folding functions can decide how to handle symlinks.
Both directory and file actions can throw exceptions and this function will try to close finished directory streams promptly (they’ll be closed by GC in the worst case).
Utilities
regularFile :: FileType Source #
Auxiliary constants to refer to different file types without allocations.
regularDirectory :: FileType Source #
Auxiliary constants to refer to different file types without allocations.
regularOther :: FileType Source #
Auxiliary constants to refer to different file types without allocations.
symlinkFile :: FileType Source #
Auxiliary constants to refer to different file types without allocations.
symlinkDirectory :: FileType Source #
Auxiliary constants to refer to different file types without allocations.
symlinkOther :: FileType Source #
Auxiliary constants to refer to different file types without allocations.