File: Hashable.hs

package info (click to toggle)
haskell-hashable 1.2.1.0-5
  • links: PTS, VCS
  • area: main
  • in suites: jessie, jessie-kfreebsd
  • size: 196 kB
  • ctags: 39
  • sloc: haskell: 975; ansic: 456; makefile: 3
file content (205 lines) | stat: -rw-r--r-- 6,626 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
{-# LANGUAGE CPP #-}
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif

------------------------------------------------------------------------
-- |
-- Module      :  Data.Hashable
-- 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
--
-- 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

module Data.Hashable
    (
      -- * Hashing and security
      -- $security

      -- * Computing hash values
      Hashable(..)

      -- * 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
      -- $generics

      -- *** Understanding a compiler error
      -- $generic_err

      -- ** Writing instances by hand
      -- $blocks

      -- *** Hashing contructors with multiple fields
      -- $multiple-fields

      -- *** Hashing types with multiple constructors
      -- $multiple-ctors

    , hashUsing
    , hashPtr
    , hashPtrWithSalt
#if defined(__GLASGOW_HASKELL__)
    , hashByteArray
    , hashByteArrayWithSalt
#endif
    ) where

import Data.Hashable.Class
#ifdef GENERICS
import Data.Hashable.Generic ()
#endif

-- $security
-- #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 'Data.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.

-- $generics
--
-- 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 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.

-- $generic_err
--
-- 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'@\".

-- $blocks
--
-- 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 'B.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

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

-- $multiple-ctors
--
-- 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