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