{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
{-# LANGUAGE MagicHash #-}
#if !defined(__PARALLEL_HASKELL__)
{-# LANGUAGE UnboxedTuples #-}
#endif
module System.Mem.StableName (
StableName,
makeStableName,
hashStableName,
eqStableName
) where
import Prelude
import Data.Typeable
import GHC.IO ( IO(..) )
import GHC.Base ( Int(..), StableName#, makeStableName#
, eqStableName#, stableNameToInt# )
data StableName a = StableName (StableName# a)
deriving Typeable
makeStableName :: a -> IO (StableName a)
#if defined(__PARALLEL_HASKELL__)
makeStableName a =
error "makeStableName not implemented in parallel Haskell"
#else
makeStableName a = IO $ \ s ->
case makeStableName# a s of (# s', sn #) -> (# s', StableName sn #)
#endif
hashStableName :: StableName a -> Int
#if defined(__PARALLEL_HASKELL__)
hashStableName (StableName sn) =
error "hashStableName not implemented in parallel Haskell"
#else
hashStableName (StableName sn) = I# (stableNameToInt# sn)
#endif
instance Eq (StableName a) where
#if defined(__PARALLEL_HASKELL__)
(StableName sn1) == (StableName sn2) =
error "eqStableName not implemented in parallel Haskell"
#else
(StableName sn1) == (StableName sn2) =
case eqStableName# sn1 sn2 of
0# -> False
_ -> True
#endif
eqStableName :: StableName a -> StableName b -> Bool
eqStableName (StableName sn1) (StableName sn2) =
case eqStableName# sn1 sn2 of
0# -> False
_ -> True