{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude, MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_HADDOCK not-home #-}
module GHC.IORef (
IORef(..),
newIORef, readIORef, writeIORef, atomicModifyIORef2Lazy,
atomicModifyIORef2, atomicModifyIORefLazy_, atomicModifyIORef'_,
atomicModifyIORefP, atomicSwapIORef, atomicModifyIORef'
) where
import GHC.Base
import GHC.STRef
import GHC.IO
newtype IORef a = IORef (STRef RealWorld a)
deriving IORef a -> IORef a -> Bool
(IORef a -> IORef a -> Bool)
-> (IORef a -> IORef a -> Bool) -> Eq (IORef a)
forall a. IORef a -> IORef a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. IORef a -> IORef a -> Bool
== :: IORef a -> IORef a -> Bool
$c/= :: forall a. IORef a -> IORef a -> Bool
/= :: IORef a -> IORef a -> Bool
Eq
newIORef :: a -> IO (IORef a)
newIORef :: forall a. a -> IO (IORef a)
newIORef a
v = ST RealWorld (STRef RealWorld a) -> IO (STRef RealWorld a)
forall a. ST RealWorld a -> IO a
stToIO (a -> ST RealWorld (STRef RealWorld a)
forall a s. a -> ST s (STRef s a)
newSTRef a
v) IO (STRef RealWorld a)
-> (STRef RealWorld a -> IO (IORef a)) -> IO (IORef a)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ STRef RealWorld a
var -> IORef a -> IO (IORef a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (STRef RealWorld a -> IORef a
forall a. STRef RealWorld a -> IORef a
IORef STRef RealWorld a
var)
readIORef :: IORef a -> IO a
readIORef :: forall a. IORef a -> IO a
readIORef (IORef STRef RealWorld a
var) = ST RealWorld a -> IO a
forall a. ST RealWorld a -> IO a
stToIO (STRef RealWorld a -> ST RealWorld a
forall s a. STRef s a -> ST s a
readSTRef STRef RealWorld a
var)
writeIORef :: IORef a -> a -> IO ()
writeIORef :: forall a. IORef a -> a -> IO ()
writeIORef (IORef STRef RealWorld a
var) a
v = ST RealWorld () -> IO ()
forall a. ST RealWorld a -> IO a
stToIO (STRef RealWorld a -> a -> ST RealWorld ()
forall s a. STRef s a -> a -> ST s ()
writeSTRef STRef RealWorld a
var a
v)
atomicModifyIORef2Lazy :: IORef a -> (a -> (a,b)) -> IO (a, (a, b))
atomicModifyIORef2Lazy :: forall a b. IORef a -> (a -> (a, b)) -> IO (a, (a, b))
atomicModifyIORef2Lazy (IORef (STRef MutVar# RealWorld a
r#)) a -> (a, b)
f =
(State# RealWorld -> (# State# RealWorld, (a, (a, b)) #))
-> IO (a, (a, b))
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
s -> case MutVar# RealWorld a
-> (a -> (a, b))
-> State# RealWorld
-> (# State# RealWorld, a, (a, b) #)
forall d a c.
MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #)
atomicModifyMutVar2# MutVar# RealWorld a
r# a -> (a, b)
f State# RealWorld
s of
(# State# RealWorld
s', a
old, (a, b)
res #) -> (# State# RealWorld
s', (a
old, (a, b)
res) #))
atomicModifyIORef2 :: IORef a -> (a -> (a,b)) -> IO (a, (a, b))
atomicModifyIORef2 :: forall a b. IORef a -> (a -> (a, b)) -> IO (a, (a, b))
atomicModifyIORef2 IORef a
ref a -> (a, b)
f = do
r :: (a, (a, b))
r@(a
_old, (a
_new, b
_res)) <- IORef a -> (a -> (a, b)) -> IO (a, (a, b))
forall a b. IORef a -> (a -> (a, b)) -> IO (a, (a, b))
atomicModifyIORef2Lazy IORef a
ref a -> (a, b)
f
(a, (a, b)) -> IO (a, (a, b))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (a, (a, b))
r
atomicModifyIORefP :: IORef a -> (a -> (a,b)) -> IO b
atomicModifyIORefP :: forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORefP IORef a
ref a -> (a, b)
f = do
(a
_old, (a
_,b
r)) <- IORef a -> (a -> (a, b)) -> IO (a, (a, b))
forall a b. IORef a -> (a -> (a, b)) -> IO (a, (a, b))
atomicModifyIORef2 IORef a
ref a -> (a, b)
f
b -> IO b
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure b
r
atomicModifyIORefLazy_ :: IORef a -> (a -> a) -> IO (a, a)
atomicModifyIORefLazy_ :: forall a. IORef a -> (a -> a) -> IO (a, a)
atomicModifyIORefLazy_ (IORef (STRef MutVar# RealWorld a
ref)) a -> a
f = (State# RealWorld -> (# State# RealWorld, (a, a) #)) -> IO (a, a)
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, (a, a) #)) -> IO (a, a))
-> (State# RealWorld -> (# State# RealWorld, (a, a) #))
-> IO (a, a)
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case MutVar# RealWorld a
-> (a -> a) -> State# RealWorld -> (# State# RealWorld, a, a #)
forall d a.
MutVar# d a -> (a -> a) -> State# d -> (# State# d, a, a #)
atomicModifyMutVar_# MutVar# RealWorld a
ref a -> a
f State# RealWorld
s of
(# State# RealWorld
s', a
old, a
new #) -> (# State# RealWorld
s', (a
old, a
new) #)
atomicModifyIORef'_ :: IORef a -> (a -> a) -> IO (a, a)
atomicModifyIORef'_ :: forall a. IORef a -> (a -> a) -> IO (a, a)
atomicModifyIORef'_ IORef a
ref a -> a
f = do
(a
old, !a
new) <- IORef a -> (a -> a) -> IO (a, a)
forall a. IORef a -> (a -> a) -> IO (a, a)
atomicModifyIORefLazy_ IORef a
ref a -> a
f
(a, a) -> IO (a, a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (a
old, a
new)
atomicSwapIORef :: IORef a -> a -> IO a
atomicSwapIORef :: forall a. IORef a -> a -> IO a
atomicSwapIORef (IORef (STRef MutVar# RealWorld a
ref)) a
new = (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (MutVar# RealWorld a
-> a -> State# RealWorld -> (# State# RealWorld, a #)
forall d a. MutVar# d a -> a -> State# d -> (# State# d, a #)
atomicSwapMutVar# MutVar# RealWorld a
ref a
new)
atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b
atomicModifyIORef' :: forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef a
ref a -> (a, b)
f = do
(a
_old, (a
_new, !b
res)) <- IORef a -> (a -> (a, b)) -> IO (a, (a, b))
forall a b. IORef a -> (a -> (a, b)) -> IO (a, (a, b))
atomicModifyIORef2 IORef a
ref ((a -> (a, b)) -> IO (a, (a, b)))
-> (a -> (a, b)) -> IO (a, (a, b))
forall a b. (a -> b) -> a -> b
$
\a
old -> case a -> (a, b)
f a
old of
r :: (a, b)
r@(!a
_new, b
_res) -> (a, b)
r
b -> IO b
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure b
res