module Darcs.UI.Commands.Util.Tree
(
treeHas
, treeHasDir
, treeHasFile
, treeHasAnycase
) where
import Prelude ()
import Darcs.Prelude
import Control.Monad ( forM )
import Control.Monad.State.Strict( gets )
import qualified Data.ByteString.Char8 as BSC
import Data.Char ( toLower )
import Darcs.Util.Tree.Monad
( withDirectory, fileExists, directoryExists
, virtualTreeMonad, currentDirectory
, TreeMonad )
import qualified Darcs.Util.Tree.Monad as HS ( exists, tree )
import Darcs.Util.Tree ( Tree, listImmediate, findTree )
import Darcs.Util.Path
( AnchoredPath(..), Name(..), floatPath )
treeHasAnycase :: (Functor m, Monad m)
=> Tree m
-> FilePath
-> m Bool
treeHasAnycase tree path =
fst `fmap` virtualTreeMonad (existsAnycase $ floatPath path) tree
existsAnycase :: (Functor m, Monad m)
=> AnchoredPath
-> TreeMonad m Bool
existsAnycase (AnchoredPath []) = return True
existsAnycase (AnchoredPath (Name x:xs)) = do
wd <- currentDirectory
Just tree <- gets (flip findTree wd . HS.tree)
let subs = [ AnchoredPath [Name n] | (Name n, _) <- listImmediate tree,
BSC.map toLower n == BSC.map toLower x ]
or `fmap` forM subs (\path -> do
file <- fileExists path
if file then return True
else withDirectory path (existsAnycase $ AnchoredPath xs))
treeHas :: (Functor m, Monad m) => Tree m -> FilePath -> m Bool
treeHas tree path = fst `fmap` virtualTreeMonad (HS.exists $ floatPath path) tree
treeHasDir :: (Functor m, Monad m) => Tree m -> FilePath -> m Bool
treeHasDir tree path = fst `fmap` virtualTreeMonad (directoryExists $ floatPath path) tree
treeHasFile :: (Functor m, Monad m) => Tree m -> FilePath -> m Bool
treeHasFile tree path = fst `fmap` virtualTreeMonad (fileExists $ floatPath path) tree