Skip to content

Commit

Permalink
Add instance for TypeRep
Browse files Browse the repository at this point in the history
  • Loading branch information
tibbe committed Dec 1, 2011
1 parent 63b3748 commit 2b0d2fe
Showing 1 changed file with 24 additions and 0 deletions.
24 changes: 24 additions & 0 deletions Data/Hashable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -80,6 +80,12 @@ import Control.Concurrent (ThreadId)
import System.Mem.StableName
#endif

import Data.Typeable
#if __GLASGOW_HASKELL__ >= 702
import GHC.Fingerprint.Type(Fingerprint(..))
import Data.Typeable.Internal(TypeRep(..))
#endif

#include "MachDeps.h"

infixl 0 `combine`, `hashWithSalt`
Expand Down Expand Up @@ -289,6 +295,24 @@ instance Hashable LT.Text where
hash = hashWithSalt stringSalt
hashWithSalt = LT.foldlChunks hashWithSalt


-- | Compute the hash of a TypeRep, in various GHC versions we can do this quickly.
hashTypeRep :: TypeRep -> Int
{-# INLINE hashTypeRep #-}
#if __GLASGOW_HASKELL__ >= 702
-- Fingerprint is just the MD5, so taking any Int from it is fine
hashTypeRep (TypeRep (Fingerprint x _) _ _) = fromIntegral x
#elif __GLASGOW_HASKELL__ >= 606
hashTypeRep = B.inlinePerformIO . typeRepKey
#else
hashTypeRep = hash . show
#endif

instance Hashable TypeRep where
hash = hashTypeRep
{-# INLINE hash #-}


------------------------------------------------------------------------
-- * Creating new instances

Expand Down

0 comments on commit 2b0d2fe

Please sign in to comment.