darcs-2.10.1: 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) 

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) 

data PatchInfoAnd 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 (Named p) wA wB) 

data WPatchInfo wA wB Source

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

Instances

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

piap :: PatchInfo -> Named p wA wB -> PatchInfoAnd p wA wB Source

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

n2pia :: Named p wX wY -> PatchInfoAnd p wX wY Source

n2pia creates a PatchInfoAnd representing a Named patch.

fmapPIAP :: (forall wA wB. p wA wB -> q wA wB) -> PatchInfoAnd p wX wY -> PatchInfoAnd q wX wY Source

fmapFLPIAP :: (FL p wX wY -> FL q wX wY) -> PatchInfoAnd p wX wY -> PatchInfoAnd q wX wY Source

conscientiously :: (Doc -> Doc) -> PatchInfoAnd p wA wB -> Named 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 p wA wB -> Named 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 p wA wB -> WPatchInfo wA wB Source

hopefullyM :: Monad m => PatchInfoAnd p wA wB -> m (Named 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

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

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