Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- getLog :: Maybe String -> Bool -> Logfile -> Maybe AskLongComment -> Maybe (String, [String]) -> Doc -> IO (String, [String], Maybe String)
- getAuthor :: String -> Bool -> Maybe String -> PatchInfo -> HijackT IO String
- editLog :: Named prim wX wY -> IO (Named prim wX wY)
- updatePatchHeader :: forall p wX wY wZ. (RepoPatch p, ApplyState p ~ Tree) => String -> AskAboutDeps p wX -> PatchSelectionOptions -> PatchHeaderConfig -> Named (PrimOf p) wX wY -> FL (PrimOf p) wY wZ -> HijackT IO (Maybe String, PatchInfoAnd p wX wZ)
- data AskAboutDeps p wX where
- AskAboutDeps :: RL (PatchInfoAnd p) w wX -> AskAboutDeps p wX
- NoAskAboutDeps :: AskAboutDeps p wX
- data PatchHeaderConfig
- patchHeaderConfig :: Config -> PatchHeaderConfig
- type HijackT = StateT HijackOptions
- data HijackOptions
- runHijackT :: Monad m => HijackOptions -> HijackT m a -> m a
Documentation
:: Maybe String | patchname option |
-> Bool | pipe option |
-> Logfile | logfile option |
-> Maybe AskLongComment | askLongComment option |
-> Maybe (String, [String]) | possibly an existing patch name and long description |
-> Doc | summary of changes to record |
-> IO (String, [String], Maybe String) | patch name, long description and possibly the path to the temporary file that should be removed later |
Get the patch name and long description from one of
- the configuration (flags, defaults, hard-coded)
- an existing log file
- stdin (e.g. a pipe)
- a text editor
It ensures the patch name is not empty nor starts with the prefix TAG.
The last result component is a possible path to a temporary file that should be removed later.
:: String | verb: command name |
-> Bool | select: prompt for new auhor |
-> Maybe String | new author: explict new author |
-> PatchInfo | patch to update |
-> HijackT IO String |
getAuthor
tries to return the updated author for the patch.
There are two different scenarios:
- [explicit] Either we want to override the patch author, be it by
prompting the user (
select
) or having them pass it in from the UI (new_author
), or - [implicit] We want to keep the original author, in which case we also double-check that we are not inadvertently "hijacking" somebody else's patch (if the patch author is not the same as the repository author, we give them a chance to abort the whole operation)
:: forall p wX wY wZ. (RepoPatch p, ApplyState p ~ Tree) | |
=> String | verb: command name |
-> AskAboutDeps p wX | |
-> PatchSelectionOptions | |
-> PatchHeaderConfig | |
-> Named (PrimOf p) wX wY | patch to edit, must be conflict-free as conflicts can't
be preserved when changing the identity of a patch. If
necessary this can be achieved by calling |
-> FL (PrimOf p) wY wZ | new primitives to add |
-> HijackT IO (Maybe String, PatchInfoAnd p wX wZ) |
Update the metadata for a patch.
This potentially involves a bit of interactivity, so we may return Nothing
if there is cause to abort what we're doing along the way
data AskAboutDeps p wX where Source #
Specify whether to ask about dependencies with respect to a particular
PatchSet
, or not
AskAboutDeps :: RL (PatchInfoAnd p) w wX -> AskAboutDeps p wX | |
NoAskAboutDeps :: AskAboutDeps p wX |
data PatchHeaderConfig Source #
type HijackT = StateT HijackOptions Source #
Transformer for interactions with a hijack warning state that we need to thread through
data HijackOptions Source #
Options for how to deal with the situation where we are somehow modifying a patch that is not our own
IgnoreHijack | accept all hijack requests |
RequestHijackPermission | prompt once, accepting subsequent hijacks if yes |
AlwaysRequestHijackPermission | always prompt |
runHijackT :: Monad m => HijackOptions -> HijackT m a -> m a Source #
Run a job that involves a hijack confirmation prompt.
See RequestHijackPermission
for initial values