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

Darcs.Patch.Prim.V1.Core

Documentation

data Prim wX wY where Source #

Constructors

Move :: !AnchoredPath -> !AnchoredPath -> Prim wX wY 
DP :: !AnchoredPath -> !(DirPatchType wX wY) -> Prim wX wY 
FP :: !AnchoredPath -> !(FilePatchType wX wY) -> Prim wX wY 
ChangePref :: !String -> !String -> !String -> Prim wX wY 

Instances

Instances details
Annotate Prim Source # 
Instance details

Defined in Darcs.Patch.Annotate

Methods

annotate :: Prim wX wY -> AnnotatedM () Source #

Apply Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Apply

Associated Types

type ApplyState Prim :: (Type -> Type) -> Type Source #

Methods

apply :: ApplyMonad (ApplyState Prim) m => Prim wX wY -> m () Source #

unapply :: ApplyMonad (ApplyState Prim) m => Prim wX wY -> m () Source #

Commute Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Commute

Methods

commute :: (Prim :> Prim) wX wY -> Maybe ((Prim :> Prim) wX wY) Source #

PatchDebug Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

patchDebugDummy :: Prim wX wY -> () Source #

ObjectIdOf (ApplyState Prim) ~ AnchoredPath => IsHunk Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

isHunk :: Prim wX wY -> Maybe (FileHunk (ObjectIdOfPatch Prim) wX wY) Source #

PatchInspect Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Invert Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

invert :: Prim wX wY -> Prim wY wX Source #

CleanMerge Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Commute

Methods

cleanMerge :: (Prim :\/: Prim) wX wY -> Maybe ((Prim :/\: Prim) wX wY) Source #

PrimApply Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Apply

Methods

applyPrimFL :: ApplyMonad (ApplyState Prim) m => FL Prim wX wY -> m () Source #

PrimCoalesce Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Coalesce

Methods

tryToShrink :: FL Prim wX wY -> Maybe (FL Prim wX wY) Source #

sortCoalesceFL :: FL Prim wX wY -> FL Prim wX wY Source #

primCoalesce :: Prim wX wY -> Prim wY wZ -> Maybe (Prim wX wZ) Source #

isIdentity :: Prim wX wY -> EqCheck wX wY Source #

comparePrim :: Prim wA wB -> Prim wC wD -> Ordering Source #

ObjectIdOf (ApplyState Prim) ~ AnchoredPath => PrimConstruct Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

PrimDetails Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Details

Methods

summarizePrim :: Prim wX wY -> [SummDetail] Source #

PrimMangleUnravelled Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Mangle

PrimRead Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Read

(Apply Prim, ApplyState Prim ~ Tree, ObjectIdOfPatch Prim ~ AnchoredPath) => PrimShow Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Show

PrimSift Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

primIsSiftable :: Prim wX wY -> Bool Source #

RepairToFL Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Apply

Methods

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

Eq2 Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

unsafeCompare :: Prim wA wB -> Prim wC wD -> Bool Source #

(=\/=) :: Prim wA wB -> Prim wA wC -> EqCheck wB wC Source #

(=/\=) :: Prim wA wC -> Prim wB wC -> EqCheck wA wB Source #

Show2 Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Show

Methods

showDict2 :: ShowDict (Prim wX wY) Source #

Show1 (Prim wX) Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Show

Methods

showDict1 :: Dict (Show (Prim wX wX0)) Source #

Show (Prim wX wY) Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Show

Methods

showsPrec :: Int -> Prim wX wY -> ShowS #

show :: Prim wX wY -> String #

showList :: [Prim wX wY] -> ShowS #

Eq (Prim wX wY) Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

(==) :: Prim wX wY -> Prim wX wY -> Bool #

(/=) :: Prim wX wY -> Prim wX wY -> Bool #

type ApplyState Prim Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Apply

data DirPatchType wX wY Source #

Constructors

RmDir 
AddDir 

Instances

Instances details
Invert DirPatchType Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

invert :: DirPatchType wX wY -> DirPatchType wY wX Source #

Eq2 DirPatchType Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

unsafeCompare :: DirPatchType wA wB -> DirPatchType wC wD -> Bool Source #

(=\/=) :: DirPatchType wA wB -> DirPatchType wA wC -> EqCheck wB wC Source #

(=/\=) :: DirPatchType wA wC -> DirPatchType wB wC -> EqCheck wA wB Source #

Show (DirPatchType wX wY) Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Show

Methods

showsPrec :: Int -> DirPatchType wX wY -> ShowS #

show :: DirPatchType wX wY -> String #

showList :: [DirPatchType wX wY] -> ShowS #

Eq (DirPatchType wX wY) Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

(==) :: DirPatchType wX wY -> DirPatchType wX wY -> Bool #

(/=) :: DirPatchType wX wY -> DirPatchType wX wY -> Bool #

Ord (DirPatchType wX wY) Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

compare :: DirPatchType wX wY -> DirPatchType wX wY -> Ordering #

(<) :: DirPatchType wX wY -> DirPatchType wX wY -> Bool #

(<=) :: DirPatchType wX wY -> DirPatchType wX wY -> Bool #

(>) :: DirPatchType wX wY -> DirPatchType wX wY -> Bool #

(>=) :: DirPatchType wX wY -> DirPatchType wX wY -> Bool #

max :: DirPatchType wX wY -> DirPatchType wX wY -> DirPatchType wX wY #

min :: DirPatchType wX wY -> DirPatchType wX wY -> DirPatchType wX wY #

data FilePatchType wX wY Source #

Instances

Instances details
Invert FilePatchType Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

invert :: FilePatchType wX wY -> FilePatchType wY wX Source #

Eq2 FilePatchType Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

unsafeCompare :: FilePatchType wA wB -> FilePatchType wC wD -> Bool Source #

(=\/=) :: FilePatchType wA wB -> FilePatchType wA wC -> EqCheck wB wC Source #

(=/\=) :: FilePatchType wA wC -> FilePatchType wB wC -> EqCheck wA wB Source #

Show (FilePatchType wX wY) Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Show

Methods

showsPrec :: Int -> FilePatchType wX wY -> ShowS #

show :: FilePatchType wX wY -> String #

showList :: [FilePatchType wX wY] -> ShowS #

Eq (FilePatchType wX wY) Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

(==) :: FilePatchType wX wY -> FilePatchType wX wY -> Bool #

(/=) :: FilePatchType wX wY -> FilePatchType wX wY -> Bool #

Ord (FilePatchType wX wY) Source # 
Instance details

Defined in Darcs.Patch.Prim.V1.Core

Methods

compare :: FilePatchType wX wY -> FilePatchType wX wY -> Ordering #

(<) :: FilePatchType wX wY -> FilePatchType wX wY -> Bool #

(<=) :: FilePatchType wX wY -> FilePatchType wX wY -> Bool #

(>) :: FilePatchType wX wY -> FilePatchType wX wY -> Bool #

(>=) :: FilePatchType wX wY -> FilePatchType wX wY -> Bool #

max :: FilePatchType wX wY -> FilePatchType wX wY -> FilePatchType wX wY #

min :: FilePatchType wX wY -> FilePatchType wX wY -> FilePatchType wX wY #