Skip to content

Instantly share code, notes, and snippets.

@Solonarv
Created April 4, 2019 19:27
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save Solonarv/193ce27121accebe73acbb0376307fd6 to your computer and use it in GitHub Desktop.
Save Solonarv/193ce27121accebe73acbb0376307fd6 to your computer and use it in GitHub Desktop.
STRefs that carry an extra tag to enable hashing, comparison &c. Safe, I think.
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RoleAnnotations #-}
module IxSTRef
( IxSTRef, ixSTRefId, ixSTRef
, IxCounter, withIxCounter, newIxSTRef
) where
import Control.Monad.ST
import Data.Function
import Data.STRef
import Data.Word
import Data.Hashable
type role IxSTRef nominal _ _
data IxSTRef i s a = IxSTRef Word (STRef s a)
deriving Eq
ixSTRefId :: IxSTRef i s a -> Word
ixSTRefId (IxSTRef i _) = i
ixSTRef :: IxSTRef i s a -> STRef s a
ixSTRef (IxSTRef _ r) = r
-- Imagine read, write, modify &c implemented in terms
-- of ixSTRef + the corresponding function from Data.STRef
instance Ord (IxSTRef i s a) where
compare = compare `on` ixSTRefId
instance Hashable (IxSTRef i s a) where
hashWithSalt = hashUsing ixSTRefId
type role IxCounter nominal _
newtype IxCounter i s = IxCounter (STRef s Word)
-- Note: this is the same trick runST uses to keep STRefs et al. from escaping
-- Here we use it to keep the counter from escaping, so you can't juggle counters
-- unsafely.
withIxCounter :: (forall i. IxCounter i s -> ST s a) -> ST s a
withIxCounter inner = newSTRef 0 >>= inner . IxCounter
newIxSTRef :: IxCounter i s -> a -> ST s (IxSTRef i s a)
newIxSTRef (IxCounter cr) v = do
i <- readSTRef cr
modifySTRef' cr (+1)
IxSTRef i <$> newSTRef v
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment