Copyright | (c) Christian Gram Kalhauge 2019 |
---|---|
License | MIT |
Maintainer | kalhauge@cs.ucla.edu |
Safe Haskell | None |
Language | Haskell2010 |
A directory tree, with helper functions to do different cool stuff. Contrary to `directory-tree`, this package does try to add as many accessors and handlers as possible. This is alos the reason that it depends on the Lens library.
Synopsis
- data DirTreeNode r a
- data RelativeFile s a
- type FileType = DirTreeNode () (RelativeFile () ())
- fileTypeOfNode :: DirTreeNode a (RelativeFile b c) -> FileType
- class AsDirTreeNode r r a | r -> r a where
- _DirTreeNode :: Prism' r (DirTreeNode r a)
- _Directory :: Prism' r r
- _File :: Prism' r a
- class AsRelativeFile r s a | r -> s a where
- _RelativeFile :: Prism' r (RelativeFile s a)
- _Symlink :: Prism' r s
- _Real :: Prism' r a
- getFileType :: FilePath -> IO FileType
- checkFileType :: FilePath -> IO (Maybe FileType)
- readPath :: FilePath -> IO (DirTreeNode [String] (RelativeFile FilePath ()))
- newtype FileMap a = FileMap {
- fileMapAsMap :: Map String a
- emptyFileMap :: FileMap a
- singletonFileMap :: String -> a -> FileMap a
- toFileList :: FileMap a -> [(String, a)]
- fromFileList :: [(String, a)] -> FileMap a
- (.*) :: String -> a -> (String, DirTree a)
- (./) :: String -> [(String, DirTree a)] -> (String, DirTree a)
- (.*>) :: String -> s -> (String, RelativeDirTree s a)
- (.*.) :: String -> a -> (String, RelativeDirTree s a)
- lookupFileMap :: String -> FileMap a -> Maybe a
- newtype DirTree a = DirTree {
- dirTreeNode :: DirTreeNode (DirForest a) a
- type RelativeDirTree s a = DirTree (RelativeFile s a)
- asRelativeDirTree :: DirTree a -> RelativeDirTree s a
- file :: a -> DirTree a
- realfile :: a -> RelativeDirTree s a
- symlink :: s -> RelativeDirTree s a
- directory :: DirForest a -> DirTree a
- directory' :: [(String, DirTree a)] -> DirTree a
- emptyDirectory :: DirTree a
- createDeepFile :: FileKey -> a -> DirTree a
- createDeepTree :: FileKey -> DirTree a -> DirTree a
- type FileKey = [String]
- fileKeyFromPath :: FilePath -> FileKey
- fileKeyToPath :: FileKey -> FilePath
- diffFileKey :: FileKey -> FileKey -> FilePath
- diffPath :: FileKey -> FilePath -> Maybe FileKey
- alterFile :: forall f a. Functor f => (Maybe (DirTree a) -> f (Maybe (DirTree a))) -> FileKey -> Maybe (DirTree a) -> f (Maybe (DirTree a))
- iflattenDirTree :: (FileKey -> DirTreeNode (FileMap m) a -> m) -> DirTree a -> m
- flattenDirTree :: (DirTreeNode (FileMap m) a -> m) -> DirTree a -> m
- depthfirst :: Semigroup m => (FileKey -> DirTreeNode [String] a -> m) -> DirTree a -> m
- findNode :: (FileKey -> DirTreeNode [String] a -> Bool) -> DirTree a -> Maybe (FileKey, DirTreeNode [String] a)
- listNodes :: DirTree a -> [(FileKey, DirTreeNode [String] a)]
- readDirTree :: (FilePath -> IO a) -> FilePath -> IO (DirTree a)
- writeDirTree :: (FilePath -> a -> IO ()) -> FilePath -> DirTree a -> IO ()
- data Link
- toLink :: FileKey -> FilePath -> Link
- readRelativeDirTree :: (FilePath -> IO a) -> FilePath -> IO (RelativeDirTree Link a)
- followLinks :: forall a. (FilePath -> IO a) -> RelativeDirTree Link a -> IO (DirTree a)
- writeRelativeDirTree :: (FilePath -> a -> IO ()) -> FilePath -> RelativeDirTree Link a -> IO ()
- newtype DirForest a = DirForest {
- getInternalFileMap :: FileMap (DirTree a)
- type RelativeDirForest s a = DirForest (RelativeFile s a)
- type ForestFileKey = NonEmpty String
- fromForestFileKey :: ForestFileKey -> FileKey
- toForestFileKey :: FileKey -> Maybe ForestFileKey
- asRelativeDirForest :: DirForest a -> RelativeDirForest s a
- emptyForest :: DirForest a
- singletonForest :: String -> DirTree a -> DirForest a
- createDeepForest :: ForestFileKey -> DirTree a -> DirForest a
- alterForest :: forall f a. Functor f => (Maybe (DirTree a) -> f (Maybe (DirTree a))) -> ForestFileKey -> DirForest a -> f (DirForest a)
DirTreeNode
The basic item of this library is a DirTreeNode.
data DirTreeNode r a Source #
A directory tree node. Everything is either a file, or a directory.
Instances
data RelativeFile s a Source #
A DirTree can contain relativeFile files. This means that some files might be symlinks.
Instances
Helpers
type FileType = DirTreeNode () (RelativeFile () ()) Source #
A FileType
is just a DirTreeNode
with no contents.
fileTypeOfNode :: DirTreeNode a (RelativeFile b c) -> FileType Source #
Gets the FileType
of a DirTreeNode
class AsDirTreeNode r r a | r -> r a where Source #
_DirTreeNode :: Prism' r (DirTreeNode r a) Source #
_Directory :: Prism' r r Source #
Instances
AsDirTreeNode (DirTree a) (DirForest a) a Source # | |
Defined in System.DirTree | |
AsDirTreeNode (DirTreeNode r a) r a Source # | |
Defined in System.DirTree _DirTreeNode :: Prism' (DirTreeNode r a) (DirTreeNode r a) Source # _Directory :: Prism' (DirTreeNode r a) r Source # _File :: Prism' (DirTreeNode r a) a Source # |
class AsRelativeFile r s a | r -> s a where Source #
_RelativeFile :: Prism' r (RelativeFile s a) Source #
Instances
AsRelativeFile (DirTreeNode a (RelativeFile b c)) b c Source # | It is quite offten that a node will be used as a relative file. |
Defined in System.DirTree _RelativeFile :: Prism' (DirTreeNode a (RelativeFile b c)) (RelativeFile b c) Source # _Symlink :: Prism' (DirTreeNode a (RelativeFile b c)) b Source # _Real :: Prism' (DirTreeNode a (RelativeFile b c)) c Source # | |
AsRelativeFile (RelativeFile s a) s a Source # | |
Defined in System.DirTree _RelativeFile :: Prism' (RelativeFile s a) (RelativeFile s a) Source # _Symlink :: Prism' (RelativeFile s a) s Source # _Real :: Prism' (RelativeFile s a) a Source # |
IO
getFileType :: FilePath -> IO FileType Source #
Check a filepath for Type, throws an IOException if path does not exist.
checkFileType :: FilePath -> IO (Maybe FileType) Source #
Check a filepath for Type, return Nothing if the path does not exist.
readPath :: FilePath -> IO (DirTreeNode [String] (RelativeFile FilePath ())) Source #
Reads the structure of the filepath
FileMap
The FileMap
is used to represent the content of a directory.
A map from file names to
FileMap | |
|
Instances
Constructors
emptyFileMap :: FileMap a Source #
An empty filemap
singletonFileMap :: String -> a -> FileMap a Source #
Single File
toFileList :: FileMap a -> [(String, a)] Source #
Create a list of pairs of filenames and file values.
fromFileList :: [(String, a)] -> FileMap a Source #
Create a FileMap
from a list of pairs of filenames a file values.
Accessors
DirTree
A DirTree
is a recursive difined tree.
A dir tree is a tree of nodes.
DirTree | |
|
Instances
Functor DirTree Source # | |
Foldable DirTree Source # | |
Defined in System.DirTree 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 # elem :: Eq a => a -> DirTree a -> Bool # maximum :: Ord a => DirTree a -> a # minimum :: Ord a => DirTree a -> a # | |
Traversable DirTree Source # | |
FunctorWithIndex FileKey DirTree Source # | |
FoldableWithIndex FileKey DirTree Source # | |
Defined in System.DirTree ifoldMap :: Monoid m => (FileKey -> a -> m) -> DirTree a -> m # ifolded :: IndexedFold FileKey (DirTree a) a # ifoldr :: (FileKey -> a -> b -> b) -> b -> DirTree a -> b # ifoldl :: (FileKey -> b -> a -> b) -> b -> DirTree a -> b # ifoldr' :: (FileKey -> a -> b -> b) -> b -> DirTree a -> b # ifoldl' :: (FileKey -> b -> a -> b) -> b -> DirTree a -> b # | |
TraversableWithIndex FileKey DirTree Source # | |
Defined in System.DirTree itraverse :: Applicative f => (FileKey -> a -> f b) -> DirTree a -> f (DirTree b) # itraversed :: IndexedTraversal FileKey (DirTree a) (DirTree b) a b # | |
Eq a => Eq (DirTree a) Source # | |
Ord a => Ord (DirTree a) Source # | |
Defined in System.DirTree | |
Show a => Show (DirTree a) Source # | |
Generic (DirTree a) Source # | |
Semigroup (DirTree a) Source # | A DirTree is a semigroup, where it merges directories and take the last entry if there files.
|
NFData a => NFData (DirTree a) Source # | |
Defined in System.DirTree | |
Ixed (DirTree a) Source # | |
Defined in System.DirTree | |
At (DirTree a) Source # | Not a completly correct Lens, since it is implossible to
delete the current DirTree. To use a correct Lens, see
|
Wrapped (DirTree a) Source # | |
DirTree a1 ~ t => Rewrapped (DirTree a2) t Source # | |
Defined in System.DirTree | |
AsDirTreeNode (DirTree a) (DirForest a) a Source # | |
Defined in System.DirTree | |
type Rep (DirTree a) Source # | |
Defined in System.DirTree type Rep (DirTree a) = D1 (MetaData "DirTree" "System.DirTree" "dirtree-0.1.2-ANt4d8ezA2c8BWLFVTMai6" True) (C1 (MetaCons "DirTree" PrefixI True) (S1 (MetaSel (Just "dirTreeNode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DirTreeNode (DirForest a) a)))) | |
type Index (DirTree a) Source # | |
Defined in System.DirTree | |
type IxValue (DirTree a) Source # | |
Defined in System.DirTree | |
type Unwrapped (DirTree a) Source # | |
Defined in System.DirTree |
type RelativeDirTree s a = DirTree (RelativeFile s a) Source #
A relative dir tree also exists.
asRelativeDirTree :: DirTree a -> RelativeDirTree s a Source #
All DirTree
s are also relative.
Constructors
realfile :: a -> RelativeDirTree s a Source #
Constructs a relative dirtree with only a real file
symlink :: s -> RelativeDirTree s a Source #
Constructs a dirtree with a symlink
emptyDirectory :: DirTree a Source #
Constructs a dirtree with a empty directory
createDeepFile :: FileKey -> a -> DirTree a Source #
Create a recursive DirTree
from a FileKey and a value.
createDeepTree :: FileKey -> DirTree a -> DirTree a Source #
Create a recursive DirTree
from a FileKey and a value.
Accessors
diffFileKey :: FileKey -> FileKey -> FilePath Source #
diffFileKey
produces a filepath which is needed to
navigate from one FileKey to a other.
>>>
diffFileKey ["hello", "world"] ["hello"]
".."
>>>
diffFileKey ["hello"] ["hello", "world", "test"]
"world/test"
>>>
diffFileKey ["world", "test"] ["hello"]
"../../hello"
diffPath :: FileKey -> FilePath -> Maybe FileKey Source #
diffPath
produces a the filekey at the end of
a relative filepath, from one filekey.
>>>
diffPath ["hello", "world"] ".."
Just ["hello"]
>>>
diffPath ["hello"] "world/test"
Just ["hello","world","test"]
>>>
diffPath ["world", "test"] "../../hello"
Just ["hello"]
>>>
diffPath ["world", "test"] "/hello"
Nothing
>>>
diffPath ["world", "test"] "../../.."
Nothing
alterFile :: forall f a. Functor f => (Maybe (DirTree a) -> f (Maybe (DirTree a))) -> FileKey -> Maybe (DirTree a) -> f (Maybe (DirTree a)) Source #
Iterators
iflattenDirTree :: (FileKey -> DirTreeNode (FileMap m) a -> m) -> DirTree a -> m Source #
This method enables eta reduction of a DirTree a with an index.
flattenDirTree :: (DirTreeNode (FileMap m) a -> m) -> DirTree a -> m Source #
This method enables eta reduction of a DirTree a.
depthfirst :: Semigroup m => (FileKey -> DirTreeNode [String] a -> m) -> DirTree a -> m Source #
Uses a semigroup to join together the results, This is slightly
less powerfull than iflattenDirTree
, but more convinient for
summations.
findNode :: (FileKey -> DirTreeNode [String] a -> Bool) -> DirTree a -> Maybe (FileKey, DirTreeNode [String] a) Source #
Find a file given a predicate that takes a FileKey
and DirTreeNode
.
IO
readDirTree :: (FilePath -> IO a) -> FilePath -> IO (DirTree a) Source #
Reads a DirTree and follow all the relative links. Might recurse forever.
writeDirTree :: (FilePath -> a -> IO ()) -> FilePath -> DirTree a -> IO () Source #
Writes a Relative DirTree to a file
A Link
can either be Internal
, pointing to something in the DirTree
or
External
pointing to an absolute FilePath
.
Instances
Eq Link Source # | |
Show Link Source # | |
Generic Link Source # | |
NFData Link Source # | |
Defined in System.DirTree | |
type Rep Link Source # | |
Defined in System.DirTree type Rep Link = D1 (MetaData "Link" "System.DirTree" "dirtree-0.1.2-ANt4d8ezA2c8BWLFVTMai6" False) (C1 (MetaCons "Internal" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FileKey)) :+: C1 (MetaCons "External" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilePath))) |
toLink :: FileKey -> FilePath -> Link Source #
Figure out a link from the FileKey and FilePath of Link
readRelativeDirTree :: (FilePath -> IO a) -> FilePath -> IO (RelativeDirTree Link a) Source #
Reads a DirTree. All file paths are absolute to the filepath
followLinks :: forall a. (FilePath -> IO a) -> RelativeDirTree Link a -> IO (DirTree a) Source #
Follow the links to create the tree. This function might recurse forever.
writeRelativeDirTree :: (FilePath -> a -> IO ()) -> FilePath -> RelativeDirTree Link a -> IO () Source #
Writes a Relative DirTree to a file
DirForest
Instances
type RelativeDirForest s a = DirForest (RelativeFile s a) Source #
A relative dir forest also exists.
type ForestFileKey = NonEmpty String Source #
All entries in a DirForest has to be non-empty
fromForestFileKey :: ForestFileKey -> FileKey Source #
Convert a ForestFileKey
to a FileKey
toForestFileKey :: FileKey -> Maybe ForestFileKey Source #
Convert a FileKey
to a ForestFileKey
Constructors
asRelativeDirForest :: DirForest a -> RelativeDirForest s a Source #
All DirTree
s are also relative.
emptyForest :: DirForest a Source #
Creates an empty forest
createDeepForest :: ForestFileKey -> DirTree a -> DirForest a Source #
Creates an deep file in a forest