{-# LANGUAGE MagicHash, UnboxedTuples #-} module Data.RangeMin.Cartesian.STInt (STInt, toSTInt, runSTInt) where import GHC.ST (ST(..)) import GHC.Exts (Int#, Int(..), State#) newtype STInt s = STInt (State# s -> (# State# s, Int# #)) {-# INLINE toSTInt #-} toSTInt :: ST s Int -> STInt s toSTInt (ST m) = STInt $ \ s# -> case m s# of (# s'#, I# i# #) -> (# s'#, i# #) runSTInt :: STInt s -> ST s Int runSTInt (STInt m) = ST $ \ s# -> case m s# of (# s'#, i# #) -> (# s'#, I# i# #)