{-# LANGUAGE OverloadedStrings #-}
module Darcs.Repository.Format
( RepoFormat(..)
, RepoProperty(..)
, identifyRepoFormat
, tryIdentifyRepoFormat
, createRepoFormat
, writeRepoFormat
, writeProblem
, readProblem
, transferProblem
, formatHas
, addToFormat
, removeFromFormat
) where
import Darcs.Prelude
import Control.Monad ( mplus, (<=<) )
import qualified Data.ByteString.Char8 as BC ( split, pack, unpack, elem )
import qualified Data.ByteString as B ( ByteString, null, empty, stripPrefix )
import Data.List ( partition, intercalate, (\\) )
import Data.Maybe ( mapMaybe )
import Data.String ( IsString )
import System.FilePath.Posix( (</>) )
import Darcs.Util.External
( fetchFilePS
, Cachable( Cachable )
)
import Darcs.Util.Lock ( writeBinFile )
import qualified Darcs.Repository.Flags as F
( WithWorkingDir (..), PatchFormat (..) )
import Darcs.Repository.Paths ( formatPath, oldInventoryPath )
import Darcs.Util.SignalHandler ( catchNonSignal )
import Darcs.Util.Exception ( catchall, prettyException )
import Darcs.Util.ByteString ( linesPS )
import Darcs.Util.Progress ( beginTedious, endTedious, finishedOneIO )
data RepoProperty = Darcs1
| Darcs2
| Darcs3
| HashedInventory
| NoWorkingDir
| RebaseInProgress
| RebaseInProgress_2_16
| UnknownFormat B.ByteString
deriving ( Eq )
darcs1Format, darcs2Format, darcs3Format,
hashedInventoryFormat, noWorkingDirFormat,
rebaseInProgressFormat, rebaseInProgress_2_16,
newStyleRebaseInProgress :: IsString s => s
darcs1Format = "darcs-1.0"
darcs2Format = "darcs-2"
darcs3Format = "darcs-3"
hashedInventoryFormat = "hashed"
noWorkingDirFormat = "no-working-dir"
rebaseInProgressFormat = "rebase-in-progress"
rebaseInProgress_2_16 = "rebase-in-progress-2-16"
newStyleRebaseInProgress = "new-style-rebase-in-progress"
instance Show RepoProperty where
show Darcs1 = darcs1Format
show Darcs2 = darcs2Format
show Darcs3 = darcs3Format
show HashedInventory = hashedInventoryFormat
show NoWorkingDir = noWorkingDirFormat
show RebaseInProgress = rebaseInProgressFormat
show RebaseInProgress_2_16 = rebaseInProgress_2_16
show (UnknownFormat f) = BC.unpack f
readRepoProperty :: B.ByteString -> RepoProperty
readRepoProperty input
| input == darcs1Format = Darcs1
| input == darcs2Format = Darcs2
| input == darcs3Format = Darcs3
| input == hashedInventoryFormat = HashedInventory
| input == noWorkingDirFormat = NoWorkingDir
| input == rebaseInProgressFormat = RebaseInProgress
| input == newStyleRebaseInProgress = RebaseInProgress_2_16
| input == rebaseInProgress_2_16 = RebaseInProgress_2_16
| otherwise = UnknownFormat input
newtype RepoFormat = RF [[RepoProperty]]
formatHas :: RepoProperty -> RepoFormat -> Bool
formatHas f (RF rps) = f `elem` concat rps
addToFormat :: RepoProperty -> RepoFormat -> RepoFormat
addToFormat f (RF rps) = RF (rps ++ [[f]])
removeFromFormat :: RepoProperty -> RepoFormat -> RepoFormat
removeFromFormat f (RF rps) = RF (rps \\ [[f]])
instance Show RepoFormat where
show (RF rf) = unlines $ map (intercalate "|" . map show) rf
identifyRepoFormat :: String -> IO RepoFormat
identifyRepoFormat = either fail return <=< tryIdentifyRepoFormat
tryIdentifyRepoFormat :: String -> IO (Either String RepoFormat)
tryIdentifyRepoFormat repo = do
let k = "Identifying repository " ++ repo
beginTedious k
finishedOneIO k "format"
formatInfo <- (fetchFilePS (repo </> formatPath) Cachable)
`catchall` (return B.empty)
format <-
if B.null formatInfo || BC.elem '<' formatInfo then do
finishedOneIO k "inventory"
missingInvErr <- checkFile (repo </> oldInventoryPath)
case missingInvErr of
Nothing -> return . Right $ RF [[Darcs1]]
Just e -> return . Left $ makeErrorMsg e
else return . Right $ readFormat formatInfo
endTedious k
return format
where
readFormat =
RF . map (map (readRepoProperty . fixupUnknownFormat)) . splitFormat
fixupUnknownFormat s =
case B.stripPrefix "Unknown format: " s of
Nothing -> s
Just s' -> fixupUnknownFormat s'
splitFormat = map (BC.split '|') . filter (not . B.null) . linesPS
checkFile path = (fetchFilePS path Cachable >> return Nothing)
`catchNonSignal`
(return . Just . prettyException)
makeErrorMsg e = "Not a repository: " ++ repo ++ " (" ++ e ++ ")"
writeRepoFormat :: RepoFormat -> FilePath -> IO ()
writeRepoFormat rf loc = writeBinFile loc $ BC.pack $ show rf
createRepoFormat :: F.PatchFormat -> F.WithWorkingDir -> RepoFormat
createRepoFormat fmt wwd = RF $ (HashedInventory : flags2wd wwd) : flags2format fmt
where
flags2format F.PatchFormat1 = []
flags2format F.PatchFormat2 = [[Darcs2]]
flags2format F.PatchFormat3 = [[Darcs3]]
flags2wd F.NoWorkingDir = [NoWorkingDir]
flags2wd F.WithWorkingDir = []
writeProblem :: RepoFormat -> Maybe String
writeProblem target = readProblem target `mplus` findProblems target wp
where
wp [] = error "impossible case"
wp x = case partition isKnown x of
(_, []) -> Nothing
(_, unknowns) -> Just . unwords $
"Can't write repository: unknown formats:" : map show unknowns
transferProblem :: RepoFormat -> RepoFormat -> Maybe String
transferProblem source target
| formatHas Darcs3 source /= formatHas Darcs3 target =
Just "Cannot mix darcs-3 repositories with older formats"
| formatHas Darcs2 source /= formatHas Darcs2 target =
Just "Cannot mix darcs-2 repositories with older formats"
| formatHas RebaseInProgress source =
Just "Cannot transfer patches from a repository \
\where an old-style rebase is in progress"
| otherwise = readProblem source `mplus` writeProblem target
readProblem :: RepoFormat -> Maybe String
readProblem source
| formatHas Darcs1 source && formatHas Darcs2 source =
Just "Invalid repository format: format 2 is incompatible with format 1"
| formatHas RebaseInProgress source && formatHas RebaseInProgress_2_16 source =
Just "Invalid repository format: \
\cannot have both old-style and new-style rebase in progress"
readProblem source = findProblems source rp
where
rp x | any isKnown x = Nothing
rp [] = error "impossible case"
rp x = Just . unwords $ "Can't read repository: unknown formats:" : map show x
findProblems :: RepoFormat -> ([RepoProperty] -> Maybe String) -> Maybe String
findProblems (RF ks) formatHasProblem = case mapMaybe formatHasProblem ks of
[] -> Nothing
xs -> Just $ unlines xs
isKnown :: RepoProperty -> Bool
isKnown p = p `elem` knownProperties
where
knownProperties :: [RepoProperty]
knownProperties = [ Darcs1
, Darcs2
, Darcs3
, HashedInventory
, NoWorkingDir
, RebaseInProgress
, RebaseInProgress_2_16
]