% Copyright (C) 2002-2005 David Roundy % % This program is free software; you can redistribute it and/or modify % it under the terms of the GNU General Public License as published by % the Free Software Foundation; either version 2, or (at your option) % any later version. % % This program is distributed in the hope that it will be useful, % but WITHOUT ANY WARRANTY; without even the implied warranty of % MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the % GNU General Public License for more details. % % You should have received a copy of the GNU General Public License % along with this program; see the file COPYING. If not, write to % the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, % Boston, MA 02110-1301, USA. \subsection{darcs check} \begin{code} module Check ( check, check_uniqueness ) where import Monad ( when ) import Maybe ( isJust ) import Directory ( setCurrentDirectory ) import Workaround ( getCurrentDirectory ) import System ( ExitCode(..), exitWith ) import List ( sort ) import DarcsCommands ( DarcsCommand(..), nodefaults ) import DarcsArguments ( DarcsFlag( Quiet, Verbose, NoTest, LeaveTestDir ), partial_check, any_verbosity, notest, leave_test_dir, working_repo_dir, ) import DarcsRepo ( am_in_repo, read_repo, get_checkpoint_by_default, apply_patches_with_feedback, lazily_read_repo, simple_feedback ) import Pristine ( identifyPristine, checkPristine, slurpPristine ) import Patch ( patch2patchinfo, showPatch ) import PatchInfo ( human_friendly ) import SlurpDirectory ( slurp ) import Diff ( smart_diff ) import Test ( run_test ) import Lock ( withTempDir, withPermDir ) import RepoPrefs ( filetype_function ) import DarcsUtils ( withCurrentDirectory ) import Depends ( get_patches_beyond_tag ) import Printer ( Doc, putDocLn, text, ($$), (<+>) ) #include "impossible.h" \end{code} \options{check} \haskell{check_description} \begin{code} check_description :: String check_description = "Check the repository for consistency." \end{code} Check verifies that the patches stored in the repository, when successively applied to an empty tree, properly recreate the stored pristine tree. \begin{options} --complete, --partial \end{options} If you have a checkpoint of the repository (as is the case if you got the repository originally using \verb!darcs get --partial!), by default \verb'darcs check' will only verify the contents since the most recent checkpoint. You can change this behavior using the \verb!--complete! flag. \begin{code} check_help :: String check_help = "Check verifies that the patches stored in the repository, when successively\n"++ "applied to an empty tree, properly recreate the stored pristine tree.\n" \end{code} \begin{code} check :: DarcsCommand check = DarcsCommand {command_name = "check", command_help = check_help, command_description = check_description, command_extra_args = 0, command_extra_arg_help = [], command_command = check_cmd, command_prereq = am_in_repo, command_get_arg_possibilities = return [], command_argdefaults = nodefaults, command_darcsoptions = [partial_check, any_verbosity,notest, leave_test_dir, working_repo_dir ]} \end{code} \begin{code} check_cmd :: [DarcsFlag] -> [String] -> IO () check_cmd opts _ = let putVerbose s = when (Verbose `elem` opts) $ putDocLn s putInfo s = when (not $ Quiet `elem` opts) $ putDocLn s in do check_uniqueness putVerbose putInfo patches <- lazily_read_repo "." maybe_chk <- get_checkpoint_by_default opts "." ftf <- filetype_function cwd <- getCurrentDirectory wd "checking" $ \chd -> do putVerbose $ text "Applying patches..." case maybe_chk of Just chk -> case patch2patchinfo chk of Just chtg -> do putVerbose $ text "I am checking from a checkpoint." apply_patches_with_feedback [] feedback putInfo $ (chtg, Just chk) : reverse (concat $ get_patches_beyond_tag chtg patches) Nothing -> impossible Nothing -> apply_patches_with_feedback [] feedback putInfo $ reverse $ concat patches is_same <- withCurrentDirectory cwd $ (identifyPristine >>= checkPristine chd) if is_same then do putInfo $ text "The repository is consistent!" if NoTest `elem` opts then exitWith ExitSuccess else do setCurrentDirectory cwd ec <- run_test opts chd exitWith ec else do putInfo $ text "Looks like we have a difference..." mc <- withCurrentDirectory cwd $ identifyPristine >>= slurpPristine when (isJust mc) $ do p <- slurp chd putInfo $ case smart_diff opts ftf p (fromJust mc) of Nothing -> text "Nothing" Just patch -> text "Just" <+> showPatch patch putInfo $ text "" $$ text "Inconsistent repository!" exitWith $ ExitFailure 1 where wd = if LeaveTestDir `elem` opts then withPermDir else withTempDir feedback = simple_feedback opts \end{code} \input{Test.lhs} \begin{options} --no-test \end{options} If you just want to check the consistency of your repository without running the test, you can call darcs check with the \verb!--no-test! option. \begin{code} check_uniqueness :: (Doc -> IO ()) -> (Doc -> IO ()) -> IO () check_uniqueness putVerbose putInfo = do putVerbose $ text "Checking that patch names are unique..." r <- read_repo "." case has_duplicate $ map fst $ concat r of Nothing -> return () Just pinf -> do putInfo $ text "Error! Duplicate patch name:" putInfo $ human_friendly pinf exitWith $ ExitFailure 1 has_duplicate :: Ord a => [a] -> Maybe a has_duplicate li = hd $ sort li where hd [_] = Nothing hd [] = Nothing hd (x1:x2:xs) | x1 == x2 = Just x1 | otherwise = hd (x2:xs) \end{code}