add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / Data / Unique.hs
1 {-# LANGUAGE CPP #-}
2
3 #ifdef __GLASGOW_HASKELL__
4 {-# LANGUAGE MagicHash, DeriveDataTypeable #-}
5 #endif
6
7 -----------------------------------------------------------------------------
8 -- |
9 -- Module      :  Data.Unique
10 -- Copyright   :  (c) The University of Glasgow 2001
11 -- License     :  BSD-style (see the file libraries/base/LICENSE)
12 -- 
13 -- Maintainer  :  libraries@haskell.org
14 -- Stability   :  experimental
15 -- Portability :  non-portable
16 --
17 -- An abstract interface to a unique symbol generator.
18 --
19 -----------------------------------------------------------------------------
20
21 module Data.Unique (
22    -- * Unique objects
23    Unique,              -- instance (Eq, Ord)
24    newUnique,           -- :: IO Unique
25    hashUnique           -- :: Unique -> Int
26  ) where
27
28 import Prelude
29
30 import System.IO.Unsafe (unsafePerformIO)
31
32 #ifdef __GLASGOW_HASKELL__
33 import GHC.Base
34 import GHC.Num
35 import GHC.Conc
36 import Data.Typeable
37 #endif
38
39 -- | An abstract unique object.  Objects of type 'Unique' may be
40 -- compared for equality and ordering and hashed into 'Int'.
41 newtype Unique = Unique Integer deriving (Eq,Ord
42 #ifdef __GLASGOW_HASKELL__
43    ,Typeable
44 #endif
45    )
46
47 uniqSource :: TVar Integer
48 uniqSource = unsafePerformIO (newTVarIO 0)
49 {-# NOINLINE uniqSource #-}
50
51 -- | Creates a new object of type 'Unique'.  The value returned will
52 -- not compare equal to any other value of type 'Unique' returned by
53 -- previous calls to 'newUnique'.  There is no limit on the number of
54 -- times 'newUnique' may be called.
55 newUnique :: IO Unique
56 newUnique = atomically $ do
57   val <- readTVar uniqSource
58   let next = val+1
59   writeTVar uniqSource $! next
60   return (Unique next)
61
62 -- SDM (18/3/2010): changed from MVar to STM.  This fixes
63 --  1. there was no async exception protection
64 --  2. there was a space leak (now new value is strict)
65 --  3. using atomicModifyIORef would be slightly quicker, but can
66 --     suffer from adverse scheduling issues (see #3838)
67 --  4. also, the STM version is faster.
68
69 -- | Hashes a 'Unique' into an 'Int'.  Two 'Unique's may hash to the
70 -- same value, although in practice this is unlikely.  The 'Int'
71 -- returned makes a good hash key.
72 hashUnique :: Unique -> Int
73 #if defined(__GLASGOW_HASKELL__)
74 hashUnique (Unique i) = I# (hashInteger i)
75 #else
76 hashUnique (Unique u) = fromInteger (u `mod` (toInteger (maxBound :: Int) + 1))
77 #endif