darcs-2.14.0: a distributed, interactive, smart revision control system

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.Match

Description

First matcher, Second matcher and Nonrange matcher

When we match for patches, we have a PatchSet, of which we want a subset. This subset is formed by the patches in a given interval which match a given criterion. If we represent time going left to right, then we have (up to) three Matchers:

  • the firstMatcher is the left bound of the interval,
  • the secondMatcher is the right bound, and
  • the nonrangeMatcher is the criterion we use to select among patches in the interval.

Synopsis

Documentation

matchParser :: Matchable p => CharParser st (MatchFun rt p) Source #

helpOnMatchers :: [String] Source #

The string that is emitted when the user runs darcs help patterns.

addInternalMatcher :: IsRepoType rt => Maybe (Matcher rt p) -> Maybe (Matcher rt p) Source #

matchFirstPatchset :: (IsRepoType rt, Matchable p) => [MatchFlag] -> PatchSet rt p wStart wX -> SealedPatchSet rt p wStart Source #

matchFirstPatchset fs ps returns the part of ps before its first matcher, ie the one that comes first dependencywise. Hence, patches in matchFirstPatchset fs ps are the context for the ones we don't want.

matchSecondPatchset :: (IsRepoType rt, Matchable p) => [MatchFlag] -> PatchSet rt p wStart wX -> SealedPatchSet rt p wStart Source #

matchSecondPatchset fs ps returns the part of ps before its second matcher, ie the one that comes last dependencywise.

splitSecondFL Source #

Arguments

:: Matchable p 
=> (forall wA wB. q wA wB -> Sealed2 (PatchInfoAnd rt p)) 
-> [MatchFlag] 
-> FL q wX wY 
-> (FL q :> FL q) wX wY

The first element is the patches before and including the first patch matching the second matcher, the second element is the patches after it

Split on the second matcher. Note that this picks up the first match starting from the earliest patch in a sequence, as opposed to matchSecondPatchset which picks up the first match starting from the latest patch

matchPatch :: (IsRepoType rt, Matchable p) => [MatchFlag] -> PatchSet rt p wStart wX -> Sealed2 (WrappedNamed rt p) Source #

matchAPatch :: (IsRepoType rt, Matchable p) => [MatchFlag] -> PatchInfoAnd rt p wX wY -> Bool Source #

matchAPatch fs p tells whether p matches the matchers in the flags fs

firstMatch :: [MatchFlag] -> Bool Source #

firstMatch fs tells whether fs implies a "first match", that is if we match against patches from a point in the past on, rather than against all patches since the creation of the repository.

secondMatch :: [MatchFlag] -> Bool Source #

secondMatch fs tells whether fs implies a "second match", that is if we match against patches up to a point in the past on, rather than against all patches until now.

haveNonrangeMatch :: forall rt p. (IsRepoType rt, Matchable p) => PatchType rt p -> [MatchFlag] -> Bool Source #

haveNonrangeMatch flags tells whether there is a flag in flags which corresponds to a match that is "non-range". Thus, --match, --patch, --hash and --index make haveNonrangeMatch true, but not --from-patch or --to-patch.

haveNonrangeExplicitMatch :: forall rt p. (IsRepoType rt, Matchable p) => PatchType rt p -> [MatchFlag] -> Bool Source #

haveNonrangeExplicitMatch flags is just like haveNonrangeMatch flags, but ignores "internal matchers" used to mask "internal patches"

havePatchsetMatch :: forall rt p. (IsRepoType rt, Matchable p) => PatchType rt p -> [MatchFlag] -> Bool Source #

havePatchsetMatch flags tells whether there is a "patchset match" in the flag list. A patchset match is --match or --patch, or --context, but not --from-patch nor (!) --index. Question: Is it supposed not to be a subset of haveNonrangeMatch?

applyInvToMatcher :: (Matchable p, ApplyMonad (ApplyState p) m) => InclusiveOrExclusive -> Matcher rt p -> PatchSet rt p Origin wX -> m () Source #

nonrangeMatcher :: (IsRepoType rt, Matchable p) => [MatchFlag] -> Maybe (Matcher rt p) Source #

nonrangeMatcher is the criterion that is used to match against patches in the interval. It is 'Just m' when the --patch, --match, --tag options are passed (or their plural variants).

matchExists :: Matcher rt p -> PatchSet rt p wStart wX -> Bool Source #

matchExists m ps tells whether there is a patch matching m in ps

applyNInv :: (Matchable p, ApplyMonad (ApplyState p) m) => Int -> PatchSet rt p Origin wX -> m () Source #

applyNInv n ps applies the inverse of the last n patches of ps.

getMatchingTag :: Matchable p => Matcher rt p -> PatchSet rt p wStart wX -> SealedPatchSet rt p wStart Source #

getMatchingTag m ps, where m is a Matcher which matches tags returns a SealedPatchSet containing all patches in the last tag which matches m. Last tag means the most recent tag in repository order, i.e. the last one you'd see if you ran darcs log -t m. Calls error if there is no matching tag.

matchAPatchset :: Matchable p => Matcher rt p -> PatchSet rt p wStart wX -> SealedPatchSet rt p wStart Source #

matchAPatchset m ps returns a prefix of ps ending in a patch matching m, and calls error if there is none.

nonrangeMatcherIsTag :: [MatchFlag] -> Bool Source #

nonrangeMatcherIsTag returns true if the matching option was '--tag'