apecs-0.7.3: Fast Entity-Component-System library for game programming

Stabilityexperimtal
Safe HaskellNone
LanguageHaskell2010

Apecs.Stores.Extra

Description

Containment module for stores that are experimental/too weird for Apecs.Stores.

Synopsis

Documentation

newtype Pushdown s c Source #

Overrides a store to have history/pushdown semantics. Setting this store adds a new value on top of the stack. Destroying pops the stack. You can view the entire stack using the Stack wrapper.

Constructors

Pushdown (s (Stack c)) 
Instances
(Monad m, ExplMembers m (s (Stack c)), Elem (s (Stack c)) ~ Stack c) => ExplMembers m (Pushdown s c) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

explMembers :: Pushdown s c -> m (Vector Int) Source #

(Monad m, ExplGet m (s (Stack c)), ExplSet m (s (Stack c)), ExplDestroy m (s (Stack c)), Elem (s (Stack c)) ~ Stack c) => ExplDestroy m (Pushdown s c) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

explDestroy :: Pushdown s c -> Int -> m () Source #

(Monad m, ExplGet m (s (Stack c)), ExplSet m (s (Stack c)), Elem (s (Stack c)) ~ Stack c) => ExplSet m (Pushdown s c) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

explSet :: Pushdown s c -> Int -> Elem (Pushdown s c) -> m () Source #

(Monad m, ExplGet m (s (Stack c)), Elem (s (Stack c)) ~ Stack c) => ExplGet m (Pushdown s c) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

explGet :: Pushdown s c -> Int -> m (Elem (Pushdown s c)) Source #

explExists :: Pushdown s c -> Int -> m Bool Source #

(Functor m, ExplInit m (s (Stack c))) => ExplInit m (Pushdown s c) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

explInit :: m (Pushdown s c) Source #

type Elem (Pushdown s c) Source # 
Instance details

Defined in Apecs.Stores.Extra

type Elem (Pushdown s c) = c

newtype Stack c Source #

Constructors

Stack 

Fields

Instances
Monad Stack Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

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

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

return :: a -> Stack a #

fail :: String -> Stack a #

Functor Stack Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

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

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

Applicative Stack Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

pure :: a -> Stack a #

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

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

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

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

Foldable Stack Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

fold :: Monoid m => Stack m -> m #

foldMap :: Monoid m => (a -> m) -> Stack a -> m #

foldr :: (a -> b -> b) -> b -> Stack a -> b #

foldr' :: (a -> b -> b) -> b -> Stack a -> b #

foldl :: (b -> a -> b) -> b -> Stack a -> b #

foldl' :: (b -> a -> b) -> b -> Stack a -> b #

foldr1 :: (a -> a -> a) -> Stack a -> a #

foldl1 :: (a -> a -> a) -> Stack a -> a #

toList :: Stack a -> [a] #

null :: Stack a -> Bool #

length :: Stack a -> Int #

elem :: Eq a => a -> Stack a -> Bool #

maximum :: Ord a => Stack a -> a #

minimum :: Ord a => Stack a -> a #

sum :: Num a => Stack a -> a #

product :: Num a => Stack a -> a #

(Storage c ~ Pushdown s c, Has w m c) => Has w m (Stack c) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

getStore :: SystemT w m (Storage (Stack c)) Source #

Eq c => Eq (Stack c) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

(==) :: Stack c -> Stack c -> Bool #

(/=) :: Stack c -> Stack c -> Bool #

Show c => Show (Stack c) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

showsPrec :: Int -> Stack c -> ShowS #

show :: Stack c -> String #

showList :: [Stack c] -> ShowS #

Semigroup (Stack c) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

(<>) :: Stack c -> Stack c -> Stack c #

sconcat :: NonEmpty (Stack c) -> Stack c #

stimes :: Integral b => b -> Stack c -> Stack c #

Monoid (Stack c) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

mempty :: Stack c #

mappend :: Stack c -> Stack c -> Stack c #

mconcat :: [Stack c] -> Stack c #

(Storage c ~ Pushdown s c, Component c) => Component (Stack c) Source # 
Instance details

Defined in Apecs.Stores.Extra

Associated Types

type Storage (Stack c) :: Type Source #

type Storage (Stack c) Source # 
Instance details

Defined in Apecs.Stores.Extra

type Storage (Stack c)

newtype ReadOnly s Source #

Wrapper that makes a store read-only. Use setReadOnly and destroyReadOnly to override.

Constructors

ReadOnly s 
Instances
ExplMembers m s => ExplMembers m (ReadOnly s) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

explMembers :: ReadOnly s -> m (Vector Int) Source #

ExplGet m s => ExplGet m (ReadOnly s) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

explGet :: ReadOnly s -> Int -> m (Elem (ReadOnly s)) Source #

explExists :: ReadOnly s -> Int -> m Bool Source #

(Functor m, ExplInit m s) => ExplInit m (ReadOnly s) Source # 
Instance details

Defined in Apecs.Stores.Extra

Methods

explInit :: m (ReadOnly s) Source #

type Elem (ReadOnly s) Source # 
Instance details

Defined in Apecs.Stores.Extra

type Elem (ReadOnly s) = Elem s

setReadOnly :: forall w m s c. (Has w m c, Storage c ~ ReadOnly s, Elem s ~ c, ExplSet m s) => Entity -> c -> SystemT w m () Source #

destroyReadOnly :: forall w m s c. (Has w m c, Storage c ~ ReadOnly s, Elem s ~ c, ExplDestroy m s) => Entity -> Proxy c -> SystemT w m () Source #