apecs-stm-0.2: STM stores for apecs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Apecs.STM

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

Instances details
ExplDestroy STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplDestroy IO (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

Typeable c => 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 #

Typeable 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 #

ExplInit STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: STM (Map c) #

ExplInit IO (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: IO (Map c) #

ExplMembers STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplMembers IO (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplSet STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplSet IO (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

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

Instances details
ExplDestroy STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplDestroy IO (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

Typeable c => 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 #

Typeable 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 #

ExplInit STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: STM (Unique c) #

ExplInit IO (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: IO (Unique c) #

ExplMembers STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplMembers IO (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplSet STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplSet IO (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

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

Instances details
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 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 #

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

Defined in Apecs.STM

Methods

explInit :: STM (Global c) #

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

Defined in Apecs.STM

Methods

explInit :: IO (Global c) #

ExplSet STM (Global c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplSet IO (Global c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

type Elem (Global c) Source # 
Instance details

Defined in Apecs.STM

type Elem (Global c) = c

STM conveniences

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

Like makeWorldAndComponents from Apecs, but uses the STM Map

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

Instances details
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] #

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 #

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 #

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 #

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 #

Methods

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

restoreM :: StM STM a -> STM a #

ExplDestroy STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplDestroy STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

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 #

Typeable c => 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 #

Typeable c => 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 #

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

Defined in Apecs.STM

Methods

explInit :: STM (Global c) #

ExplInit STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: STM (Map c) #

ExplInit STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

explInit :: STM (Unique c) #

ExplMembers STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplMembers STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplSet STM (Global c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplSet STM (Map c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

ExplSet STM (Unique c) Source # 
Instance details

Defined in Apecs.STM

Methods

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

type StM STM a 
Instance details

Defined in Control.Monad.Trans.Control

type StM STM a = a