dirtree-0.1.2: A small library for working with directories.

Copyright(c) Christian Gram Kalhauge 2019
LicenseMIT
Maintainerkalhauge@cs.ucla.edu
Safe HaskellNone
LanguageHaskell2010

System.DirTree

Contents

Description

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

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.

Constructors

Directory r 
File a 
Instances
Bitraversable DirTreeNode Source # 
Instance details

Defined in System.DirTree

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> DirTreeNode a b -> f (DirTreeNode c d) #

Bifoldable DirTreeNode Source # 
Instance details

Defined in System.DirTree

Methods

bifold :: Monoid m => DirTreeNode m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> DirTreeNode a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> DirTreeNode a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> DirTreeNode a b -> c #

Bifunctor DirTreeNode Source # 
Instance details

Defined in System.DirTree

Methods

bimap :: (a -> b) -> (c -> d) -> DirTreeNode a c -> DirTreeNode b d #

first :: (a -> b) -> DirTreeNode a c -> DirTreeNode b c #

second :: (b -> c) -> DirTreeNode a b -> DirTreeNode a c #

Functor (DirTreeNode r) Source # 
Instance details

Defined in System.DirTree

Methods

fmap :: (a -> b) -> DirTreeNode r a -> DirTreeNode r b #

(<$) :: a -> DirTreeNode r b -> DirTreeNode r a #

Foldable (DirTreeNode r) Source # 
Instance details

Defined in System.DirTree

Methods

fold :: Monoid m => DirTreeNode r m -> m #

foldMap :: Monoid m => (a -> m) -> DirTreeNode r a -> m #

foldr :: (a -> b -> b) -> b -> DirTreeNode r a -> b #

foldr' :: (a -> b -> b) -> b -> DirTreeNode r a -> b #

foldl :: (b -> a -> b) -> b -> DirTreeNode r a -> b #

foldl' :: (b -> a -> b) -> b -> DirTreeNode r a -> b #

foldr1 :: (a -> a -> a) -> DirTreeNode r a -> a #

foldl1 :: (a -> a -> a) -> DirTreeNode r a -> a #

toList :: DirTreeNode r a -> [a] #

null :: DirTreeNode r a -> Bool #

length :: DirTreeNode r a -> Int #

elem :: Eq a => a -> DirTreeNode r a -> Bool #

maximum :: Ord a => DirTreeNode r a -> a #

minimum :: Ord a => DirTreeNode r a -> a #

sum :: Num a => DirTreeNode r a -> a #

product :: Num a => DirTreeNode r a -> a #

Traversable (DirTreeNode r) Source # 
Instance details

Defined in System.DirTree

Methods

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

sequenceA :: Applicative f => DirTreeNode r (f a) -> f (DirTreeNode r a) #

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

sequence :: Monad m => DirTreeNode r (m a) -> m (DirTreeNode r a) #

(Eq r, Eq a) => Eq (DirTreeNode r a) Source # 
Instance details

Defined in System.DirTree

Methods

(==) :: DirTreeNode r a -> DirTreeNode r a -> Bool #

(/=) :: DirTreeNode r a -> DirTreeNode r a -> Bool #

(Ord r, Ord a) => Ord (DirTreeNode r a) Source # 
Instance details

Defined in System.DirTree

Methods

compare :: DirTreeNode r a -> DirTreeNode r a -> Ordering #

(<) :: DirTreeNode r a -> DirTreeNode r a -> Bool #

(<=) :: DirTreeNode r a -> DirTreeNode r a -> Bool #

(>) :: DirTreeNode r a -> DirTreeNode r a -> Bool #

(>=) :: DirTreeNode r a -> DirTreeNode r a -> Bool #

max :: DirTreeNode r a -> DirTreeNode r a -> DirTreeNode r a #

min :: DirTreeNode r a -> DirTreeNode r a -> DirTreeNode r a #

(Show r, Show a) => Show (DirTreeNode r a) Source # 
Instance details

Defined in System.DirTree

Methods

showsPrec :: Int -> DirTreeNode r a -> ShowS #

show :: DirTreeNode r a -> String #

showList :: [DirTreeNode r a] -> ShowS #

Generic (DirTreeNode r a) Source # 
Instance details

Defined in System.DirTree

Associated Types

type Rep (DirTreeNode r a) :: Type -> Type #

Methods

from :: DirTreeNode r a -> Rep (DirTreeNode r a) x #

to :: Rep (DirTreeNode r a) x -> DirTreeNode r a #

(NFData r, NFData a) => NFData (DirTreeNode r a) Source # 
Instance details

Defined in System.DirTree

Methods

rnf :: DirTreeNode r a -> () #

AsDirTreeNode (DirTreeNode r a) r a Source # 
Instance details

Defined in System.DirTree

AsRelativeFile (DirTreeNode a (RelativeFile b c)) b c Source #

It is quite offten that a node will be used as a relative file.

Instance details

Defined in System.DirTree

type Rep (DirTreeNode r a) Source # 
Instance details

Defined in System.DirTree

type Rep (DirTreeNode r a) = D1 (MetaData "DirTreeNode" "System.DirTree" "dirtree-0.1.2-ANt4d8ezA2c8BWLFVTMai6" False) (C1 (MetaCons "Directory" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 r)) :+: C1 (MetaCons "File" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data RelativeFile s a Source #

A DirTree can contain relativeFile files. This means that some files might be symlinks.

Constructors

Symlink s 
Real a 
Instances
Bitraversable RelativeFile Source # 
Instance details

Defined in System.DirTree

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> RelativeFile a b -> f (RelativeFile c d) #

Bifoldable RelativeFile Source # 
Instance details

Defined in System.DirTree

Methods

bifold :: Monoid m => RelativeFile m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> RelativeFile a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> RelativeFile a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> RelativeFile a b -> c #

Bifunctor RelativeFile Source # 
Instance details

Defined in System.DirTree

Methods

bimap :: (a -> b) -> (c -> d) -> RelativeFile a c -> RelativeFile b d #

first :: (a -> b) -> RelativeFile a c -> RelativeFile b c #

second :: (b -> c) -> RelativeFile a b -> RelativeFile a c #

Functor (RelativeFile s) Source # 
Instance details

Defined in System.DirTree

Methods

fmap :: (a -> b) -> RelativeFile s a -> RelativeFile s b #

(<$) :: a -> RelativeFile s b -> RelativeFile s a #

Foldable (RelativeFile s) Source # 
Instance details

Defined in System.DirTree

Methods

fold :: Monoid m => RelativeFile s m -> m #

foldMap :: Monoid m => (a -> m) -> RelativeFile s a -> m #

foldr :: (a -> b -> b) -> b -> RelativeFile s a -> b #

foldr' :: (a -> b -> b) -> b -> RelativeFile s a -> b #

foldl :: (b -> a -> b) -> b -> RelativeFile s a -> b #

foldl' :: (b -> a -> b) -> b -> RelativeFile s a -> b #

foldr1 :: (a -> a -> a) -> RelativeFile s a -> a #

foldl1 :: (a -> a -> a) -> RelativeFile s a -> a #

toList :: RelativeFile s a -> [a] #

null :: RelativeFile s a -> Bool #

length :: RelativeFile s a -> Int #

elem :: Eq a => a -> RelativeFile s a -> Bool #

maximum :: Ord a => RelativeFile s a -> a #

minimum :: Ord a => RelativeFile s a -> a #

sum :: Num a => RelativeFile s a -> a #

product :: Num a => RelativeFile s a -> a #

Traversable (RelativeFile s) Source # 
Instance details

Defined in System.DirTree

Methods

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

sequenceA :: Applicative f => RelativeFile s (f a) -> f (RelativeFile s a) #

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

sequence :: Monad m => RelativeFile s (m a) -> m (RelativeFile s a) #

(Eq s, Eq a) => Eq (RelativeFile s a) Source # 
Instance details

Defined in System.DirTree

Methods

(==) :: RelativeFile s a -> RelativeFile s a -> Bool #

(/=) :: RelativeFile s a -> RelativeFile s a -> Bool #

(Ord s, Ord a) => Ord (RelativeFile s a) Source # 
Instance details

Defined in System.DirTree

(Show s, Show a) => Show (RelativeFile s a) Source # 
Instance details

Defined in System.DirTree

Generic (RelativeFile s a) Source # 
Instance details

Defined in System.DirTree

Associated Types

type Rep (RelativeFile s a) :: Type -> Type #

Methods

from :: RelativeFile s a -> Rep (RelativeFile s a) x #

to :: Rep (RelativeFile s a) x -> RelativeFile s a #

(NFData s, NFData a) => NFData (RelativeFile s a) Source # 
Instance details

Defined in System.DirTree

Methods

rnf :: RelativeFile s a -> () #

AsRelativeFile (DirTreeNode a (RelativeFile b c)) b c Source #

It is quite offten that a node will be used as a relative file.

Instance details

Defined in System.DirTree

AsRelativeFile (RelativeFile s a) s a Source # 
Instance details

Defined in System.DirTree

type Rep (RelativeFile s a) Source # 
Instance details

Defined in System.DirTree

type Rep (RelativeFile s a) = D1 (MetaData "RelativeFile" "System.DirTree" "dirtree-0.1.2-ANt4d8ezA2c8BWLFVTMai6" False) (C1 (MetaCons "Symlink" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 s)) :+: C1 (MetaCons "Real" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

Helpers

type FileType = DirTreeNode () (RelativeFile () ()) Source #

A FileType is just a DirTreeNode with no contents.

class AsDirTreeNode r r a | r -> r a where Source #

Minimal complete definition

_DirTreeNode

class AsRelativeFile r s a | r -> s a where Source #

Minimal complete definition

_RelativeFile

Instances
AsRelativeFile (DirTreeNode a (RelativeFile b c)) b c Source #

It is quite offten that a node will be used as a relative file.

Instance details

Defined in System.DirTree

AsRelativeFile (RelativeFile s a) s a Source # 
Instance details

Defined in System.DirTree

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.

newtype FileMap a Source #

A map from file names to

Constructors

FileMap 

Fields

Instances
Functor FileMap Source # 
Instance details

Defined in System.DirTree

Methods

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

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

Foldable FileMap Source # 
Instance details

Defined in System.DirTree

Methods

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

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

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

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

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

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

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

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

toList :: FileMap a -> [a] #

null :: FileMap a -> Bool #

length :: FileMap a -> Int #

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

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

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

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

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

Traversable FileMap Source # 
Instance details

Defined in System.DirTree

Methods

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

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

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

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

FunctorWithIndex String FileMap Source # 
Instance details

Defined in System.DirTree

Methods

imap :: (String -> a -> b) -> FileMap a -> FileMap b #

imapped :: IndexedSetter String (FileMap a) (FileMap b) a b #

FoldableWithIndex String FileMap Source # 
Instance details

Defined in System.DirTree

Methods

ifoldMap :: Monoid m => (String -> a -> m) -> FileMap a -> m #

ifolded :: IndexedFold String (FileMap a) a #

ifoldr :: (String -> a -> b -> b) -> b -> FileMap a -> b #

ifoldl :: (String -> b -> a -> b) -> b -> FileMap a -> b #

ifoldr' :: (String -> a -> b -> b) -> b -> FileMap a -> b #

ifoldl' :: (String -> b -> a -> b) -> b -> FileMap a -> b #

TraversableWithIndex String FileMap Source # 
Instance details

Defined in System.DirTree

Methods

itraverse :: Applicative f => (String -> a -> f b) -> FileMap a -> f (FileMap b) #

itraversed :: IndexedTraversal String (FileMap a) (FileMap b) a b #

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

Defined in System.DirTree

Methods

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

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

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

Defined in System.DirTree

Methods

compare :: FileMap a -> FileMap a -> Ordering #

(<) :: FileMap a -> FileMap a -> Bool #

(<=) :: FileMap a -> FileMap a -> Bool #

(>) :: FileMap a -> FileMap a -> Bool #

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

max :: FileMap a -> FileMap a -> FileMap a #

min :: FileMap a -> FileMap a -> FileMap a #

Generic (FileMap a) Source # 
Instance details

Defined in System.DirTree

Associated Types

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

Methods

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

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

Semigroup a => Semigroup (FileMap a) Source #

The FileMap is a semigroup if the contnent is. It tries to union the content under each item.

Instance details

Defined in System.DirTree

Methods

(<>) :: FileMap a -> FileMap a -> FileMap a #

sconcat :: NonEmpty (FileMap a) -> FileMap a #

stimes :: Integral b => b -> FileMap a -> FileMap a #

Semigroup a => Monoid (FileMap a) Source #

The empty monoid is the emptyFileMap

Instance details

Defined in System.DirTree

Methods

mempty :: FileMap a #

mappend :: FileMap a -> FileMap a -> FileMap a #

mconcat :: [FileMap a] -> FileMap a #

NFData a => NFData (FileMap a) Source # 
Instance details

Defined in System.DirTree

Methods

rnf :: FileMap a -> () #

Ixed (FileMap a) Source # 
Instance details

Defined in System.DirTree

Methods

ix :: Index (FileMap a) -> Traversal' (FileMap a) (IxValue (FileMap a)) #

At (FileMap a) Source # 
Instance details

Defined in System.DirTree

Methods

at :: Index (FileMap a) -> Lens' (FileMap a) (Maybe (IxValue (FileMap a))) #

type Rep (FileMap a) Source # 
Instance details

Defined in System.DirTree

type Rep (FileMap a) = D1 (MetaData "FileMap" "System.DirTree" "dirtree-0.1.2-ANt4d8ezA2c8BWLFVTMai6" True) (C1 (MetaCons "FileMap" PrefixI True) (S1 (MetaSel (Just "fileMapAsMap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map String a))))
type Index (FileMap a) Source # 
Instance details

Defined in System.DirTree

type Index (FileMap a) = String
type IxValue (FileMap a) Source # 
Instance details

Defined in System.DirTree

type IxValue (FileMap a) = a

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.

(.*) :: String -> a -> (String, DirTree a) Source #

Create a file

(./) :: String -> [(String, DirTree a)] -> (String, DirTree a) Source #

Create a directory

(.*>) :: String -> s -> (String, RelativeDirTree s a) Source #

Create a symbolic link

(.*.) :: String -> a -> (String, RelativeDirTree s a) Source #

Create a real file

Accessors

lookupFileMap :: String -> FileMap a -> Maybe a Source #

Lookup a file using a filename

DirTree

A DirTree is a recursive difined tree.

newtype DirTree a Source #

A dir tree is a tree of nodes.

Constructors

DirTree 
Instances
Functor DirTree Source # 
Instance details

Defined in System.DirTree

Methods

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

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

Foldable DirTree Source # 
Instance details

Defined in System.DirTree

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.DirTree

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

FunctorWithIndex FileKey DirTree Source # 
Instance details

Defined in System.DirTree

Methods

imap :: (FileKey -> a -> b) -> DirTree a -> DirTree b #

imapped :: IndexedSetter FileKey (DirTree a) (DirTree b) a b #

FoldableWithIndex FileKey DirTree Source # 
Instance details

Defined in System.DirTree

Methods

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 # 
Instance details

Defined in System.DirTree

Methods

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 # 
Instance details

Defined in System.DirTree

Methods

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

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

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

Defined in System.DirTree

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 # 
Instance details

Defined in System.DirTree

Methods

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

show :: DirTree a -> String #

showList :: [DirTree a] -> ShowS #

Generic (DirTree a) Source # 
Instance details

Defined in System.DirTree

Associated Types

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

Methods

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

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

Semigroup (DirTree a) Source #

A DirTree is a semigroup, where it merges directories and take the last entry if there files.

>>> file 'a' <> file 'b'
file 'b'
>>> directory' [ "a" .* 'a', "b" .* 'b'] <> directory' [ "b" .* 'd', "c" .* 'c']
directory (fromFileList ["a" .* 'a',"b" .* 'd',"c" .* 'c'])
Instance details

Defined in System.DirTree

Methods

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

sconcat :: NonEmpty (DirTree a) -> DirTree a #

stimes :: Integral b => b -> DirTree a -> DirTree a #

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

Defined in System.DirTree

Methods

rnf :: DirTree a -> () #

Ixed (DirTree a) Source # 
Instance details

Defined in System.DirTree

Methods

ix :: Index (DirTree a) -> Traversal' (DirTree a) (IxValue (DirTree a)) #

At (DirTree a) Source #

Not a completly correct Lens, since it is implossible to delete the current DirTree. To use a correct Lens, see alterFile.

>>> emptyDirectory & at ["file", "path"] ?~ file 'x'
directory (fromFileList ["file" ./ ["path" .* 'x']])
Instance details

Defined in System.DirTree

Methods

at :: Index (DirTree a) -> Lens' (DirTree a) (Maybe (IxValue (DirTree a))) #

Wrapped (DirTree a) Source # 
Instance details

Defined in System.DirTree

Associated Types

type Unwrapped (DirTree a) :: Type #

Methods

_Wrapped' :: Iso' (DirTree a) (Unwrapped (DirTree a)) #

DirTree a1 ~ t => Rewrapped (DirTree a2) t Source # 
Instance details

Defined in System.DirTree

AsDirTreeNode (DirTree a) (DirForest a) a Source # 
Instance details

Defined in System.DirTree

type Rep (DirTree a) Source # 
Instance details

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 # 
Instance details

Defined in System.DirTree

type Index (DirTree a) = FileKey
type IxValue (DirTree a) Source # 
Instance details

Defined in System.DirTree

type IxValue (DirTree a) = DirTree a
type Unwrapped (DirTree a) Source # 
Instance details

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 DirTrees are also relative.

Constructors

file :: a -> DirTree a Source #

Constructs a dirtree with only a file

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

directory :: DirForest a -> DirTree a Source #

Constructs a dirtree with a directory

directory' :: [(String, DirTree a)] -> DirTree a Source #

Constructs a dirtree with a file list

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

type FileKey = [String] Source #

A FileKey is a list of filenames to get to the final file

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 #

Alter File is the DirTree version of alterF.

>>> alterFile (\x -> [Nothing, x, Just (file 'b')]) [] (Just (file 'a'))
[Nothing,Just (file 'a'),Just (file 'b')]

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

data Link Source #

A Link can either be Internal, pointing to something in the DirTree or External pointing to an absolute 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

A DirForest is the content of a directory. A DirForest is more useful in some cases

newtype DirForest a Source #

Constructors

DirForest 
Instances
Functor DirForest Source # 
Instance details

Defined in System.DirTree

Methods

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

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

Foldable DirForest Source # 
Instance details

Defined in System.DirTree

Methods

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

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

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

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

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

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

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

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

toList :: DirForest a -> [a] #

null :: DirForest a -> Bool #

length :: DirForest a -> Int #

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

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

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

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

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

Traversable DirForest Source # 
Instance details

Defined in System.DirTree

Methods

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

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

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

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

FunctorWithIndex ForestFileKey DirForest Source # 
Instance details

Defined in System.DirTree

FoldableWithIndex ForestFileKey DirForest Source # 
Instance details

Defined in System.DirTree

Methods

ifoldMap :: Monoid m => (ForestFileKey -> a -> m) -> DirForest a -> m #

ifolded :: IndexedFold ForestFileKey (DirForest a) a #

ifoldr :: (ForestFileKey -> a -> b -> b) -> b -> DirForest a -> b #

ifoldl :: (ForestFileKey -> b -> a -> b) -> b -> DirForest a -> b #

ifoldr' :: (ForestFileKey -> a -> b -> b) -> b -> DirForest a -> b #

ifoldl' :: (ForestFileKey -> b -> a -> b) -> b -> DirForest a -> b #

TraversableWithIndex ForestFileKey DirForest Source # 
Instance details

Defined in System.DirTree

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

Defined in System.DirTree

Methods

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

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

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

Defined in System.DirTree

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

Defined in System.DirTree

Generic (DirForest a) Source # 
Instance details

Defined in System.DirTree

Associated Types

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

Methods

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

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

Semigroup (DirForest a) Source # 
Instance details

Defined in System.DirTree

Methods

(<>) :: DirForest a -> DirForest a -> DirForest a #

sconcat :: NonEmpty (DirForest a) -> DirForest a #

stimes :: Integral b => b -> DirForest a -> DirForest a #

Monoid (DirForest a) Source # 
Instance details

Defined in System.DirTree

NFData a => NFData (DirForest a) Source # 
Instance details

Defined in System.DirTree

Methods

rnf :: DirForest a -> () #

Ixed (DirForest a) Source # 
Instance details

Defined in System.DirTree

At (DirForest a) Source # 
Instance details

Defined in System.DirTree

Methods

at :: Index (DirForest a) -> Lens' (DirForest a) (Maybe (IxValue (DirForest a))) #

Wrapped (DirForest a) Source # 
Instance details

Defined in System.DirTree

Associated Types

type Unwrapped (DirForest a) :: Type #

DirForest a1 ~ t => Rewrapped (DirForest a2) t Source # 
Instance details

Defined in System.DirTree

AsDirTreeNode (DirTree a) (DirForest a) a Source # 
Instance details

Defined in System.DirTree

type Rep (DirForest a) Source # 
Instance details

Defined in System.DirTree

type Rep (DirForest a) = D1 (MetaData "DirForest" "System.DirTree" "dirtree-0.1.2-ANt4d8ezA2c8BWLFVTMai6" True) (C1 (MetaCons "DirForest" PrefixI True) (S1 (MetaSel (Just "getInternalFileMap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (FileMap (DirTree a)))))
type Index (DirForest a) Source # 
Instance details

Defined in System.DirTree

type IxValue (DirForest a) Source # 
Instance details

Defined in System.DirTree

type Unwrapped (DirForest a) Source # 
Instance details

Defined in System.DirTree

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

Constructors

asRelativeDirForest :: DirForest a -> RelativeDirForest s a Source #

All DirTrees are also relative.

emptyForest :: DirForest a Source #

Creates an empty forest

singletonForest :: String -> DirTree a -> DirForest a Source #

Creates an singleton forest

createDeepForest :: ForestFileKey -> DirTree a -> DirForest a Source #

Creates an deep file in a forest

Iterators

alterForest :: forall f a. Functor f => (Maybe (DirTree a) -> f (Maybe (DirTree a))) -> ForestFileKey -> DirForest a -> f (DirForest a) Source #