directory-ospath-streaming-0.2: Stream directory entries in constant memory in vanilla IO
Copyright(c) Sergey Vinokurov 2024
LicenseApache-2.0 (see LICENSE)
Maintainerserg.foo@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.Directory.OsPath.Streaming

Description

You’ll most likely be interested in either

Synopsis

Documentation

data DirStream Source #

Abstract handle to directory contents.

May be closed multiple times and will be automatically closed by GC when it goes out of scope.

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 #

Constructors

Regular 
Symlink 

Instances

Instances details
Generic SymlinkType Source # 
Instance details

Defined in System.Directory.OsPath.Types

Associated Types

type Rep SymlinkType :: Type -> Type #

Read SymlinkType Source # 
Instance details

Defined in System.Directory.OsPath.Types

Show SymlinkType Source # 
Instance details

Defined in System.Directory.OsPath.Types

NFData SymlinkType Source # 
Instance details

Defined in System.Directory.OsPath.Types

Methods

rnf :: SymlinkType -> () #

Eq SymlinkType Source # 
Instance details

Defined in System.Directory.OsPath.Types

Ord SymlinkType Source # 
Instance details

Defined in System.Directory.OsPath.Types

type Rep SymlinkType Source # 
Instance details

Defined in System.Directory.OsPath.Types

type Rep SymlinkType = D1 ('MetaData "SymlinkType" "System.Directory.OsPath.Types" "directory-ospath-streaming-0.2-7RVORjIhdhMHkPO5xAl8fN" 'False) (C1 ('MetaCons "Regular" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Symlink" 'PrefixI 'False) (U1 :: Type -> Type))

data FileType Source #

Instances

Instances details
Generic FileType Source # 
Instance details

Defined in System.Directory.OsPath.Types

Associated Types

type Rep FileType :: Type -> Type #

Methods

from :: FileType -> Rep FileType x #

to :: Rep FileType x -> FileType #

Read FileType Source # 
Instance details

Defined in System.Directory.OsPath.Types

Show FileType Source # 
Instance details

Defined in System.Directory.OsPath.Types

NFData FileType Source # 
Instance details

Defined in System.Directory.OsPath.Types

Methods

rnf :: FileType -> () #

Eq FileType Source # 
Instance details

Defined in System.Directory.OsPath.Types

Ord FileType Source # 
Instance details

Defined in System.Directory.OsPath.Types

type Rep FileType Source # 
Instance details

Defined in System.Directory.OsPath.Types

type Rep FileType = D1 ('MetaData "FileType" "System.Directory.OsPath.Types" "directory-ospath-streaming-0.2-7RVORjIhdhMHkPO5xAl8fN" '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))))

newtype Basename a Source #

Basename part of filename, without directory separators.

Constructors

Basename 

Fields

Instances

Instances details
Foldable Basename Source # 
Instance details

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 #

toList :: Basename a -> [a] #

null :: Basename a -> Bool #

length :: Basename a -> Int #

elem :: Eq a => a -> Basename a -> Bool #

maximum :: Ord a => Basename a -> a #

minimum :: Ord a => Basename a -> a #

sum :: Num a => Basename a -> a #

product :: Num a => Basename a -> a #

Traversable Basename Source # 
Instance details

Defined in System.Directory.OsPath.Types

Methods

traverse :: Applicative f => (a -> f b) -> Basename a -> f (Basename b) #

sequenceA :: Applicative f => Basename (f a) -> f (Basename a) #

mapM :: Monad m => (a -> m b) -> Basename a -> m (Basename b) #

sequence :: Monad m => Basename (m a) -> m (Basename a) #

Functor Basename Source # 
Instance details

Defined in System.Directory.OsPath.Types

Methods

fmap :: (a -> b) -> Basename a -> Basename b #

(<$) :: a -> Basename b -> Basename a #

Generic1 Basename Source # 
Instance details

Defined in System.Directory.OsPath.Types

Associated Types

type Rep1 Basename :: k -> Type #

Methods

from1 :: forall (a :: k). Basename a -> Rep1 Basename a #

to1 :: forall (a :: k). Rep1 Basename a -> Basename a #

Generic (Basename a) Source # 
Instance details

Defined in System.Directory.OsPath.Types

Associated Types

type Rep (Basename a) :: Type -> Type #

Methods

from :: Basename a -> Rep (Basename a) x #

to :: Rep (Basename a) x -> Basename a #

Show a => Show (Basename a) Source # 
Instance details

Defined in System.Directory.OsPath.Types

Methods

showsPrec :: Int -> Basename a -> ShowS #

show :: Basename a -> String #

showList :: [Basename a] -> ShowS #

NFData a => NFData (Basename a) Source # 
Instance details

Defined in System.Directory.OsPath.Types

Methods

rnf :: Basename a -> () #

Eq a => Eq (Basename a) Source # 
Instance details

Defined in System.Directory.OsPath.Types

Methods

(==) :: Basename a -> Basename a -> Bool #

(/=) :: Basename a -> Basename a -> Bool #

Ord a => Ord (Basename a) Source # 
Instance details

Defined in System.Directory.OsPath.Types

Methods

compare :: Basename a -> Basename a -> Ordering #

(<) :: Basename a -> Basename a -> Bool #

(<=) :: Basename a -> Basename a -> Bool #

(>) :: Basename a -> Basename a -> Bool #

(>=) :: Basename a -> Basename a -> Bool #

max :: Basename a -> Basename a -> Basename a #

min :: Basename a -> Basename a -> Basename a #

type Rep1 Basename Source # 
Instance details

Defined in System.Directory.OsPath.Types

type Rep1 Basename = D1 ('MetaData "Basename" "System.Directory.OsPath.Types" "directory-ospath-streaming-0.2-7RVORjIhdhMHkPO5xAl8fN" 'True) (C1 ('MetaCons "Basename" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBasename") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Basename a) Source # 
Instance details

Defined in System.Directory.OsPath.Types

type Rep (Basename a) = D1 ('MetaData "Basename" "System.Directory.OsPath.Types" "directory-ospath-streaming-0.2-7RVORjIhdhMHkPO5xAl8fN" 'True) (C1 ('MetaCons "Basename" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBasename") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

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.

listContentsRecFold Source #

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 IO c argument.

Returns IO c where c is hidden from the user so the only way to make it is to construct from the passed IO c action.

Arguments:

  • OsPath - absolute path to the visited directory
  • b - root of the visited directory as passed originally in f b to the bigger fold function
  • Relative OsPath - path to the visited directory relative to the previous b argument
  • Basename OsPath - name of the visited directory without slashes
  • SymlinkType - symlink status of the visited directory
  • (a -> IO c -> IO c) - can be used to record some output (a) about the directory itself
  • (IO c -> IO c) - traverse inside this directory, can be ignored to skip its children
  • IO c - continue scanning not yet visited parts, must be used to construct return value (otherwise it won’t typecheck!)

The passed (IO c -> IO c) argument function should (but is not required to) be applied in the returned function and it will prepend results for subdirectories of the directory being analyzed. If not applied these subdirectories will be skipped, this way ignoring particular directory and all its children can be achieved.

-> (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.