%  Copyright (C) 2007 Eric Kow
%
%  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.

\subsubsection{darcs show contents}
\begin{code}
module Darcs.Commands.ShowContents ( show_contents ) where

import Control.Monad ( filterM )
import System.IO ( stdout )
import System.FilePath.Posix ( takeFileName )

import qualified Data.ByteString as B
import Workaround ( getCurrentDirectory )

import Darcs.Commands ( DarcsCommand(..), nodefaults )
import Darcs.Arguments ( DarcsFlag, match_one,
                         working_repo_dir, fixSubPaths )
import Darcs.RepoPath ( toFilePath, sp2fn )
import Darcs.IO ( mReadFilePS, mDoesFileExist )
import Darcs.Match ( get_partial_nonrange_match, have_nonrange_match )
import Darcs.Repository ( withRepository, ($-), findRepository,
                          createPartialsPristineDirectoryTree )
import Darcs.Lock ( withTempDir )
\end{code}

\options{show contents}
\begin{code}
show_contents_description :: String
show_contents_description = "Outputs a specific version of a file."
\end{code}
\haskell{show_contents_help}
\begin{code}
show_contents_help :: String
show_contents_help =
  "Show contents can be used to display an earlier version of some file(s).\n"++
  "If you give show contents no version arguments, it displays the recorded\n"++
  "version of the file(s).\n"

show_contents :: DarcsCommand
show_contents = DarcsCommand {command_name = "contents",
                              command_help = show_contents_help,
                              command_description = show_contents_description,
                              command_extra_args = -1,
                              command_extra_arg_help
                                    = ["[FILE]..."],
                              command_command = show_contents_cmd,
                              command_prereq = findRepository,
                              command_get_arg_possibilities = return [],
                              command_argdefaults = nodefaults,
                              command_advanced_options = [],
                              command_basic_options = [match_one, working_repo_dir]}

show_contents_cmd :: [DarcsFlag] -> [String] -> IO ()
show_contents_cmd opts args = withRepository opts $- \repository -> do
  formerdir <- getCurrentDirectory
  path_list <- map sp2fn `fmap` fixSubPaths opts args
  thename <- return $ takeFileName formerdir
  withTempDir thename $ \dir -> do
     if have_nonrange_match opts
        then get_partial_nonrange_match repository opts path_list
        else createPartialsPristineDirectoryTree repository path_list (toFilePath dir)
     filterM mDoesFileExist path_list >>= mapM_ (\f -> mReadFilePS f >>= B.hPut stdout)
\end{code}