hashable-1.4.2.0: A class for types that can be converted to a hash value
Copyright(c) Milan Straka 2010
(c) Johan Tibell 2011
(c) Bryan O'Sullivan 2011 2012
LicenseBSD-3-Clause
Maintainerjohan.tibell@gmail.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Hashable

Description

This module defines a class, Hashable, for types that can be converted to a hash value. This class exists for the benefit of hashing-based data structures. The module provides instances for most standard types. Efficient instances for other types can be generated automatically and effortlessly using the generics support in GHC 7.4 and above.

The easiest way to get started is to use the hash function. Here is an example session with ghci.

ghci> import Data.Hashable
ghci> hash "foo"
60853164
Synopsis

Hashing and security

Applications that use hash-based data structures to store input from untrusted users can be susceptible to "hash DoS", a class of denial-of-service attack that uses deliberately chosen colliding inputs to force an application into unexpectedly behaving with quadratic time complexity.

At this time, the string hashing functions used in this library are susceptible to such attacks and users are recommended to either use a Map to store keys derived from untrusted input or to use a hash function (e.g. SipHash) that's resistant to such attacks. A future version of this library might ship with such hash functions.

Computing hash values

class Eq a => Hashable a where Source #

The class of types that can be converted to a hash value.

Minimal implementation: hashWithSalt.

Note: the hash is not guaranteed to be stable across library versions, operating systems or architectures. For stable hashing use named hashes: SHA256, CRC32 etc.

If you are looking for Hashable instance in time package, check time-compat

Minimal complete definition

Nothing

Methods

hashWithSalt :: Int -> a -> Int infixl 0 Source #

Return a hash value for the argument, using the given salt.

The general contract of hashWithSalt is:

  • If two values are equal according to the == method, then applying the hashWithSalt method on each of the two values must produce the same integer result if the same salt is used in each case.
  • It is not required that if two values are unequal according to the == method, then applying the hashWithSalt method 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.
  • 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. This implies that any instance that defines hashWithSalt must make use of the salt in its implementation.
  • hashWithSalt may return negative Int values.

default hashWithSalt :: (Generic a, GHashable Zero (Rep a)) => Int -> a -> Int Source #

hash :: a -> Int Source #

Like hashWithSalt, but no salt is used. The default implementation uses hashWithSalt with some default salt. Instances might want to implement this method to provide a more efficient implementation than the default implementation.

Instances

Instances details
Hashable SomeTypeRep Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Unique Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Version Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Void Source # 
Instance details

Defined in Data.Hashable.Class

Hashable IntPtr Source # 
Instance details

Defined in Data.Hashable.Class

Hashable WordPtr Source # 
Instance details

Defined in Data.Hashable.Class

Hashable ThreadId Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Fingerprint Source #

Since: 1.3.0.0

Instance details

Defined in Data.Hashable.Class

Hashable Int16 Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Int32 Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Int64 Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Int8 Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Word16 Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Word32 Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Word64 Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Word8 Source # 
Instance details

Defined in Data.Hashable.Class

Hashable ByteString Source # 
Instance details

Defined in Data.Hashable.Class

Hashable ByteString Source # 
Instance details

Defined in Data.Hashable.Class

Hashable ShortByteString Source # 
Instance details

Defined in Data.Hashable.Class

Hashable IntSet Source #

Since: 1.3.4.0

Instance details

Defined in Data.Hashable.Class

Hashable ByteArray Source #

This instance was available since 1.4.1.0 only for GHC-9.4+

Since: 1.4.2.0

Instance details

Defined in Data.Hashable.Class

Hashable BigNat Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Ordering Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Text Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Text Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Integer Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Natural Source # 
Instance details

Defined in Data.Hashable.Class

Hashable () Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> () -> Int Source #

hash :: () -> Int Source #

Hashable Bool Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Char Source # 
Instance details

Defined in Data.Hashable.Class

Hashable Double Source #

Note: prior to hashable-1.3.0.0, hash 0.0 /= hash (-0.0)

The hash of NaN is not well defined.

Since: 1.3.0.0

Instance details

Defined in Data.Hashable.Class

Hashable Float Source #

Note: prior to hashable-1.3.0.0, hash 0.0 /= hash (-0.0)

The hash of NaN is not well defined.

Since: 1.3.0.0

Instance details

Defined in Data.Hashable.Class

Hashable Int Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int -> Int Source #

hash :: Int -> Int Source #

Hashable Word Source # 
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable (Complex a) Source # 
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable (Identity a) Source # 
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable (First a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> First a -> Int Source #

hash :: First a -> Int Source #

Hashable a => Hashable (Last a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Last a -> Int Source #

hash :: Last a -> Int Source #

Hashable a => Hashable (Max a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Max a -> Int Source #

hash :: Max a -> Int Source #

Hashable a => Hashable (Min a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Min a -> Int Source #

hash :: Min a -> Int Source #

Hashable a => Hashable (WrappedMonoid a) Source # 
Instance details

Defined in Data.Hashable.Class

Hashable (FunPtr a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> FunPtr a -> Int Source #

hash :: FunPtr a -> Int Source #

Hashable (Ptr a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Ptr a -> Int Source #

hash :: Ptr a -> Int Source #

Hashable a => Hashable (Ratio a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Ratio a -> Int Source #

hash :: Ratio a -> Int Source #

Hashable (StableName a) Source # 
Instance details

Defined in Data.Hashable.Class

Hashable v => Hashable (IntMap v) Source #

Since: 1.3.4.0

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> IntMap v -> Int Source #

hash :: IntMap v -> Int Source #

Hashable v => Hashable (Seq v) Source #

Since: 1.3.4.0

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Seq v -> Int Source #

hash :: Seq v -> Int Source #

Hashable v => Hashable (Set v) Source #

Since: 1.3.4.0

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Set v -> Int Source #

hash :: Set v -> Int Source #

Hashable v => Hashable (Tree v) Source #

Since: 1.3.4.0

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Tree v -> Int Source #

hash :: Tree v -> Int Source #

Eq a => Hashable (Hashed a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Hashed a -> Int Source #

hash :: Hashed a -> Int Source #

Hashable a => Hashable (NonEmpty a) Source # 
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable (Maybe a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Maybe a -> Int Source #

hash :: Maybe a -> Int Source #

Hashable a => Hashable (a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a) -> Int Source #

hash :: (a) -> Int Source #

Hashable a => Hashable [a] Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> [a] -> Int Source #

hash :: [a] -> Int Source #

(Hashable a, Hashable b) => Hashable (Either a b) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Either a b -> Int Source #

hash :: Either a b -> Int Source #

Hashable (Fixed a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Fixed a -> Int Source #

hash :: Fixed a -> Int Source #

Hashable (Proxy a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int Source #

hash :: Proxy a -> Int Source #

Hashable a => Hashable (Arg a b) Source #

Note: Prior to hashable-1.3.0.0 the hash computation included the second argument of Arg which wasn't consistent with its Eq instance.

Since: 1.3.0.0

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Arg a b -> Int Source #

hash :: Arg a b -> Int Source #

Hashable (TypeRep a) Source # 
Instance details

Defined in Data.Hashable.Class

(Hashable k, Hashable v) => Hashable (Map k v) Source #

Since: 1.3.4.0

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Map k v -> Int Source #

hash :: Map k v -> Int Source #

(Hashable a1, Hashable a2) => Hashable (a1, a2) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2) -> Int Source #

hash :: (a1, a2) -> Int Source #

Hashable a => Hashable (Const a b) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Const a b -> Int Source #

hash :: Const a b -> Int Source #

(Hashable a1, Hashable a2, Hashable a3) => Hashable (a1, a2, a3) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3) -> Int Source #

hash :: (a1, a2, a3) -> Int Source #

(Hashable1 f, Hashable1 g, Hashable a) => Hashable (Product f g a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Product f g a -> Int Source #

hash :: Product f g a -> Int Source #

(Hashable1 f, Hashable1 g, Hashable a) => Hashable (Sum f g a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Sum f g a -> Int Source #

hash :: Sum f g a -> Int Source #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4) => Hashable (a1, a2, a3, a4) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4) -> Int Source #

hash :: (a1, a2, a3, a4) -> Int Source #

(Hashable1 f, Hashable1 g, Hashable a) => Hashable (Compose f g a) Source #

In general, hash (Compose x) ≠ hash x. However, hashWithSalt satisfies its variant of this equivalence.

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Compose f g a -> Int Source #

hash :: Compose f g a -> Int Source #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5) => Hashable (a1, a2, a3, a4, a5) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5) -> Int Source #

hash :: (a1, a2, a3, a4, a5) -> Int Source #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6) => Hashable (a1, a2, a3, a4, a5, a6) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5, a6) -> Int Source #

hash :: (a1, a2, a3, a4, a5, a6) -> Int Source #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6, Hashable a7) => Hashable (a1, a2, a3, a4, a5, a6, a7) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5, a6, a7) -> Int Source #

hash :: (a1, a2, a3, a4, a5, a6, a7) -> Int Source #

Creating new instances

There are two ways to create new instances: by deriving instances automatically using GHC's generic programming support or by writing instances manually.

Generic instances

The recommended way to make instances of Hashable for most types is to use the compiler's support for automatically generating default instances using GHC.Generics.

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics (Generic)
import Data.Hashable

data Foo a = Foo a String
             deriving (Eq, Generic)

instance Hashable a => Hashable (Foo a)

data Colour = Red | Green | Blue
              deriving Generic

instance Hashable Colour

If you omit a body for the instance declaration, GHC will generate a default instance that correctly and efficiently hashes every constructor and parameter.

The default implementations are provided by genericHashWithSalt and genericLiftHashWithSalt; those together with the generic type class GHashable and auxiliary functions are exported from the Data.Hashable.Generic module.

Understanding a compiler error

Suppose you intend to use the generic machinery to automatically generate a Hashable instance.

data Oops = Oops
     -- forgot to add "deriving Generic" here!

instance Hashable Oops

And imagine that, as in the example above, you forget to add a "deriving Generic" clause to your data type. At compile time, you will get an error message from GHC that begins roughly as follows:

No instance for (GHashable (Rep Oops))

This error can be confusing, as GHashable is not exported (it is an internal typeclass used by this library's generics machinery). The correct fix is simply to add the missing "deriving Generic".

Writing instances by hand

To maintain high quality hashes, new Hashable instances should be built using existing Hashable instances, combinators, and hash functions.

The functions below can be used when creating new instances of Hashable. For example, for many string-like types the hashWithSalt method can be defined in terms of either hashPtrWithSalt or hashByteArrayWithSalt. Here's how you could implement an instance for the ByteString data type, from the bytestring package:

import qualified Data.ByteString as B
import qualified Data.ByteString.Internal as B
import qualified Data.ByteString.Unsafe as B
import Data.Hashable
import Foreign.Ptr (castPtr)

instance Hashable B.ByteString where
    hashWithSalt salt bs = B.inlinePerformIO $
                           B.unsafeUseAsCStringLen bs $ \(p, len) ->
                           hashPtrWithSalt p (fromIntegral len) salt

Hashing contructors with multiple fields

Hash constructors with multiple fields by chaining hashWithSalt:

data Date = Date Int Int Int

instance Hashable Date where
    hashWithSalt s (Date yr mo dy) =
        s `hashWithSalt`
        yr `hashWithSalt`
        mo `hashWithSalt` dy

If you need to chain hashes together, use hashWithSalt and follow this recipe:

combineTwo h1 h2 = h1 `hashWithSalt` h2

Hashing types with multiple constructors

For a type with several value constructors, there are a few possible approaches to writing a Hashable instance.

If the type is an instance of Enum, the easiest path is to convert it to an Int, and use the existing Hashable instance for Int.

data Color = Red | Green | Blue
             deriving Enum

instance Hashable Color where
    hashWithSalt = hashUsing fromEnum

If the type's constructors accept parameters, it is important to distinguish the constructors. To distinguish the constructors, add a different integer to the hash computation of each constructor:

data Time = Days Int
          | Weeks Int
          | Months Int

instance Hashable Time where
    hashWithSalt s (Days n)   = s `hashWithSalt`
                                (0::Int) `hashWithSalt` n
    hashWithSalt s (Weeks n)  = s `hashWithSalt`
                                (1::Int) `hashWithSalt` n
    hashWithSalt s (Months n) = s `hashWithSalt`
                                (2::Int) `hashWithSalt` n

hashUsing Source #

Arguments

:: Hashable b 
=> (a -> b)

Transformation function.

-> Int

Salt.

-> a

Value to transform.

-> Int 

Transform a value into a Hashable value, then hash the transformed value using the given salt.

This is a useful shorthand in cases where a type can easily be mapped to another type that is already an instance of Hashable. Example:

data Foo = Foo | Bar
         deriving (Enum)

instance Hashable Foo where
    hashWithSalt = hashUsing fromEnum

Since: 1.2.0.0

hashPtr Source #

Arguments

:: Ptr a

pointer to the data to hash

-> Int

length, in bytes

-> IO Int

hash value

Compute a hash value for the content of this pointer.

hashPtrWithSalt Source #

Arguments

:: Ptr a

pointer to the data to hash

-> Int

length, in bytes

-> Salt

salt

-> IO Salt

hash value

Compute a hash value for the content of this pointer, using an initial salt.

This function can for example be used to hash non-contiguous segments of memory as if they were one contiguous segment, by using the output of one hash as the salt for the next.

hashByteArray Source #

Arguments

:: ByteArray#

data to hash

-> Int

offset, in bytes

-> Int

length, in bytes

-> Int

hash value

Compute a hash value for the content of this ByteArray#, beginning at the specified offset, using specified number of bytes.

hashByteArrayWithSalt Source #

Arguments

:: ByteArray#

data to hash

-> Int

offset, in bytes

-> Int

length, in bytes

-> Salt

salt

-> Salt

hash value

Compute a hash value for the content of this ByteArray#, using an initial salt.

This function can for example be used to hash non-contiguous segments of memory as if they were one contiguous segment, by using the output of one hash as the salt for the next.

Caching hashes

data Hashed a Source #

A hashable value along with the result of the hash function.

Instances

Instances details
Foldable Hashed Source # 
Instance details

Defined in Data.Hashable.Class

Methods

fold :: Monoid m => Hashed m -> m #

foldMap :: Monoid m => (a -> m) -> Hashed a -> m #

foldMap' :: Monoid m => (a -> m) -> Hashed a -> m #

foldr :: (a -> b -> b) -> b -> Hashed a -> b #

foldr' :: (a -> b -> b) -> b -> Hashed a -> b #

foldl :: (b -> a -> b) -> b -> Hashed a -> b #

foldl' :: (b -> a -> b) -> b -> Hashed a -> b #

foldr1 :: (a -> a -> a) -> Hashed a -> a #

foldl1 :: (a -> a -> a) -> Hashed a -> a #

toList :: Hashed a -> [a] #

null :: Hashed a -> Bool #

length :: Hashed a -> Int #

elem :: Eq a => a -> Hashed a -> Bool #

maximum :: Ord a => Hashed a -> a #

minimum :: Ord a => Hashed a -> a #

sum :: Num a => Hashed a -> a #

product :: Num a => Hashed a -> a #

Eq1 Hashed Source # 
Instance details

Defined in Data.Hashable.Class

Methods

liftEq :: (a -> b -> Bool) -> Hashed a -> Hashed b -> Bool #

Ord1 Hashed Source # 
Instance details

Defined in Data.Hashable.Class

Methods

liftCompare :: (a -> b -> Ordering) -> Hashed a -> Hashed b -> Ordering #

Show1 Hashed Source # 
Instance details

Defined in Data.Hashable.Class

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Hashed a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Hashed a] -> ShowS #

Hashable1 Hashed Source # 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Hashed a -> Int Source #

(IsString a, Hashable a) => IsString (Hashed a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

fromString :: String -> Hashed a #

Show a => Show (Hashed a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

showsPrec :: Int -> Hashed a -> ShowS #

show :: Hashed a -> String #

showList :: [Hashed a] -> ShowS #

NFData a => NFData (Hashed a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

rnf :: Hashed a -> () #

Eq a => Eq (Hashed a) Source #

Uses precomputed hash to detect inequality faster

Instance details

Defined in Data.Hashable.Class

Methods

(==) :: Hashed a -> Hashed a -> Bool #

(/=) :: Hashed a -> Hashed a -> Bool #

Ord a => Ord (Hashed a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

compare :: Hashed a -> Hashed a -> Ordering #

(<) :: Hashed a -> Hashed a -> Bool #

(<=) :: Hashed a -> Hashed a -> Bool #

(>) :: Hashed a -> Hashed a -> Bool #

(>=) :: Hashed a -> Hashed a -> Bool #

max :: Hashed a -> Hashed a -> Hashed a #

min :: Hashed a -> Hashed a -> Hashed a #

Eq a => Hashable (Hashed a) Source # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Hashed a -> Int Source #

hash :: Hashed a -> Int Source #

hashed :: Hashable a => a -> Hashed a Source #

Wrap a hashable value, caching the hash function result.

hashedHash :: Hashed a -> Int Source #

hash has Eq requirement.

Since: 1.4.0.0

unhashed :: Hashed a -> a Source #

Unwrap hashed value.

mapHashed :: Hashable b => (a -> b) -> Hashed a -> Hashed b Source #

Hashed cannot be Functor

traverseHashed :: (Hashable b, Functor f) => (a -> f b) -> Hashed a -> f (Hashed b) Source #