filesystem-trees-0.1.0.1: Recursively manipulate and traverse filesystems as lazy rose trees.

Safe HaskellTrustworthy

System.File.Tree

Contents

Synopsis

Directory tree structure

newtype FSTree Source

A representation of a filesystem tree. The root label contains the path context, and every child node is a single file/directory name.

For example, say we have the following directory structure on our filesystem:

 
   /example$ tree foo --charset ASCII
   foo
   `-- bar
       `-- test
           |-- a
           |-- A
           |   |-- x
           |   `-- y
           |-- b
           `-- B

then calling getDirectory "/example/foo/bar/test" will yield a FSTree with the following structure:

  /example$ ghci
  Prelude Data.Tree System.Directory.Tree> putStrLn . drawTree . toTree =<< getDirectory "/example/foo/bar/test"
  /example/foo/bar/test
  |
  +- A
  |  |
  |  +- x
  |  |
  |  `- y
  |
  +- B
  |
  +- a
  |
  `- b

Constructors

FSTree 

Fields

toTree :: Tree FilePath
 

mkFSTree :: FilePath -> FSForest -> FSTreeSource

A pseudo-constructor for FSTree.

Generic rose trees

Re-exported from Data.Tree

data Tree a

Multi-way trees, also known as rose trees.

Constructors

Node 

Fields

rootLabel :: a

label value

subForest :: Forest a

zero or more child trees

type Forest a = [Tree a]

Overloaded tree lenses

class TreeLens t a | t -> a whereSource

Overloaded lenses for Tree and FSTree

Methods

label :: Lens t aSource

Lens for the value at a tree node

children :: Lens t [t]Source

Lens for a list of children nodes

Retrieve directory trees from the filesystem

getDirectory :: FilePath -> IO FSTreeSource

Lazily retrieves a representation of a directory and its contents recursively.

Relative paths are not converted to absolute. Thus, a FSTree formed from a relative path will contain a "relative tree", and the usual caveats of current directories and relative paths apply to the tree as a whole.

getDirectory' :: FilePath -> IO FSTreeSource

A strict variant of getDirectory.

Though race conditionals are still a possibility, this function will avoid some race conditions that could be caused from the use of lazy IO. For large directories, this function can easily cause memory leaks.

IO operations on directory trees

copy

copyTo :: FilePath -> FSTree -> IO FSTreeSource

Copy a filesystem tree to a new location, creating directories as necessary. The resulting FSTree represents all of the copied directories/files in their new home.

Note that an single exception will halt the entire operation.

move

moveTo :: FilePath -> FSTree -> IO FSTreeSource

Move a filesystem tree to a new location, deleting any file/directory that was present at the given destination path.

Directories listed in the source filesystem tree are removed if the move operation empties their contents completely. The resulting FSTree represents all the moved directories/files in their new home.

Note that an single exception will halt the entire operation.

mergeInto :: FilePath -> FSTree -> IO FSTreeSource

This is similar to moveTo, except that whatever was present at the destination path isn't deleted before the move operation commences.

Note that an single exception will halt the entire operation.

remove

remove :: FSTree -> IO ()Source

Remove a given filesystem tree. Directories are only removed if the remove operation empties its contents.

Note that an single exception will halt the entire operation.

tryRemove :: FSTree -> IO [IOException]Source

A variant of remove. IOExceptions do not stop the removal process, and all IOExceptions are accumulated into a list as the result of the operation.

tryRemoveWith :: (IOException -> IO a) -> FSTree -> IO [a]Source

A variant of remove. Allows you to specify your own exception handler to handle exceptions for each removal operation.

Operations on directory trees

basic operations

pop :: FSTree -> (FilePath, FSForest)Source

Remove the root node of a filesystem tree, while preserving the paths of its children. In other words, this function does not alter where any paths point to.

pop_ :: FSTree -> FSForestSource

 pop_ = snd . pop

flatten :: FSTree -> [FilePath]Source

Flattens a filesystem tree into a list of its contents. This is a pre-order traversal of the tree.

flattenPostOrder :: FSTree -> [FilePath]Source

A post-order traversal of the filesystem tree.

levels :: FSTree -> [[FilePath]]Source

List of file paths at each level of the tree.

map over subtrees

map :: (FilePath -> b) -> FSTree -> Tree bSource

Applies a function over the filepaths of a directory tree.

Because we can't guarantee that the internal FSTree representation is preserved in any way, the result is a regular Tree.

mapM :: Monad m => (FilePath -> m b) -> FSTree -> m (Tree b)Source

Applies a monadic action to every filepath in a filesystem tree.

mapM_ :: Monad m => (FilePath -> m b) -> FSTree -> m ()Source

mapM with the result discarded.

find subtrees

find :: (FilePath -> Bool) -> FSForest -> FSForestSource

Find all sub-forests within a forest that match the given predicate.

findM :: Monad m => (FilePath -> m Bool) -> FSForest -> m FSForestSource

Monadic find.

filter subtrees

filter :: (FilePath -> Bool) -> FSForest -> FSForestSource

Applies a predicate to each path name in a filesystem forest, and removes all unsuccessful paths from the result. If a directory fails the predicate test, then it will only be removed if all of its children also fail the test

filterM :: Monad m => (FilePath -> m Bool) -> FSForest -> m FSForestSource

Monadic filter.

useful predicates

isFile :: FilePath -> IO BoolSource

Checks if a path refers to a file.

isDir :: FilePath -> IO BoolSource

Checks if a path refer to a directory.

isSymLink :: FilePath -> IO BoolSource

Checks if a path refers to a symbolic link. NOTE: always returns False on Windows

isSymDir :: FilePath -> IO BoolSource

Checks if a path refers to a symbolically linked directory

isSymFile :: FilePath -> IO BoolSource

Checks if a path refers to a symbolically linked file

isRealFile :: FilePath -> IO BoolSource

Checks if a path refers to a real file (not a symbolic link)

isRealDir :: FilePath -> IO BoolSource

Checks if a path refers to a real directory (not a symbolic link)

extract subtrees

extract :: (FilePath -> Bool) -> FSForest -> (FSForest, FSForest)Source

The first element of the result represents the forest after removing all subtrees that match the given predicate, and the second element is a list of trees that matched. This could be useful if you want to handle certain directories specially from others within a sub-filesystem.

extractM :: Monad m => (FilePath -> m Bool) -> FSForest -> m (FSForest, FSForest)Source

Monadic extract.

truncate tree to a maximum level

truncateAt :: TreeLens t a => Word -> t -> tSource

Truncate a tree to a given maximum level, where root is level 0.

zip with destination tree

zipWithDest :: (FilePath -> FilePath -> a) -> FilePath -> FSTree -> [a]Source

A generalization of the various move, copy, and remove operations. This operation pairs each node of a FSTree with a second path formed by rerooting the filesystem tree to the given destination path.

zipWithDestM :: Monad m => (FilePath -> FilePath -> m a) -> FilePath -> FSTree -> m [a]Source

Monadic zipWithDest

zipWithDestM_ :: Monad m => (FilePath -> FilePath -> m a) -> FilePath -> FSTree -> m FSTreeSource

A variant of zipWithDestM where the result is discarded and instead the rerooted filesystem tree is returned.