effectful-2.5.0.0: An easy to use, performant extensible effects library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Effectful.Prim.IORef

Description

Lifted Data.IORef.

Note: it requires Prim because MutVar from the primitive library is a generalization of IORef.

Since: 2.4.0.0

Synopsis

Effect

data Prim (a :: Type -> Type) b #

Provide the ability to perform primitive state-transformer actions.

Instances

Instances details
type DispatchOf Prim 
Instance details

Defined in Effectful.Internal.Monad

data StaticRep Prim 
Instance details

Defined in Effectful.Internal.Monad

Handlers

runPrim :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => Eff (Prim ': es) a -> Eff es a #

Run an Eff computation with primitive state-transformer actions.

IORef

data IORef a #

A mutable variable in the IO monad.

>>> import Data.IORef
>>> r <- newIORef 0
>>> readIORef r
0
>>> writeIORef r 1
>>> readIORef r
1
>>> atomicWriteIORef r 2
>>> readIORef r
2
>>> modifyIORef' r (+ 1)
>>> readIORef r
3
>>> atomicModifyIORef' r (\a -> (a + 1, ()))
>>> readIORef r
4

See also STRef and MVar.

Instances

Instances details
NFData1 IORef

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> IORef a -> () #

NFData (IORef a)

NOTE: Only strict in the reference and not the referenced value.

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: IORef a -> () #

Eq (IORef a)

Pointer equality.

Since: base-4.0.0.0

Instance details

Defined in GHC.IORef

Methods

(==) :: IORef a -> IORef a -> Bool #

(/=) :: IORef a -> IORef a -> Bool #

newIORef :: Prim :> es => a -> Eff es (IORef a) Source #

Lifted newIORef.

readIORef :: Prim :> es => IORef a -> Eff es a Source #

Lifted readIORef.

writeIORef :: Prim :> es => IORef a -> a -> Eff es () Source #

Lifted writeIORef.

modifyIORef :: Prim :> es => IORef a -> (a -> a) -> Eff es () Source #

Lifted modifyIORef.

modifyIORef' :: Prim :> es => IORef a -> (a -> a) -> Eff es () Source #

Lifted modifyIORef'.

atomicModifyIORef :: Prim :> es => IORef a -> (a -> (a, b)) -> Eff es b Source #

atomicModifyIORef' :: Prim :> es => IORef a -> (a -> (a, b)) -> Eff es b Source #

atomicWriteIORef :: Prim :> es => IORef a -> a -> Eff es () Source #

mkWeakIORef :: (HasCallStack, Prim :> es) => IORef a -> Eff es () -> Eff es (Weak (IORef a)) Source #

Lifted mkWeakIORef.

Note: the finalizer will run a cloned environment, so any changes it makes to thread local data will not be visible outside of it.