{-# LANGUAGE MagicHash #-}{-# LANGUAGE Trustworthy #-}{-# LANGUAGE UnboxedTuples #-}------------------------------------------------------------------------------- |-- Module : System.Mem.StableName-- Copyright : (c) The University of Glasgow 2001-- License : BSD-style (see the file libraries/base/LICENSE)---- Maintainer : libraries@haskell.org-- Stability : stable-- Portability : non-portable---- Stable names are a way of performing fast ( \(\mathcal{O}(1)\) ),-- not-quite-exact comparison between objects.---- Stable names solve the following problem: suppose you want to build-- a hash table with Haskell objects as keys, but you want to use-- pointer equality for comparison; maybe because the keys are large-- and hashing would be slow, or perhaps because the keys are infinite-- in size. We can\'t build a hash table using the address of the-- object as the key, because objects get moved around by the garbage-- collector, meaning a re-hash would be necessary after every garbage-- collection.---------------------------------------------------------------------------------moduleGHC.StableName(-- * Stable NamesStableName (..),makeStableName ,hashStableName ,eqStableName )whereimportGHC.IO (IO (..))importGHC.Base (Int (..),StableName# ,makeStableName# ,eqStableName# ,stableNameToInt# )------------------------------------------------------------------------------- Stable Names{-|
 An abstract name for an object, that supports equality and hashing.
 Stable names have the following property:
 * If @sn1 :: StableName@ and @sn2 :: StableName@ and @sn1 == sn2@
 then @sn1@ and @sn2@ were created by calls to @makeStableName@ on
 the same object.
 The reverse is not necessarily true: if two stable names are not
 equal, then the objects they name may still be equal. Note in particular
 that `makeStableName` may return a different `StableName` after an
 object is evaluated.
 Stable Names are similar to Stable Pointers ("Foreign.StablePtr"),
 but differ in the following ways:
 * There is no @freeStableName@ operation, unlike "Foreign.StablePtr"s.
 Stable names are reclaimed by the runtime system when they are no
 longer needed.
 * There is no @deRefStableName@ operation. You can\'t get back from
 a stable name to the original Haskell object. The reason for
 this is that the existence of a stable name for an object does not
 guarantee the existence of the object itself; it can still be garbage
 collected.
-}dataStableName a =StableName (StableName# a )-- | Makes a 'StableName' for an arbitrary object. The object passed as-- the first argument is not evaluated by 'makeStableName'.makeStableName ::a ->IO (StableName a )makeStableName :: forall a. a -> IO (StableName a)
makeStableName a
a =(State# RealWorld -> (# State# RealWorld, StableName a #))
-> IO (StableName a)
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, StableName a #))
 -> IO (StableName a))
-> (State# RealWorld -> (# State# RealWorld, StableName a #))
-> IO (StableName a)
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->casea -> State# RealWorld -> (# State# RealWorld, StableName# a #)
forall a.
a -> State# RealWorld -> (# State# RealWorld, StableName# a #)
makeStableName# a
a State# RealWorld
s of(#State# RealWorld
s' ,StableName# a
sn #)->(#State# RealWorld
s' ,StableName# a -> StableName a
forall a. StableName# a -> StableName a
StableName StableName# a
sn #)-- | Convert a 'StableName' to an 'Int'. The 'Int' returned is not-- necessarily unique; several 'StableName's may map to the same 'Int'-- (in practice however, the chances of this are small, so the result-- of 'hashStableName' makes a good hash key).hashStableName ::StableName a ->Int hashStableName :: forall a. StableName a -> Int
hashStableName (StableName StableName# a
sn )=Int# -> Int
I# (StableName# a -> Int#
forall a. StableName# a -> Int#
stableNameToInt# StableName# a
sn )-- | @since 2.01instanceEq (StableName a )where(StableName StableName# a
sn1 )== :: StableName a -> StableName a -> Bool
== (StableName StableName# a
sn2 )=caseStableName# a -> StableName# a -> Int#
forall a b. StableName# a -> StableName# b -> Int#
eqStableName# StableName# a
sn1 StableName# a
sn2 ofInt#
0#->Bool
False Int#
_->Bool
True -- | Equality on 'StableName' that does not require that the types of-- the arguments match.---- @since 4.7.0.0eqStableName ::StableName a ->StableName b ->Bool eqStableName :: forall a b. StableName a -> StableName b -> Bool
eqStableName (StableName StableName# a
sn1 )(StableName StableName# b
sn2 )=caseStableName# a -> StableName# b -> Int#
forall a b. StableName# a -> StableName# b -> Int#
eqStableName# StableName# a
sn1 StableName# b
sn2 ofInt#
0#->Bool
False Int#
_->Bool
True -- Requested by Emil Axelsson on glasgow-haskell-users, who wants to-- use it for implementing observable sharing.

AltStyle によって変換されたページ (->オリジナル) /