Safe Haskell | Safe-Infered |
---|
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 Matcher
s:
- 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.
- matchFirstPatchset :: RepoPatch p => [DarcsFlag] -> PatchSet p start x -> SealedPatchSet p start
- matchSecondPatchset :: RepoPatch p => [DarcsFlag] -> PatchSet p start x -> SealedPatchSet p start
- matchPatch :: RepoPatch p => [DarcsFlag] -> PatchSet p start x -> Sealed2 (Named p)
- matchAPatch :: Patchy p => [DarcsFlag] -> Named p x y -> Bool
- matchAPatchread :: Patchy p => [DarcsFlag] -> PatchInfoAnd p x y -> Bool
- getFirstMatch :: (ApplyMonad IO (ApplyState p), RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> IO ()
- getNonrangeMatch :: (ApplyMonad IO (ApplyState p), RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> IO ()
- getNonrangeMatchS :: (ApplyMonad m (ApplyState p), MonadProgress m, RepoPatch p, ApplyState p ~ Tree) => [DarcsFlag] -> PatchSet p Origin x -> m ()
- getPartialFirstMatch :: (RepoPatch p, ApplyMonad IO (ApplyState p), ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> Maybe [FileName] -> IO ()
- getPartialSecondMatch :: (RepoPatch p, ApplyMonad IO (ApplyState p), ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> Maybe [FileName] -> IO ()
- getPartialNonrangeMatch :: (RepoPatch p, ApplyMonad IO (ApplyState p), ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> [FileName] -> IO ()
- firstMatch :: [DarcsFlag] -> Bool
- secondMatch :: [DarcsFlag] -> Bool
- haveNonrangeMatch :: [DarcsFlag] -> Bool
- havePatchsetMatch :: [DarcsFlag] -> Bool
- getOnePatchset :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> IO (SealedPatchSet p Origin)
- checkMatchSyntax :: [DarcsFlag] -> IO ()
- applyInvToMatcher :: (RepoPatch p, ApplyMonad m (ApplyState p)) => InclusiveOrExclusive -> Matcher p -> PatchSet p Origin x -> m ()
- nonrangeMatcher :: Patchy p => [DarcsFlag] -> Maybe (Matcher p)
- data InclusiveOrExclusive
- matchExists :: Matcher p -> PatchSet p start x -> Bool
- applyNInv :: (RepoPatch p, ApplyMonad m (ApplyState p)) => Int -> PatchSet p Origin x -> m ()
- hasIndexRange :: [DarcsFlag] -> Maybe (Int, Int)
Documentation
matchFirstPatchset :: RepoPatch p => [DarcsFlag] -> PatchSet p start x -> SealedPatchSet p startSource
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 :: RepoPatch p => [DarcsFlag] -> PatchSet p start x -> SealedPatchSet p startSource
matchSecondPatchset fs ps
returns the part of ps
before its
second matcher, ie the one that comes last dependencywise.
matchAPatch :: Patchy p => [DarcsFlag] -> Named p x y -> BoolSource
matchAPatch fs p
tells whether p
matches the matchers in
the flags fs
matchAPatchread :: Patchy p => [DarcsFlag] -> PatchInfoAnd p x y -> BoolSource
matchAPatchread fs p
tells whether p
matches the matchers in
the flags listed in fs
.
getFirstMatch :: (ApplyMonad IO (ApplyState p), RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> IO ()Source
getNonrangeMatch :: (ApplyMonad IO (ApplyState p), RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> IO ()Source
getNonrangeMatchS :: (ApplyMonad m (ApplyState p), MonadProgress m, RepoPatch p, ApplyState p ~ Tree) => [DarcsFlag] -> PatchSet p Origin x -> m ()Source
getPartialFirstMatch :: (RepoPatch p, ApplyMonad IO (ApplyState p), ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> Maybe [FileName] -> IO ()Source
getPartialSecondMatch :: (RepoPatch p, ApplyMonad IO (ApplyState p), ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> Maybe [FileName] -> IO ()Source
getPartialNonrangeMatch :: (RepoPatch p, ApplyMonad IO (ApplyState p), ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> [FileName] -> IO ()Source
firstMatch :: [DarcsFlag] -> BoolSource
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 :: [DarcsFlag] -> BoolSource
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 :: [DarcsFlag] -> BoolSource
haveNonrangeMatch flags
tells whether there is a flag in
flags
which corresponds to a match that is non-range. Thus,
--match
, --patch
and --index
make haveNonrangeMatch
true, but not --from-patch
or --to-patch
.
havePatchsetMatch :: [DarcsFlag] -> BoolSource
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
?
getOnePatchset :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> IO (SealedPatchSet p Origin)Source
checkMatchSyntax :: [DarcsFlag] -> IO ()Source
applyInvToMatcher :: (RepoPatch p, ApplyMonad m (ApplyState p)) => InclusiveOrExclusive -> Matcher p -> PatchSet p Origin x -> m ()Source
nonrangeMatcher :: Patchy p => [DarcsFlag] -> 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).
matchExists :: Matcher p -> PatchSet p start x -> BoolSource
matchExists m ps
tells whether there is a patch matching
m
in ps
applyNInv :: (RepoPatch p, ApplyMonad m (ApplyState p)) => Int -> PatchSet p Origin x -> m ()Source
applyNInv
n ps applies the inverse of the last n
patches of ps
.