% 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. \subsection{darcs show bug} \begin{code} {-# OPTIONS_GHC -cpp #-} {-# LANGUAGE CPP #-} module Darcs.Commands.ShowBug ( show_bug ) where import Darcs.Commands ( DarcsCommand(..), nodefaults ) import Darcs.Arguments ( DarcsFlag, working_repo_dir ) import Darcs.Repository ( findRepository ) #include "impossible.h" \end{code} \options{show bug} \begin{code} show_bug_description :: String show_bug_description = "Pretends to be a bug in darcs." \end{code} \haskell{show_bug_help} \begin{code} show_bug_help :: String show_bug_help = "Show bug can be used to see what darcs would show you if you encountered.\n" ++"a bug in darcs.\n" show_bug :: DarcsCommand show_bug = DarcsCommand {command_name = "bug", command_help = show_bug_help, command_description = show_bug_description, command_extra_args = 0, command_extra_arg_help = [], command_command = show_bug_cmd, command_prereq = findRepository, command_get_arg_possibilities = return [], command_argdefaults = nodefaults, command_advanced_options = [], command_basic_options = [working_repo_dir]} show_bug_cmd :: [DarcsFlag] -> [String] -> IO () show_bug_cmd _ _ = bug "This is actually a fake bug in darcs." \end{code}