% 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. \begin{code} module Darcs.Flags ( DarcsFlag( .. ), want_external_merge ) where import Darcs.Patch.MatchData ( PatchMatch ) import Darcs.RepoPath ( AbsolutePath ) \end{code} \begin{code} data DarcsFlag = Help | ListOptions | NoTest | Test | HelpOnMatch | OnlyChangesToFiles | LeaveTestDir | NoLeaveTestDir | Timings | Debug | DebugVerbose | Verbose | NormalVerbosity | Quiet | Target String | Cc String | Output String | OutputAutoName | Subject String | SendmailCmd String | Author String | PatchName String | OnePatch String | SeveralPatch String | AfterPatch String | UpToPatch String | TagName String | LastN Int | OneTag String | AfterTag String | UpToTag String | Context String | Count | LogFile String | RmLogFile | DistName String | All | Recursive | NoRecursive | Reorder | RestrictPaths | DontRestrictPaths | AskDeps | NoAskDeps | IgnoreTimes | LookForAdds | NoLookForAdds | AnyOrder | CreatorHash String | Intersection | Union | Complement | Sign | SignAs String | NoSign | SignSSL String | HappyForwarding | Verify String | VerifySSL String | SSHControlMaster | NoSSHControlMaster | EditDescription | NoEditDescription | Toks String | EditLongComment | NoEditLongComment | PromptLongComment | AllowConflicts | MarkConflicts | NoAllowConflicts | Boring | AllowCaseOnly | DontGrabDeps | Compress | NoCompress | UnCompress | WorkDir String | RepoDir String | RemoteRepo String | Reply String | ApplyAs String | MachineReadable | HumanReadable | Pipe | Interactive | DiffCmd String | ExternalMerge String | Summary | NoSummary | Unified | Reverse | CheckPoint | Partial | Complete | Lazy | Ephemeral | FixFilePath AbsolutePath String | DiffFlags String | XMLOutput | ForceReplace | OnePattern PatchMatch | SeveralPattern PatchMatch | AfterPattern PatchMatch | UpToPattern PatchMatch | NonApply | NonVerify | NonForce | DryRun | SetDefault | NoSetDefault | FancyMoveAdd | NoFancyMoveAdd | Disable | SetScriptsExecutable | DontSetScriptsExecutable | UseHashedInventory | UseOldFashionedInventory | UseFormat2 | PristinePlain | PristineNone | NoUpdateWorking | Sibling String | Relink | RelinkPristine | NoLinks | Files | NoFiles | Directories | NoDirectories | Pending | NoPending | PosthookCmd String | NoPosthook | AskPosthook | RunPosthook | PrehookCmd String | NoPrehook | AskPrehook | RunPrehook | UMask String | StoreInMemory | NullFlag deriving ( Eq, Show ) want_external_merge :: [DarcsFlag] -> Maybe String want_external_merge [] = Nothing want_external_merge (ExternalMerge c:_) = Just c want_external_merge (_:fs) = want_external_merge fs \end{code}