%  Copyright (C) 2003-2004 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 diff}
\begin{code}
{-# OPTIONS_GHC -cpp #-}
{-# LANGUAGE CPP #-}

module Darcs.Commands.Diff ( diff_command ) where

import System.FilePath.Posix ( takeFileName )
import System.Directory ( setCurrentDirectory )
import Workaround ( getCurrentDirectory )
import Darcs.Utils ( askUser, withCurrentDirectory )
import Control.Monad ( when )
import Data.List ( (\\) )

import Autoconf ( diff_program )
import CommandLine ( parseCmd )
import Darcs.Commands ( DarcsCommand(..), nodefaults )
import Darcs.Arguments ( DarcsFlag(DiffFlags, Unified, DiffCmd,
                                   LastN, AfterPatch),
                        match_range, store_in_memory, 
                        diff_cmd_flag, diffflags, unidiff,
                         working_repo_dir, fixSubPaths,
                      )
import Darcs.Hopefully ( info )
import Darcs.RepoPath ( toFilePath, sp2fn )
import Darcs.Match ( get_partial_first_match, get_partial_second_match,
                     first_match, second_match,
                     match_first_patchset, match_second_patchset )
import Darcs.Repository ( PatchSet, withRepository, ($-), read_repo,
                          amInRepository, slurp_recorded_and_unrecorded,
                          createPristineDirectoryTree,
                          createPartialsPristineDirectoryTree )
import Darcs.SlurpDirectory ( get_path_list, writeSlurpy )
import Darcs.Patch ( RepoPatch )
import Darcs.Ordered ( mapRL, concatRL )
import Darcs.Patch.Info ( PatchInfo, human_friendly )
import Darcs.External ( execPipeIgnoreError, clonePaths )
import Darcs.Lock ( withTempDir )
import Darcs.Sealed ( unsafeUnseal )
import Printer ( Doc, putDoc, vcat, empty, ($$) )
#include "impossible.h"
\end{code}

\options{diff}
\begin{code}
diff_description :: String
diff_description = "Create a diff between two versions of the repository."
\end{code}
\haskell{diff_help}
\begin{code}
diff_help :: String
diff_help =
 "Diff can be used to create a diff between two versions which are in your\n"++
 "repository.  Specifying just --from-patch will get you a diff against\n"++
 "your working copy.  If you give diff no version arguments, it gives\n"++
 "you the same information as whatsnew except that the patch is\n"++
 "formatted as the output of a diff command\n"

diff_command :: DarcsCommand
diff_command = DarcsCommand {command_name = "diff",
                             command_help = diff_help,
                             command_description = diff_description,
                             command_extra_args = -1,
                             command_extra_arg_help
                                 = ["[FILE or DIRECTORY]..."],
                             command_command = diff_cmd,
                             command_prereq = amInRepository,
                             command_get_arg_possibilities = return [],
                             command_argdefaults = nodefaults,
                             command_advanced_options = [],
                             command_basic_options = [match_range,
                                                     diff_cmd_flag,
                                                     diffflags, unidiff,
                                                     working_repo_dir, store_in_memory]}
\end{code}

\begin{options}
--diff-opts
\end{options}

Diff calls an external ``diff'' command to do the actual work, and passes
any unrecognized flags to this diff command.  Thus you can call
\begin{verbatim}
% darcs diff -t 0.9.8 -t 0.9.10 -- -u
\end{verbatim}
to get a diff in the unified format.  Actually, thanks to the wonders of
getopt you need the ``\verb!--!'' shown above before any arguments to diff.
You can also specify additional arguments to diff using the
\verb!--diff-opts! flag.  The above command would look like this:
\begin{verbatim}
% darcs diff --diff-opts -u -t 0.9.8 -t 0.9.10
\end{verbatim}
This may not seem like an improvement, but it really pays off when you want
to always give diff the same options.  You can do this by adding
\begin{verbatim}
% diff diff-opts -udp
\end{verbatim}
to your \verb!_darcs/prefs/defaults! file.

\begin{code}
get_diff_opts :: [DarcsFlag] -> [String]
get_diff_opts [] = []
get_diff_opts (Unified:fs) = "-u" : get_diff_opts fs
get_diff_opts (DiffFlags f:fs) = f : get_diff_opts fs
get_diff_opts (_:fs) = get_diff_opts fs

has_diff_cmd_flag :: [DarcsFlag] -> Bool
has_diff_cmd_flag (DiffCmd _:_) = True
has_diff_cmd_flag (_:t) = has_diff_cmd_flag t
has_diff_cmd_flag []  = False

-- | Returns the command we should use for diff as a tuple (command, arguments).
-- This will either be whatever the user specified via --diff-command  or the
-- default 'diff_program'.  Note that this potentially involves parsing the
-- user's diff-command, hence the possibility for failure with an exception.
get_diff_cmd_and_args :: [DarcsFlag] -> String -> String
                      -> Either String (String, [String])
get_diff_cmd_and_args opts f1 f2 = helper opts where
  helper (DiffCmd c:_) =
    case parseCmd [ ('1', f1) , ('2', f2) ] c of
    Left err        -> Left $ show err
    Right ([],_)    -> bug $ "parseCmd should never return empty list"
    Right ((h:t),_) -> Right (h,t)
  helper [] = -- if no command specified, use 'diff'
    Right (diff_program, ("-rN":get_diff_opts opts++[f1,f2]))
  helper (_:t) = helper t
\end{code}

If you want to view only the differences to one or more files, you can do
so with a command such as
\begin{verbatim}
% darcs diff foo.c bar.c baz/
\end{verbatim}

\begin{options}
--diff-command
\end{options}

You can use a different program to view differences by including
the flag \verb!--diff-command!, e.g.
\begin{verbatim}
--diff-command 'opendiff %1 %2'.
\end{verbatim}
The \verb!%1! and \verb!%2!  are replaced with the two versions to be
merged.  The above example works with the FileMerge.app tool that comes with
Apple's developer tools.  To use xxdiff, you would use
\begin{verbatim}
--diff-command 'xxdiff %1 %2'
\end{verbatim}
To use \verb!kdiff3!, you can use
\begin{verbatim}
--diff-command 'kdiff3 %1 %2'
\end{verbatim}

Note that the command is split into space-separated words and the first one is
\verb!exec!ed with the rest as arguments---it is not a shell command.  Also
the substitution of the \verb!%! escapes is only done on complete words.
See \ref{resolution} for how you might work around this fact, for example,
with Emacs' Ediff package.

Note also that the \verb!--diff-opts! flag is ignored if you use this option.

\begin{code}
diff_cmd :: [DarcsFlag] -> [String] -> IO ()
diff_cmd opts args = withRepository opts $- \repository -> do
  when (not (null [i | LastN i <- opts])
       && not (null [p | AfterPatch p <- opts])
       ) $
    fail ("using --patch and --last at the same time with the 'diff' command"
         ++ " doesn't make sense. Use --from-patch to create a diff from this"
         ++ " patch to the present, or use just '--patch' to view this specific"
         ++ " patch.")
  formerdir <- getCurrentDirectory
  path_list <- if null args
               then return []
               else map sp2fn `fmap` fixSubPaths opts args
  thename <- return $ takeFileName formerdir
  withTempDir ("old-"++thename) $ \odir -> do
    setCurrentDirectory formerdir
    withTempDir ("new-"++thename) $ \ndir -> do
    if first_match opts
       then withCurrentDirectory odir $
            get_partial_first_match repository opts path_list
       else if null path_list
            then createPristineDirectoryTree repository (toFilePath odir)
            else createPartialsPristineDirectoryTree repository path_list (toFilePath odir)
    if second_match opts
       then withCurrentDirectory ndir $
            get_partial_second_match repository opts path_list
       else do (_, s) <- slurp_recorded_and_unrecorded repository
               let ps = concatMap (get_path_list s . toFilePath) path_list
               if null path_list
                  then withCurrentDirectory ndir $ writeSlurpy s "."
                  else clonePaths formerdir (toFilePath ndir) ps
    thediff <- withCurrentDirectory (toFilePath odir ++ "/..") $
                   case path_list of
                   [] -> rundiff (takeFileName $ toFilePath odir) (takeFileName $ toFilePath ndir)
                   fs -> vcat `fmap`
                         mapM (\f -> rundiff
                               (takeFileName (toFilePath odir) ++ "/" ++ toFilePath f)
                               (takeFileName (toFilePath ndir) ++ "/" ++ toFilePath f)) fs
    morepatches <- read_repo repository
    putDoc $ changelog (get_diff_info opts morepatches)
            $$ thediff
    where rundiff :: String -> String -> IO Doc
          rundiff f1 f2 =
            case get_diff_cmd_and_args opts f1 f2 of
            Left err -> fail err
            Right (d_cmd, d_args) ->
              let other_diff = has_diff_cmd_flag opts in
              do when other_diff $ putStrLn $
                   "Running command '" ++ unwords (d_cmd:d_args) ++ "'"
                 output <- execPipeIgnoreError d_cmd d_args empty
                 when other_diff $ do
                    askUser "Hit return to move on..."
                    return ()
                 return output

get_diff_info :: RepoPatch p => [DarcsFlag] -> PatchSet p -> [PatchInfo]
get_diff_info opts ps =
    let pi1s = mapRL info $ concatRL $ if first_match opts
                                       then unsafeUnseal $ match_first_patchset opts ps
                                       else ps
        pi2s = mapRL info $ concatRL $ if second_match opts
                                       then unsafeUnseal $ match_second_patchset opts ps
                                       else ps
        in pi2s \\ pi1s

changelog :: [PatchInfo] -> Doc
changelog pis = vcat $ map human_friendly pis
\end{code}