directory-contents-0.1.0.0: Recursively build a tree of directory contents.

Safe HaskellNone
LanguageHaskell2010

System.Directory.Contents

Contents

Description

Modeled after the linux tree command (when invoked with the follow-symlinks option), this module recursively lists the contents of a directory while avoiding symlink loops. See the documentation of buildDirTree for an example.

In addition to building the directory-contents tree, this module provides facilities for filtering, displaying, and navigating the directory hierarchy.

Synopsis

Documentation

data DirTree a Source #

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

Instances
Functor DirTree Source # 
Instance details

Defined in System.Directory.Contents

Methods

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

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

Foldable DirTree Source # 
Instance details

Defined in System.Directory.Contents

Methods

fold :: Monoid m => DirTree m -> 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

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) #

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

Defined in System.Directory.Contents

Methods

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

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

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

Defined in System.Directory.Contents

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 #

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

Defined in System.Directory.Contents

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

Defined in System.Directory.Contents

Methods

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

show :: DirTree a -> String #

showList :: [DirTree a] -> ShowS #

Generic (DirTree a) Source # 
Instance details

Defined in System.Directory.Contents

Associated Types

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

Methods

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

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

type Rep (DirTree a) Source # 
Instance details

Defined in System.Directory.Contents

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.

Constructing a tree

buildDirTree :: FilePath -> IO (Maybe (DirTree FilePath)) Source #

Recursively list the contents of a FilePath, representing the results as a hierarchical DirTree. This function should produce results similar to the linux command tree -l.

For example, given this directory and symlink structure (as shown by tree -l):

test
├── A
│   ├── a
│   ├── A -> ../A  [recursive, not followed]
│   └── B -> ../B
│       ├── A -> ../A  [recursive, not followed]
│       └── b
├── B
│   ├── A -> ../A  [recursive, not followed]
│   └── b
└── C -> ../C
    └── c

this function will produce the following (as rendererd by drawDirTree):

test
|
+- A
|  |
|  +- A -> ../A
|  |
|  +- B -> ../B
|  |
|  `- a
|
+- B
|  |
|  +- A -> ../A
|  |
|  `- b
|
`- C -> ../C
   |
   `- c

dereferenceSymlinks :: DirTree FilePath -> IO (DirTree FilePath) Source #

De-reference one layer of symlinks

Example

Expand

Given:

tmp
|
+- A
|  |
|  `- a
|
+- a -> A/a
|
`- C
   |
   `- A -> ../A

This function will follow one level of symlinks, producing:

tmp
|
+- A
|  |
|  `- a
|
+- a
|
`- C
   |
   `- A
      |
      `- a

Navigate

walkDirTree :: FilePath -> DirTree a -> Maybe (DirTree a) Source #

Starting from the root directory, try to walk the given filepath and return the DirTree at the end of the route. For example, given the following tree:

src
└── System
    └── Directory
            └── Contents.hs

walkDirTree "src/System" should produce

Directory
|
`- Contents.hs

This function does not dereference symlinks, nor does it handle the special paths . and ...

walkContents :: FilePath -> DirTree a -> Maybe (DirTree a) Source #

Like walkDirTree but skips the outermost containing directory. Useful for walking paths relative from the root directory passed to buildDirTree.

Given the following DirTree:

src
└── System
    └── Directory
            └── Contents.hs

walkContents System should produce

Directory
|
`- Contents.hs

Filter

newtype DirTreeMaybe a Source #

This wrapper really just represents the no-path/empty case so that filtering works

Constructors

DirTreeMaybe 
Instances
Functor DirTreeMaybe Source # 
Instance details

Defined in System.Directory.Contents

Methods

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

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

Foldable DirTreeMaybe Source # 
Instance details

Defined in System.Directory.Contents

Methods

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

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

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

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

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

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

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

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

toList :: DirTreeMaybe a -> [a] #

null :: DirTreeMaybe a -> Bool #

length :: DirTreeMaybe a -> Int #

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

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

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

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

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

Traversable DirTreeMaybe Source # 
Instance details

Defined in System.Directory.Contents

Methods

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

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

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

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

Witherable DirTreeMaybe Source # 
Instance details

Defined in System.Directory.Contents

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> DirTreeMaybe a -> f (DirTreeMaybe b) #

witherM :: Monad m => (a -> m (Maybe b)) -> DirTreeMaybe a -> m (DirTreeMaybe b) #

filterA :: Applicative f => (a -> f Bool) -> DirTreeMaybe a -> f (DirTreeMaybe a) #

Filterable DirTreeMaybe Source # 
Instance details

Defined in System.Directory.Contents

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

Defined in System.Directory.Contents

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

Defined in System.Directory.Contents

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

Defined in System.Directory.Contents

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

Defined in System.Directory.Contents

withDirTreeMaybe :: (DirTreeMaybe a -> DirTreeMaybe b) -> DirTree a -> Maybe (DirTree b) Source #

Map a function that could produce an empty result over a DirTree

withDirTreeMaybeF :: Functor f => (DirTreeMaybe a -> f (DirTreeMaybe b)) -> DirTree a -> f (Maybe (DirTree b)) Source #

Map a function that could produce an empty result in the given functor

witherDirTree :: Applicative f => (a -> f (Maybe b)) -> DirTree a -> f (Maybe (DirTree b)) Source #

wither for DirTree. This represents the case of no paths left after filtering with Nothing (something that the DirTree type can't represent on its own). NB: Filtering does not remove directories, only files. The directory structure remains intact. To remove empty directories, see pruneDirTree.

pruneDirTree :: DirTree a -> Maybe (DirTree a) Source #

Remove empty directories from the DirTree

Display

drawDirTree :: DirTree a -> Text Source #

Produces a tree drawing (using only text) of a DirTree hierarchy.

drawDirTreeWith :: (String -> a -> String) -> DirTree a -> String Source #

Apply a rendering function to each file when drawing the directory hierarchy

printDirTree :: DirTree a -> IO () Source #

Print the DirTree as a tree. For example:

System
|
`- Directory
   |
   `- Contents.hs

Utilities

mkRelative :: FilePath -> FilePath -> FilePath Source #

Make one filepath relative to another

alternative :: Alternative f => [f a] -> f a Source #

Get the first Alternative

filePath :: DirTree a -> FilePath Source #

Extract the FilePath from a DirTree node