Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This is the top-level module of LargeHashable, a library for efficiently hashing any Haskell data type using a hash algorithm like MD5, SHA256 etc.
Normal users shoud import this module.
Synopsis
- class LargeHashable a where
- updateHash :: a -> LH ()
- updateHashStable :: a -> LH ()
- class LargeHashable' t where
- updateHash' :: LargeHashable a => t a -> LH ()
- updateHashStable' :: LargeHashable a => t a -> LH ()
- data LH a
- data HashAlgorithm h
- largeHash :: LargeHashable a => HashAlgorithm h -> a -> h
- largeHashStable :: LargeHashable a => HashAlgorithm h -> a -> h
- deriveLargeHashable :: Name -> Q [Dec]
- deriveLargeHashableNoCtx :: Name -> Q [Dec]
- deriveLargeHashableCtx :: Name -> ([TypeQ] -> [PredQ]) -> Q [Dec]
- deriveLargeHashableCustomCtx :: Name -> ([TypeQ] -> [PredQ] -> [PredQ]) -> Q [Dec]
- newtype MD5Hash = MD5Hash {}
- md5HashAlgorithm :: HashAlgorithm MD5Hash
- runMD5 :: LH () -> MD5Hash
- module Data.LargeHashable.LargeWord
Documentation
class LargeHashable a where Source #
A type class for computing hashes (i.e. MD5, SHA256, ...) from haskell values.
The laws of this typeclass are the following:
- If two values are equal
according to
==
, then the finally computed hashes must also be equal according to==
. However it is not required that the hashes of inequal values have to be inequal. Also note that an instance ofLargeHashable
does not require a instance ofEq
. Using any sane algorithm the chance of a collision should be 1 / n where n is the number of different hashes possible. - If two values are inequal
according to
==
, then the probability of a hash collision is 1/n, where n is the number of possible hashes produced by the underlying hash algorithm.
A rule of thumb: hash all information that you would also need for serializing/deserializing values of your datatype. For instance, when hashing lists, you would not only hash the list elements but also the length of the list. Consider the following datatype
data Foo = Foo [Int] [Int]
We now write an instance for LargeHashable like this
instance LargeHashable Foo where updateHash (Foo l1 l2) = updateHash l1 >> updateHash l2
If we did not hash the length of a list, then the following two values
of Foo
would produce identical hashes:
Foo [1,2,3] [] Foo [1] [2,3]
Nothing
updateHash :: a -> LH () Source #
updateHashStable :: a -> LH () Source #
Instances
class LargeHashable' t where Source #
updateHash' :: LargeHashable a => t a -> LH () Source #
updateHashStable' :: LargeHashable a => t a -> LH () Source #
The LH
monad (LH
stands for "large hash") is used in the definition of
hashing functions for arbitrary data types.
data HashAlgorithm h Source #
The interface for a hashing algorithm. The interface contains a simple run function, which is used to update the hash with all values needed, and the outputs the resulting hash.
largeHash :: LargeHashable a => HashAlgorithm h -> a -> h Source #
largeHash
is the central function of this package.
For a given value it computes a Hash
using the given
HashAlgorithm
. The library tries to keep the
hash values for LargeHashable
instances provided by
library stable across releases, but there is no guarantee.
See @largeHashStable&
largeHashStable :: LargeHashable a => HashAlgorithm h -> a -> h Source #
largeHashStable
is similar to largeHash
, but the hash
value is guaranteed to remain stable across releases,
even if this causes performance to degrade.
deriveLargeHashableNoCtx :: Name -> Q [Dec] Source #
Derive a LargeHashable
instance with no constraints in the context of the instance.
deriveLargeHashableCtx Source #
:: Name | |
-> ([TypeQ] -> [PredQ]) | Function mapping the type variables in the instance head to the additional constraints |
-> Q [Dec] |
Derive a LargeHashable
instance with extra constraints in the
context of the instance.
deriveLargeHashableCustomCtx Source #
:: Name | |
-> ([TypeQ] -> [PredQ] -> [PredQ]) | Function mapping the type variables in the instance head and the constraints that would normally be generated to the constraints that should be generated. |
-> Q [Dec] |
Derive a LargeHashable
instance with a completely custom instance context.
module Data.LargeHashable.LargeWord