mutable-containers-0.1.2.0: Abstactions and concrete implementations of mutable containers

Safe HaskellNone
LanguageHaskell2010

Data.Mutable.Class

Description

Various typeclasses for mutable containers.

Synopsis

Documentation

class Monad m => PrimMonad m

Class of primitive state-transformer monads

Minimal complete definition

primitive, internal

Associated Types

type PrimState m :: *

State token type

Instances

type family PrimState m :: *

State token type

Instances

type PrimState IO = RealWorld 
type PrimState (ST s) = s 

data RealWorld :: *

RealWorld is deeply magical. It is primitive, but it is not unlifted (hence ptrArg). We never manipulate values of type RealWorld; it's only used in the type system, to parameterise State#.

type MutableDeque c = (MutableQueue c, MutablePushFront c, MutablePopBack c) Source

data IORef a :: * -> *

A mutable variable in the IO monad

data STRef s a :: * -> * -> *

a value of type STRef s a is a mutable variable in state thread s, containing a value of type a

Instances

asSTRef :: STRef s a -> STRef s a Source

data MutVar s a :: * -> * -> *

A MutVar behaves like a single-element mutable array associated with a primitive state token.

Instances

class MutableContainer c => MutableRef c where Source

Associated Types

type RefElement c Source

Methods

newRef :: (PrimMonad m, PrimState m ~ MCState c) => RefElement c -> m c Source

readRef :: (PrimMonad m, PrimState m ~ MCState c) => c -> m (RefElement c) Source

writeRef :: (PrimMonad m, PrimState m ~ MCState c) => c -> RefElement c -> m () Source

modifyRef :: (PrimMonad m, PrimState m ~ MCState c) => c -> (RefElement c -> RefElement c) -> m () Source

modifyRef' :: (PrimMonad m, PrimState m ~ MCState c) => c -> (RefElement c -> RefElement c) -> m () Source

Instances

class MutableRef c => MutableAtomicRef c where Source

Methods

atomicModifyRef :: (PrimMonad m, PrimState m ~ MCState c) => c -> (RefElement c -> (RefElement c, a)) -> m a Source

atomicModifyRef' :: (PrimMonad m, PrimState m ~ MCState c) => c -> (RefElement c -> (RefElement c, a)) -> m a Source

class MutableContainer c => MutableCollection c where Source

Associated Types

type CollElement c Source

Methods

newColl :: (PrimMonad m, PrimState m ~ MCState c) => m c Source