% Copyright (C) 2003-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. \darcsCommand{tag} \begin{code} module Darcs.Commands.Tag ( tag ) where import Control.Monad ( when ) import Darcs.Commands ( DarcsCommand(DarcsCommand, command_name, command_help, command_description, command_extra_args, command_extra_arg_help, command_command, command_prereq, command_get_arg_possibilities, command_argdefaults, command_advanced_options, command_basic_options), nodefaults ) import Darcs.Arguments ( nocompress, umask_option, patchname_option, author, checkpoint, pipe_interactive, ask_long_comment, working_repo_dir, get_author ) import Darcs.Hopefully ( n2pia ) import Darcs.Repository ( amInRepository, withRepoLock, ($-), read_repo, tentativelyAddPatch, finalizeRepositoryChanges, ) import Darcs.Repository.Checkpoint ( write_recorded_checkpoint ) import Darcs.Patch ( infopatch, identity, adddeps ) import Darcs.Patch.Info ( patchinfo ) import Darcs.Patch.Depends ( get_tags_right ) import Darcs.Commands.Record ( get_date, get_log ) import Darcs.Ordered ( FL(..) ) import Darcs.Lock ( world_readable_temp ) import Darcs.Flags ( DarcsFlag(..) ) import System.IO ( hPutStr, stderr ) tag_description :: String tag_description = "Name the current repository state for future reference." tag_help :: String tag_help = "The `darcs tag' command names the current repository state, so that it\n" ++ "can easily be referred to later. Every `important' state should be\n" ++ "tagged; in particular it is good practice to tag each stable release\n" ++ "with a number or codename. Advice on release numbering can be found\n" ++ "at http://producingoss.com/en/development-cycle.html.\n" ++ "\n" ++ "To reproduce the state of a repository `R' as at tag `t', use the\n" ++ "command `darcs get --tag t R'. The command `darcs show tags' lists\n" ++ "all tags in the current repository.\n" ++ "\n" ++ "Tagging also provides significant performance benefits: when Darcs\n" ++ "reaches a shared tag that depends on all antecedent patches, it can\n" ++ "simply stop processing.\n" ++ "\n" ++ "Like normal patches, a tag has a name, an author, a timestamp and an\n" ++ "optional long description, but it does not change the working tree.\n" ++ "A tag can have any name, but it is generally best to pick a naming\n" ++ "scheme and stick to it.\n" ++ "\n" ++ "The `darcs tag' command accepts the --pipe and --checkpoint options,\n" ++ "which behave as described in `darcs record' and `darcs optimize'\n" ++ "respectively.\n" tag :: DarcsCommand tag = DarcsCommand {command_name = "tag", command_help = tag_help, command_description = tag_description, command_extra_args = -1, command_extra_arg_help = ["[TAGNAME]"], command_command = tag_cmd, command_prereq = amInRepository, command_get_arg_possibilities = return [], command_argdefaults = nodefaults, command_advanced_options = [nocompress,umask_option], command_basic_options = [patchname_option, author, checkpoint, pipe_interactive, ask_long_comment, working_repo_dir]} tag_cmd :: [DarcsFlag] -> [String] -> IO () tag_cmd opts args = withRepoLock opts $- \repository -> do date <- get_date opts the_author <- get_author opts deps <- get_tags_right `fmap` read_repo repository (name, long_comment) <- get_name_log opts args myinfo <- patchinfo date name the_author long_comment let mypatch = infopatch myinfo identity tentativelyAddPatch repository opts $ n2pia $ adddeps mypatch deps finalizeRepositoryChanges repository when (CheckPoint `elem` opts) $ write_recorded_checkpoint repository myinfo putStrLn $ "Finished tagging patch '"++name++"'" where get_name_log :: [DarcsFlag] -> [String] -> IO (String, [String]) get_name_log o a = do let o2 = if null a then o else (add_patch_name o (unwords a)) (name, comment, _) <- get_log o2 Nothing (world_readable_temp "darcs-tag") NilFL when (length name < 2) $ hPutStr stderr $ "Do you really want to tag '" ++name++"'? If not type: darcs obliterate --last=1\n" return ("TAG " ++ name, comment) add_patch_name :: [DarcsFlag] -> String -> [DarcsFlag] add_patch_name o a| has_patch_name o = o | otherwise = [PatchName a] ++ o has_patch_name (PatchName _:_) = True has_patch_name (_:fs) = has_patch_name fs has_patch_name [] = False -- This may be useful for developers, but users don't care about -- internals: -- -- A tagged version automatically depends on all patches in the -- repository. This allows you to later reproduce precisely that -- version. The tag does this by depending on all patches in the -- repository, except for those which are depended upon by other tags -- already in the repository. In the common case of a sequential -- series of tags, this means that the tag depends on all patches -- since the last tag, plus that tag itself. \end{code}