apecs-stm-0.1.1: STM stores for apecs

Safe HaskellNone
LanguageHaskell2010

Apecs.STM

Contents

Description

This module contains STM-supporting versions of regular apecs stores, and some convenience functions. It is designed to be imported qualified, since it shadows both apecs and STM names. There is also an Apecs.STM.Prelude module, which can be imported by itself.

Note that if you want to be able to create entities in STM, you will also need to use a STM-supported EntityCounter, typically done through this module's makeWorld.

Synopsis

Stores

newtype Map c Source #

Constructors

Map (Map Int c) 
Instances
ExplInit IO (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: IO (Map c) #

ExplInit STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: STM (Map c) #

ExplGet IO (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explGet :: Map c -> Int -> IO (Elem (Map c)) #

explExists :: Map c -> Int -> IO Bool #

ExplGet STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explGet :: Map c -> Int -> STM (Elem (Map c)) #

explExists :: Map c -> Int -> STM Bool #

ExplSet IO (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explSet :: Map c -> Int -> Elem (Map c) -> IO () #

ExplSet STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explSet :: Map c -> Int -> Elem (Map c) -> STM () #

ExplDestroy IO (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explDestroy :: Map c -> Int -> IO () #

ExplDestroy STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explDestroy :: Map c -> Int -> STM () #

ExplMembers IO (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explMembers :: Map c -> IO (Vector Int) #

ExplMembers STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explMembers :: Map c -> STM (Vector Int) #

type Elem (Map c) Source # 
Instance details

Defined in Apecs.STM

type Elem (Map c) = c

newtype Unique c Source #

Constructors

Unique (TVar (Maybe (Int, c))) 
Instances
ExplInit IO (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: IO (Unique c) #

ExplInit STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: STM (Unique c) #

ExplGet IO (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explGet :: Unique c -> Int -> IO (Elem (Unique c)) #

explExists :: Unique c -> Int -> IO Bool #

ExplGet STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explGet :: Unique c -> Int -> STM (Elem (Unique c)) #

explExists :: Unique c -> Int -> STM Bool #

ExplSet IO (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explSet :: Unique c -> Int -> Elem (Unique c) -> IO () #

ExplSet STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explSet :: Unique c -> Int -> Elem (Unique c) -> STM () #

ExplDestroy IO (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explDestroy :: Unique c -> Int -> IO () #

ExplDestroy STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explDestroy :: Unique c -> Int -> STM () #

ExplMembers IO (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explMembers :: Unique c -> IO (Vector Int) #

ExplMembers STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explMembers :: Unique c -> STM (Vector Int) #

type Elem (Unique c) Source # 
Instance details

Defined in Apecs.STM

type Elem (Unique c) = c

newtype Global c Source #

Constructors

Global (TVar c) 
Instances
Monoid c => ExplInit IO (Global c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: IO (Global c) #

Monoid c => ExplInit STM (Global c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: STM (Global c) #

ExplGet IO (Global c) Source # 
Instance details

Defined in Apecs.STM

Methods

explGet :: Global c -> Int -> IO (Elem (Global c)) #

explExists :: Global c -> Int -> IO Bool #

ExplGet STM (Global c) Source # 
Instance details

Defined in Apecs.STM

Methods

explGet :: Global c -> Int -> STM (Elem (Global c)) #

explExists :: Global c -> Int -> STM Bool #

ExplSet IO (Global c) Source # 
Instance details

Defined in Apecs.STM

Methods

explSet :: Global c -> Int -> Elem (Global c) -> IO () #

ExplSet STM (Global c) Source # 
Instance details

Defined in Apecs.STM

Methods

explSet :: Global c -> Int -> Elem (Global c) -> STM () #

type Elem (Global c) Source # 
Instance details

Defined in Apecs.STM

type Elem (Global c) = c

EntityCounter

makeWorld :: String -> [Name] -> Q [Dec] Source #

Like makeWorld from Apecs, but uses the STM EntityCounter

STM conveniences

atomically :: SystemT w STM a -> SystemT w IO a Source #

atomically from STM, lifted to the System level.

retry :: SystemT w STM a Source #

retry from STM, lifted to the System level.

check :: Bool -> SystemT w STM () Source #

check from STM, lifted to the System level.

forkSys :: SystemT w IO () -> SystemT w IO ThreadId Source #

Runs a system on a new thread.

threadDelay :: Int -> SystemT w IO () Source #

Suspends the current thread for a number of microseconds.

data STM a #

A monad supporting atomic memory transactions.

Instances
Monad STM

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

(>>=) :: STM a -> (a -> STM b) -> STM b #

(>>) :: STM a -> STM b -> STM b #

return :: a -> STM a #

fail :: String -> STM a #

Functor STM

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

fmap :: (a -> b) -> STM a -> STM b #

(<$) :: a -> STM b -> STM a #

Applicative STM

Since: base-4.8.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

pure :: a -> STM a #

(<*>) :: STM (a -> b) -> STM a -> STM b #

liftA2 :: (a -> b -> c) -> STM a -> STM b -> STM c #

(*>) :: STM a -> STM b -> STM b #

(<*) :: STM a -> STM b -> STM a #

Alternative STM

Since: base-4.8.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

empty :: STM a #

(<|>) :: STM a -> STM a -> STM a #

some :: STM a -> STM [a] #

many :: STM a -> STM [a] #

MonadPlus STM

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

mzero :: STM a #

mplus :: STM a -> STM a -> STM a #

MonadBaseControl STM STM 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM STM a :: Type #

Methods

liftBaseWith :: (RunInBase STM STM -> STM a) -> STM a #

restoreM :: StM STM a -> STM a #

Monoid c => ExplInit STM (Global c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: STM (Global c) #

ExplInit STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: STM (Unique c) #

ExplInit STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: STM (Map c) #

ExplGet STM (Global c) Source # 
Instance details

Defined in Apecs.STM

Methods

explGet :: Global c -> Int -> STM (Elem (Global c)) #

explExists :: Global c -> Int -> STM Bool #

ExplGet STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explGet :: Unique c -> Int -> STM (Elem (Unique c)) #

explExists :: Unique c -> Int -> STM Bool #

ExplGet STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explGet :: Map c -> Int -> STM (Elem (Map c)) #

explExists :: Map c -> Int -> STM Bool #

ExplSet STM (Global c) Source # 
Instance details

Defined in Apecs.STM

Methods

explSet :: Global c -> Int -> Elem (Global c) -> STM () #

ExplSet STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explSet :: Unique c -> Int -> Elem (Unique c) -> STM () #

ExplSet STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explSet :: Map c -> Int -> Elem (Map c) -> STM () #

ExplDestroy STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explDestroy :: Unique c -> Int -> STM () #

ExplDestroy STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explDestroy :: Map c -> Int -> STM () #

ExplMembers STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explMembers :: Unique c -> STM (Vector Int) #

ExplMembers STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explMembers :: Map c -> STM (Vector Int) #

type StM STM a 
Instance details

Defined in Control.Monad.Trans.Control

type StM STM a = a