File: MarkConflicts.hs

package info (click to toggle)
darcs 2.12.4-2
  • links: PTS, VCS
  • area: main
  • in suites: stretch
  • size: 5,748 kB
  • sloc: haskell: 42,936; sh: 11,086; ansic: 837; perl: 129; makefile: 8
file content (166 lines) | stat: -rw-r--r-- 6,925 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
--  Copyright (C) 2002-2003,2005 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.

{-# LANGUAGE CPP #-}

module Darcs.UI.Commands.MarkConflicts ( markconflicts ) where

import Prelude ()
import Darcs.Prelude

import Prelude hiding ( (^) )

import System.Exit ( exitSuccess )
import Data.List.Ordered ( nubSort )
import Control.Monad ( when, unless )
import Control.Exception ( catch, IOException )

import Darcs.Util.Prompt ( promptYorn )
import Darcs.Util.Path ( AbsolutePath )
import Darcs.Util.SignalHandler ( withSignalsBlocked )
import Darcs.Util.Printer( putDocLn, putDocLnWith, text, redText, ($$) )
import Darcs.Util.Printer.Color (fancyPrinters)

import Darcs.UI.Commands ( DarcsCommand(..), withStdOpts, nodefaults, amInHashedRepository )
import Darcs.UI.Flags ( DarcsFlag, diffingOpts, verbosity, dryRun, umask, useCache )
import Darcs.UI.Options ( DarcsOption, (^), odesc, ocheck, onormalise, defaultFlags )
import qualified Darcs.UI.Options.All as O
import Darcs.Repository.Flags ( UpdateWorking (..) )
import Darcs.Repository ( withRepoLock, RepoJob(..), addToPending,
                    applyToWorking,
                    readRepo, unrecordedChanges, Repository
                    )
import Darcs.Patch ( invert, PrimOf, listTouchedFiles )
import Darcs.Patch.Witnesses.Ordered ( FL(..) )
import Darcs.Patch.Witnesses.Sealed ( Sealed(Sealed) )
import Darcs.Repository.Resolution ( patchsetConflictResolutions )
#include "impossible.h"

markconflictsDescription :: String
markconflictsDescription =
 "Mark unresolved conflicts in working tree, for manual resolution."

markconflictsHelp :: String
markconflictsHelp = unlines
 ["Darcs requires human guidance to unify changes to the same part of a"
 ,"source file.  When a conflict first occurs, darcs will add the"
 ,"initial state and both choices to the working tree, delimited by the"
 ,"markers `v v v`, `=====`,  `* * *` and `^ ^ ^`, as follows:"
 ,""
 ,"    v v v v v v v"
 ,"    Initial state."
 ,"    ============="
 ,"    First choice."
 ,"    *************"
 ,"    Second choice."
 ,"    ^ ^ ^ ^ ^ ^ ^"
 ,""
 ,"However, you might revert or manually delete these markers without"
 ,"actually resolving the conflict.  In this case, `darcs mark-conflicts`"
 ,"is useful to show where are the unresolved conflicts.  It is also"
 ,"useful if `darcs apply` is called with `--apply-conflicts`,"
 ,"where conflicts aren't marked initially."
 ,""
 ,"Unless you use the `--dry-run` flag, any unrecorded changes to the"
 ,"working tree WILL be lost forever when you run this command!"
 ,"You will be prompted for confirmation before this takes place."
 ]

markconflictsBasicOpts :: DarcsOption a
                          (O.UseIndex
                           -> Maybe String
                           -> O.DiffAlgorithm
                           -> O.DryRun
                           -> O.XmlOutput
                           -> a)
markconflictsBasicOpts
    = O.useIndex
    ^ O.workingRepoDir
    ^ O.diffAlgorithm
    ^ O.dryRunXml

markconflictsAdvancedOpts :: DarcsOption a (O.UMask -> a)
markconflictsAdvancedOpts = O.umask

markconflictsOpts :: DarcsOption a
                     (O.UseIndex
                      -> Maybe String
                      -> O.DiffAlgorithm
                      -> O.DryRun
                      -> O.XmlOutput
                      -> Maybe O.StdCmdAction
                      -> Bool
                      -> Bool
                      -> O.Verbosity
                      -> Bool
                      -> O.UMask
                      -> O.UseCache
                      -> Maybe String
                      -> Bool
                      -> Maybe String
                      -> Bool
                      -> a)
markconflictsOpts = markconflictsBasicOpts `withStdOpts` markconflictsAdvancedOpts

markconflicts :: DarcsCommand [DarcsFlag]
markconflicts = DarcsCommand
    { commandProgramName = "darcs"
    , commandName = "mark-conflicts"
    , commandHelp = markconflictsHelp
    , commandDescription = markconflictsDescription
    , commandExtraArgs = 0
    , commandExtraArgHelp = []
    , commandCommand = markconflictsCmd
    , commandPrereq = amInHashedRepository
    , commandGetArgPossibilities = return []
    , commandArgdefaults = nodefaults
    , commandAdvancedOptions = odesc markconflictsAdvancedOpts
    , commandBasicOptions = odesc markconflictsBasicOpts
    , commandDefaults = defaultFlags markconflictsOpts
    , commandCheckOptions = ocheck markconflictsOpts
    , commandParseOptions = onormalise markconflictsOpts
    }

markconflictsCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
markconflictsCmd _ opts [] = withRepoLock (dryRun opts) (useCache opts) YesUpdateWorking (umask opts) $ RepoJob $ \(repository :: Repository rt p wR wU wR) -> do
  pend <- unrecordedChanges (diffingOpts opts) repository Nothing
  r <- readRepo repository
  Sealed res <- return $ patchsetConflictResolutions r
  case nubSort $ listTouchedFiles res of
    []  -> putStrLn "No conflicts to mark." >> exitSuccess
    cfs -> putDocLnWith fancyPrinters $
              redText "Conflicts found in the following files:" $$ text (unlines cfs)
  when (dryRun opts == O.YesDryRun) $ do
      putDocLn $ text "Conflicts will not be marked: this is a dry run."
      exitSuccess
  let undoUnrec :: FL (PrimOf p) wR wU -> IO (Repository rt p wR wR wR)
      undoUnrec NilFL = return repository
      undoUnrec pend' =
              do putStrLn ("This will trash any unrecorded changes"++
                          " in the working directory.")
                 confirmed <- promptYorn "Are you sure? "
                 unless confirmed exitSuccess
                 applyToWorking repository (verbosity opts) (invert pend') `catch` \(e :: IOException) ->
                    bug ("Can't undo pending changes!" ++ show e)
  repository' <- undoUnrec pend
  withSignalsBlocked $
    do addToPending repository' YesUpdateWorking res
       _ <- applyToWorking repository' (verbosity opts) res `catch` \(e :: IOException) ->
           bug ("Problem marking conflicts in mark-conflicts!" ++ show e)
       return ()
  putStrLn "Finished marking conflicts."
markconflictsCmd _ _ _ = impossible