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

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.V3.Core

Description

Conflictors a la camp.

Similar to the camp paper, but with a few differences:

  • no reverse conflictors and no Invert instance
  • instead we directly implement cleanMerge
  • minor details of merge and commute due to bug fixes
Synopsis

Documentation

data RepoPatchV3 name prim wX wY where Source #

Constructors

Prim :: PrimWithName name prim wX wY -> RepoPatchV3 name prim wX wY 
Conflictor 

Fields

Instances
FromPrim (RepoPatchV3 prim) Source # 
Instance details

Defined in Darcs.Patch.V3

Methods

fromAnonymousPrim :: PrimOf (RepoPatchV3 prim) wX wY -> RepoPatchV3 prim wX wY Source #

fromPrim :: PatchId (RepoPatchV3 prim) -> PrimOf (RepoPatchV3 prim) wX wY -> RepoPatchV3 prim wX wY Source #

fromPrims :: PatchInfo -> FL (PrimOf (RepoPatchV3 prim)) wX wY -> FL (RepoPatchV3 prim) wX wY Source #

(SignedId name, Eq2 prim, Commute prim) => Eq2 (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

unsafeCompare :: RepoPatchV3 name prim wA wB -> RepoPatchV3 name prim wC wD -> Bool Source #

(=\/=) :: RepoPatchV3 name prim wA wB -> RepoPatchV3 name prim wA wC -> EqCheck wB wC Source #

(=/\=) :: RepoPatchV3 name prim wA wC -> RepoPatchV3 name prim wB wC -> EqCheck wA wB Source #

PatchListFormat (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

(Show name, Show2 prim) => Show2 (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

showDict2 :: ShowDict (RepoPatchV3 name prim wX wY) Source #

PatchDebug prim => PatchDebug (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

patchDebugDummy :: RepoPatchV3 name prim wX wY -> () Source #

(SignedId name, StorableId name, PrimPatch prim) => Commute (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

commute :: (RepoPatchV3 name prim :> RepoPatchV3 name prim) wX wY -> Maybe ((RepoPatchV3 name prim :> RepoPatchV3 name prim) wX wY) Source #

(SignedId name, StorableId name, PrimPatch prim) => Merge (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

merge :: (RepoPatchV3 name prim :\/: RepoPatchV3 name prim) wX wY -> (RepoPatchV3 name prim :/\: RepoPatchV3 name prim) wX wY Source #

(SignedId name, StorableId name, PrimPatch prim) => CleanMerge (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

cleanMerge :: (RepoPatchV3 name prim :\/: RepoPatchV3 name prim) wX wY -> Maybe ((RepoPatchV3 name prim :/\: RepoPatchV3 name prim) wX wY) Source #

(SignedId name, StorableId name, PrimPatch prim) => CommuteNoConflicts (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

commuteNoConflicts :: (RepoPatchV3 name prim :> RepoPatchV3 name prim) wX wY -> Maybe ((RepoPatchV3 name prim :> RepoPatchV3 name prim) wX wY) Source #

PatchInspect prim => PatchInspect (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

listTouchedFiles :: RepoPatchV3 name prim wX wY -> [AnchoredPath] Source #

hunkMatches :: (ByteString -> Bool) -> RepoPatchV3 name prim wX wY -> Bool Source #

PrimPatch prim => Apply (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Associated Types

type ApplyState (RepoPatchV3 name prim) :: (Type -> Type) -> Type Source #

Methods

apply :: ApplyMonad (ApplyState (RepoPatchV3 name prim)) m => RepoPatchV3 name prim wX wY -> m () Source #

unapply :: ApplyMonad (ApplyState (RepoPatchV3 name prim)) m => RepoPatchV3 name prim wX wY -> m () Source #

(SignedId name, StorableId name, PrimPatch prim) => ShowPatch (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

content :: RepoPatchV3 name prim wX wY -> Doc Source #

description :: RepoPatchV3 name prim wX wY -> Doc Source #

summary :: RepoPatchV3 name prim wX wY -> Doc Source #

summaryFL :: FL (RepoPatchV3 name prim) wX wY -> Doc Source #

thing :: RepoPatchV3 name prim wX wY -> String Source #

things :: RepoPatchV3 name prim wX wY -> String Source #

(StorableId name, PrimPatch prim) => ShowContextPatch (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

showContextPatch :: ApplyMonad (ApplyState (RepoPatchV3 name prim)) m => ShowPatchFor -> RepoPatchV3 name prim wX wY -> m Doc Source #

(StorableId name, PrimPatch prim) => ShowPatchBasic (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

showPatch :: ShowPatchFor -> RepoPatchV3 name prim wX wY -> Doc Source #

SignedId name => Ident (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

ident :: RepoPatchV3 name prim wX wY -> PatchId (RepoPatchV3 name prim) Source #

IsHunk prim => IsHunk (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

isHunk :: RepoPatchV3 name prim wX wY -> Maybe (FileHunk wX wY) Source #

(SignedId name, StorableId name, PrimPatch prim) => ReadPatch (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

readPatch' :: Parser (Sealed (RepoPatchV3 name prim wX)) Source #

PrimPatch prim => RepairToFL (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

applyAndTryToFixFL :: ApplyMonad (ApplyState (RepoPatchV3 name prim)) m => RepoPatchV3 name prim wX wY -> m (Maybe (String, FL (RepoPatchV3 name prim) wX wY)) Source #

PrimPatch prim => Check (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

isInconsistent :: RepoPatchV3 name prim wX wY -> Maybe Doc Source #

ToPrim (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

toPrim :: RepoPatchV3 name prim wX wY -> Maybe (PrimOf (RepoPatchV3 name prim) wX wY) Source #

PrimPatch prim => PrimPatchBase (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Associated Types

type PrimOf (RepoPatchV3 name prim) :: Type -> Type -> Type Source #

(Invert prim, Commute prim, Eq2 prim) => Unwind (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

fullUnwind :: RepoPatchV3 name prim wX wY -> Unwound (PrimOf (RepoPatchV3 name prim)) wX wY Source #

Summary (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

conflictedEffect :: RepoPatchV3 name prim wX wY -> [IsConflictedPrim (PrimOf (RepoPatchV3 name prim))] Source #

Effect (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

effect :: RepoPatchV3 name prim wX wY -> FL (PrimOf (RepoPatchV3 name prim)) wX wY Source #

(SignedId name, StorableId name, PrimPatch prim) => Conflict (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Resolution

Methods

resolveConflicts :: RL (RepoPatchV3 name prim) wO wX -> RL (RepoPatchV3 name prim) wX wY -> [ConflictDetails (PrimOf (RepoPatchV3 name prim)) wY] Source #

(Show name, Show2 prim) => Show1 (RepoPatchV3 name prim wX) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

showDict1 :: Dict (Show (RepoPatchV3 name prim wX wX0)) Source #

(Show name, Show2 prim) => Show (RepoPatchV3 name prim wX wY) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

showsPrec :: Int -> RepoPatchV3 name prim wX wY -> ShowS #

show :: RepoPatchV3 name prim wX wY -> String #

showList :: [RepoPatchV3 name prim wX wY] -> ShowS #

type ApplyState (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

type ApplyState (RepoPatchV3 name prim) = ApplyState prim
type PatchId (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

type PatchId (RepoPatchV3 name prim) = name
type PrimOf (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

type PrimOf (RepoPatchV3 name prim) = prim

pattern PrimP :: TestOnly => PrimWithName name prim wX wY -> RepoPatchV3 name prim wX wY Source #

pattern ConflictorP :: TestOnly => FL (PrimWithName name prim) wX wY -> Set (Contexted (PrimWithName name prim) wY) -> Contexted (PrimWithName name prim) wY -> RepoPatchV3 name prim wX wY Source #

(+|) :: Ord a => a -> Set a -> Set a infixr 9 Source #

A handy synonym for insert.

(-|) :: Ord a => a -> Set a -> Set a infixr 9 Source #

A handy synonym for delete.