| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Darcs.Util.ValidHash
Synopsis
- class (Eq h, IsSizeHash h) => ValidHash h where
- dirofValidHash :: h -> HashedDir
 - calcValidHash :: ByteString -> h
 
 - data InventoryHash
 - data PatchHash
 - data PristineHash
 - data HashedDir
 - encodeValidHash :: ValidHash h => h -> String
 - decodeValidHash :: ValidHash h => String -> Maybe h
 - parseValidHash :: ValidHash h => Parser h
 - getHash :: ValidHash h => h -> Hash
 - getSize :: ValidHash h => h -> Maybe Int
 - fromHash :: ValidHash h => Hash -> h
 - fromSizeAndHash :: ValidHash h => Int -> Hash -> h
 - checkHash :: ValidHash h => h -> ByteString -> Bool
 - okayHash :: String -> Bool
 
Documentation
class (Eq h, IsSizeHash h) => ValidHash h where Source #
External API for the various hash types.
Minimal complete definition
Methods
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 Methods  | |
| ValidHash PatchHash Source # | |
Defined in Darcs.Util.ValidHash Methods dirofValidHash :: PatchHash -> HashedDir Source # calcValidHash :: ByteString -> PatchHash Source #  | |
| ValidHash PristineHash Source # | |
Defined in Darcs.Util.ValidHash Methods  | |
data InventoryHash Source #
Instances
| Show InventoryHash Source # | |
Defined in Darcs.Util.ValidHash Methods showsPrec :: Int -> InventoryHash -> ShowS # show :: InventoryHash -> String # showList :: [InventoryHash] -> ShowS #  | |
| ValidHash InventoryHash Source # | |
Defined in Darcs.Util.ValidHash Methods  | |
| Eq InventoryHash Source # | |
Defined in Darcs.Util.ValidHash Methods (==) :: InventoryHash -> InventoryHash -> Bool # (/=) :: InventoryHash -> InventoryHash -> Bool #  | |
data PristineHash Source #
Instances
| Show PristineHash Source # | |
Defined in Darcs.Util.ValidHash Methods showsPrec :: Int -> PristineHash -> ShowS # show :: PristineHash -> String # showList :: [PristineHash] -> ShowS #  | |
| ValidHash PristineHash Source # | |
Defined in Darcs.Util.ValidHash Methods  | |
| Eq PristineHash Source # | |
Defined in Darcs.Util.ValidHash  | |
Semantically, this is the type of hashed objects. Git has a type tag inside the hashed file itself, whereas in Darcs the type is determined by the subdirectory.
Constructors
| HashedPristineDir | |
| HashedPatchesDir | |
| HashedInventoriesDir | 
encodeValidHash :: ValidHash h => h -> String Source #
parseValidHash :: ValidHash h => Parser h Source #