%  Copyright (C) 2008 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 authors}
\begin{code}
module Darcs.Commands.ShowAuthors ( show_authors ) where

import Data.List ( sort, group )

import Darcs.Arguments ( DarcsFlag(..), working_repo_dir )
import Darcs.Commands ( DarcsCommand(..), nodefaults )
import Darcs.External ( viewDoc )
import Darcs.Hopefully ( info )
import Darcs.Repository ( amInRepository, read_repo, withRepository, ($-) )
import Darcs.Patch.Info ( pi_author )
import Darcs.Ordered ( mapRL, concatRL )
import Printer ( text )
\end{code}

\options{show authors}

\haskell{show_authors_help}

\begin{code}
show_authors_description :: String
show_authors_description = "Show all authors in the repository."

show_authors_help :: String
show_authors_help =
 "The authors command writes a list of all patch authors in the repository to\n" ++
 "standard output."

show_authors :: DarcsCommand
show_authors = DarcsCommand {
  command_name = "authors",
  command_help = show_authors_help,
  command_description = show_authors_description,
  command_extra_args = 0,
  command_extra_arg_help = [],
  command_command = authors_cmd,
  command_prereq = amInRepository,
  command_get_arg_possibilities = return [],
  command_argdefaults = nodefaults,
  command_advanced_options = [],
  command_basic_options = [working_repo_dir] }

authors_cmd :: [DarcsFlag] -> [String] -> IO ()
authors_cmd opts _ = withRepository opts $- \repository -> do
  patches <- read_repo repository
  let authors = mapRL process $ concatRL patches
  viewDoc $ text $ unlines $
   if Verbose `elem` opts
      then authors
      else reverse $ map shownames $ sort $
           map (\s -> (length s,head s)) $ group $ sort authors
  where
    process =  pi_author . info
    shownames (n, a) = show n ++ "\t" ++ a
\end{code}