{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples #-}
{-# OPTIONS_HADDOCK not-home #-}
module GHC.STRef (
STRef(..),
newSTRef, readSTRef, writeSTRef
) where
import GHC.ST
import GHC.Base
data STRef s a = STRef (MutVar# s a)
newSTRef :: a -> ST s (STRef s a)
newSTRef :: forall a s. a -> ST s (STRef s a)
newSTRef a
init = STRep s (STRef s a) -> ST s (STRef s a)
forall s a. STRep s a -> ST s a
ST (STRep s (STRef s a) -> ST s (STRef s a))
-> STRep s (STRef s a) -> ST s (STRef s a)
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
case a -> State# s -> (# State# s, MutVar# s a #)
forall a d. a -> State# d -> (# State# d, MutVar# d a #)
newMutVar# a
init State# s
s1# of { (# State# s
s2#, MutVar# s a
var# #) ->
(# State# s
s2#, MutVar# s a -> STRef s a
forall s a. MutVar# s a -> STRef s a
STRef MutVar# s a
var# #) }
readSTRef :: STRef s a -> ST s a
readSTRef :: forall s a. STRef s a -> ST s a
readSTRef (STRef MutVar# s a
var#) = STRep s a -> ST s a
forall s a. STRep s a -> ST s a
ST (STRep s a -> ST s a) -> STRep s a -> ST s a
forall a b. (a -> b) -> a -> b
$ \State# s
s1# -> MutVar# s a -> STRep s a
forall d a. MutVar# d a -> State# d -> (# State# d, a #)
readMutVar# MutVar# s a
var# State# s
s1#
writeSTRef :: STRef s a -> a -> ST s ()
writeSTRef :: forall s a. STRef s a -> a -> ST s ()
writeSTRef (STRef MutVar# s a
var#) a
val = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
case MutVar# s a -> a -> State# s -> State# s
forall d a. MutVar# d a -> a -> State# d -> State# d
writeMutVar# MutVar# s a
var# a
val State# s
s1# of { State# s
s2# ->
(# State# s
s2#, () #) }
instance Eq (STRef s a) where
STRef MutVar# s a
v1# == :: STRef s a -> STRef s a -> Bool
== STRef MutVar# s a
v2# = Int# -> Bool
isTrue# (MutVar# s a -> MutVar# s a -> Int#
forall s a. MutVar# s a -> MutVar# s a -> Int#
sameMutVar# MutVar# s a
v1# MutVar# s a
v2#)