darcs-2.18.2: a distributed, interactive, smart revision control system
Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.Named

Description

Named patches group a set of changes with meta data (PatchInfo) and explicit dependencies (created using `darcs tag` or using --ask-deps).

While the data constructor NamedP is exported for technical reasons, code outside this modules should (and generally does) treat it as an abstract data type. The only exception is the rebase implementation i.e. the modules under Darcs.Patch.Rebase.

Synopsis

Documentation

data Named (p :: Type -> Type -> Type) wX wY where #

The Named type adds a patch info about a patch, that is a name.

NamedP info deps p represents patch p with name info. deps is a list of dependencies added at the named patch level, compared with the unnamed level (ie, dependencies added with darcs record --ask-deps).

Constructors

NamedP :: forall (p :: Type -> Type -> Type) wX wY. !PatchInfo -> ![PatchInfo] -> !(FL p wX wY) -> Named p wX wY 

Instances

Instances details
Apply p => Apply (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Associated Types

type ApplyState (Named p) 
Instance details

Defined in Darcs.Patch.Named

Methods

apply :: ApplyMonad (ApplyState (Named p)) m => Named p wX wY -> m () #

unapply :: ApplyMonad (ApplyState (Named p)) m => Named p wX wY -> m () #

Commute p => Commute (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

commute :: (Named p :> Named p) wX wY -> Maybe ((Named p :> Named p) wX wY) #

(Commute p, Conflict p, Summary p, PrimPatchBase p, PatchListFormat p, ShowPatch p) => Conflict (Named p) #

This instance takes care of handling the interaction between conflict resolution and explicit dependencies. A conflict involves a set of two or more patches and the general rule is that the conflict is considered resolved if there is another (later) patch that (transitively) depends on each of the (mutually) conflicting patches.

This principle extends to explicit dependencies between Named patches. In particular, recording a tag has the effect of resolving any as yet unresolved conflicts in a repo.

In general a Named patch contains multiple changes ( a "changeset"). Consider the named patches

  Named A [] a
  Named B [] (b1;b2)
  Named C [] c
  Named D [A,B] _

where, at the RepoPatch level, a conflicts with b1, and c with b2. D depends explicitly on both A and B, so it fully covers the conflict between a and b1 and thus we would be justified to consider that particular conflict as resolved. Unfortunately we cannot detect this at the Named patch level because RepoPatchV1 and V2 have no notion of patch identities. Thus, at the Named level the two underlying conflicts appear as a single large conflict between the three named patches A, B, and C, and this means that patch D does not count as a (partial) resolution (even though it arguably should).

When we decide that a set of conflicting Named patches is resolved, we move the RepoPatches contained in them to the context of the resolution. For all other named patches, we must commute as much of their contents as possible past the ones marked as resolved, using commutation at the RepoPatch level (i.e. ignoring explicit dependencies).

Instance details

Defined in Darcs.Patch.Named

Methods

isConflicted :: Named p wX wY -> Bool #

resolveConflicts :: RL (Named p) wO wX -> RL (Named p) wX wY -> [ConflictDetails (PrimOf (Named p)) wY] #

(Commute p, Conflict p, Summary p, PrimPatchBase p, PatchListFormat p, ShowPatch p) => Conflict (PatchInfoAnd p) # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

Methods

isConflicted :: PatchInfoAnd p wX wY -> Bool #

resolveConflicts :: RL (PatchInfoAnd p) wO wX -> RL (PatchInfoAnd p) wX wY -> [ConflictDetails (PrimOf (PatchInfoAnd p)) wY] #

PatchDebug p => PatchDebug (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

patchDebugDummy :: Named p wX wY -> () #

Effect p => Effect (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

effect :: Named p wX wY -> FL (PrimOf (Named p)) wX wY #

IsHunk (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

isHunk :: Named p wX wY -> Maybe (FileHunk (ObjectIdOfPatch (Named p)) wX wY) #

PatchListFormat (Named p) # 
Instance details

Defined in Darcs.Patch.Named

PrimPatchBase p => PrimPatchBase (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Associated Types

type PrimOf (Named p) 
Instance details

Defined in Darcs.Patch.Named

type PrimOf (Named p) = PrimOf p
Ident (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

ident :: Named p wX wY -> PatchId (Named p) #

PatchInspect p => PatchInspect (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

listTouchedFiles :: Named p wX wY -> [AnchoredPath] #

hunkMatches :: (ByteString -> Bool) -> Named p wX wY -> Bool #

CleanMerge p => CleanMerge (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

cleanMerge :: (Named p :\/: Named p) wX wY -> Maybe ((Named p :/\: Named p) wX wY) #

Merge p => Merge (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

merge :: (Named p :\/: Named p) wX wY -> (Named p :/\: Named p) wX wY #

HasDeps (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

getdeps :: Named p wX wY -> [PatchInfo] #

(ReadPatch p, PatchListFormat p) => ReadPatch (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

readPatch' :: Parser (Sealed (Named p wX)) #

Check p => Check (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

isInconsistent :: Named p wX wY -> Maybe Doc #

RepairToFL p => Repair (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

applyAndTryToFix :: ApplyMonad (ApplyState (Named p)) m => Named p wX wY -> m (Maybe (String, Named p wX wY)) #

RepairToFL p => Repair (PatchInfoAnd p) # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

(Apply p, IsHunk p, PatchListFormat p, ObjectId (ObjectIdOfPatch p), ShowContextPatch p) => ShowContextPatch (Named p) # 
Instance details

Defined in Darcs.Patch.Named

(Summary p, PatchListFormat p, PrimPatchBase p, ShowPatch p) => ShowPatch (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

content :: Named p wX wY -> Doc #

description :: Named p wX wY -> Doc #

summary :: Named p wX wY -> Doc #

summaryFL :: FL (Named p) wX wY -> Doc #

thing :: Named p wX wY -> String #

things :: Named p wX wY -> String #

(PatchListFormat p, ShowPatchBasic p) => ShowPatchBasic (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

showPatch :: ShowPatchFor -> Named p wX wY -> Doc #

Summary p => Summary (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

conflictedEffect :: Named p wX wY -> [IsConflictedPrim (PrimOf (Named p))] #

(PrimPatchBase p, Unwind p) => Unwind (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

fullUnwind :: Named p wX wY -> Unwound (PrimOf (Named p)) wX wY #

(Commute p, Eq2 p) => Eq2 (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

unsafeCompare :: Named p wA wB -> Named p wC wD -> Bool #

(=\/=) :: Named p wA wB -> Named p wA wC -> EqCheck wB wC #

(=/\=) :: Named p wA wC -> Named p wB wC -> EqCheck wA wB #

Show2 p => Show2 (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

showDict2 :: ShowDict (Named p wX wY) #

Show2 p => Show2 (PatchInfoAnd p) # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

Methods

showDict2 :: ShowDict (PatchInfoAnd p wX wY) #

Show2 p => Show1 (Named p wX) # 
Instance details

Defined in Darcs.Patch.Named

Methods

showDict1 :: Dict (Show (Named p wX wX0)) #

Show2 p => Show1 (PatchInfoAnd p wX) # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

Methods

showDict1 :: Dict (Show (PatchInfoAnd p wX wX0)) #

Show2 p => Show (Named p wX wY) # 
Instance details

Defined in Darcs.Patch.Named

Methods

showsPrec :: Int -> Named p wX wY -> ShowS #

show :: Named p wX wY -> String #

showList :: [Named p wX wY] -> ShowS #

type ApplyState (Named p) # 
Instance details

Defined in Darcs.Patch.Named

type PrimOf (Named p) # 
Instance details

Defined in Darcs.Patch.Named

type PrimOf (Named p) = PrimOf p
type PatchId (Named p) # 
Instance details

Defined in Darcs.Patch.Named

infopatch :: forall (p :: Type -> Type -> Type) wX wY. FromPrim p => PatchInfo -> FL (PrimOf p) wX wY -> Named p wX wY #

adddeps :: forall (p :: Type -> Type -> Type) wX wY. Named p wX wY -> [PatchInfo] -> Named p wX wY #

setinfo :: forall (p :: Type -> Type -> Type) wX wY. PatchInfo -> Named p wX wY -> Named p wX wY #

anonymous :: forall (p :: Type -> Type -> Type) wX wY. FromPrim p => FL (PrimOf p) wX wY -> IO (Named p wX wY) #

class HasDeps (p :: Type -> Type -> Type) where #

This slightly ad-hoc class is here so we can call getdeps with patch types that wrap a Named, such as RebaseChange.

Methods

getdeps :: p wX wY -> [PatchInfo] #

Instances

Instances details
HasDeps (Named p) # 
Instance details

Defined in Darcs.Patch.Named

Methods

getdeps :: Named p wX wY -> [PatchInfo] #

HasDeps (RebaseChange prim) # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Methods

getdeps :: RebaseChange prim wX wY -> [PatchInfo] #

patch2patchinfo :: forall (p :: Type -> Type -> Type) wX wY. Named p wX wY -> PatchInfo #

patchname :: forall (p :: Type -> Type -> Type) wX wY. Named p wX wY -> String #

patchcontents :: forall (p :: Type -> Type -> Type) wX wY. Named p wX wY -> FL p wX wY #

fmapNamed :: (forall wA wB. p wA wB -> q wA wB) -> Named p wX wY -> Named q wX wY #

fmapFL_Named :: forall (p :: Type -> Type -> Type) wA wB (q :: Type -> Type -> Type) wC wD. (FL p wA wB -> FL q wC wD) -> Named p wA wB -> Named q wC wD #

mergerIdNamed :: forall (p1 :: Type -> Type -> Type) (p2 :: Type -> Type -> Type). MergeFn p1 p2 -> MergeFn p1 (Named p2) #

data ShowDepsFormat #

Instances

Instances details
Eq ShowDepsFormat # 
Instance details

Defined in Darcs.Patch.Named

data ShowWhichDeps #

Support for rebase

Instances

Instances details
Eq ShowWhichDeps # 
Instance details

Defined in Darcs.Patch.Named