directory-tree-0.12.1: A simple directory-like tree datatype, with useful IO functions

Copyright(c) Brandon Simmons
LicenseBSD3
MaintainerBrandon Simmons <brandon.m.simmons@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

System.Directory.Tree

Contents

Description

Provides a simple data structure mirroring a directory tree on the filesystem, as well as useful functions for reading and writing file and directory structures in the IO monad.

Errors are caught in a special constructor in the DirTree type.

Defined instances of Functor, Traversable and Foldable allow for easily operating on a directory of files. For example, you could use Foldable.foldr to create a hash of the entire contents of a directory.

The functions readDirectoryWithL and buildL allow for doing directory-traversing IO lazily as required by the execution of pure code. This allows you to treat large directories the same way as you would a lazy infinite list.

The AnchoredDirTree type is a simple wrapper for DirTree to keep track of a base directory context for the DirTree.

Please send me any requests, bugs, or other feedback on this module!

Synopsis

Data types for representing directory trees

data DirTree a Source #

the String in the name field is always a file name, never a full path. The free type variable is used in the File constructor and can hold Handles, Strings representing a file's contents or anything else you can think of. We catch any IO errors in the Failed constructor. an Exception can be converted to a String with show.

Constructors

Failed 

Fields

Dir 

Fields

File 

Fields

Instances

Functor DirTree Source # 

Methods

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

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

Foldable DirTree Source # 

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 # 

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 #

Two DirTrees are equal if they have the same constructor, the same name (and in the case of Dirs) their sorted contents are equal:

Methods

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

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

(Ord a, Eq a) => Ord (DirTree a) Source #

First compare constructors: Failed < Dir < File... Then compare name... Then compare free variable parameter of File constructors

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 #

Show a => Show (DirTree a) Source # 

Methods

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

show :: DirTree a -> String #

showList :: [DirTree a] -> ShowS #

data AnchoredDirTree a Source #

a simple wrapper to hold a base directory name, which can be either an absolute or relative path. This lets us give the DirTree a context, while still letting us store only directory and file names (not full paths) in the DirTree. (uses an infix constructor; don't be scared)

Constructors

(:/) 

Fields

type FileName = String Source #

an element in a FilePath:

High level IO functions

readDirectory :: FilePath -> IO (AnchoredDirTree String) Source #

Build an AnchoredDirTree, given the path to a directory, opening the files using readFile. Uses readDirectoryWith readFile internally and has the effect of traversing the entire directory structure. See readDirectoryWithL for lazy production of a DirTree structure.

readDirectoryWith :: (FilePath -> IO a) -> FilePath -> IO (AnchoredDirTree a) Source #

Build a DirTree rooted at p and using f to fill the file field of File nodes.

The FilePath arguments to f will be the full path to the current file, and will include the root p as a prefix. For example, the following would return a tree of full FilePaths like "../tmp/foo" and "../tmp/bar/baz":

readDirectoryWith return "../tmp"

Note though that the build function below already does this.

readDirectoryWithL :: (FilePath -> IO a) -> FilePath -> IO (AnchoredDirTree a) Source #

A "lazy" version of readDirectoryWith that does IO operations as needed i.e. as the tree is traversed in pure code.

NOTE: This function uses unsafeInterleaveIO under the hood. This means that:

  • side effects are tied to evaluation order and only run on demand
  • you might receive exceptions in pure code

writeDirectory :: AnchoredDirTree String -> IO (AnchoredDirTree ()) Source #

write a DirTree of strings to disk. Clobbers files of the same name. Doesn't affect files in the directories (if any already exist) with different names. Returns a new AnchoredDirTree where failures were lifted into a Failed constructor:

writeDirectoryWith :: (FilePath -> a -> IO b) -> AnchoredDirTree a -> IO (AnchoredDirTree b) Source #

writes the directory structure to disk and uses the provided function to write the contents of Files to disk. The return value of the function will become the new contents of the returned, where IO errors at each node are replaced with Failed constructors. The returned tree can be compared to the passed tree to see what operations, if any, failed:

Lower level functions

build :: FilePath -> IO (AnchoredDirTree FilePath) Source #

builds a DirTree from the contents of the directory passed to it, saving the base directory in the Anchored* wrapper. Errors are caught in the tree in the Failed constructor. The file fields initially are populated with full paths to the files they are abstracting.

buildL :: FilePath -> IO (AnchoredDirTree FilePath) Source #

identical to build but does directory reading IO lazily as needed:

openDirectory :: FilePath -> IOMode -> IO (AnchoredDirTree Handle) Source #

a simple application of readDirectoryWith openFile:

writeJustDirs :: AnchoredDirTree a -> IO (AnchoredDirTree a) Source #

writes the directory structure (not files) of a DirTree to the anchored directory. Returns a structure identical to the supplied tree with errors replaced by Failed constructors:

Manipulating FilePaths

zipPaths :: AnchoredDirTree a -> DirTree (FilePath, a) Source #

tuple up the complete file path with the file contents, by building up the path, trie-style, from the root. The filepath will be relative to "anchored" directory.

This allows us to, for example, mapM_ uncurry writeFile over a DirTree of strings, although writeDirectory does a better job of this.

free :: AnchoredDirTree a -> DirTree a Source #

Deprecated: Use record dirTree

DEPRECATED. Use record dirTree instead.

Utility functions

Shape comparison and equality

equalShape :: DirTree a -> DirTree b -> Bool Source #

Tests equality of two trees, ignoring their free variable portion. Can be used to check if any files have been added or deleted, for instance.

comparingShape :: DirTree a -> DirTree b -> Ordering Source #

a compare function that ignores the free "file" type variable:

Handling failure

successful :: DirTree a -> Bool Source #

True if there are no Failed constructors in the tree

anyFailed :: DirTree a -> Bool Source #

True if any Failed constructors in the tree

failed :: DirTree a -> Bool Source #

returns true if argument is a Failed constructor:

failures :: DirTree a -> [DirTree a] Source #

returns a list of Failed constructors only:

failedMap :: (FileName -> IOException -> DirTree a) -> DirTree a -> DirTree a Source #

maps a function to convert Failed DirTrees to Files or Dirs

Tree Manipulations

flattenDir :: DirTree a -> [DirTree a] Source #

Flattens a DirTree into a (never empty) list of tree constructors. Dir constructors will have [] as their contents:

sortDir :: Ord a => DirTree a -> DirTree a Source #

Recursively sort a directory tree according to the Ord instance

sortDirShape :: DirTree a -> DirTree a Source #

Recursively sort a tree as in sortDir but ignore the file contents of a File constructor

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

applies the predicate to each constructor in the tree, removing it (and its children, of course) when the predicate returns False. The topmost constructor will always be preserved:

Low-level

transformDir :: (DirTree a -> DirTree a) -> DirTree a -> DirTree a Source #

At Dir constructor, apply transformation function to all of directory's contents, then remove the Nothing's and recurse. This always preserves the topomst constructor.

Navigation

dropTo :: FileName -> AnchoredDirTree a -> Maybe (AnchoredDirTree a) Source #

If the argument is a Dir containing a sub-DirTree matching FileName then return that subtree, appending the name of the old root Dir to the anchor of the AnchoredDirTree wrapper. Otherwise return Nothing.

Operators

(</$>) :: Functor f => (DirTree a -> DirTree b) -> f (AnchoredDirTree a) -> f (AnchoredDirTree b) infixl 4 Source #

Allows for a function on a bare DirTree to be applied to an AnchoredDirTree within a Functor. Very similar to and useful in combination with <$>:

Lenses

These are compatible with the "lens" library

_contents :: Applicative f => ([DirTree a] -> f [DirTree a]) -> DirTree a -> f (DirTree a) Source #

_file :: Applicative f => (a -> f a) -> DirTree a -> f (DirTree a) Source #

_name :: Functor f => (FileName -> f FileName) -> DirTree a -> f (DirTree a) Source #