dirforest-0.1.0.0: Typed directory forest
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.DirForest

Description

A directory forest of files associated with values

This module is meant to be imported like this:

import Data.DirForest (DirForest)
import qualified Data.DirForest as DF
Synopsis

Dirforest types

data DirTree a Source #

Constructors

NodeFile a 
NodeDir (DirForest a) 

Instances

Instances details
Foldable DirTree Source # 
Instance details

Defined in Data.DirForest

Methods

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

foldMap :: Monoid m => (a -> m) -> DirTree a -> 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 #

Eq1 DirTree Source # 
Instance details

Defined in Data.DirForest

Methods

liftEq :: (a -> b -> Bool) -> DirTree a -> DirTree b -> Bool #

Ord1 DirTree Source # 
Instance details

Defined in Data.DirForest

Methods

liftCompare :: (a -> b -> Ordering) -> DirTree a -> DirTree b -> Ordering #

Traversable DirTree Source # 
Instance details

Defined in Data.DirForest

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

Functor DirTree Source # 
Instance details

Defined in Data.DirForest

Methods

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

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

HasCodec a => FromJSON (DirTree a) Source # 
Instance details

Defined in Data.DirForest

HasCodec a => ToJSON (DirTree a) Source # 
Instance details

Defined in Data.DirForest

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

Defined in Data.DirForest

Generic (DirTree a) Source # 
Instance details

Defined in Data.DirForest

Associated Types

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

Methods

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

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

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

Defined in Data.DirForest

Methods

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

show :: DirTree a -> String #

showList :: [DirTree a] -> ShowS #

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

Defined in Data.DirForest

Methods

rnf :: DirTree a -> () #

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

Defined in Data.DirForest

Methods

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

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

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

Defined in Data.DirForest

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 #

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

Defined in Data.DirForest

Methods

validate :: DirTree a -> Validation #

type Rep (DirTree a) Source # 
Instance details

Defined in Data.DirForest

type Rep (DirTree a) = D1 ('MetaData "DirTree" "Data.DirForest" "dirforest-0.1.0.0-Kx7FjqyA5HqHM6ZA0ofIz0" 'False) (C1 ('MetaCons "NodeFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "NodeDir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DirForest a))))

newtype DirForest a Source #

Constructors

DirForest 

Instances

Instances details
Foldable DirForest Source # 
Instance details

Defined in Data.DirForest

Methods

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

foldMap :: Monoid m => (a -> m) -> DirForest a -> 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 #

Eq1 DirForest Source # 
Instance details

Defined in Data.DirForest

Methods

liftEq :: (a -> b -> Bool) -> DirForest a -> DirForest b -> Bool #

Ord1 DirForest Source # 
Instance details

Defined in Data.DirForest

Methods

liftCompare :: (a -> b -> Ordering) -> DirForest a -> DirForest b -> Ordering #

Traversable DirForest Source # 
Instance details

Defined in Data.DirForest

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

Functor DirForest Source # 
Instance details

Defined in Data.DirForest

Methods

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

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

HasCodec a => FromJSON (DirForest a) Source # 
Instance details

Defined in Data.DirForest

HasCodec a => ToJSON (DirForest a) Source # 
Instance details

Defined in Data.DirForest

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

Defined in Data.DirForest

Generic (DirForest a) Source # 
Instance details

Defined in Data.DirForest

Associated Types

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

Methods

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

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

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

Defined in Data.DirForest

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

Defined in Data.DirForest

Methods

rnf :: DirForest a -> () #

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

Defined in Data.DirForest

Methods

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

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

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

Defined in Data.DirForest

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

Defined in Data.DirForest

type Rep (DirForest a) Source # 
Instance details

Defined in Data.DirForest

type Rep (DirForest a) = D1 ('MetaData "DirForest" "Data.DirForest" "dirforest-0.1.0.0-Kx7FjqyA5HqHM6ZA0ofIz0" 'True) (C1 ('MetaCons "DirForest" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDirForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map FilePath (DirTree a)))))

data InsertionError a Source #

Instances

Instances details
Generic (InsertionError a) Source # 
Instance details

Defined in Data.DirForest

Associated Types

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

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

Defined in Data.DirForest

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

Defined in Data.DirForest

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

Defined in Data.DirForest

Validity a => Validity (InsertionError a) Source # 
Instance details

Defined in Data.DirForest

type Rep (InsertionError a) Source # 
Instance details

Defined in Data.DirForest

data FOD a Source #

File or Dir

Constructors

F a 
D 

Instances

Instances details
Functor FOD Source # 
Instance details

Defined in Data.DirForest

Methods

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

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

Generic (FOD a) Source # 
Instance details

Defined in Data.DirForest

Associated Types

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

Methods

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

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

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

Defined in Data.DirForest

Methods

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

show :: FOD a -> String #

showList :: [FOD a] -> ShowS #

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

Defined in Data.DirForest

Methods

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

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

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

Defined in Data.DirForest

Methods

compare :: FOD a -> FOD a -> Ordering #

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

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

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

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

max :: FOD a -> FOD a -> FOD a #

min :: FOD a -> FOD a -> FOD a #

Validity a => Validity (FOD a) Source # 
Instance details

Defined in Data.DirForest

Methods

validate :: FOD a -> Validation #

type Rep (FOD a) Source # 
Instance details

Defined in Data.DirForest

type Rep (FOD a) = D1 ('MetaData "FOD" "Data.DirForest" "dirforest-0.1.0.0-Kx7FjqyA5HqHM6ZA0ofIz0" 'False) (C1 ('MetaCons "F" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "D" 'PrefixI 'False) (U1 :: Type -> Type))

Comparisons

eq1DirTree :: (a -> b -> Bool) -> DirTree a -> DirTree b -> Bool Source #

ord1DirTree :: (a -> b -> Ordering) -> DirTree a -> DirTree b -> Ordering Source #

eq1DirForest :: (a -> b -> Bool) -> DirForest a -> DirForest b -> Bool Source #

Query

null :: DirForest a -> Bool Source #

True iff the forest is entirely empty

nullFiles :: DirForest a -> Bool Source #

True iff there are only empty directories in the directory forest

lookup :: forall a. Path Rel File -> DirForest a -> Maybe a Source #

Construction

empty :: DirForest a Source #

The empty forest

Traversal

mapWithPath :: (Path Rel File -> a -> b) -> DirForest a -> DirForest b Source #

traverseWithPath :: forall a b f. Applicative f => (Path Rel File -> a -> f b) -> DirForest a -> f (DirForest b) Source #

traverseWithPath_ :: forall a b f. Applicative f => (Path Rel File -> a -> f b) -> DirForest a -> f () Source #

Pruning

pruneEmptyDirs :: DirForest a -> Maybe (DirForest a) Source #

Remove all empty directories from a DirForest

This will return Nothing if the root was also empty.

Conversion

Map

List

IO

Read

read :: forall a b m. MonadIO m => Path b Dir -> (Path b File -> m a) -> m (DirForest a) Source #

readNonHidden :: forall a b m. MonadIO m => Path b Dir -> (Path b File -> m a) -> m (DirForest a) Source #

readFiltered :: forall a b m. MonadIO m => (Path b File -> Bool) -> (Path b Dir -> Bool) -> Path b Dir -> (Path b File -> m a) -> m (DirForest a) Source #

readNonHiddenFiltered :: forall a b m. MonadIO m => (Path b File -> Bool) -> (Path b Dir -> Bool) -> Path b Dir -> (Path b File -> m a) -> m (DirForest a) Source #

readOneLevel :: forall a b m. MonadIO m => Path b Dir -> (Path b File -> m a) -> m (DirForest a) Source #

readOneLevelNonHidden :: forall a b m. MonadIO m => Path b Dir -> (Path b File -> m a) -> m (DirForest a) Source #

readOneLevelFiltered :: forall a b m. MonadIO m => (Path b File -> Bool) -> (Path b Dir -> Bool) -> Path b Dir -> (Path b File -> m a) -> m (DirForest a) Source #

readOneLevelNonHiddenFiltered :: forall a b m. MonadIO m => (Path b File -> Bool) -> (Path b Dir -> Bool) -> Path b Dir -> (Path b File -> m a) -> m (DirForest a) Source #

Write

write :: forall a b. (Show a, Ord a) => Path b Dir -> DirForest a -> (Path b File -> a -> IO ()) -> IO () Source #

Combinations

Union

data InsertValidation e a Source #

Instances

Instances details
Applicative (InsertValidation e) Source # 
Instance details

Defined in Data.DirForest

Functor (InsertValidation e) Source # 
Instance details

Defined in Data.DirForest

Methods

fmap :: (a -> b) -> InsertValidation e a -> InsertValidation e b #

(<$) :: a -> InsertValidation e b -> InsertValidation e a #

Generic (InsertValidation e a) Source # 
Instance details

Defined in Data.DirForest

Associated Types

type Rep (InsertValidation e a) :: Type -> Type #

(Show e, Show a) => Show (InsertValidation e a) Source # 
Instance details

Defined in Data.DirForest

(Eq e, Eq a) => Eq (InsertValidation e a) Source # 
Instance details

Defined in Data.DirForest

(Validity e, Validity a) => Validity (InsertValidation e a) Source # 
Instance details

Defined in Data.DirForest

type Rep (InsertValidation e a) Source # 
Instance details

Defined in Data.DirForest

type Rep (InsertValidation e a) = D1 ('MetaData "InsertValidation" "Data.DirForest" "dirforest-0.1.0.0-Kx7FjqyA5HqHM6ZA0ofIz0" 'False) (C1 ('MetaCons "InsertionErrors" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (InsertionError e)))) :+: C1 ('MetaCons "NoInsertionErrors" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

unionWith :: (a -> a -> a) -> DirForest a -> DirForest a -> InsertValidation a (DirForest a) Source #

unionWithKey :: forall a. (Path Rel File -> a -> a -> a) -> DirForest a -> DirForest a -> InsertValidation a (DirForest a) Source #

Intersection

intersectionWith :: (a -> b -> c) -> DirForest a -> DirForest b -> DirForest c Source #

intersectionWithKey :: forall a b c. (Path Rel File -> a -> b -> c) -> DirForest a -> DirForest b -> DirForest c Source #

Difference

differenceWith :: (a -> b -> Maybe a) -> DirForest a -> DirForest b -> DirForest a Source #

differenceWithKey :: forall a b. (Path Rel File -> a -> b -> Maybe a) -> DirForest a -> DirForest b -> DirForest a Source #

Filter

filter :: (a -> Bool) -> DirForest a -> DirForest a Source #

filterWithKey :: forall a. (Path Rel File -> a -> Bool) -> DirForest a -> DirForest a Source #