large-hashable-0.1.0.4: 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]

Methods

updateHash :: a -> LH () Source #

updateHash :: (GenericLargeHashable (Rep a), Generic a) => a -> LH () Source #

Instances

LargeHashable Bool Source # 

Methods

updateHash :: Bool -> LH () Source #

LargeHashable Char Source # 

Methods

updateHash :: Char -> LH () Source #

LargeHashable Double Source # 

Methods

updateHash :: Double -> LH () Source #

LargeHashable Float Source # 

Methods

updateHash :: Float -> LH () Source #

LargeHashable Int Source # 

Methods

updateHash :: Int -> LH () Source #

LargeHashable Int8 Source # 

Methods

updateHash :: Int8 -> LH () Source #

LargeHashable Int16 Source # 

Methods

updateHash :: Int16 -> LH () Source #

LargeHashable Int32 Source # 

Methods

updateHash :: Int32 -> LH () Source #

LargeHashable Int64 Source # 

Methods

updateHash :: Int64 -> LH () Source #

LargeHashable Integer Source # 

Methods

updateHash :: Integer -> LH () Source #

LargeHashable Ordering Source # 

Methods

updateHash :: Ordering -> LH () Source #

LargeHashable Word Source # 

Methods

updateHash :: Word -> LH () Source #

LargeHashable Word8 Source # 

Methods

updateHash :: Word8 -> LH () Source #

LargeHashable Word16 Source # 

Methods

updateHash :: Word16 -> LH () Source #

LargeHashable Word32 Source # 

Methods

updateHash :: Word32 -> LH () Source #

LargeHashable Word64 Source # 

Methods

updateHash :: Word64 -> LH () Source #

LargeHashable () Source # 

Methods

updateHash :: () -> LH () Source #

LargeHashable ByteString Source # 

Methods

updateHash :: ByteString -> LH () Source #

LargeHashable ByteString Source # 

Methods

updateHash :: ByteString -> LH () Source #

LargeHashable Scientific Source # 

Methods

updateHash :: Scientific -> LH () Source #

LargeHashable Text Source # 

Methods

updateHash :: Text -> LH () Source #

LargeHashable UTCTime Source # 

Methods

updateHash :: UTCTime -> LH () Source #

LargeHashable Value Source # 

Methods

updateHash :: Value -> LH () Source #

LargeHashable Text Source # 

Methods

updateHash :: Text -> LH () Source #

LargeHashable Void Source # 

Methods

updateHash :: Void -> LH () Source #

LargeHashable CChar Source # 

Methods

updateHash :: CChar -> LH () Source #

LargeHashable CUChar Source # 

Methods

updateHash :: CUChar -> LH () Source #

LargeHashable CShort Source # 

Methods

updateHash :: CShort -> LH () Source #

LargeHashable CUShort Source # 

Methods

updateHash :: CUShort -> LH () Source #

LargeHashable CInt Source # 

Methods

updateHash :: CInt -> LH () Source #

LargeHashable CUInt Source # 

Methods

updateHash :: CUInt -> LH () Source #

LargeHashable CLong Source # 

Methods

updateHash :: CLong -> LH () Source #

LargeHashable CULong Source # 

Methods

updateHash :: CULong -> LH () Source #

LargeHashable ShortByteString Source # 
LargeHashable IntSet Source # 

Methods

updateHash :: IntSet -> LH () Source #

LargeHashable AbsoluteTime Source # 
LargeHashable LocalTime Source # 

Methods

updateHash :: LocalTime -> LH () Source #

LargeHashable ZonedTime Source # 

Methods

updateHash :: ZonedTime -> LH () Source #

LargeHashable TimeOfDay Source # 

Methods

updateHash :: TimeOfDay -> LH () Source #

LargeHashable TimeZone Source # 

Methods

updateHash :: TimeZone -> LH () Source #

LargeHashable NominalDiffTime Source # 
LargeHashable Day Source # 

Methods

updateHash :: Day -> LH () Source #

LargeHashable UniversalTime Source # 
LargeHashable DiffTime Source # 

Methods

updateHash :: DiffTime -> LH () Source #

LargeHashable a => LargeHashable [a] Source # 

Methods

updateHash :: [a] -> LH () Source #

LargeHashable a => LargeHashable (Maybe a) Source # 

Methods

updateHash :: Maybe a -> LH () Source #

(Integral a, LargeHashable a) => LargeHashable (Ratio a) Source # 

Methods

updateHash :: Ratio a -> LH () Source #

HasResolution a => LargeHashable (Fixed a) Source # 

Methods

updateHash :: Fixed a -> LH () Source #

LargeHashable a => LargeHashable (IntMap a) Source # 

Methods

updateHash :: IntMap a -> LH () Source #

LargeHashable a => LargeHashable (Seq a) Source # 

Methods

updateHash :: Seq a -> LH () Source #

LargeHashable a => LargeHashable (Set a) Source # 

Methods

updateHash :: Set a -> LH () Source #

LargeHashable a => LargeHashable (HashSet a) Source # 

Methods

updateHash :: HashSet a -> LH () Source #

LargeHashable a => LargeHashable (Vector a) Source # 

Methods

updateHash :: Vector a -> LH () Source #

(LargeHashable a, LargeHashable b) => LargeHashable (Either a b) Source # 

Methods

updateHash :: Either a b -> LH () Source #

(LargeHashable a, LargeHashable b) => LargeHashable (a, b) Source # 

Methods

updateHash :: (a, b) -> LH () Source #

(LargeHashable k, LargeHashable v) => LargeHashable (HashMap k v) Source # 

Methods

updateHash :: HashMap k v -> LH () Source #

(LargeHashable k, LargeHashable a) => LargeHashable (Map k a) Source # 

Methods

updateHash :: Map k a -> LH () Source #

(LargeHashable a, LargeHashable b) => LargeHashable (Pair a b) Source # 

Methods

updateHash :: Pair a b -> LH () Source #

(LargeHashable a, LargeHashable b, LargeHashable c) => LargeHashable (a, b, c) Source # 

Methods

updateHash :: (a, b, c) -> LH () Source #

(LargeHashable a, LargeHashable b, LargeHashable c, LargeHashable d) => LargeHashable (a, b, c, d) Source # 

Methods

updateHash :: (a, b, c, d) -> LH () Source #

(LargeHashable a, LargeHashable b, LargeHashable c, LargeHashable d, LargeHashable e) => LargeHashable (a, b, c, d, e) Source # 

Methods

updateHash :: (a, b, c, d, e) -> LH () Source #

class LargeHashable' t where Source #

Minimal complete definition

updateHash'

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.

Instances

Monad LH Source # 

Methods

(>>=) :: LH a -> (a -> LH b) -> LH b #

(>>) :: LH a -> LH b -> LH b #

return :: a -> LH a #

fail :: String -> LH a #

Functor LH Source # 

Methods

fmap :: (a -> b) -> LH a -> LH b #

(<$) :: a -> LH b -> LH a #

Applicative LH Source # 

Methods

pure :: a -> LH a #

(<*>) :: LH (a -> b) -> LH a -> LH b #

(*>) :: LH a -> LH b -> LH b #

(<*) :: LH a -> LH b -> LH a #

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.

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.