module UnliftIO.IORef
( IORef
, newIORef
, readIORef
, writeIORef
, modifyIORef
, modifyIORef'
, atomicModifyIORef
, atomicModifyIORef'
, atomicWriteIORef
, mkWeakIORef
) where
import Data.IORef (IORef)
import qualified Data.IORef as I
import Control.Monad.IO.Unlift
import System.Mem.Weak (Weak)
newIORef :: MonadIO m => a -> m (IORef a)
newIORef = liftIO . I.newIORef
readIORef :: MonadIO m => IORef a -> m a
readIORef = liftIO . I.readIORef
writeIORef :: MonadIO m => IORef a -> a -> m ()
writeIORef ref = liftIO . I.writeIORef ref
modifyIORef :: MonadIO m => IORef a -> (a -> a) -> m ()
modifyIORef ref = liftIO . I.modifyIORef ref
modifyIORef' :: MonadIO m => IORef a -> (a -> a) -> m ()
modifyIORef' ref = liftIO . I.modifyIORef' ref
atomicModifyIORef :: MonadIO m => IORef a -> (a -> (a, b)) -> m b
atomicModifyIORef ref = liftIO . I.atomicModifyIORef ref
atomicModifyIORef' :: MonadIO m => IORef a -> (a -> (a, b)) -> m b
atomicModifyIORef' ref = liftIO . I.atomicModifyIORef' ref
atomicWriteIORef :: MonadIO m => IORef a -> a -> m ()
atomicWriteIORef ref = liftIO . I.atomicWriteIORef ref
mkWeakIORef :: MonadUnliftIO m => IORef a -> m () -> m (Weak (IORef a))
mkWeakIORef ref final = withRunInIO $ \run -> I.mkWeakIORef ref (run final)