{-# LANGUAGE CPP #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE Trustworthy #-}
#if MIN_VERSION_base(4,9,0)
{-# LANGUAGE TypeInType #-}
#endif
module Data.Parameterized.Nonce
(
NonceGenerator
, freshNonce
, countNoncesGenerated
, Nonce
, indexValue
, newSTNonceGenerator
, newIONonceGenerator
, withIONonceGenerator
, withSTNonceGenerator
, runSTNonceGenerator
, withGlobalSTNonceGenerator
, GlobalNonceGenerator
, globalNonceGenerator
) where
import Control.Monad.ST
import Data.Hashable
import Data.IORef
import Data.STRef
import Data.Typeable
import Data.Word
import Unsafe.Coerce
import System.IO.Unsafe (unsafePerformIO)
import Data.Parameterized.Classes
import Data.Parameterized.Some
#if MIN_VERSION_base(4,9,0) && __GLASGOW_HASKELL__ < 805
import Data.Kind
#endif
data NonceGenerator (m :: * -> *) (s :: *) where
STNG :: !(STRef t Word64) -> NonceGenerator (ST t) s
IONG :: !(IORef Word64) -> NonceGenerator IO s
#if MIN_VERSION_base(4,9,0)
freshNonce :: forall m s k (tp :: k) . NonceGenerator m s -> m (Nonce s tp)
#else
freshNonce :: forall m s (tp :: k) . NonceGenerator m s -> m (Nonce s tp)
#endif
freshNonce (IONG r) =
atomicModifyIORef' r $ \n -> (n+1, Nonce n)
freshNonce (STNG r) = do
i <- readSTRef r
writeSTRef r $! i+1
return $ Nonce i
{-# INLINE freshNonce #-}
countNoncesGenerated :: NonceGenerator m s -> m Integer
countNoncesGenerated (IONG r) = toInteger <$> readIORef r
countNoncesGenerated (STNG r) = toInteger <$> readSTRef r
newSTNonceGenerator :: ST t (Some (NonceGenerator (ST t)))
newSTNonceGenerator = Some . STNG <$> newSTRef (toEnum 0)
runSTNonceGenerator :: (forall s . NonceGenerator (ST s) s -> ST s a)
-> a
runSTNonceGenerator f = runST $ f . STNG =<< newSTRef 0
newIONonceGenerator :: IO (Some (NonceGenerator IO))
newIONonceGenerator = Some . IONG <$> newIORef (toEnum 0)
withSTNonceGenerator :: (forall s . NonceGenerator (ST t) s -> ST t r) -> ST t r
withSTNonceGenerator f = do
Some r <- newSTNonceGenerator
f r
withIONonceGenerator :: (forall s . NonceGenerator IO s -> IO r) -> IO r
withIONonceGenerator f = do
Some r <- newIONonceGenerator
f r
newtype Nonce (s :: *) (tp :: k) = Nonce { indexValue :: Word64 }
deriving (Eq, Ord, Hashable, Show)
type role Nonce nominal nominal
instance TestEquality (Nonce s) where
testEquality x y | indexValue x == indexValue y = unsafeCoerce (Just Refl)
| otherwise = Nothing
instance OrdF (Nonce s) where
compareF x y =
case compare (indexValue x) (indexValue y) of
LT -> LTF
EQ -> unsafeCoerce EQF
GT -> GTF
instance HashableF (Nonce s) where
hashWithSaltF s (Nonce x) = hashWithSalt s x
instance ShowF (Nonce s)
data GlobalNonceGenerator
globalNonceIORef :: IORef Word64
globalNonceIORef = unsafePerformIO (newIORef 0)
{-# NOINLINE globalNonceIORef #-}
globalNonceGenerator :: NonceGenerator IO GlobalNonceGenerator
globalNonceGenerator = IONG globalNonceIORef
withGlobalSTNonceGenerator :: (forall t . NonceGenerator (ST t) t -> ST t r) -> r
withGlobalSTNonceGenerator f = runST $ do
r <- newSTRef (toEnum 0)
f $! STNG r