Copyright | (c) Brandon Simmons |
---|---|
License | BSD3 |
Maintainer | Brandon Simmons <brandon.m.simmons@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
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!
- data DirTree a
- data AnchoredDirTree a = (:/) {}
- type FileName = String
- readDirectory :: FilePath -> IO (AnchoredDirTree String)
- readDirectoryWith :: (FilePath -> IO a) -> FilePath -> IO (AnchoredDirTree a)
- readDirectoryWithL :: (FilePath -> IO a) -> FilePath -> IO (AnchoredDirTree a)
- writeDirectory :: AnchoredDirTree String -> IO (AnchoredDirTree ())
- writeDirectoryWith :: (FilePath -> a -> IO b) -> AnchoredDirTree a -> IO (AnchoredDirTree b)
- build :: FilePath -> IO (AnchoredDirTree FilePath)
- buildL :: FilePath -> IO (AnchoredDirTree FilePath)
- openDirectory :: FilePath -> IOMode -> IO (AnchoredDirTree Handle)
- writeJustDirs :: AnchoredDirTree a -> IO (AnchoredDirTree a)
- zipPaths :: AnchoredDirTree a -> DirTree (FilePath, a)
- free :: AnchoredDirTree a -> DirTree a
- equalShape :: DirTree a -> DirTree b -> Bool
- comparingShape :: DirTree a -> DirTree b -> Ordering
- successful :: DirTree a -> Bool
- anyFailed :: DirTree a -> Bool
- failed :: DirTree a -> Bool
- failures :: DirTree a -> [DirTree a]
- failedMap :: (FileName -> IOException -> DirTree a) -> DirTree a -> DirTree a
- flattenDir :: DirTree a -> [DirTree a]
- sortDir :: Ord a => DirTree a -> DirTree a
- sortDirShape :: DirTree a -> DirTree a
- filterDir :: (DirTree a -> Bool) -> DirTree a -> DirTree a
- transformDir :: (DirTree a -> DirTree a) -> DirTree a -> DirTree a
- dropTo :: FileName -> AnchoredDirTree a -> Maybe (AnchoredDirTree a)
- (</$>) :: Functor f => (DirTree a -> DirTree b) -> f (AnchoredDirTree a) -> f (AnchoredDirTree b)
- _contents :: Applicative f => ([DirTree a] -> f [DirTree a]) -> DirTree a -> f (DirTree a)
- _err :: Applicative f => (IOException -> f IOException) -> DirTree a -> f (DirTree a)
- _file :: Applicative f => (a -> f a) -> DirTree a -> f (DirTree a)
- _name :: Functor f => (FileName -> f FileName) -> DirTree a -> f (DirTree a)
- _anchor :: Functor f => (FilePath -> f FilePath) -> AnchoredDirTree a -> f (AnchoredDirTree a)
- _dirTree :: Functor f => (DirTree t -> f (DirTree a)) -> AnchoredDirTree t -> f (AnchoredDirTree a)
Data types for representing directory trees
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
.
Functor DirTree Source # | |
Foldable DirTree Source # | |
Traversable DirTree Source # | |
Eq a => Eq (DirTree a) Source # | Two DirTrees are equal if they have the same constructor, the same name
(and in the case of |
(Ord a, Eq a) => Ord (DirTree a) Source # | First compare constructors: Failed < Dir < File...
Then compare |
Show a => Show (DirTree a) Source # | |
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)
Functor AnchoredDirTree Source # | |
Eq a => Eq (AnchoredDirTree a) Source # | |
Ord a => Ord (AnchoredDirTree a) Source # | |
Show a => Show (AnchoredDirTree a) Source # | |
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 FilePath
s
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 #
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
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 #
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 #
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
_err :: Applicative f => (IOException -> f IOException) -> DirTree a -> f (DirTree a) Source #
_anchor :: Functor f => (FilePath -> f FilePath) -> AnchoredDirTree a -> f (AnchoredDirTree a) Source #
_dirTree :: Functor f => (DirTree t -> f (DirTree a)) -> AnchoredDirTree t -> f (AnchoredDirTree a) Source #