Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Inventory = Inventory {}
- type HeadInventory = (PristineHash, Inventory)
- type InventoryEntry = (PatchInfo, PatchHash)
- class (Eq h, IsSizeHash h) => ValidHash h where
- dirofValidHash :: h -> HashedDir
- calcValidHash :: ByteString -> h
- decodeValidHash :: ValidHash h => String -> Maybe h
- encodeValidHash :: ValidHash h => h -> String
- data InventoryHash
- data PatchHash
- data PristineHash
- inventoryPatchNames :: Inventory -> [String]
- parseInventory :: ByteString -> Either String Inventory
- parseHeadInventory :: ByteString -> Either String HeadInventory
- showInventory :: Inventory -> Doc
- showInventoryPatches :: [InventoryEntry] -> Doc
- showInventoryEntry :: InventoryEntry -> Doc
- emptyInventory :: Inventory
- pokePristineHash :: PristineHash -> ByteString -> Doc
- peekPristineHash :: ByteString -> PristineHash
- skipPristineHash :: ByteString -> ByteString
- pristineName :: ByteString
- prop_inventoryParseShow :: Inventory -> Bool
- prop_peekPokePristineHash :: (PristineHash, ByteString) -> Bool
- prop_skipPokePristineHash :: (PristineHash, ByteString) -> Bool
Documentation
type HeadInventory = (PristineHash, Inventory) Source #
type InventoryEntry = (PatchInfo, PatchHash) Source #
class (Eq h, IsSizeHash h) => ValidHash h where Source #
External API for the various hash types.
dirofValidHash :: h -> HashedDir Source #
The HashedDir
belonging to this type of hash
calcValidHash :: ByteString -> h Source #
Compute hash from file content.
Instances
ValidHash InventoryHash Source # | |
Defined in Darcs.Util.ValidHash | |
ValidHash PatchHash Source # | |
Defined in Darcs.Util.ValidHash dirofValidHash :: PatchHash -> HashedDir Source # calcValidHash :: ByteString -> PatchHash Source # | |
ValidHash PristineHash Source # | |
Defined in Darcs.Util.ValidHash |
encodeValidHash :: ValidHash h => h -> String Source #
data InventoryHash Source #
Instances
Show InventoryHash Source # | |
Defined in Darcs.Util.ValidHash showsPrec :: Int -> InventoryHash -> ShowS # show :: InventoryHash -> String # showList :: [InventoryHash] -> ShowS # | |
ValidHash InventoryHash Source # | |
Defined in Darcs.Util.ValidHash | |
Eq InventoryHash Source # | |
Defined in Darcs.Util.ValidHash (==) :: InventoryHash -> InventoryHash -> Bool # (/=) :: InventoryHash -> InventoryHash -> Bool # |
data PristineHash Source #
Instances
Show PristineHash Source # | |
Defined in Darcs.Util.ValidHash showsPrec :: Int -> PristineHash -> ShowS # show :: PristineHash -> String # showList :: [PristineHash] -> ShowS # | |
ValidHash PristineHash Source # | |
Defined in Darcs.Util.ValidHash | |
Eq PristineHash Source # | |
Defined in Darcs.Util.ValidHash (==) :: PristineHash -> PristineHash -> Bool # (/=) :: PristineHash -> PristineHash -> Bool # |
inventoryPatchNames :: Inventory -> [String] Source #
showInventory :: Inventory -> Doc Source #
showInventoryPatches :: [InventoryEntry] -> Doc Source #
pokePristineHash :: PristineHash -> ByteString -> Doc Source #
Replace the pristine hash at the start of a raw, unparsed HeadInventory
or add it if none is present.
skipPristineHash :: ByteString -> ByteString Source #
skipPristineHash drops the 'pristine: HASH' prefix line, if present.