Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Hopefully a wX wY
- = Hopefully (SimpleHopefully a wX wY)
- | Hashed String (SimpleHopefully a wX wY)
- data SimpleHopefully a wX wY
- = Actually (a wX wY)
- | Unavailable String
- data PatchInfoAnd rt p wA wB = PIAP !PatchInfo (Hopefully (WrappedNamed rt p) wA wB)
- data WPatchInfo wA wB
- unWPatchInfo :: WPatchInfo wA wB -> PatchInfo
- compareWPatchInfo :: WPatchInfo wA wB -> WPatchInfo wC wD -> EqCheck (wA, wB) (wC, wD)
- piap :: PatchInfo -> WrappedNamed rt p wA wB -> PatchInfoAnd rt p wA wB
- n2pia :: WrappedNamed rt p wX wY -> PatchInfoAnd rt p wX wY
- patchInfoAndPatch :: PatchInfo -> Hopefully (WrappedNamed rt p) wA wB -> PatchInfoAnd rt p wA wB
- fmapFLPIAP :: (FL p wX wY -> FL q wX wY) -> ((RebaseTypeOf rt :~~: IsRebase) -> p :~: q) -> PatchInfoAnd rt p wX wY -> PatchInfoAnd rt q wX wY
- generaliseRepoTypePIAP :: PatchInfoAnd (RepoType NoRebase) p wA wB -> PatchInfoAnd rt p wA wB
- conscientiously :: (Doc -> Doc) -> PatchInfoAnd rt p wA wB -> WrappedNamed rt p wA wB
- hopefully :: PatchInfoAnd rt p wA wB -> WrappedNamed rt p wA wB
- info :: PatchInfoAnd rt p wA wB -> PatchInfo
- winfo :: PatchInfoAnd rt p wA wB -> WPatchInfo wA wB
- hopefullyM :: Monad m => PatchInfoAnd rt p wA wB -> m (WrappedNamed rt p wA wB)
- createHashed :: String -> (String -> IO (Sealed (a wX))) -> IO (Sealed (Hopefully a wX))
- extractHash :: PatchInfoAnd rt p wA wB -> Either (WrappedNamed rt p wA wB) String
- actually :: a wX wY -> Hopefully a wX wY
- unavailable :: String -> Hopefully a wX wY
- patchDesc :: forall rt p wX wY. PatchInfoAnd rt p wX wY -> String
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.
Hopefully (SimpleHopefully a wX wY) | |
Hashed String (SimpleHopefully 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
.
Actually (a wX wY) | |
Unavailable String |
Show (a wX wY) => Show (SimpleHopefully a wX wY) Source # | |
data PatchInfoAnd rt p wA wB 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 wA wB
PIAP !PatchInfo (Hopefully (WrappedNamed rt p) wA wB) |
data WPatchInfo wA wB Source #
represents the info of a patch, marked with
the patch's witnesses.WPatchInfo
wA wB
unWPatchInfo :: WPatchInfo wA wB -> PatchInfo 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 #
creates a PatchInfoAnd containing p with info i.piap
i p
n2pia :: WrappedNamed rt p wX wY -> PatchInfoAnd rt p wX wY Source #
n2pia
creates a PatchInfoAnd representing a Named
patch.
patchInfoAndPatch :: PatchInfo -> Hopefully (WrappedNamed rt p) wA wB -> PatchInfoAnd rt p wA wB Source #
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 #
generaliseRepoTypePIAP :: PatchInfoAnd (RepoType NoRebase) p wA wB -> PatchInfoAnd rt p wA wB Source #
conscientiously :: (Doc -> Doc) -> PatchInfoAnd rt p wA wB -> WrappedNamed rt p wA wB Source #
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 rt p wA wB -> WrappedNamed rt p wA wB Source #
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 rt p wA wB -> PatchInfo Source #
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.
extractHash :: PatchInfoAnd rt p wA wB -> Either (WrappedNamed rt p wA wB) String Source #
unavailable :: String -> Hopefully a wX wY Source #
patchDesc :: forall rt p wX wY. PatchInfoAnd rt p wX wY -> String Source #