apecs-0.9.6: Fast Entity-Component-System library for game programming
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Apecs.Experimental.Stores

Description

This module is experimental, and its API might change between point releases. Use at your own risk.

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

Instances details
(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.Experimental.Stores

Methods

explDestroy :: Pushdown s c -> Int -> 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.Experimental.Stores

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.Experimental.Stores

Methods

explInit :: m (Pushdown s c) Source #

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

Defined in Apecs.Experimental.Stores

Methods

explMembers :: Pushdown s c -> m (Vector Int) 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.Experimental.Stores

Methods

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

type Elem (Pushdown s c) Source # 
Instance details

Defined in Apecs.Experimental.Stores

type Elem (Pushdown s c) = c

newtype Stack c Source #

Constructors

Stack 

Fields

Instances

Instances details
Foldable Stack Source # 
Instance details

Defined in Apecs.Experimental.Stores

Methods

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

foldMap :: Monoid m => (a -> m) -> Stack a -> 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 #

Applicative Stack Source # 
Instance details

Defined in Apecs.Experimental.Stores

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 #

Functor Stack Source # 
Instance details

Defined in Apecs.Experimental.Stores

Methods

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

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

Monad Stack Source # 
Instance details

Defined in Apecs.Experimental.Stores

Methods

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

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

return :: a -> Stack a #

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

Defined in Apecs.Experimental.Stores

Methods

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

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

Defined in Apecs.Experimental.Stores

Associated Types

type Storage (Stack c) Source #

Monoid (Stack c) Source # 
Instance details

Defined in Apecs.Experimental.Stores

Methods

mempty :: Stack c #

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

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

Semigroup (Stack c) Source # 
Instance details

Defined in Apecs.Experimental.Stores

Methods

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

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

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

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

Defined in Apecs.Experimental.Stores

Methods

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

show :: Stack c -> String #

showList :: [Stack c] -> ShowS #

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

Defined in Apecs.Experimental.Stores

Methods

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

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

type Storage (Stack c) Source # 
Instance details

Defined in Apecs.Experimental.Stores

type Storage (Stack c)