large-hashable-0.1.0.0: Efficiently hash (large) Haskell values

Safe HaskellNone
LanguageHaskell2010

Data.LargeHashable

Description

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

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:

  1. 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 of LargeHashable does not require a instance of Eq. Using any sane algorithm the chance of a collision should be 1 / n where n is the number of different hashes possible.
  2. 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]

Minimal complete definition

Nothing

Methods

updateHash :: a -> LH () Source

Instances

LargeHashable Bool Source 
LargeHashable Char Source 
LargeHashable Double Source 
LargeHashable Float Source 
LargeHashable Int Source 
LargeHashable Int8 Source 
LargeHashable Int16 Source 
LargeHashable Int32 Source 
LargeHashable Int64 Source 
LargeHashable Integer Source 
LargeHashable Ordering Source 
LargeHashable Word Source 
LargeHashable Word8 Source 
LargeHashable Word16 Source 
LargeHashable Word32 Source 
LargeHashable Word64 Source 
LargeHashable () Source 
LargeHashable ByteString Source 
LargeHashable Scientific Source 
LargeHashable ByteString Source 
LargeHashable Text Source 
LargeHashable UTCTime Source 
LargeHashable Value Source 
LargeHashable Text Source 
LargeHashable Void Source 
LargeHashable CChar Source 
LargeHashable CUChar Source 
LargeHashable CShort Source 
LargeHashable CUShort Source 
LargeHashable CInt Source 
LargeHashable CUInt Source 
LargeHashable CLong Source 
LargeHashable CULong Source 
LargeHashable ShortByteString Source 
LargeHashable IntSet Source 
LargeHashable AbsoluteTime Source 
LargeHashable LocalTime Source 
LargeHashable ZonedTime Source 
LargeHashable TimeOfDay Source 
LargeHashable TimeZone Source 
LargeHashable NominalDiffTime Source 
LargeHashable Day Source 
LargeHashable UniversalTime Source 
LargeHashable DiffTime Source 
LargeHashable a => LargeHashable [a] Source 
(Integral a, LargeHashable a) => LargeHashable (Ratio a) Source 
LargeHashable a => LargeHashable (Maybe a) Source 
HasResolution a => LargeHashable (Fixed a) Source 
LargeHashable a => LargeHashable (IntMap a) Source 
LargeHashable a => LargeHashable (Set a) Source 
LargeHashable a => LargeHashable (Seq a) Source 
LargeHashable a => LargeHashable (HashSet a) Source 
LargeHashable a => LargeHashable (Vector a) Source 
(LargeHashable a, LargeHashable b) => LargeHashable (Either a b) Source 
(LargeHashable a, LargeHashable b) => LargeHashable (a, b) Source 
(LargeHashable k, LargeHashable v) => LargeHashable (HashMap k v) Source 
(LargeHashable k, LargeHashable a) => LargeHashable (Map k a) Source 
(LargeHashable a, LargeHashable b) => LargeHashable (Pair a b) Source 
(LargeHashable a, LargeHashable b, LargeHashable c) => LargeHashable (a, b, c) Source 
(LargeHashable a, LargeHashable b, LargeHashable c, LargeHashable d) => LargeHashable (a, b, c, d) Source 
(LargeHashable a, LargeHashable b, LargeHashable c, LargeHashable d, LargeHashable e) => LargeHashable (a, b, c, d, e) Source 

class LargeHashable' t where Source

Methods

updateHash' :: LargeHashable a => t a -> LH () Source

data LH a 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.

deriveLargeHashable :: Name -> Q [Dec] Source

Template Haskell function to automatically derive instances of LargeHashable. The derived instances first calls updateHash with an unique identifier number for every constructor, followed by updateHash calls for every field of the constructor (if existent). It also works for type families.

E. g. for the following code

data BlaFoo a = Foo
              | Bar Int a
              | Baz a a

$(deriveLargeHashable ''BlaFoo)
  

The following instance gets generated:

instance LargeHashable a_apg8 =>
        LargeHashable (BlaFoo a_apg8) where
 updateHash Foo = updateHash (0 :: Foreign.C.Types.CULong)
 updateHash (Bar a b)
   = (((updateHash (1 :: Foreign.C.Types.CULong)) >> (updateHash a))
      >> (updateHash b))
 updateHash (XY a b)
   = (((updateHash (2 :: Foreign.C.Types.CULong)) >> (updateHash a))
      >> (updateHash b))
   

deriveLargeHashableNoCtx :: Name -> Q [Dec] Source

Derive a LargeHashable instance with no constraints in the context of the instance.

deriveLargeHashableCtx Source

Arguments

:: 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

Arguments

:: 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.

newtype MD5Hash Source

Constructors

MD5Hash 

Fields

unMD5Hash :: Word128