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

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.Invertible

Description

Formal inverses for patches that aren't really invertible. Note that most the mixed {Fwd,Rev} cases for Commute and Eq2 are just errors.

Synopsis

Documentation

data Invertible p wX wY Source #

Wrapper type to allow formal inversion of patches which aren't really invertible.

Instances
Eq2 p => Eq2 (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

Methods

unsafeCompare :: Invertible p wA wB -> Invertible p wC wD -> Bool Source #

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

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

Invert (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

Methods

invert :: Invertible p wX wY -> Invertible p wY wX Source #

Commute p => Commute (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

Methods

commute :: (Invertible p :> Invertible p) wX wY -> Maybe ((Invertible p :> Invertible p) wX wY) Source #

PatchInspect p => PatchInspect (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

Apply p => Apply (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

Associated Types

type ApplyState (Invertible p) :: (Type -> Type) -> Type Source #

Methods

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

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

ShowPatch p => ShowPatch (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

Methods

content :: Invertible p wX wY -> Doc Source #

description :: Invertible p wX wY -> Doc Source #

summary :: Invertible p wX wY -> Doc Source #

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

thing :: Invertible p wX wY -> String Source #

things :: Invertible p wX wY -> String Source #

ShowContextPatch p => ShowContextPatch (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

ShowPatchBasic p => ShowPatchBasic (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

Methods

showPatch :: ShowPatchFor -> Invertible p wX wY -> Doc Source #

Ident p => Ident (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

Methods

ident :: Invertible p wX wY -> PatchId (Invertible p) Source #

PrimPatchBase p => PrimPatchBase (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

Associated Types

type PrimOf (Invertible p) :: Type -> Type -> Type Source #

type ApplyState (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

type PatchId (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

type PrimOf (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

type PrimOf (Invertible p) = PrimOf p

mkInvertible :: p wX wY -> Invertible p wX wY Source #

Wrap a patch to make it (formally) Invertible. The result is initially positive i.e. Fwd.

fromPositiveInvertible :: Invertible p wX wY -> p wX wY Source #

Get the underlying patch from an Invertible, assuming (as a precondition) that it is positive i.e. Fwd.

withInvertible :: (forall wA wB. p wA wB -> r) -> Invertible p wX wY -> r Source #

Run a function on the patch inside an Invertible. The function has to be parametric in the witnesses, so we can run it with both a Fwd and a Rev patch.