--  Copyright (C) 2002-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.

module Darcs.UI.Commands.Show ( showCommand ) where

import Darcs.Prelude

import Darcs.UI.Commands ( DarcsCommand(..)
                         , normalCommand
                         , amInRepository
                         )
import Darcs.UI.Commands.ShowAuthors ( showAuthors )
import Darcs.UI.Commands.ShowContents ( showContents )
import Darcs.UI.Commands.ShowDependencies ( showDeps )
import Darcs.UI.Commands.ShowFiles ( showFiles )
import Darcs.UI.Commands.ShowTags ( showTags )
import Darcs.UI.Commands.ShowRepo ( showRepo )
import Darcs.UI.Commands.ShowIndex ( showIndex, showPristine )
import Darcs.UI.Commands.ShowPatchIndex ( showPatchIndex )
import Darcs.Util.Printer ( Doc, formatWords )

showDescription :: String
showDescription :: String
showDescription = String
"Show information about the given repository."

showHelp :: Doc
showHelp :: Doc
showHelp = [String] -> Doc
formatWords
  [ String
"Display various information about a repository. See description of the"
  , String
"subcommands for details."
  ]

showCommand :: DarcsCommand
showCommand :: DarcsCommand
showCommand = SuperCommand :: String
-> String
-> Doc
-> String
-> ([DarcsFlag] -> IO (Either String ()))
-> [CommandControl]
-> DarcsCommand
SuperCommand
    { commandProgramName :: String
commandProgramName = String
"darcs"
    , commandName :: String
commandName = String
"show"
    , commandHelp :: Doc
commandHelp = Doc
showHelp
    , commandDescription :: String
commandDescription = String
showDescription
    , commandPrereq :: [DarcsFlag] -> IO (Either String ())
commandPrereq = [DarcsFlag] -> IO (Either String ())
amInRepository
    , commandSubCommands :: [CommandControl]
commandSubCommands =
      [ DarcsCommand -> CommandControl
normalCommand DarcsCommand
showContents
      , DarcsCommand -> CommandControl
normalCommand DarcsCommand
showDeps
      , DarcsCommand -> CommandControl
normalCommand DarcsCommand
showFiles
      , DarcsCommand -> CommandControl
normalCommand DarcsCommand
showIndex
      , DarcsCommand -> CommandControl
normalCommand DarcsCommand
showPristine
      , DarcsCommand -> CommandControl
normalCommand DarcsCommand
showRepo
      , DarcsCommand -> CommandControl
normalCommand DarcsCommand
showAuthors
      , DarcsCommand -> CommandControl
normalCommand DarcsCommand
showTags
      , DarcsCommand -> CommandControl
normalCommand DarcsCommand
showPatchIndex ]
    }