| Stability | stable Portability: GHC |
|---|---|
| Safe Haskell | None |
Data.Hashable.Generic
Description
Documentation
gHashWithSalt :: (Generic a, GHashable (Rep a)) => Int -> a -> IntSource
GHC.Generics-based hashWithSalt implementation
This provides a generic hashWithSalt implementation for one type at a
time. If the type of the value gHashWithSalt is asked to hash
contains values of other types, those types have to provide
Hashable instances. This also means that recursive types can only
be used with gHashWithSalt if a Hashable instance has been defined
as well (see examples below).
The typical usage for gHashWithSalt is for reducing boilerplate code
when defining Hashable instances for ordinary algebraic
datatypes. See the code below for some simple usage examples:
{-# LANGUAGE DeriveGeneric #-}
import Data.Hashable
import Data.Hashable.Generic ( gHashWithSalt )
import GHC.Generics
-- simple record
data Foo = Foo AccountId Name Address
deriving Generic
type Address = [String]
type Name = String
newtype AccountId = AccountId Int
-- Note: Even though gHashWithSalt could be curried, we explicitly list
-- the parameters. If you don't do this, GHC will not inline the
-- definition of gHashWithSalt, and the performance will not match
-- a non-generic implementation. If you use this method, the generic
-- hashWithSalt will generate the exact same code as a hand-rolled
-- one.
--
-- Also, the INLINEABLE pragma is there to help hashable data
-- structures in other modules write more efficient generic hashable
-- instances too. This is the best way to get extremely performant,
-- fully generic hash functions.
instance Hashable AccountId
instance Hashable Foo where
hashWithSalt s x = gHashWithSalt s x
{-# INLINEABLE hashWithSalt #-}
-- recursive list-like type
data N = Z | S N deriving Generic
instance Hashable N where
hashWithSalt s x = gHashWithSalt s x
{-# INLINEABLE hashWithSalt #-}
-- parametric and recursive type
data Bar a = Bar0 | Bar1 a | Bar2 (Bar a)
deriving Generic
instance Hashable a => Hashable (Bar a) where
hashWithSalt s x = gHashWithSalt s x
{-# INLINEABLE hashWithSalt #-}
I intend for gHashWithSalt to be just as fast as a hand-rolled
implementation. Benchmarks are currently showing a 1.3x slowdown. Patches
to improve performance are welcome!
Note: The GHashable type-class showing up in the type-signature is
used internally and not exported on purpose.
class Hashable a where
The class of types that can be converted to a hash value.
Minimal implementation: hash or hashWithSalt.
Methods
Return a hash value for the argument.
The general contract of hash is:
- This integer need not remain consistent from one execution of an application to another execution of the same application.
- If two values are equal according to the
==method, then applying thehashmethod on each of the two values must produce the same integer result. - It is not required that if two values are unequal
according to the
==method, then applying thehashmethod on each of the two values must produce distinct integer results. However, the programmer should be aware that producing distinct integer results for unequal values may improve the performance of hashing-based data structures.
hashWithSalt :: Int -> a -> Int
Return a hash value for the argument, using the given salt.
This method can be used to compute different hash values for the same input by providing a different salt in each application of the method.
The contract for hashWithSalt is the same as for hash, with
the additional requirement that any instance that defines
hashWithSalt must make use of the salt in its implementation.
Instances