%  Copyright (C) 2003,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 repair}
\begin{code}
module Darcs.Commands.Repair ( repair ) where
import System.IO

import Darcs.Commands
import Darcs.Arguments ( DarcsFlag(),
                        working_repo_dir, umask_option,
                      )
import Darcs.Repository ( withRepoLock, ($-), amInRepository,
                          replacePristineFromSlurpy, writePatchSet )
import Darcs.Repository.Repair( replayRepository,
                                RepositoryConsistency(..) )
\end{code}

\options{repair}
\begin{code}
repair_description :: String
repair_description = "Repair a corrupted repository."
\end{code}
\haskell{repair_help}

\begin{code}
repair_help :: String
repair_help =
 "The `darcs repair' command attempts to fix corruption in the current\n" ++
 "repository.  Currently it can only repair damage to the pristine tree,\n" ++
 "which is where most corruption occurs.\n"

repair :: DarcsCommand
repair = DarcsCommand {command_name = "repair",
                       command_help = repair_help,
                       command_description = repair_description,
                       command_extra_args = 0,
                       command_extra_arg_help = [],
                       command_command = repair_cmd,
                       command_prereq = amInRepository,
                       command_get_arg_possibilities = return [],
                       command_argdefaults = nodefaults,
                       command_advanced_options = [umask_option],
                       command_basic_options = [working_repo_dir]}

repair_cmd :: [DarcsFlag] -> [String] -> IO ()
repair_cmd opts _ = withRepoLock opts $- \repository -> do
  replayRepository repository opts $ \state ->
    case state of
      RepositoryConsistent ->
          putStrLn "The repository is already consistent, no changes made."
      BrokenPristine s -> do
               putStrLn "Fixing pristine tree..."
               replacePristineFromSlurpy repository s
      BrokenPatches s newps  -> do
               putStrLn "Writing out repaired patches..."
               writePatchSet newps opts
               putStrLn "Fixing pristine tree..."
               replacePristineFromSlurpy repository s
               return ()

\end{code}