| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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 firstMatcheris the left bound of the interval,
- the secondMatcheris the right bound, and
- the nonrangeMatcheris the criterion we use to select among patches in the interval.
- matchParser :: Matchable p => CharParser st (MatchFun p)
- helpOnMatchers :: [String]
- addInternalMatcher :: Matchable p => Maybe (Matcher p) -> Maybe (Matcher p)
- matchFirstPatchset :: Matchable p => [MatchFlag] -> PatchSet p wStart wX -> SealedPatchSet p wStart
- matchSecondPatchset :: Matchable p => [MatchFlag] -> PatchSet p wStart wX -> SealedPatchSet p wStart
- splitSecondFL :: Matchable p => (forall wA wB. q wA wB -> Sealed2 (PatchInfoAnd p)) -> [MatchFlag] -> FL q wX wY -> (FL q :> FL q) wX wY
- matchPatch :: Matchable p => [MatchFlag] -> PatchSet p wStart wX -> Sealed2 (Named p)
- matchAPatch :: Matchable p => [MatchFlag] -> PatchInfoAnd p wX wY -> Bool
- matchAPatchread :: Matchable p => [MatchFlag] -> PatchInfoAnd p wX wY -> Bool
- getNonrangeMatchS :: (ApplyMonad m (ApplyState p), MonadProgress m, Matchable p, ApplyState p ~ Tree) => [MatchFlag] -> PatchSet p Origin wX -> m ()
- firstMatch :: [MatchFlag] -> Bool
- secondMatch :: [MatchFlag] -> Bool
- haveNonrangeMatch :: forall p. Matchable p => PatchType p -> [MatchFlag] -> Bool
- havePatchsetMatch :: [MatchFlag] -> Bool
- checkMatchSyntax :: [MatchFlag] -> IO ()
- applyInvToMatcher :: (Matchable p, ApplyMonad m (ApplyState p)) => InclusiveOrExclusive -> Matcher p -> PatchSet p Origin wX -> m ()
- nonrangeMatcher :: Matchable p => [MatchFlag] -> Maybe (Matcher p)
- data InclusiveOrExclusive
- matchExists :: Matcher p -> PatchSet p wStart wX -> Bool
- applyNInv :: (Matchable p, ApplyMonad m (ApplyState p)) => Int -> PatchSet p Origin wX -> m ()
- hasIndexRange :: [MatchFlag] -> Maybe (Int, Int)
- getMatchingTag :: Matchable p => Matcher p -> PatchSet p wStart wX -> SealedPatchSet p wStart
- matchAPatchset :: Matchable p => Matcher p -> PatchSet p wStart wX -> SealedPatchSet p wStart
- getFirstMatchS :: (ApplyMonad m (ApplyState p), MonadProgress m, Matchable p) => [MatchFlag] -> PatchSet p Origin wX -> m ()
- nonrangeMatcherIsTag :: [MatchFlag] -> Bool
- data MatchFlag- = OnePattern String
- | SeveralPattern String
- | AfterPattern String
- | UpToPattern String
- | OnePatch String
- | OneHash String
- | AfterHash String
- | UpToHash String
- | SeveralPatch String
- | AfterPatch String
- | UpToPatch String
- | OneTag String
- | AfterTag String
- | UpToTag String
- | LastN Int
- | PatchIndexRange Int Int
- | Context AbsolutePath
 
Documentation
matchParser :: Matchable p => CharParser st (MatchFun p) Source
helpOnMatchers :: [String] Source
The string that is emitted when the user runs darcs help --match.
addInternalMatcher :: Matchable p => Maybe (Matcher p) -> Maybe (Matcher p) Source
matchFirstPatchset :: Matchable p => [MatchFlag] -> PatchSet p wStart wX -> SealedPatchSet 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 :: Matchable p => [MatchFlag] -> PatchSet p wStart wX -> SealedPatchSet p wStart Source
matchSecondPatchset fs ps returns the part of ps before its
 second matcher, ie the one that comes last dependencywise.
Arguments
| :: Matchable p | |
| => (forall wA wB. q wA wB -> Sealed2 (PatchInfoAnd 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
matchAPatch :: Matchable p => [MatchFlag] -> PatchInfoAnd p wX wY -> Bool Source
matchAPatch fs p tells whether p matches the matchers in
 the flags fs
matchAPatchread :: Matchable p => [MatchFlag] -> PatchInfoAnd p wX wY -> Bool Source
matchAPatchread fs p tells whether p matches the matchers in
 the flags listed in fs.
getNonrangeMatchS :: (ApplyMonad m (ApplyState p), MonadProgress m, Matchable p, ApplyState p ~ Tree) => [MatchFlag] -> PatchSet p Origin wX -> m () Source
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 p. Matchable p => PatchType 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.
havePatchsetMatch :: [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?
checkMatchSyntax :: [MatchFlag] -> IO () Source
applyInvToMatcher :: (Matchable p, ApplyMonad m (ApplyState p)) => InclusiveOrExclusive -> Matcher p -> PatchSet p Origin wX -> m () Source
nonrangeMatcher :: Matchable p => [MatchFlag] -> Maybe (Matcher 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).
data InclusiveOrExclusive Source
Instances
matchExists :: Matcher p -> PatchSet p wStart wX -> Bool Source
matchExists m ps tells whether there is a patch matching
 m in ps
applyNInv :: (Matchable p, ApplyMonad m (ApplyState p)) => Int -> PatchSet p Origin wX -> m () Source
applyNInv n ps applies the inverse of the last n patches of ps.
getMatchingTag :: Matchable p => Matcher p -> PatchSet p wStart wX -> SealedPatchSet 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 changes -t m. Calls
 error if there is no matching tag.
matchAPatchset :: Matchable p => Matcher p -> PatchSet p wStart wX -> SealedPatchSet p wStart Source
matchAPatchset m ps returns a (the largest?) subset of ps
 ending in patch which matches m. Calls error if there is none.
getFirstMatchS :: (ApplyMonad m (ApplyState p), MonadProgress m, Matchable p) => [MatchFlag] -> PatchSet p Origin wX -> m () Source
nonrangeMatcherIsTag :: [MatchFlag] -> Bool Source
nonrangeMatcherIsTag returns true if the matching option was
 '--tag'
Constructors