| Copyright | (c) Milan Straka 2010 (c) Johan Tibell 2011 (c) Bryan O'Sullivan 2011, 2012 | 
|---|---|
| License | BSD-style | 
| Maintainer | johan.tibell@gmail.com | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell98 | 
Data.Hashable
Contents
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.2 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
- class Hashable a where- hashWithSalt :: Int -> a -> Int
- hash :: a -> Int
 
- hashUsing :: Hashable b => (a -> b) -> Int -> a -> Int
- hashPtr :: Ptr a -> Int -> IO Int
- hashPtrWithSalt :: Ptr a -> Int -> Int -> IO Int
- hashByteArray :: ByteArray# -> Int -> Int -> Int
- hashByteArrayWithSalt :: ByteArray# -> Int -> Int -> Int -> Int
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
The class of types that can be converted to a hash value.
Minimal implementation: hashWithSalt.
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 thehashWithSaltmethod 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 thehashWithSaltmethod 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 hashWithSaltmust make use of the salt in its implementation.
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
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
Beginning with GHC 7.2, the recommended way to make instances of
 Hashable for most types is to use the compiler's support for
 automatically generating default instances.
{-# 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 ColourIf you omit a body for the instance declaration, GHC will generate a default instance that correctly and efficiently hashes every constructor and parameter.
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 OopsAnd imagine that, as in the example above, you forget to add a
 "deriving " clause to your data type. At compile time,
 you will get an error message from GHC that begins roughly as
 follows:Generic
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) saltHashing 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` dyIf 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 fromEnumIf 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` nTransform 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 fromEnumCompute a hash value for the content of this pointer.
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.
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.
Arguments
| :: ByteArray# | data to hash | 
| -> Int | offset, in bytes | 
| -> Int | length, in bytes | 
| -> Int | salt | 
| -> Int | 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.