Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Lifted Data.IORef.Strict.
Since: 2.4.0.0
Synopsis
- data Prim (a :: Type -> Type) b
- runPrim :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => Eff (Prim ': es) a -> Eff es a
- data IORef' a
- newIORef' :: Prim :> es => a -> Eff es (IORef' a)
- readIORef' :: Prim :> es => IORef' a -> Eff es a
- writeIORef' :: Prim :> es => IORef' a -> a -> Eff es ()
- modifyIORef' :: Prim :> es => IORef' a -> (a -> a) -> Eff es ()
- atomicModifyIORef' :: Prim :> es => IORef' a -> (a -> (a, b)) -> Eff es b
- atomicWriteIORef' :: Prim :> es => IORef' a -> a -> Eff es ()
- mkWeakIORef' :: (HasCallStack, Prim :> es) => IORef' a -> Eff es () -> Eff es (Weak (IORef' a))
Effect
data Prim (a :: Type -> Type) b #
Provide the ability to perform primitive state-transformer actions.
Instances
type DispatchOf Prim | |
Defined in Effectful.Internal.Monad | |
data StaticRep Prim | |
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
A strict (WHNF) variant of IORef
.
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 #
Lifted atomicModifyIORef'
.
atomicWriteIORef' :: Prim :> es => IORef' a -> a -> Eff es () Source #
Lifted atomicWriteIORef'
.
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.