Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Hopefully a wX wY
- type PatchInfoAnd p = PatchInfoAndG (Named p)
- data PatchInfoAndG p wA wB
- piap :: PatchInfo -> p wA wB -> PatchInfoAndG p wA wB
- n2pia :: (Ident p, PatchId p ~ PatchInfo) => p wX wY -> PatchInfoAndG p wX wY
- patchInfoAndPatch :: PatchInfo -> Hopefully p wA wB -> PatchInfoAndG p wA wB
- fmapPIAP :: (p wX wY -> q wX wY) -> PatchInfoAndG p wX wY -> PatchInfoAndG q wX wY
- fmapFLPIAP :: (FL p wX wY -> FL q wX wY) -> PatchInfoAnd p wX wY -> PatchInfoAnd q wX wY
- hopefully :: PatchInfoAndG p wA wB -> p wA wB
- info :: PatchInfoAndG p wA wB -> PatchInfo
- hopefullyM :: PatchInfoAndG p wA wB -> Maybe (p wA wB)
- createHashed :: PatchHash -> (PatchHash -> IO (Sealed (a wX))) -> IO (Sealed (Hopefully a wX))
- extractHash :: PatchInfoAndG p wA wB -> Either (p wA wB) PatchHash
- actually :: a wX wY -> Hopefully a wX wY
- unavailable :: String -> Hopefully a wX wY
- patchDesc :: forall p wX wY. PatchInfoAnd 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.
type PatchInfoAnd p = PatchInfoAndG (Named p) Source #
data PatchInfoAndG 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
Instances
piap :: PatchInfo -> p wA wB -> PatchInfoAndG p wA wB Source #
creates a PatchInfoAnd containing p with info i.piap
i p
n2pia :: (Ident p, PatchId p ~ PatchInfo) => p wX wY -> PatchInfoAndG p wX wY Source #
n2pia
creates a PatchInfoAnd representing a Named
patch.
patchInfoAndPatch :: PatchInfo -> Hopefully p wA wB -> PatchInfoAndG p wA wB Source #
fmapPIAP :: (p wX wY -> q wX wY) -> PatchInfoAndG p wX wY -> PatchInfoAndG q wX wY Source #
fmapFLPIAP :: (FL p wX wY -> FL q wX wY) -> PatchInfoAnd p wX wY -> PatchInfoAnd q wX wY Source #
hopefully :: PatchInfoAndG p wA wB -> 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 :: PatchInfoAndG p wA wB -> PatchInfo Source #
hopefullyM :: PatchInfoAndG p wA wB -> Maybe (p wA wB) Source #
createHashed :: PatchHash -> (PatchHash -> IO (Sealed (a wX))) -> IO (Sealed (Hopefully a wX)) Source #
extractHash :: PatchInfoAndG p wA wB -> Either (p wA wB) PatchHash Source #
unavailable :: String -> Hopefully a wX wY Source #
patchDesc :: forall p wX wY. PatchInfoAnd p wX wY -> String Source #