{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE BangPatterns, CPP, GeneralizedNewtypeDeriving, MagicHash,
NoImplicitPrelude, UnboxedTuples #-}
module GHC.Event.Unique
(
UniqueSource
, Unique(..)
, newSource
, newUnique
) where
import GHC.Base
import GHC.Num(Num)
import GHC.Show(Show(..))
#include "MachDeps.h"
data UniqueSource = US (MutableByteArray# RealWorld)
newtype Unique = Unique { Unique -> Int
asInt :: Int }
deriving ( Eq
, Ord
, Num
)
instance Show Unique where
show :: Unique -> String
show = Int -> String
forall a. Show a => a -> String
show (Int -> String) -> (Unique -> Int) -> Unique -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unique -> Int
asInt
newSource :: IO UniqueSource
newSource :: IO UniqueSource
newSource = (State# RealWorld -> (# State# RealWorld, UniqueSource #))
-> IO UniqueSource
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, UniqueSource #))
-> IO UniqueSource)
-> (State# RealWorld -> (# State# RealWorld, UniqueSource #))
-> IO UniqueSource
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# Int#
size State# RealWorld
s of
(# State# RealWorld
s', MutableByteArray# RealWorld
mba #) -> (# State# RealWorld
s', MutableByteArray# RealWorld -> UniqueSource
US MutableByteArray# RealWorld
mba #)
where
!(I# Int#
size) = SIZEOF_HSINT
newUnique :: UniqueSource -> IO Unique
newUnique :: UniqueSource -> IO Unique
newUnique (US MutableByteArray# RealWorld
mba) = (State# RealWorld -> (# State# RealWorld, Unique #)) -> IO Unique
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, Unique #)) -> IO Unique)
-> (State# RealWorld -> (# State# RealWorld, Unique #))
-> IO Unique
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case MutableByteArray# RealWorld
-> Int# -> Int# -> State# RealWorld -> (# State# RealWorld, Int# #)
forall d.
MutableByteArray# d
-> Int# -> Int# -> State# d -> (# State# d, Int# #)
fetchAddIntArray# MutableByteArray# RealWorld
mba Int#
0# Int#
1# State# RealWorld
s of
(# State# RealWorld
s', Int#
a #) -> (# State# RealWorld
s', Int -> Unique
Unique (Int# -> Int
I# Int#
a) #)
{-# INLINE newUnique #-}