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

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.PatchInfoAnd

Synopsis

Documentation

data Hopefully a wX wY Source #

Hopefully p C (x y) is Either String (p C (x y)) in a form adapted to darcs patches. The C (x y) represents the type witness for the patch that should be there. The Hopefully type just tells whether we expect the patch to be hashed or not, and SimpleHopefully does the real work of emulating Either. Hopefully sh represents an expected unhashed patch, and Hashed hash sh represents an expected hashed patch with its hash.

Constructors

Hopefully (SimpleHopefully a wX wY) 
Hashed String (SimpleHopefully a wX wY) 

Instances

Show (a wX wY) => Show (Hopefully a wX wY) Source # 

Methods

showsPrec :: Int -> Hopefully a wX wY -> ShowS #

show :: Hopefully a wX wY -> String #

showList :: [Hopefully a wX wY] -> ShowS #

data SimpleHopefully a wX wY Source #

SimpleHopefully is a variant of Either String adapted for type witnesses. Actually is the equivalent of Right, while Unavailable is Left.

Constructors

Actually (a wX wY) 
Unavailable String 

Instances

Show (a wX wY) => Show (SimpleHopefully a wX wY) Source # 

Methods

showsPrec :: Int -> SimpleHopefully a wX wY -> ShowS #

show :: SimpleHopefully a wX wY -> String #

showList :: [SimpleHopefully a wX wY] -> ShowS #

data PatchInfoAnd rt p wA wB Source #

PatchInfoAnd p wA wB represents a hope we have to get a patch through its info. We're not sure we have the patch, but we know its info.

Constructors

PIAP !PatchInfo (Hopefully (WrappedNamed rt p) wA wB) 

Instances

Show2 p => Show2 (PatchInfoAnd rt p) Source # 

Methods

showDict2 :: ShowDict (PatchInfoAnd rt p wX wY) Source #

MyEq (PatchInfoAnd rt p) Source # 

Methods

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

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

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

PatchListFormat (PatchInfoAnd rt p) Source # 
Commute p => Commute (PatchInfoAnd rt p) Source # 

Methods

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

PatchDebug p => PatchDebug (PatchInfoAnd rt p) Source # 

Methods

patchDebugDummy :: PatchInfoAnd rt p wX wY -> () Source #

PatchInspect p => PatchInspect (PatchInfoAnd rt p) Source # 

Methods

listTouchedFiles :: PatchInfoAnd rt p wX wY -> [FilePath] Source #

hunkMatches :: (ByteString -> Bool) -> PatchInfoAnd rt p wX wY -> Bool Source #

Invert p => Invert (PatchInfoAnd rt p) Source # 

Methods

invert :: PatchInfoAnd rt p wX wY -> PatchInfoAnd rt p wY wX Source #

Merge p => Merge (PatchInfoAnd rt p) Source # 

Methods

merge :: (PatchInfoAnd rt p :\/: PatchInfoAnd rt p) wX wY -> (PatchInfoAnd rt p :/\: PatchInfoAnd rt p) wX wY Source #

(ReadPatch p, PatchListFormat p, PrimPatchBase p, Effect p, FromPrim p, IsRepoType rt) => ReadPatch (PatchInfoAnd rt p) Source # 

Methods

readPatch' :: ParserM m => m (Sealed (PatchInfoAnd rt p wX)) Source #

Apply p => Apply (PatchInfoAnd rt p) Source # 

Associated Types

type ApplyState (PatchInfoAnd rt p :: * -> * -> *) :: (* -> *) -> * Source #

Methods

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

RepairToFL p => Repair (PatchInfoAnd rt p) Source # 

Methods

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

(Apply p, Conflict p, CommuteNoConflicts p, IsHunk p, PatchListFormat p, PrimPatchBase p, ShowPatch p, (~) ((* -> *) -> *) (ApplyState p) Tree) => ShowPatch (PatchInfoAnd rt p) Source # 

Methods

showNicely :: PatchInfoAnd rt p wX wY -> Doc Source #

showContextPatch :: (Monad m, ApplyMonad (ApplyState (PatchInfoAnd rt p)) m) => PatchInfoAnd rt p wX wY -> m Doc Source #

description :: PatchInfoAnd rt p wX wY -> Doc Source #

summary :: PatchInfoAnd rt p wX wY -> Doc Source #

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

thing :: PatchInfoAnd rt p wX wY -> String Source #

things :: PatchInfoAnd rt p wX wY -> String Source #

(PatchListFormat p, ShowPatchBasic p) => ShowPatchBasic (PatchInfoAnd rt p) Source # 

Methods

showPatch :: PatchInfoAnd rt p wX wY -> Doc Source #

IsHunk (PatchInfoAnd rt p) Source # 

Methods

isHunk :: PatchInfoAnd rt p wX wY -> Maybe (FileHunk wX wY) Source #

(Patchy p, (~) ((* -> *) -> *) (ApplyState p) Tree) => Patchy (PatchInfoAnd rt p) Source # 
PrimPatchBase p => PrimPatchBase (PatchInfoAnd rt p) Source # 

Associated Types

type PrimOf (PatchInfoAnd rt p :: * -> * -> *) :: * -> * -> * Source #

Effect p => Effect (PatchInfoAnd rt p) Source # 

Methods

effect :: PatchInfoAnd rt p wX wY -> FL (PrimOf (PatchInfoAnd rt p)) wX wY Source #

effectRL :: PatchInfoAnd rt p wX wY -> RL (PrimOf (PatchInfoAnd rt p)) wX wY Source #

Show2 p => Show1 (PatchInfoAnd rt p wX) Source # 

Methods

showDict1 :: ShowDict (PatchInfoAnd rt p wX wX) Source #

Show2 p => Show (PatchInfoAnd rt p wA wB) Source # 

Methods

showsPrec :: Int -> PatchInfoAnd rt p wA wB -> ShowS #

show :: PatchInfoAnd rt p wA wB -> String #

showList :: [PatchInfoAnd rt p wA wB] -> ShowS #

type ApplyState (PatchInfoAnd rt p) Source # 
type PrimOf (PatchInfoAnd rt p) Source # 
type PrimOf (PatchInfoAnd rt p) = PrimOf p

data WPatchInfo wA wB Source #

WPatchInfo wA wB represents the info of a patch, marked with the patch's witnesses.

Instances

MyEq WPatchInfo Source # 

Methods

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

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

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

compareWPatchInfo :: WPatchInfo wA wB -> WPatchInfo wC wD -> EqCheck (wA, wB) (wC, wD) Source #

piap :: PatchInfo -> WrappedNamed rt p wA wB -> PatchInfoAnd rt p wA wB Source #

piap i p creates a PatchInfoAnd containing p with info i.

n2pia :: WrappedNamed rt p wX wY -> PatchInfoAnd rt p wX wY Source #

n2pia creates a PatchInfoAnd representing a Named patch.

fmapFLPIAP :: (FL p wX wY -> FL q wX wY) -> ((RebaseTypeOf rt :~~: IsRebase) -> p :~: q) -> PatchInfoAnd rt p wX wY -> PatchInfoAnd rt q wX wY Source #

conscientiously :: (Doc -> Doc) -> PatchInfoAnd rt p wA wB -> WrappedNamed rt p wA wB Source #

conscientiously er hp tries to extract a patch from a PatchInfoAnd. If it fails, it applies the error handling function er to a description of the patch info component of hp.

hopefully :: PatchInfoAnd rt p wA wB -> WrappedNamed rt p wA wB Source #

hopefully hp tries to get a patch from a PatchInfoAnd value. If it fails, it outputs an error "failed to read patch: <description of the patch>". We get the description of the patch from the info part of hp

winfo :: PatchInfoAnd rt p wA wB -> WPatchInfo wA wB Source #

hopefullyM :: Monad m => PatchInfoAnd rt p wA wB -> m (WrappedNamed rt p wA wB) Source #

hopefullyM is a version of hopefully which calls fail in a monad instead of erroring.

createHashed :: String -> (String -> IO (Sealed (a wX))) -> IO (Sealed (Hopefully a wX)) Source #

extractHash :: PatchInfoAnd rt p wA wB -> Either (WrappedNamed rt p wA wB) String Source #

actually :: a wX wY -> Hopefully a wX wY Source #

patchDesc :: forall rt p wX wY. PatchInfoAnd rt p wX wY -> String Source #