Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data DirTree a
- = DirTree_Dir FilePath (Map FileName (DirTree a))
- | DirTree_File FilePath a
- | DirTree_Symlink FilePath (Symlink a)
- data Symlink a
- filePath :: DirTree a -> FilePath
- type FileName = String
- fileName :: DirTree a -> FileName
- fileNameMap :: [DirTree a] -> Map FileName (DirTree a)
- insertSibling :: DirTree a -> Map FileName (DirTree a) -> Map FileName (DirTree a)
- removeSibling :: DirTree a -> Map FileName (DirTree a) -> Map FileName (DirTree a)
- withFirstChild :: Map FileName (DirTree a) -> (DirTree a -> Map FileName (DirTree a) -> x) -> Maybe x
Documentation
The contents of a directory, represented as a tree. See Symlink
for
special handling of symlinks.
DirTree_Dir FilePath (Map FileName (DirTree a)) | |
DirTree_File FilePath a | |
DirTree_Symlink FilePath (Symlink a) |
Instances
Symlink cycles are prevented by separating symlinks into two categories: those that point to paths already within the directory hierarchy being recursively listed, and those that are not. In the former case, rather than following the symlink and listing the target redundantly, we simply store the symlink reference itself. In the latter case, we treat the symlink as we would any other folder and produce a list of its contents.
The String
argument represents the symlink reference (e.g., "../somefile").
In the Symlink_Internal
case, the second (FilePath
) argument is the path
to the symlink target.
In the Symlink_External
case, the second ([DirTree a]
) argument contains
the contents of the symlink target.
Instances
Functor Symlink Source # | |
Foldable Symlink Source # | |
Defined in System.Directory.Contents.Types fold :: Monoid m => Symlink m -> m # foldMap :: Monoid m => (a -> m) -> Symlink a -> m # foldr :: (a -> b -> b) -> b -> Symlink a -> b # foldr' :: (a -> b -> b) -> b -> Symlink a -> b # foldl :: (b -> a -> b) -> b -> Symlink a -> b # foldl' :: (b -> a -> b) -> b -> Symlink a -> b # foldr1 :: (a -> a -> a) -> Symlink a -> a # foldl1 :: (a -> a -> a) -> Symlink a -> a # elem :: Eq a => a -> Symlink a -> Bool # maximum :: Ord a => Symlink a -> a # minimum :: Ord a => Symlink a -> a # | |
Traversable Symlink Source # | |
Eq a => Eq (Symlink a) Source # | |
Data a => Data (Symlink a) Source # | |
Defined in System.Directory.Contents.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Symlink a -> c (Symlink a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Symlink a) # toConstr :: Symlink a -> Constr # dataTypeOf :: Symlink a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Symlink a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Symlink a)) # gmapT :: (forall b. Data b => b -> b) -> Symlink a -> Symlink a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Symlink a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Symlink a -> r # gmapQ :: (forall d. Data d => d -> u) -> Symlink a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Symlink a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Symlink a -> m (Symlink a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Symlink a -> m (Symlink a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Symlink a -> m (Symlink a) # | |
Ord a => Ord (Symlink a) Source # | |
Defined in System.Directory.Contents.Types | |
Read a => Read (Symlink a) Source # | |
Show a => Show (Symlink a) Source # | |
Generic (Symlink a) Source # | |
type Rep (Symlink a) Source # | |
Defined in System.Directory.Contents.Types type Rep (Symlink a) = D1 (MetaData "Symlink" "System.Directory.Contents.Types" "directory-contents-0.2.0.0-inplace" False) (C1 (MetaCons "Symlink_Internal" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) :+: C1 (MetaCons "Symlink_External" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map FileName (DirTree a))))) |
Utilities
type FileName = String Source #
File names, as opposed to file paths, are used to uniquely identify siblings at each level
fileNameMap :: [DirTree a] -> Map FileName (DirTree a) Source #
Construct a map of files indexed by filename. Should only be used for a particular generation or level in the directory hierarchy (since that's the only time we can be sure that names are unique)
insertSibling :: DirTree a -> Map FileName (DirTree a) -> Map FileName (DirTree a) Source #
Add a sibling to a map of files