module Darcs.UI.PatchHeader
( getLog
, getAuthor
, editLog
, updatePatchHeader, AskAboutDeps(..)
, PatchHeaderConfig
, patchHeaderConfig
, HijackT, HijackOptions(..)
, runHijackT
) where
import Darcs.Prelude
import Darcs.Patch ( PrimOf, RepoPatch, summaryFL )
import Darcs.Patch.Apply ( ApplyState )
import Darcs.Patch.Info
( PatchInfo
, patchinfo
, piAuthor
, piDateString
, piLog
, piName
)
import Darcs.Patch.Named
( Named
, adddeps
, getdeps
, infopatch
, patch2patchinfo
, patchcontents
, setinfo
)
import Darcs.Patch.PatchInfoAnd ( PatchInfoAnd, n2pia )
import Darcs.Patch.Prim ( canonizeFL )
import Darcs.Patch.Witnesses.Ordered ( FL(..), RL(..), (+>+) )
import Darcs.Util.Lock ( readTextFile, writeTextFile )
import Darcs.UI.External ( editFile )
import Darcs.UI.Flags ( getEasyAuthor, promptAuthor, getDate )
import Darcs.UI.Options ( Config, (?) )
import qualified Darcs.UI.Options.All as O
import qualified Darcs.UI.SelectChanges as S ( PatchSelectionOptions(..) )
import Darcs.UI.SelectChanges ( askAboutDepends )
import qualified Darcs.Util.Diff as D ( DiffAlgorithm )
import Darcs.Util.English ( capitalize )
import Darcs.Util.Global ( darcsLastMessage )
import Darcs.Util.Path ( FilePathLike, toFilePath )
import Darcs.Util.Prompt ( PromptConfig(..), askUser, promptChar, promptYorn )
import Darcs.Util.Printer ( Doc, text, ($+$), vcat, prefixLines, renderString )
import qualified Darcs.Util.Ratified as Ratified ( hGetContents )
import Darcs.Util.Tree ( Tree )
import Control.Exception ( catch, IOException )
import Control.Monad ( when, void )
import Control.Monad.Trans ( liftIO )
import Control.Monad.Trans.State.Strict ( StateT(..), evalStateT, get, put )
import Data.List ( isPrefixOf, stripPrefix )
import Data.Maybe ( fromMaybe, isJust )
import System.Exit ( exitSuccess )
import System.IO ( stdin )
data PName = FlagPatchName String | PriorPatchName String | NoPatchName
data HijackOptions = IgnoreHijack
| RequestHijackPermission
| AlwaysRequestHijackPermission
type HijackT = StateT HijackOptions
getLog :: Maybe String
-> Bool
-> O.Logfile
-> Maybe O.AskLongComment
-> Maybe (String, [String])
-> Doc
-> IO (String, [String], Maybe String)
getLog :: Maybe String
-> Bool
-> Logfile
-> Maybe AskLongComment
-> Maybe (String, [String])
-> Doc
-> IO (String, [String], Maybe String)
getLog Maybe String
m_name Bool
has_pipe Logfile
log_file Maybe AskLongComment
ask_long Maybe (String, [String])
m_old Doc
chs =
(String, [String], Maybe String)
-> (String, [String], Maybe String)
forall {b} {c}. (String, b, c) -> (String, b, c)
restoreTagPrefix ((String, [String], Maybe String)
-> (String, [String], Maybe String))
-> IO (String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool
-> Logfile
-> Maybe AskLongComment
-> IO (String, [String], Maybe String)
go Bool
has_pipe Logfile
log_file Maybe AskLongComment
ask_long
where
go :: Bool
-> Logfile
-> Maybe AskLongComment
-> IO (String, [String], Maybe String)
go Bool
True Logfile
_ Maybe AskLongComment
_ = do
String
p <- case PName
patchname_specified of
FlagPatchName String
p -> String -> IO ()
check_badname String
p IO () -> IO String -> IO String
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
p
PriorPatchName String
p -> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
p
PName
NoPatchName -> Bool -> IO String
prompt_patchname Bool
False
String -> IO ()
putStrLn String
"What is the log?"
[String]
thelog <- String -> [String]
lines (String -> [String]) -> IO String -> IO [String]
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Handle -> IO String
Ratified.hGetContents Handle
stdin
(String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
p, [String]
thelog, Maybe String
forall a. Maybe a
Nothing)
go Bool
_ (O.Logfile { _logfile :: Logfile -> Maybe AbsolutePath
O._logfile = Just AbsolutePath
f }) Maybe AskLongComment
_ = do
[String]
mlp <- AbsolutePath -> IO [String]
forall p. FilePathLike p => p -> IO [String]
readTextFile AbsolutePath
f IO [String] -> (IOException -> IO [String]) -> IO [String]
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` (\(IOException
_ :: IOException) -> [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [])
String
firstname <- case (PName
patchname_specified, [String]
mlp) of
(FlagPatchName String
p, []) -> String -> IO ()
check_badname String
p IO () -> IO String -> IO String
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
p
(PName
_, String
p:[String]
_) -> if String -> Bool
is_badname String
p
then Bool -> IO String
prompt_patchname Bool
True
else String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
p
(PriorPatchName String
p, []) -> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
p
(PName
NoPatchName, []) -> Bool -> IO String
prompt_patchname Bool
True
AbsolutePath -> String -> IO ()
forall {p}. FilePathLike p => p -> String -> IO ()
append_info AbsolutePath
f String
firstname
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe AskLongComment
ask_long Maybe AskLongComment -> Maybe AskLongComment -> Bool
forall a. Eq a => a -> a -> Bool
== AskLongComment -> Maybe AskLongComment
forall a. a -> Maybe a
Just AskLongComment
O.YesEditLongComment) (IO (ExitCode, Bool) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO (ExitCode, Bool) -> IO ()) -> IO (ExitCode, Bool) -> IO ()
forall a b. (a -> b) -> a -> b
$ AbsolutePath -> IO (ExitCode, Bool)
forall p. FilePathLike p => p -> IO (ExitCode, Bool)
editFile AbsolutePath
f)
(String
name, [String]
thelog) <- AbsolutePath -> String -> IO (String, [String])
forall p. FilePathLike p => p -> String -> IO (String, [String])
read_long_comment AbsolutePath
f String
firstname
(String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
name, [String]
thelog, if Logfile -> Bool
O._rmlogfile Logfile
log_file then String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ AbsolutePath -> String
forall a. FilePathLike a => a -> String
toFilePath AbsolutePath
f else Maybe String
forall a. Maybe a
Nothing)
go Bool
_ Logfile
_ (Just AskLongComment
O.YesEditLongComment) =
case PName
patchname_specified of
FlagPatchName String
p -> String -> IO (String, [String], Maybe String)
get_log_using_editor String
p
PriorPatchName String
p -> String -> IO (String, [String], Maybe String)
get_log_using_editor String
p
PName
NoPatchName -> String -> IO (String, [String], Maybe String)
get_log_using_editor String
""
go Bool
_ Logfile
_ (Just AskLongComment
O.NoEditLongComment) =
case PName
patchname_specified of
FlagPatchName String
p -> String -> IO ()
check_badname String
p IO ()
-> IO (String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
p, [String]
default_log, Maybe String
forall a. Maybe a
Nothing)
PriorPatchName String
p -> (String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
p, [String]
default_log, Maybe String
forall a. Maybe a
Nothing)
PName
NoPatchName -> do String
p <- Bool -> IO String
prompt_patchname Bool
True
(String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
p, [], Maybe String
forall a. Maybe a
Nothing)
go Bool
_ Logfile
_ (Just AskLongComment
O.PromptLongComment) =
case PName
patchname_specified of
FlagPatchName String
p -> String -> IO ()
check_badname String
p IO ()
-> IO (String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO (String, [String], Maybe String)
prompt_long_comment String
p
PriorPatchName String
p -> String -> IO (String, [String], Maybe String)
prompt_long_comment String
p
PName
NoPatchName -> Bool -> IO String
prompt_patchname Bool
True IO String
-> (String -> IO (String, [String], Maybe String))
-> IO (String, [String], Maybe String)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> IO (String, [String], Maybe String)
prompt_long_comment
go Bool
_ Logfile
_ Maybe AskLongComment
Nothing =
case PName
patchname_specified of
FlagPatchName String
p -> String -> IO ()
check_badname String
p IO ()
-> IO (String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
p, [String]
default_log, Maybe String
forall a. Maybe a
Nothing)
PriorPatchName String
"" -> String -> IO (String, [String], Maybe String)
get_log_using_editor String
""
PriorPatchName String
p -> (String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
p, [String]
default_log, Maybe String
forall a. Maybe a
Nothing)
PName
NoPatchName -> String -> IO (String, [String], Maybe String)
get_log_using_editor String
""
tagPrefix :: String
tagPrefix = String
"TAG "
hasTagPrefix :: String -> Bool
hasTagPrefix String
name = String
tagPrefix String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
name
restoreTagPrefix :: (String, b, c) -> (String, b, c)
restoreTagPrefix (String
name, b
log, c
file)
| Just (String
old_name, [String]
_) <- Maybe (String, [String])
m_old
, String -> Bool
hasTagPrefix String
old_name = (String
tagPrefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name, b
log, c
file)
restoreTagPrefix (String, b, c)
args = (String, b, c)
args
stripTagPrefix :: String -> String
stripTagPrefix String
name = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
name (Maybe String -> String) -> Maybe String -> String
forall a b. (a -> b) -> a -> b
$ String -> String -> Maybe String
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix String
tagPrefix String
name
patchname_specified :: PName
patchname_specified =
case (Maybe String
m_name, Maybe (String, [String])
m_old) of
(Just String
name, Maybe (String, [String])
_) -> String -> PName
FlagPatchName String
name
(Maybe String
Nothing, Just (String
name, [String]
_)) -> String -> PName
PriorPatchName (String -> String
stripTagPrefix String
name)
(Maybe String
Nothing, Maybe (String, [String])
Nothing) -> PName
NoPatchName
default_log :: [String]
default_log = case Maybe (String, [String])
m_old of
Maybe (String, [String])
Nothing -> []
Just (String
_,[String]
l) -> [String]
l
check_badname :: String -> IO ()
check_badname = IO () -> (String -> IO ()) -> Maybe String -> IO ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) String -> IO ()
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (Maybe String -> IO ())
-> (String -> Maybe String) -> String -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe String
just_a_badname
prompt_patchname :: Bool -> IO String
prompt_patchname Bool
retry = do
String
n <- String -> IO String
askUser String
"What is the patch name? "
IO String -> (String -> IO String) -> Maybe String -> IO String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
n) String -> IO String
prompt_again (Maybe String -> IO String) -> Maybe String -> IO String
forall a b. (a -> b) -> a -> b
$ String -> Maybe String
just_a_badname String
n
where
prompt_again :: String -> IO String
prompt_again String
msg = do
String -> IO ()
putStrLn String
msg
if Bool
retry then Bool -> IO String
prompt_patchname Bool
retry else String -> IO String
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Bad patch name!"
just_a_badname :: String -> Maybe String
just_a_badname String
n =
if String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
n then
String -> Maybe String
forall a. a -> Maybe a
Just String
"Error: The patch name must not be empty!"
else if String -> Bool
hasTagPrefix String
n then
String -> Maybe String
forall a. a -> Maybe a
Just String
"Error: The patch name must not start with \"TAG \"!"
else
Maybe String
forall a. Maybe a
Nothing
is_badname :: String -> Bool
is_badname = Maybe String -> Bool
forall a. Maybe a -> Bool
isJust (Maybe String -> Bool)
-> (String -> Maybe String) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe String
just_a_badname
prompt_long_comment :: String -> IO (String, [String], Maybe String)
prompt_long_comment String
oldname =
do let verb :: String
verb = case Maybe (String, [String])
m_old of Maybe (String, [String])
Nothing -> String
"add a"; Just (String, [String])
_ -> String
"edit the"
Bool
y <- String -> IO Bool
promptYorn (String -> IO Bool) -> String -> IO Bool
forall a b. (a -> b) -> a -> b
$ String
"Do you want to "String -> String -> String
forall a. [a] -> [a] -> [a]
++String
verbString -> String -> String
forall a. [a] -> [a] -> [a]
++String
" long comment?"
if Bool
y then String -> IO (String, [String], Maybe String)
get_log_using_editor String
oldname
else (String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
oldname, [String]
default_log, Maybe String
forall a. Maybe a
Nothing)
get_log_using_editor :: String -> IO (String, [String], Maybe String)
get_log_using_editor String
p =
do let logf :: String
logf = String
darcsLastMessage
String -> String -> IO ()
forall {p}. FilePathLike p => p -> String -> IO ()
writeTextFile String
logf (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ String
p String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
default_log
String -> String -> IO ()
forall {p}. FilePathLike p => p -> String -> IO ()
append_info String
logf String
p
(ExitCode, Bool)
_ <- String -> IO (ExitCode, Bool)
forall p. FilePathLike p => p -> IO (ExitCode, Bool)
editFile String
logf
(String
name,[String]
long) <- String -> String -> IO (String, [String])
forall p. FilePathLike p => p -> String -> IO (String, [String])
read_long_comment String
logf String
p
String -> IO ()
check_badname String
name
(String, [String], Maybe String)
-> IO (String, [String], Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
name,[String]
long,String -> Maybe String
forall a. a -> Maybe a
Just String
logf)
read_long_comment :: FilePathLike p => p -> String -> IO (String, [String])
read_long_comment :: forall p. FilePathLike p => p -> String -> IO (String, [String])
read_long_comment p
f String
oldname =
do [String]
t <- p -> IO [String]
forall p. FilePathLike p => p -> IO [String]
readTextFile p
f
let filter_out_info :: [String] -> [String]
filter_out_info = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not(Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(String
"#" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf`))
case [String] -> [String]
forall a. [a] -> [a]
reverse ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String] -> [String]
forall a. [a] -> [a]
reverse ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String] -> [String]
filter_out_info [String]
t of
[] -> (String, [String]) -> IO (String, [String])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
oldname, [])
(String
n:[String]
ls) -> do
String -> IO ()
check_badname String
n
(String, [String]) -> IO (String, [String])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
n, [String]
ls)
append_info :: p -> String -> IO ()
append_info p
f String
oldname = do
[String]
fc <- p -> IO [String]
forall p. FilePathLike p => p -> IO [String]
readTextFile p
f
p -> String -> IO ()
forall {p}. FilePathLike p => p -> String -> IO ()
writeTextFile p
f (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Doc -> String
renderString
(Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vcat ((String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map String -> Doc
text ([String] -> [Doc]) -> [String] -> [Doc]
forall a b. (a -> b) -> a -> b
$ if [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
fc then [String
oldname] else [String]
fc)
Doc -> Doc -> Doc
$+$ [Doc] -> Doc
vcat
[ String -> Doc
text String
"# Please enter the patch name in the first line, and"
, String -> Doc
text String
"# optionally, a long description in the following lines."
, String -> Doc
text String
"#"
, String -> Doc
text String
"# Lines starting with '#' will be ignored."
, String -> Doc
text String
"#"
, String -> Doc
text String
"#"
, String -> Doc
text String
"# Summary of selected changes:"
, String -> Doc
text String
"#"
, Doc -> Doc -> Doc
prefixLines (String -> Doc
text String
"#") Doc
chs
]
editLog :: Named prim wX wY -> IO (Named prim wX wY)
editLog :: forall (prim :: * -> * -> *) wX wY.
Named prim wX wY -> IO (Named prim wX wY)
editLog Named prim wX wY
p = do
let pi :: PatchInfo
pi = Named prim wX wY -> PatchInfo
forall (p :: * -> * -> *) wX wY. Named p wX wY -> PatchInfo
patch2patchinfo Named prim wX wY
p
(String
name, [String]
log, Maybe String
_) <-
Maybe String
-> Bool
-> Logfile
-> Maybe AskLongComment
-> Maybe (String, [String])
-> Doc
-> IO (String, [String], Maybe String)
getLog Maybe String
forall a. Maybe a
Nothing Bool
False (Maybe AbsolutePath -> Bool -> Logfile
O.Logfile Maybe AbsolutePath
forall a. Maybe a
Nothing Bool
False)
(AskLongComment -> Maybe AskLongComment
forall a. a -> Maybe a
Just AskLongComment
O.YesEditLongComment) ((String, [String]) -> Maybe (String, [String])
forall a. a -> Maybe a
Just (PatchInfo -> String
piName PatchInfo
pi, PatchInfo -> [String]
piLog PatchInfo
pi)) Doc
forall a. Monoid a => a
mempty
PatchInfo
pi' <- String -> String -> String -> [String] -> IO PatchInfo
patchinfo (PatchInfo -> String
piDateString PatchInfo
pi) String
name (PatchInfo -> String
piAuthor PatchInfo
pi) [String]
log
Named prim wX wY -> IO (Named prim wX wY)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Named prim wX wY -> IO (Named prim wX wY))
-> Named prim wX wY -> IO (Named prim wX wY)
forall a b. (a -> b) -> a -> b
$ PatchInfo -> Named prim wX wY -> Named prim wX wY
forall (p :: * -> * -> *) wX wY.
PatchInfo -> Named p wX wY -> Named p wX wY
setinfo PatchInfo
pi' Named prim wX wY
p
data AskAboutDeps p wX where
AskAboutDeps :: (RL (PatchInfoAnd p) w wX) -> AskAboutDeps p wX
NoAskAboutDeps :: AskAboutDeps p wX
runHijackT :: Monad m => HijackOptions -> HijackT m a -> m a
runHijackT :: forall (m :: * -> *) a.
Monad m =>
HijackOptions -> HijackT m a -> m a
runHijackT = (HijackT m a -> HijackOptions -> m a)
-> HijackOptions -> HijackT m a -> m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip HijackT m a -> HijackOptions -> m a
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT
data =
{ PatchHeaderConfig -> DiffAlgorithm
diffAlgorithm :: D.DiffAlgorithm
, PatchHeaderConfig -> Bool
keepDate :: Bool
, PatchHeaderConfig -> Bool
selectAuthor :: Bool
, PatchHeaderConfig -> Maybe String
author :: Maybe String
, PatchHeaderConfig -> Maybe String
patchname :: Maybe String
, :: Maybe O.AskLongComment
}
patchHeaderConfig :: Config -> PatchHeaderConfig
Config
cfg = PatchHeaderConfig
{ diffAlgorithm :: DiffAlgorithm
diffAlgorithm = PrimOptSpec DarcsOptDescr Flag a DiffAlgorithm
PrimDarcsOption DiffAlgorithm
O.diffAlgorithm PrimDarcsOption DiffAlgorithm -> Config -> DiffAlgorithm
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? Config
cfg
, keepDate :: Bool
keepDate = PrimOptSpec DarcsOptDescr Flag a Bool
PrimDarcsOption Bool
O.keepDate PrimDarcsOption Bool -> Config -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? Config
cfg
, selectAuthor :: Bool
selectAuthor = PrimOptSpec DarcsOptDescr Flag a Bool
PrimDarcsOption Bool
O.selectAuthor PrimDarcsOption Bool -> Config -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? Config
cfg
, author :: Maybe String
author = PrimOptSpec DarcsOptDescr Flag a (Maybe String)
PrimDarcsOption (Maybe String)
O.author PrimDarcsOption (Maybe String) -> Config -> Maybe String
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? Config
cfg
, patchname :: Maybe String
patchname = PrimOptSpec DarcsOptDescr Flag a (Maybe String)
PrimDarcsOption (Maybe String)
O.patchname PrimDarcsOption (Maybe String) -> Config -> Maybe String
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? Config
cfg
, askLongComment :: Maybe AskLongComment
askLongComment = PrimOptSpec DarcsOptDescr Flag a (Maybe AskLongComment)
PrimDarcsOption (Maybe AskLongComment)
O.askLongComment PrimDarcsOption (Maybe AskLongComment)
-> Config -> Maybe AskLongComment
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? Config
cfg
}
updatePatchHeader :: forall p wX wY wZ . (RepoPatch p, ApplyState p ~ Tree)
=> String
-> AskAboutDeps p wX
-> S.PatchSelectionOptions
-> PatchHeaderConfig
-> Named (PrimOf p) wX wY
-> FL (PrimOf p) wY wZ
-> HijackT IO (Maybe String, PatchInfoAnd p wX wZ)
String
verb AskAboutDeps p wX
ask_deps PatchSelectionOptions
pSelOpts PatchHeaderConfig{Bool
Maybe String
Maybe AskLongComment
DiffAlgorithm
diffAlgorithm :: PatchHeaderConfig -> DiffAlgorithm
keepDate :: PatchHeaderConfig -> Bool
selectAuthor :: PatchHeaderConfig -> Bool
author :: PatchHeaderConfig -> Maybe String
patchname :: PatchHeaderConfig -> Maybe String
askLongComment :: PatchHeaderConfig -> Maybe AskLongComment
diffAlgorithm :: DiffAlgorithm
keepDate :: Bool
selectAuthor :: Bool
author :: Maybe String
patchname :: Maybe String
askLongComment :: Maybe AskLongComment
..} Named (PrimOf p) wX wY
oldp FL (PrimOf p) wY wZ
chs = do
let newchs :: FL (PrimOf p) wX wZ
newchs = DiffAlgorithm -> FL (PrimOf p) wX wZ -> FL (PrimOf p) wX wZ
forall (prim :: * -> * -> *) wX wY.
(IsHunk prim, PrimCoalesce prim, PrimConstruct prim) =>
DiffAlgorithm -> FL prim wX wY -> FL prim wX wY
canonizeFL DiffAlgorithm
diffAlgorithm (Named (PrimOf p) wX wY -> FL (PrimOf p) wX wY
forall (p :: * -> * -> *) wX wY. Named p wX wY -> FL p wX wY
patchcontents Named (PrimOf p) wX wY
oldp FL (PrimOf p) wX wY -> FL (PrimOf p) wY wZ -> FL (PrimOf p) wX wZ
forall (a :: * -> * -> *) wX wY wZ.
FL a wX wY -> FL a wY wZ -> FL a wX wZ
+>+ FL (PrimOf p) wY wZ
chs)
let old_pdeps :: [PatchInfo]
old_pdeps = Named (PrimOf p) wX wY -> [PatchInfo]
forall wX wY. Named (PrimOf p) wX wY -> [PatchInfo]
forall (p :: * -> * -> *) wX wY.
HasDeps p =>
p wX wY -> [PatchInfo]
getdeps Named (PrimOf p) wX wY
oldp
[PatchInfo]
newdeps <-
case AskAboutDeps p wX
ask_deps of
AskAboutDeps RL (PatchInfoAnd p) w wX
patches ->
IO [PatchInfo] -> StateT HijackOptions IO [PatchInfo]
forall a. IO a -> StateT HijackOptions IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [PatchInfo] -> StateT HijackOptions IO [PatchInfo])
-> IO [PatchInfo] -> StateT HijackOptions IO [PatchInfo]
forall a b. (a -> b) -> a -> b
$ RL (PatchInfoAnd p) w wX
-> FL (PrimOf p) wX wZ
-> PatchSelectionOptions
-> [PatchInfo]
-> IO [PatchInfo]
forall (p :: * -> * -> *) wX wR wT.
(RepoPatch p, ApplyState p ~ Tree) =>
RL (PatchInfoAnd p) wX wR
-> FL (PrimOf p) wR wT
-> PatchSelectionOptions
-> [PatchInfo]
-> IO [PatchInfo]
askAboutDepends RL (PatchInfoAnd p) w wX
patches FL (PrimOf p) wX wZ
newchs PatchSelectionOptions
pSelOpts [PatchInfo]
old_pdeps
AskAboutDeps p wX
NoAskAboutDeps -> [PatchInfo] -> StateT HijackOptions IO [PatchInfo]
forall a. a -> StateT HijackOptions IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [PatchInfo]
old_pdeps
let old_pinf :: PatchInfo
old_pinf = Named (PrimOf p) wX wY -> PatchInfo
forall (p :: * -> * -> *) wX wY. Named p wX wY -> PatchInfo
patch2patchinfo Named (PrimOf p) wX wY
oldp
prior :: (String, [String])
prior = (PatchInfo -> String
piName PatchInfo
old_pinf, PatchInfo -> [String]
piLog PatchInfo
old_pinf)
String
date <- if Bool
keepDate then String -> StateT HijackOptions IO String
forall a. a -> StateT HijackOptions IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (PatchInfo -> String
piDateString PatchInfo
old_pinf) else IO String -> StateT HijackOptions IO String
forall a. IO a -> StateT HijackOptions IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> StateT HijackOptions IO String)
-> IO String -> StateT HijackOptions IO String
forall a b. (a -> b) -> a -> b
$ Bool -> IO String
getDate Bool
False
String
new_author <- String
-> Bool
-> Maybe String
-> PatchInfo
-> StateT HijackOptions IO String
getAuthor String
verb Bool
selectAuthor Maybe String
author PatchInfo
old_pinf
IO (Maybe String, PatchInfoAnd p wX wZ)
-> HijackT IO (Maybe String, PatchInfoAnd p wX wZ)
forall a. IO a -> StateT HijackOptions IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe String, PatchInfoAnd p wX wZ)
-> HijackT IO (Maybe String, PatchInfoAnd p wX wZ))
-> IO (Maybe String, PatchInfoAnd p wX wZ)
-> HijackT IO (Maybe String, PatchInfoAnd p wX wZ)
forall a b. (a -> b) -> a -> b
$ do
(String
new_name, [String]
new_log, Maybe String
mlogf) <- Maybe String
-> Bool
-> Logfile
-> Maybe AskLongComment
-> Maybe (String, [String])
-> Doc
-> IO (String, [String], Maybe String)
getLog
Maybe String
patchname Bool
False (Maybe AbsolutePath -> Bool -> Logfile
O.Logfile Maybe AbsolutePath
forall a. Maybe a
Nothing Bool
False) Maybe AskLongComment
askLongComment ((String, [String]) -> Maybe (String, [String])
forall a. a -> Maybe a
Just (String, [String])
prior) (FL (PrimOf p) wY wZ -> Doc
forall wX wY. FL (PrimOf p) wX wY -> Doc
forall (p :: * -> * -> *) wX wY. ShowPatch p => FL p wX wY -> Doc
summaryFL FL (PrimOf p) wY wZ
chs)
PatchInfo
new_pinf <- String -> String -> String -> [String] -> IO PatchInfo
patchinfo String
date String
new_name String
new_author [String]
new_log
let newp :: PatchInfoAnd p wX wZ
newp = Named p wX wZ -> PatchInfoAnd p wX wZ
forall (p :: * -> * -> *) wX wY.
(Ident p, PatchId p ~ PatchInfo) =>
p wX wY -> PatchInfoAndG p wX wY
n2pia (Named p wX wZ -> [PatchInfo] -> Named p wX wZ
forall (p :: * -> * -> *) wX wY.
Named p wX wY -> [PatchInfo] -> Named p wX wY
adddeps (PatchInfo -> FL (PrimOf p) wX wZ -> Named p wX wZ
forall (p :: * -> * -> *) wX wY.
FromPrim p =>
PatchInfo -> FL (PrimOf p) wX wY -> Named p wX wY
infopatch PatchInfo
new_pinf FL (PrimOf p) wX wZ
newchs) [PatchInfo]
newdeps)
(Maybe String, PatchInfoAnd p wX wZ)
-> IO (Maybe String, PatchInfoAnd p wX wZ)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe String
mlogf, PatchInfoAnd p wX wZ
newp)
getAuthor :: String
-> Bool
-> Maybe String
-> PatchInfo
-> HijackT IO String
getAuthor :: String
-> Bool
-> Maybe String
-> PatchInfo
-> StateT HijackOptions IO String
getAuthor String
_ Bool
True Maybe String
_ PatchInfo
_ = do
String
auth <- IO String -> StateT HijackOptions IO String
forall a. IO a -> StateT HijackOptions IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> StateT HijackOptions IO String)
-> IO String -> StateT HijackOptions IO String
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> IO String
promptAuthor Bool
False Bool
True
String -> StateT HijackOptions IO String
forall a. a -> StateT HijackOptions IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
auth
getAuthor String
_ Bool
False (Just String
new) PatchInfo
_ =
String -> StateT HijackOptions IO String
forall a. a -> StateT HijackOptions IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
new
getAuthor String
verb Bool
False Maybe String
Nothing PatchInfo
pinfo = do
[String]
whitelist <- IO [String] -> StateT HijackOptions IO [String]
forall a. IO a -> StateT HijackOptions IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [String] -> StateT HijackOptions IO [String])
-> IO [String] -> StateT HijackOptions IO [String]
forall a b. (a -> b) -> a -> b
$ IO [String]
getEasyAuthor
HijackOptions
hj <- StateT HijackOptions IO HijackOptions
forall (m :: * -> *) s. Monad m => StateT s m s
get
if String
orig String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
whitelist Bool -> Bool -> Bool
|| HijackOptions -> Bool
canIgnore HijackOptions
hj
then StateT HijackOptions IO String
allowHijack
else do
Char
hijackResp <- IO Char -> StateT HijackOptions IO Char
forall a. IO a -> StateT HijackOptions IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Char -> StateT HijackOptions IO Char)
-> IO Char -> StateT HijackOptions IO Char
forall a b. (a -> b) -> a -> b
$ HijackOptions -> IO Char
askAboutHijack HijackOptions
hj
case Char
hijackResp of
Char
'y' -> StateT HijackOptions IO String
allowHijack
Char
'a' -> HijackOptions -> StateT HijackOptions IO ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put HijackOptions
IgnoreHijack StateT HijackOptions IO ()
-> StateT HijackOptions IO String -> StateT HijackOptions IO String
forall a b.
StateT HijackOptions IO a
-> StateT HijackOptions IO b -> StateT HijackOptions IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> StateT HijackOptions IO String
allowHijack
Char
_ -> IO String -> StateT HijackOptions IO String
forall a. IO a -> StateT HijackOptions IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
forall a. IO a
exitSuccess
where
askAboutHijack :: HijackOptions -> IO Char
askAboutHijack HijackOptions
hj = PromptConfig -> IO Char
promptChar (String -> String -> String -> Maybe Char -> String -> PromptConfig
PromptConfig String
msg String
opts [] Maybe Char
forall a. Maybe a
Nothing [])
where
msg :: String
msg = String
"You're not " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
orig String -> String -> String
forall a. [a] -> [a] -> [a]
++String
"! " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
capitalize String
verb String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" anyway? "
opts :: String
opts = case HijackOptions
hj of
HijackOptions
AlwaysRequestHijackPermission -> String
"yn"
HijackOptions
_ -> String
"yna"
canIgnore :: HijackOptions -> Bool
canIgnore HijackOptions
IgnoreHijack = Bool
True
canIgnore HijackOptions
RequestHijackPermission = Bool
False
canIgnore HijackOptions
AlwaysRequestHijackPermission = Bool
False
allowHijack :: StateT HijackOptions IO String
allowHijack = String -> StateT HijackOptions IO String
forall a. a -> StateT HijackOptions IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
orig
orig :: String
orig = PatchInfo -> String
piAuthor PatchInfo
pinfo