d7d27a3c51c0932f106fb0ea9e76fb379bfc71ba
[ghc-base.git] / System / Mem / StableName.hs
1 {-# LANGUAGE CPP #-}
2 #ifdef __GLASGOW_HASKELL__
3 {-# LANGUAGE MagicHash #-}
4 #if !defined(__PARALLEL_HASKELL__)
5 {-# LANGUAGE UnboxedTuples #-}
6 #endif
7 #endif
8
9 -----------------------------------------------------------------------------
10 -- |
11 -- Module      :  System.Mem.StableName
12 -- Copyright   :  (c) The University of Glasgow 2001
13 -- License     :  BSD-style (see the file libraries/base/LICENSE)
14 -- 
15 -- Maintainer  :  libraries@haskell.org
16 -- Stability   :  experimental
17 -- Portability :  non-portable
18 --
19 -- Stable names are a way of performing fast (O(1)), not-quite-exact
20 -- comparison between objects.
21 -- 
22 -- Stable names solve the following problem: suppose you want to build
23 -- a hash table with Haskell objects as keys, but you want to use
24 -- pointer equality for comparison; maybe because the keys are large
25 -- and hashing would be slow, or perhaps because the keys are infinite
26 -- in size.  We can\'t build a hash table using the address of the
27 -- object as the key, because objects get moved around by the garbage
28 -- collector, meaning a re-hash would be necessary after every garbage
29 -- collection.
30 --
31 -------------------------------------------------------------------------------
32
33 module System.Mem.StableName (
34   -- * Stable Names
35   StableName,
36   makeStableName,
37   hashStableName,
38   ) where
39
40 import Prelude
41
42 import Data.Typeable
43
44 #ifdef __HUGS__
45 import Hugs.Stable
46 #endif
47
48 #ifdef __GLASGOW_HASKELL__
49 import GHC.IO           ( IO(..) )
50 import GHC.Base         ( Int(..), StableName#, makeStableName#
51                         , eqStableName#, stableNameToInt# )
52
53 -----------------------------------------------------------------------------
54 -- Stable Names
55
56 {-|
57   An abstract name for an object, that supports equality and hashing.
58
59   Stable names have the following property:
60
61   * If @sn1 :: StableName@ and @sn2 :: StableName@ and @sn1 == sn2@
62    then @sn1@ and @sn2@ were created by calls to @makeStableName@ on 
63    the same object.
64
65   The reverse is not necessarily true: if two stable names are not
66   equal, then the objects they name may still be equal.  Note in particular
67   that `mkStableName` may return a different `StableName` after an
68   object is evaluated.
69
70   Stable Names are similar to Stable Pointers ("Foreign.StablePtr"),
71   but differ in the following ways:
72
73   * There is no @freeStableName@ operation, unlike "Foreign.StablePtr"s.
74     Stable names are reclaimed by the runtime system when they are no
75     longer needed.
76
77   * There is no @deRefStableName@ operation.  You can\'t get back from
78     a stable name to the original Haskell object.  The reason for
79     this is that the existence of a stable name for an object does not
80     guarantee the existence of the object itself; it can still be garbage
81     collected.
82 -}
83
84 data StableName a = StableName (StableName# a)
85
86
87 -- | Makes a 'StableName' for an arbitrary object.  The object passed as
88 -- the first argument is not evaluated by 'makeStableName'.
89 makeStableName  :: a -> IO (StableName a)
90 #if defined(__PARALLEL_HASKELL__)
91 makeStableName a = 
92   error "makeStableName not implemented in parallel Haskell"
93 #else
94 makeStableName a = IO $ \ s ->
95     case makeStableName# a s of (# s', sn #) -> (# s', StableName sn #)
96 #endif
97
98 -- | Convert a 'StableName' to an 'Int'.  The 'Int' returned is not
99 -- necessarily unique; several 'StableName's may map to the same 'Int'
100 -- (in practice however, the chances of this are small, so the result
101 -- of 'hashStableName' makes a good hash key).
102 hashStableName :: StableName a -> Int
103 #if defined(__PARALLEL_HASKELL__)
104 hashStableName (StableName sn) = 
105   error "hashStableName not implemented in parallel Haskell"
106 #else
107 hashStableName (StableName sn) = I# (stableNameToInt# sn)
108 #endif
109
110 instance Eq (StableName a) where 
111 #if defined(__PARALLEL_HASKELL__)
112     (StableName sn1) == (StableName sn2) = 
113       error "eqStableName not implemented in parallel Haskell"
114 #else
115     (StableName sn1) == (StableName sn2) = 
116        case eqStableName# sn1 sn2 of
117          0# -> False
118          _  -> True
119 #endif
120
121 #endif /* __GLASGOW_HASKELL__ */
122
123 #include "Typeable.h"
124 INSTANCE_TYPEABLE1(StableName,stableNameTc,"StableName")