directory-contents-0.2.0.2: Recursively build, navigate, and operate on a tree of directory contents.
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.Directory.Contents.Types

Contents

Description

 
Synopsis

Documentation

data DirTree a Source #

The contents of a directory, represented as a tree. See Symlink for special handling of symlinks.

Instances

Instances details
Foldable DirTree Source # 
Instance details

Defined in System.Directory.Contents.Types

Methods

fold :: Monoid m => DirTree m -> m #

foldMap :: Monoid m => (a -> m) -> DirTree a -> m #

foldMap' :: Monoid m => (a -> m) -> DirTree a -> m #

foldr :: (a -> b -> b) -> b -> DirTree a -> b #

foldr' :: (a -> b -> b) -> b -> DirTree a -> b #

foldl :: (b -> a -> b) -> b -> DirTree a -> b #

foldl' :: (b -> a -> b) -> b -> DirTree a -> b #

foldr1 :: (a -> a -> a) -> DirTree a -> a #

foldl1 :: (a -> a -> a) -> DirTree a -> a #

toList :: DirTree a -> [a] #

null :: DirTree a -> Bool #

length :: DirTree a -> Int #

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

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

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

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

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

Traversable DirTree Source # 
Instance details

Defined in System.Directory.Contents.Types

Methods

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

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

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

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

Functor DirTree Source # 
Instance details

Defined in System.Directory.Contents.Types

Methods

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

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

Data a => Data (DirTree a) Source # 
Instance details

Defined in System.Directory.Contents.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirTree a -> c (DirTree a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DirTree a) #

toConstr :: DirTree a -> Constr #

dataTypeOf :: DirTree a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DirTree a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DirTree a)) #

gmapT :: (forall b. Data b => b -> b) -> DirTree a -> DirTree a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirTree a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirTree a -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirTree a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirTree a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirTree a -> m (DirTree a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirTree a -> m (DirTree a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirTree a -> m (DirTree a) #

Generic (DirTree a) Source # 
Instance details

Defined in System.Directory.Contents.Types

Methods

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

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

Read a => Read (DirTree a) Source # 
Instance details

Defined in System.Directory.Contents.Types

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

Defined in System.Directory.Contents.Types

Methods

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

show :: DirTree a -> String #

showList :: [DirTree a] -> ShowS #

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

Defined in System.Directory.Contents.Types

Methods

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

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

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

Defined in System.Directory.Contents.Types

Methods

compare :: DirTree a -> DirTree a -> Ordering #

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

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

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

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

max :: DirTree a -> DirTree a -> DirTree a #

min :: DirTree a -> DirTree a -> DirTree a #

type Rep (DirTree a) Source # 
Instance details

Defined in System.Directory.Contents.Types

data Symlink a Source #

Symlink cycles are prevented by separating symlinks into two categories: those that point to paths already within the directory hierarchy being recursively listed, and those that are not. In the former case, rather than following the symlink and listing the target redundantly, we simply store the symlink reference itself. In the latter case, we treat the symlink as we would any other folder and produce a list of its contents.

The String argument represents the symlink reference (e.g., "../somefile"). In the Symlink_Internal case, the second (FilePath) argument is the path to the symlink target. In the Symlink_External case, the second ([DirTree a]) argument contains the contents of the symlink target.

Instances

Utilities

filePath :: DirTree a -> FilePath Source #

Extract the FilePath from a DirTree node

type FileName = String Source #

File names, as opposed to file paths, are used to uniquely identify siblings at each level

fileName :: DirTree a -> FileName Source #

Generate the key used to identify siblings

fileNameMap :: [DirTree a] -> Map FileName (DirTree a) Source #

Construct a map of files indexed by filename. Should only be used for a particular generation or level in the directory hierarchy (since that's the only time we can be sure that names are unique)

insertSibling :: DirTree a -> Map FileName (DirTree a) -> Map FileName (DirTree a) Source #

Add a sibling to a map of files

removeSibling :: DirTree a -> Map FileName (DirTree a) -> Map FileName (DirTree a) Source #

Remove sibling from a map of files

withFirstChild :: Map FileName (DirTree a) -> (DirTree a -> Map FileName (DirTree a) -> x) -> Maybe x Source #

Map a function over the first child and the rest of the children