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

Effectful.Prim.IORef.Strict

Description

Lifted Data.IORef.Strict.

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 strict (WHNF) variant of IORef.

Instances

Instances details
NFData1 IORef' 
Instance details

Defined in Data.IORef.Strict

Methods

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

NFData (IORef' a) 
Instance details

Defined in Data.IORef.Strict

Methods

rnf :: IORef' a -> () #

Eq (IORef' a) 
Instance details

Defined in Data.IORef.Strict

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'.

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.