% 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 Darcs.Commands.Check ( check, check_uniqueness ) where import Control.Monad ( when ) import System.Directory ( setCurrentDirectory ) import Workaround ( getCurrentDirectory ) import System.Exit ( ExitCode(..), exitWith ) import Data.List ( sort ) import Darcs.Commands ( DarcsCommand(..), nodefaults ) import Darcs.Arguments ( DarcsFlag( Quiet, Verbose, NoTest, LeaveTestDir ), partial_check, notest, leave_test_dir, working_repo_dir, ) import Darcs.Hopefully ( info, piap ) import Darcs.Repository ( Repository, amInRepository, read_repo, withRepository, ($-), slurp_recorded, checkPristineAgainstCwd ) import Darcs.Repository.Checkpoint ( get_checkpoint_by_default ) import Darcs.Repository.ApplyPatches ( apply_patches_with_feedback ) import Darcs.Patch ( RepoPatch, patch2patchinfo, showPatch ) import Darcs.Patch.Ordered ( FL(..), reverseRL, mapRL, concatRL ) import Darcs.Patch.Info ( human_friendly ) import Darcs.SlurpDirectory ( slurp ) import Darcs.Diff ( smart_diff ) import Darcs.Test ( run_test ) import Darcs.Progress ( debugMessage ) import Darcs.Lock ( withTempDir, withPermDir ) import Darcs.Repository.Prefs ( filetype_function ) import Darcs.Patch.Depends ( get_patches_beyond_tag ) import Darcs.Sealed ( Sealed(..), unsafeUnflippedseal ) import Printer ( Doc, putDocLn, text, ($$), (<+>) ) \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 = amInRepository, command_get_arg_possibilities = return [], command_argdefaults = nodefaults, command_advanced_options = [], command_basic_options = [partial_check, notest, leave_test_dir, working_repo_dir ]} \end{code} \begin{code} check_cmd :: [DarcsFlag] -> [String] -> IO () check_cmd opts _ = withRepository opts $- \repository -> do let putVerbose s = when (Verbose `elem` opts) $ putDocLn s putInfo s = when (not $ Quiet `elem` opts) $ putDocLn s debugMessage "I'm about to check for uniqueness of patches." check_uniqueness putVerbose putInfo repository Sealed patches <- read_repo repository -- FIXME: This should be lazy! maybe_chk <- get_checkpoint_by_default repository ftf <- filetype_function cwd <- getCurrentDirectory wd "checking" $ \chd -> do putVerbose $ text "Checking patches..." case maybe_chk of Just chk -> do let chtg = patch2patchinfo chk putVerbose $ text "I am checking from a checkpoint." apply_patches_with_feedback [] "Checking patch" $ (chtg `piap` chk) :>: reverseRL (concatRL $ unsafeUnflippedseal $ get_patches_beyond_tag chtg patches) Nothing -> apply_patches_with_feedback [] "Checking patch" $ reverseRL $ concatRL patches is_same <- checkPristineAgainstCwd repository 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 <- slurp_recorded repository p <- slurp chd putInfo $ case smart_diff opts ftf p mc of NilFL -> text "Nothing" patch -> text "Difference: " <+> showPatch patch putInfo $ text "" $$ text "Inconsistent repository!" exitWith $ ExitFailure 1 where wd = if LeaveTestDir `elem` opts then withPermDir else withTempDir \end{code} \input{Darcs/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 :: RepoPatch p => (Doc -> IO ()) -> (Doc -> IO ()) -> Repository p -> IO () check_uniqueness putVerbose putInfo repository = do putVerbose $ text "Checking that patch names are unique..." Sealed r <- read_repo repository case has_duplicate $ mapRL info $ concatRL 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}