Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Lifted Data.IORef.
Note: it requires Prim
because MutVar
from the primitive
library is a
generalization of IORef
.
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 ()
- modifyIORef' :: Prim :> es => IORef a -> (a -> a) -> Eff es ()
- atomicModifyIORef :: Prim :> es => IORef a -> (a -> (a, b)) -> Eff es b
- 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 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
Instances
NFData1 IORef | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
NFData (IORef a) | NOTE: Only strict in the reference and not the referenced value. Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
Eq (IORef a) | Pointer equality. Since: base-4.0.0.0 |
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 #
Lifted atomicModifyIORef
.
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.