Skip to content

Commit

Permalink
Initial import of version 1.0.0
Browse files Browse the repository at this point in the history
  • Loading branch information
foxik committed Aug 15, 2010
0 parents commit 915d3d7
Show file tree
Hide file tree
Showing 6 changed files with 186 additions and 0 deletions.
4 changes: 4 additions & 0 deletions CHANGES
@@ -0,0 +1,4 @@
= Version 1.0.0, 2010-08-15 =
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
* Separating Hashable class to its own package
from hashmap 1.0.0.3.
113 changes: 113 additions & 0 deletions Data/Hashable.hs
@@ -0,0 +1,113 @@
{-# LANGUAGE ForeignFunctionInterface #-}

-----------------------------------------------------------------------------
-- |
-- Module : Data.Hash
-- Copyright : (c) Milan Straka 2010
-- License : BSD-style
-- Maintainer : fox@ucw.cz
-- Stability : provisional
-- Portability : portable
--
-- 'Hashable' class for hashable types, with instances for basic types. The only
-- function of this class is
--
-- @
-- 'hash' :: Hashable h => h -> Int
-- @
--
-- The 'hash' function should be as collision-free as possible, the probability
-- of @'hash' a == 'hash' b@ should ideally be 1 over the number of representable
-- values in an 'Int'.
--
-- Returning an 'Int' is a result of the 'Data.IntMap.IntMap' using 'Int' as
-- a key, as inserting the hash values to the 'Data.IntMap.IntMap' was the
-- purpose of creating this class.
-----------------------------------------------------------------------------

module Data.Hashable ( Hashable(..)
, combine
) where

import Data.Bits
import Data.Int
import Data.Word
import Data.List (foldl')
import qualified Data.ByteString as B
import qualified Data.ByteString.Internal as BInt
import qualified Data.ByteString.Unsafe as BInt
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Internal as BLInt
import Foreign.C

-- | The class containing a function 'hash' which computes the hash values of
-- given value.
class Hashable a where
-- | The computed 'hash' value should be as collision-free as possible, the
-- probability of @'hash' a == 'hash' b@ should ideally be 1 over the
-- number of representable values in an 'Int'.
hash :: a -> Int

-- | Combines two given hash values.
combine :: Int -> Int -> Int
combine h1 h2 = (h1 + h1 `shiftL` 5) `xor` h2

hashAndCombine :: Hashable h => Int -> h -> Int
hashAndCombine acc h = acc `combine` hash h

instance Hashable () where hash _ = 0

instance Hashable Bool where hash x = case x of { True -> 1; False -> 0 }

instance Hashable Int where hash = id
instance Hashable Int8 where hash = fromIntegral
instance Hashable Int16 where hash = fromIntegral
instance Hashable Int32 where hash = fromIntegral
instance Hashable Int64 where hash = fromIntegral

instance Hashable Word where hash = fromIntegral
instance Hashable Word8 where hash = fromIntegral
instance Hashable Word16 where hash = fromIntegral
instance Hashable Word32 where hash = fromIntegral
instance Hashable Word64 where hash = fromIntegral

instance Hashable Char where hash = fromEnum

instance Hashable a => Hashable (Maybe a) where
hash Nothing = 0
hash (Just a) = 42 `combine` hash a

instance (Hashable a1, Hashable a2) => Hashable (a1, a2) where
hash (a1, a2) = hash a1 `combine` hash a2

instance (Hashable a1, Hashable a2, Hashable a3) => Hashable (a1, a2, a3) where
hash (a1, a2, a3) = hash a1 `combine` hash a2 `combine` hash a3

instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4) => Hashable (a1, a2, a3, a4) where
hash (a1, a2, a3, a4) = hash a1 `combine` hash a2 `combine` hash a3 `combine` hash a4

instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5)
=> Hashable (a1, a2, a3, a4, a5) where
hash (a1, a2, a3, a4, a5) =
hash a1 `combine` hash a2 `combine` hash a3 `combine` hash a4 `combine` hash a5

instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6)
=> Hashable (a1, a2, a3, a4, a5, a6) where
hash (a1, a2, a3, a4, a5, a6) =
hash a1 `combine` hash a2 `combine` hash a3 `combine` hash a4 `combine` hash a5 `combine` hash a6

instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6, Hashable a7)
=> Hashable (a1, a2, a3, a4, a5, a6, a7) where
hash (a1, a2, a3, a4, a5, a6, a7) =
hash a1 `combine` hash a2 `combine` hash a3 `combine` hash a4 `combine` hash a5 `combine` hash a6 `combine` hash a7

instance Hashable a => Hashable [a] where
{-# SPECIALIZE instance Hashable [Char] #-}
hash = foldl' hashAndCombine 0

foreign import ccall unsafe hashByteString :: CString -> CInt -> IO CInt
instance Hashable B.ByteString where
hash bstr = fromIntegral $ BInt.inlinePerformIO $ BInt.unsafeUseAsCStringLen bstr $
\(str, len) -> hashByteString str (fromIntegral len)

instance Hashable BL.ByteString where hash = BLInt.foldlChunks hashAndCombine 0
30 changes: 30 additions & 0 deletions LICENSE
@@ -0,0 +1,30 @@
Copyright Milan Straka 2010

All rights reserved.

Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are met:

* Redistributions of source code must retain the above copyright
notice, this list of conditions and the following disclaimer.

* Redistributions in binary form must reproduce the above
copyright notice, this list of conditions and the following
disclaimer in the documentation and/or other materials provided
with the distribution.

* Neither the name of Milan Straka nor the names of other
contributors may be used to endorse or promote products derived
from this software without specific prior written permission.

THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
3 changes: 3 additions & 0 deletions Setup.hs
@@ -0,0 +1,3 @@
#!/usr/bin/env runhaskell
import Distribution.Simple
main = defaultMain
27 changes: 27 additions & 0 deletions hashable.cabal
@@ -0,0 +1,27 @@
Name: hashable
Version: 1.0.0
Synopsis: Class Hashable providing a hash method.
Description: This package provides a class 'Hashable', which contains
one method @'hash' :: 'Hashable' a => a -> 'Int'@, which
returns the hash of the given element.
.
The instances for various integral types, 'String' and 'ByteString'
are provided.
Homepage: http://fox.auryn.cz/darcs/hashable
License: BSD3
License-file: LICENSE
Author: Milan Straka
Maintainer: fox@ucw.cz
Stability: Provisional
Category: Data
Build-type: Simple
Cabal-version: >=1.2
Extra-source-files: CHANGES


Library
Exposed-modules: Data.Hashable
Build-depends: base >= 4.0 && < 5,
bytestring >= 0.9

C-sources: src/hashByteString.c
9 changes: 9 additions & 0 deletions src/hashByteString.c
@@ -0,0 +1,9 @@
int hashByteString(const char* str, int len) {
int hash = 0;

while (len--) {
hash = (hash * 33) ^ *str++;
}

return hash;
}

0 comments on commit 915d3d7

Please sign in to comment.