- data Hopefully a
- data PatchInfoAnd p
- data WPatchInfo
- unWPatchInfo :: WPatchInfo -> PatchInfo
- compareWPatchInfo :: WPatchInfo -> WPatchInfo -> EqCheck
- piap :: PatchInfo -> Named p -> PatchInfoAnd p
- n2pia :: Named p -> PatchInfoAnd p
- patchInfoAndPatch :: PatchInfo -> Hopefully (Named p) -> PatchInfoAnd p
- conscientiously :: (Doc -> Doc) -> PatchInfoAnd p -> Named p
- hopefully :: PatchInfoAnd p -> Named p
- info :: PatchInfoAnd p -> PatchInfo
- winfo :: PatchInfoAnd p -> WPatchInfo
- hopefullyM :: Monad m => PatchInfoAnd p -> m (Named p)
- createHashed :: String -> (String -> IO (Sealed a)) -> IO (Sealed (Hopefully a))
- extractHash :: PatchInfoAnd p -> Either (Named p) String
- actually :: a -> Hopefully a
- unavailable :: String -> Hopefully a
- patchDesc :: forall p. PatchInfoAnd p -> String
Documentation
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.
data PatchInfoAnd p Source
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.
PatchInfoAnd
p
MyEq p => MyEq (PatchInfoAnd p) | |
Invert p => Invert (PatchInfoAnd p) | |
ReadPatch p => ReadPatch (PatchInfoAnd p) | |
(Conflict p, Effect p, ShowPatch p) => ShowPatch (PatchInfoAnd p) | |
Commute p => Commute (PatchInfoAnd p) | |
Apply p => Apply (PatchInfoAnd p) | |
RepoPatch p => Patchy (PatchInfoAnd p) | |
Effect p => Effect (PatchInfoAnd p) | |
Conflict p => Conflict (PatchInfoAnd p) |
data WPatchInfo Source
represents the info of a patch, marked with
the patch's witnesses.
WPatchInfo
piap :: PatchInfo -> Named p -> PatchInfoAnd pSource
creates a PatchInfoAnd containing p with info i.
piap
i p
n2pia :: Named p -> PatchInfoAnd pSource
n2pia
creates a PatchInfoAnd representing a Named
patch.
patchInfoAndPatch :: PatchInfo -> Hopefully (Named p) -> PatchInfoAnd pSource
conscientiously :: (Doc -> Doc) -> PatchInfoAnd p -> Named pSource
tries to extract a patch from a conscientiously
er hpPatchInfoAnd
.
If it fails, it applies the error handling function er
to a description
of the patch info component of hp
.
hopefully :: PatchInfoAnd p -> Named pSource
tries to get a patch from a hopefully
hpPatchInfoAnd
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
info :: PatchInfoAnd p -> PatchInfoSource
winfo :: PatchInfoAnd p -> WPatchInfoSource
hopefullyM :: Monad m => PatchInfoAnd p -> m (Named p)Source
hopefullyM
is a version of hopefully
which calls fail
in a
monad instead of erroring.
extractHash :: PatchInfoAnd p -> Either (Named p) StringSource
unavailable :: String -> Hopefully aSource
patchDesc :: forall p. PatchInfoAnd p -> StringSource