{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Clash.Unique
( Unique
, Uniquable (..)
, fromGhcUnique
) where
import Data.Word (Word64)
#if MIN_VERSION_ghc(9,0,0)
import qualified GHC.Types.Unique as GHC
#else
import qualified Unique as GHC
#endif
type Unique = Int
class Uniquable a where
getUnique :: a -> Unique
setUnique :: a -> Unique -> a
instance Uniquable Unique where
getUnique :: Unique -> Unique
getUnique = Unique -> Unique
forall a. a -> a
id
setUnique :: Unique -> Unique -> Unique
setUnique = (Unique -> Unique -> Unique) -> Unique -> Unique -> Unique
forall a b c. (a -> b -> c) -> b -> a -> c
flip Unique -> Unique -> Unique
forall a b. a -> b -> a
const
instance Uniquable Word64 where
getUnique :: Word64 -> Unique
getUnique = Word64 -> Unique
forall a b. (Integral a, Num b) => a -> b
fromIntegral
setUnique :: Word64 -> Unique -> Word64
setUnique Word64
_ = Unique -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
#if MIN_VERSION_ghc(9,10,0)
fromGhcUnique :: GHC.Unique -> Unique
fromGhcUnique = fromIntegral . GHC.getKey
#else
fromGhcUnique :: GHC.Unique -> Unique
fromGhcUnique :: Unique -> Unique
fromGhcUnique = Unique -> Unique
forall a. a -> a
id (Unique -> Unique) -> (Unique -> Unique) -> Unique -> Unique
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unique -> Unique
GHC.getKey
#endif