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

module Darcs.Commands.SetPref ( setpref ) where

import System.Exit ( exitWith, ExitCode(..) )
import Control.Monad (when)

import Darcs.Commands ( DarcsCommand(..), nodefaults )
import Darcs.Arguments ( DarcsFlag, working_repo_dir, umask_option )
import Darcs.Repository ( amInRepository, add_to_pending, withRepoLock, ($-) )
import Darcs.Patch ( changepref )
import Darcs.Ordered ( FL(..) )
import Darcs.Repository.Prefs ( get_prefval, change_prefval, )
#include "impossible.h"

-- | A list of all valid preferences for @_darcs/prefs/prefs@.
valid_pref_data :: [(String, String)] -- ^ (name, one line description)
valid_pref_data =
    [("test", "a shell command that runs regression tests"),
     ("predist", "a shell command to run before `darcs dist'"),
     ("boringfile", "the path to a version-controlled boring file"),
     ("binariesfile", "the path to a version-controlled binaries file")]

valid_prefs :: [String]
valid_prefs = map fst valid_pref_data

setpref_description :: String
setpref_description = "Set the value of a preference (" ++ ps ++ ")."
    where ps = iter valid_prefs
          iter [x] = x
          iter [x,y] = x ++ " or " ++ y
          iter (x:xs) = x ++ ", " ++ (iter xs)
          iter [] = ""           -- impossible, but keeps -Wall happy

setpref_help :: String
setpref_help =
 "When working on project with multiple repositories and contributors,\n" ++
 "it is sometimes desirable for a preference to be set consistently\n" ++
 "project-wide.  This is achieved by treating a preference set with\n" ++
 "`darcs setpref' as an unrecorded change, which can then be recorded\n" ++
 "and then treated like any other patch.\n" ++
 "\n" ++
 "Valid preferences are:\n" ++
 "\n" ++
 (unlines $ map unwords $ map (\ (x,y) -> [" ",x,"--",y]) valid_pref_data) ++
 "\n" ++
 "For example, a project using GNU autotools, with a `make test' target\n" ++
 "to perform regression tests, might enable Darcs' integrated regression\n" ++
 "testing with the following command:\n" ++
 "\n" ++
 "  darcs setpref test 'autoconf && ./configure && make && make test'\n" ++
 "\n" ++
 "Note that merging is not currently implemented for preferences: if two\n" ++
 "patches attempt to set the same preference, the last patch applied to\n" ++
 "the repository will always take precedence.  This is considered a\n" ++
 "low-priority bug, because preferences are seldom set.\n"

setpref :: DarcsCommand
setpref = DarcsCommand {command_name = "setpref",
                        command_help = setpref_help,
                        command_description = setpref_description,
                        command_extra_args = 2,
                        command_extra_arg_help = ["<PREF>",
                                                  "<VALUE>"],
                        command_command = setpref_cmd,
                        command_prereq = amInRepository,
                        command_get_arg_possibilities = return valid_prefs,
                        command_argdefaults = nodefaults,
                        command_advanced_options = [umask_option],
                        command_basic_options =
                            [working_repo_dir]}

setpref_cmd :: [DarcsFlag] -> [String] -> IO ()
setpref_cmd opts [pref,val] = withRepoLock opts $- \repository -> do
  when (' ' `elem` pref) $ do
    putStrLn $ "'"++pref++
               "' is not a valid preference name:  no spaces allowed!"
    exitWith $ ExitFailure 1
  when (not $ pref `elem` valid_prefs) $ do
    putStrLn $ "'"++pref++"' is not a valid preference name!"
    putStrLn $ "Try one of: " ++ unwords valid_prefs
    exitWith $ ExitFailure 1
  oval <- get_prefval pref
  old <- case oval of Just v -> return v
                      Nothing -> return ""
  change_prefval pref old val
  putStrLn $ "Changing value of "++pref++" from '"++old++"' to '"++val++"'"
  add_to_pending repository (changepref pref old val :>: NilFL)
setpref_cmd _ _ = impossible
\end{code}