module Darcs.Repository.Identify
( maybeIdentifyRepository
, identifyRepository
, identifyRepositoryFor
, IdentifyRepo(..)
, findRepository
, amInRepository
, amNotInRepository
, amInHashedRepository
, seekRepo
, findAllReposInDir
) where
import Prelude ()
import Darcs.Prelude
import Control.Monad ( forM )
import Darcs.Repository.Format ( tryIdentifyRepoFormat
, readProblem
, transferProblem
)
import System.Directory ( doesDirectoryExist
, setCurrentDirectory
, createDirectoryIfMissing
, doesFileExist
, getDirectoryContents
)
import System.FilePath.Posix ( (</>) )
import System.IO.Error ( catchIOError )
import Data.Maybe ( fromMaybe )
import Darcs.Repository.Old ( oldRepoFailMsg )
import Darcs.Repository.Flags ( UseCache(..), WorkRepo (..) )
import Darcs.Util.Path
( toFilePath
, ioAbsoluteOrRemote
, toPath
)
import Darcs.Util.Exception ( catchall )
import Darcs.Util.URL ( isValidLocalPath )
import Darcs.Util.Workaround
( getCurrentDirectory
)
import Darcs.Repository.Prefs ( getCaches )
import Darcs.Repository.InternalTypes( Repository
, PristineType(..)
, mkRepo
, repoFormat
, repoPristineType
)
import Darcs.Util.Global ( darcsdir )
import System.Mem( performGC )
data IdentifyRepo rt p wR wU wT
= BadRepository String
| NonRepository String
| GoodRepository (Repository rt p wR wU wT)
maybeIdentifyRepository :: UseCache -> String -> IO (IdentifyRepo rt p wR wU wT)
maybeIdentifyRepository useCache "." =
do darcs <- doesDirectoryExist darcsdir
if not darcs
then return (NonRepository $ "Missing " ++ darcsdir ++ " directory")
else do
repoFormatOrError <- tryIdentifyRepoFormat "."
here <- toPath `fmap` ioAbsoluteOrRemote "."
case repoFormatOrError of
Left err -> return $ NonRepository err
Right rf ->
case readProblem rf of
Just err -> return $ BadRepository err
Nothing -> do pris <- identifyPristine
cs <- getCaches useCache here
return $ GoodRepository $ mkRepo here rf pris cs
maybeIdentifyRepository useCache url' =
do url <- toPath `fmap` ioAbsoluteOrRemote url'
repoFormatOrError <- tryIdentifyRepoFormat url
case repoFormatOrError of
Left e -> return $ NonRepository e
Right rf -> case readProblem rf of
Just err -> return $ BadRepository err
Nothing -> do cs <- getCaches useCache url
return $ GoodRepository $ mkRepo url rf NoPristine cs
identifyPristine :: IO PristineType
identifyPristine =
do pristine <- doesDirectoryExist $ darcsdir++"/pristine"
current <- doesDirectoryExist $ darcsdir++"/current"
hashinv <- doesFileExist $ darcsdir++"/hashed_inventory"
case (pristine || current, hashinv) of
(False, False) -> return NoPristine
(True, False) -> return PlainPristine
(False, True ) -> return HashedPristine
_ -> fail "Multiple pristine trees."
identifyRepository :: forall rt p wR wU wT. UseCache -> String
-> IO (Repository rt p wR wU wT)
identifyRepository useCache url =
do er <- maybeIdentifyRepository useCache url
case er of
BadRepository s -> fail s
NonRepository s -> fail s
GoodRepository r -> return r
identifyRepositoryFor :: forall rt p wR wU wT vR vU vT.
Repository rt p wR wU wT
-> UseCache
-> String
-> IO (Repository rt p vR vU vT)
identifyRepositoryFor source useCache url =
do target <- identifyRepository useCache url
case transferProblem (repoFormat target) (repoFormat source) of
Just e -> fail $ "Incompatibility with repository " ++ url ++ ":\n" ++ e
Nothing -> return target
amInRepository :: WorkRepo -> IO (Either String ())
amInRepository (WorkRepoDir d) =
do
setCurrentDirectory d
status <- maybeIdentifyRepository YesUseCache "."
case status of
GoodRepository _ -> return (Right ())
BadRepository e -> return (Left $ "While " ++ d ++ " looks like a repository directory, we have a problem with it:\n" ++ e)
NonRepository _ -> return (Left "You need to be in a repository directory to run this command.")
`catchIOError`
\e -> return (Left (show e))
amInRepository _ =
fromMaybe (Left "You need to be in a repository directory to run this command.") <$> seekRepo
amInHashedRepository :: WorkRepo -> IO (Either String ())
amInHashedRepository wd
= do inrepo <- amInRepository wd
case inrepo of
Right _ -> do pristine <- identifyPristine
case pristine of
HashedPristine -> return (Right ())
_ -> return (Left oldRepoFailMsg)
left -> return left
seekRepo :: IO (Maybe (Either String ()))
seekRepo = getCurrentDirectory >>= helper where
helper startpwd = do
status <- maybeIdentifyRepository YesUseCache "."
case status of
GoodRepository _ -> return . Just $ Right ()
BadRepository e -> return . Just $ Left e
NonRepository _ ->
do cd <- toFilePath `fmap` getCurrentDirectory
setCurrentDirectory ".."
cd' <- toFilePath `fmap` getCurrentDirectory
if cd' /= cd
then helper startpwd
else do setCurrentDirectory startpwd
return Nothing
amNotInRepository :: WorkRepo -> IO (Either String ())
amNotInRepository (WorkRepoDir d) = do
createDirectoryIfMissing False d
`catchall` (performGC >> createDirectoryIfMissing False d)
setCurrentDirectory d
amNotInRepository WorkRepoCurrentDir
amNotInRepository _ = do
status <- maybeIdentifyRepository YesUseCache "."
case status of
GoodRepository _ -> return (Left "You may not run this command in a repository.")
BadRepository e -> return (Left $ "You may not run this command in a repository.\nBy the way, we have a problem with it:\n" ++ e)
NonRepository _ -> return (Right ())
findRepository :: WorkRepo -> IO (Either String ())
findRepository workrepo =
case workrepo of
WorkRepoPossibleURL d | isValidLocalPath d -> do
setCurrentDirectory d
findRepository WorkRepoCurrentDir
WorkRepoDir d -> do
setCurrentDirectory d
findRepository WorkRepoCurrentDir
_ -> fromMaybe (Right ()) <$> seekRepo
`catchIOError` \e ->
return (Left (show e))
findAllReposInDir :: FilePath -> IO [FilePath]
findAllReposInDir topDir = do
isDir <- doesDirectoryExist topDir
if isDir
then do
status <- maybeIdentifyRepository NoUseCache topDir
case status of
GoodRepository repo
| HashedPristine <- repoPristineType repo -> return [topDir]
| otherwise -> return []
_ -> getRecursiveDarcsRepos' topDir
else return []
where
getRecursiveDarcsRepos' d = do
names <- getDirectoryContents d
let properNames = filter (\x -> head x /= '.') names
paths <- forM properNames $ \name -> do
let path = d </> name
findAllReposInDir path
return (concat paths)