ecstasy-0.1.1.0: A GHC.Generics based entity component system.

Safe HaskellSafe
LanguageHaskell2010

Data.Ecstasy

Synopsis

Documentation

class HasWorld world where Source #

This class provides all of the functionality necessary to manipulate the ECS.

Methods

getEntity :: Monad m => Ent -> SystemT world m (world FieldOf) Source #

Fetches an entity from the world given its Ent.

getEntity :: (GGetEntity (Rep (world WorldOf)) (Rep (world FieldOf)), Generic (world FieldOf), Generic (world WorldOf), Monad m) => Ent -> SystemT world m (world FieldOf) Source #

Fetches an entity from the world given its Ent.

setEntity :: Monad m => Ent -> world SetterOf -> SystemT world m () Source #

Updates an Ent in the world given its setter.

setEntity :: (GSetEntity (Rep (world SetterOf)) (Rep (world WorldOf)), Generic (world WorldOf), Generic (world SetterOf), Monad m) => Ent -> world SetterOf -> SystemT world m () Source #

Updates an Ent in the world given its setter.

convertSetter :: world FieldOf -> world SetterOf Source #

Transforms an entity into a setter to transform the default entity into the given one. Used by newEntity.

convertSetter :: (GConvertSetter (Rep (world FieldOf)) (Rep (world SetterOf)), Generic (world FieldOf), Generic (world SetterOf)) => world FieldOf -> world SetterOf Source #

Transforms an entity into a setter to transform the default entity into the given one. Used by newEntity.

defEntity :: world FieldOf Source #

The default entity, owning no components.

defEntity :: (Generic (world FieldOf), GDefault True (Rep (world FieldOf))) => world FieldOf Source #

The default entity, owning no components.

defEntity' :: world SetterOf Source #

The default setter, which keeps all components with their previous value.

defEntity' :: (Generic (world SetterOf), GDefault True (Rep (world SetterOf))) => world SetterOf Source #

The default setter, which keeps all components with their previous value.

delEntity :: world SetterOf Source #

A setter which will delete the entity if its QueryT matches.

delEntity :: (Generic (world SetterOf), GDefault False (Rep (world SetterOf))) => world SetterOf Source #

A setter which will delete the entity if its QueryT matches.

defWorld :: world WorldOf Source #

The default world, which contains only empty containers.

defWorld :: (Generic (world WorldOf), GDefault True (Rep (world WorldOf))) => world WorldOf Source #

The default world, which contains only empty containers.

Instances

(Generic (world SetterOf), Generic (world WorldOf), Generic (world FieldOf), GSetEntity (Rep (world SetterOf)) (Rep (world WorldOf)), GGetEntity (Rep (world WorldOf)) (Rep (world FieldOf)), GConvertSetter (Rep (world FieldOf)) (Rep (world SetterOf)), GDefault True (Rep (world FieldOf)), GDefault False (Rep (world SetterOf)), GDefault True (Rep (world SetterOf)), GDefault True (Rep (world WorldOf))) => HasWorld world Source # 

Methods

getEntity :: Monad m => Ent -> SystemT world m (world FieldOf) Source #

setEntity :: Monad m => Ent -> world SetterOf -> SystemT world m () Source #

convertSetter :: world FieldOf -> world SetterOf Source #

defEntity :: world FieldOf Source #

defEntity' :: world SetterOf Source #

delEntity :: world SetterOf Source #

defWorld :: world WorldOf Source #

nextEntity :: Monad m => SystemT a m Ent Source #

Retrieve a unique Ent.

newEntity :: (HasWorld world, Monad m) => world FieldOf -> SystemT world m Ent Source #

Create a new entity.

deleteEntity :: (HasWorld world, Monad m) => Ent -> SystemT world m () Source #

Delete an entity.

unQueryT :: QueryT world m a -> world FieldOf -> m (Maybe a) Source #

Evaluate a QueryT.

emap :: (HasWorld world, Monad m) => QueryT world m (world SetterOf) -> SystemT world m () Source #

Map a QueryT transformation over all entites that match it.

efor :: (HasWorld world, Monad m) => (Ent -> QueryT world m a) -> SystemT world m [a] Source #

Collect the results of a monadic computation over every entity matching a QueryT.

runQueryT :: (HasWorld world, Monad m) => Ent -> QueryT world m a -> SystemT world m (Maybe a) Source #

Run a QueryT over a particular Ent.

yieldSystemT :: Monad m => SystemState world -> SystemT world m a -> m (SystemState world, a) Source #

Provides a resumable SystemT. This is a pretty big hack until I come up with a better formalization for everything.

runSystemT :: Monad m => world WorldOf -> SystemT world m a -> m a Source #

Evaluate a SystemT.

runSystem :: world WorldOf -> System world a -> a Source #

Evaluate a System.

getWorld :: Monad m => SystemT world m (world WorldOf) Source #

Get the world.

with :: Monad m => (world FieldOf -> Maybe a) -> QueryT world m () Source #

Only evaluate this QueryT for entities which have the given component.

without :: Monad m => (world FieldOf -> Maybe a) -> QueryT world m () Source #

Only evaluate this QueryT for entities which do not have the given component.

get :: Monad m => (world FieldOf -> Maybe a) -> QueryT world m a Source #

Get the value of a component, failing the QueryT if it isn't present.

getMaybe :: Monad m => (world FieldOf -> Maybe a) -> QueryT world m (Maybe a) Source #

Attempt to get the value of a component.

newtype Ent Source #

The key for an entity.

Constructors

Ent 

Fields

Instances

Eq Ent Source # 

Methods

(==) :: Ent -> Ent -> Bool #

(/=) :: Ent -> Ent -> Bool #

Ord Ent Source # 

Methods

compare :: Ent -> Ent -> Ordering #

(<) :: Ent -> Ent -> Bool #

(<=) :: Ent -> Ent -> Bool #

(>) :: Ent -> Ent -> Bool #

(>=) :: Ent -> Ent -> Bool #

max :: Ent -> Ent -> Ent #

min :: Ent -> Ent -> Ent #

Show Ent Source # 

Methods

showsPrec :: Int -> Ent -> ShowS #

show :: Ent -> String #

showList :: [Ent] -> ShowS #

type SystemState w = (Int, w WorldOf) Source #

The internal state of the SystemT monad.

type SystemT w = StateT (SystemState w) Source #

A monad transformer over an ECS given a world w.

type System w = SystemT w Identity Source #

A monad over an ECS given a world w.

type QueryT w m = ReaderT (w FieldOf) (MaybeT m) Source #

A computation to run over a particular entity.

data StorageType Source #

Data kind used to parameterize the ECS record.

Constructors

FieldOf

Used to construct the actual entity.

WorldOf

Used to construct the world's storage.

SetterOf

Used to construct a setter to update an entity.

data ComponentType Source #

Data kind used to parameterize the fields of the ECS record.

Constructors

Field

This component can be owned by any entity.

Unique

This component can be owned by only a single entity at a time.

data Update a Source #

Describes how we can change an a.

Constructors

Keep

Keep the current value.

Unset

Delete the current value if it exists.

Set a

Set the current value.

Instances

Eq a => Eq (Update a) Source # 

Methods

(==) :: Update a -> Update a -> Bool #

(/=) :: Update a -> Update a -> Bool #

Ord a => Ord (Update a) Source # 

Methods

compare :: Update a -> Update a -> Ordering #

(<) :: Update a -> Update a -> Bool #

(<=) :: Update a -> Update a -> Bool #

(>) :: Update a -> Update a -> Bool #

(>=) :: Update a -> Update a -> Bool #

max :: Update a -> Update a -> Update a #

min :: Update a -> Update a -> Update a #

Read a => Read (Update a) Source # 
Show a => Show (Update a) Source # 

Methods

showsPrec :: Int -> Update a -> ShowS #

show :: Update a -> String #

showList :: [Update a] -> ShowS #

type family Component (s :: StorageType) (c :: ComponentType) (a :: *) :: * where ... Source #

A type family to be used in your ECS recrod.

class Generic a #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Minimal complete definition

from, to

Instances

Generic Bool 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering 

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic () 

Associated Types

type Rep () :: * -> * #

Methods

from :: () -> Rep () x #

to :: Rep () x -> () #

Generic Fixity 

Associated Types

type Rep Fixity :: * -> * #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity 

Associated Types

type Rep Associativity :: * -> * #

Generic SourceUnpackedness 
Generic SourceStrictness 
Generic DecidedStrictness 
Generic [a] 

Associated Types

type Rep [a] :: * -> * #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (Maybe a) 

Associated Types

type Rep (Maybe a) :: * -> * #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Generic (Par1 p) 

Associated Types

type Rep (Par1 p) :: * -> * #

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (Identity a) 

Associated Types

type Rep (Identity a) :: * -> * #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Generic (Either a b) 

Associated Types

type Rep (Either a b) :: * -> * #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (V1 k p) 

Associated Types

type Rep (V1 k p) :: * -> * #

Methods

from :: V1 k p -> Rep (V1 k p) x #

to :: Rep (V1 k p) x -> V1 k p #

Generic (U1 k p) 

Associated Types

type Rep (U1 k p) :: * -> * #

Methods

from :: U1 k p -> Rep (U1 k p) x #

to :: Rep (U1 k p) x -> U1 k p #

Generic (a, b) 

Associated Types

type Rep (a, b) :: * -> * #

Methods

from :: (a, b) -> Rep (a, b) x #

to :: Rep (a, b) x -> (a, b) #

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

from :: Proxy k t -> Rep (Proxy k t) x #

to :: Rep (Proxy k t) x -> Proxy k t #

Generic (Rec1 k f p) 

Associated Types

type Rep (Rec1 k f p) :: * -> * #

Methods

from :: Rec1 k f p -> Rep (Rec1 k f p) x #

to :: Rep (Rec1 k f p) x -> Rec1 k f p #

Generic (URec k (Ptr ()) p) 

Associated Types

type Rep (URec k (Ptr ()) p) :: * -> * #

Methods

from :: URec k (Ptr ()) p -> Rep (URec k (Ptr ()) p) x #

to :: Rep (URec k (Ptr ()) p) x -> URec k (Ptr ()) p #

Generic (URec k Char p) 

Associated Types

type Rep (URec k Char p) :: * -> * #

Methods

from :: URec k Char p -> Rep (URec k Char p) x #

to :: Rep (URec k Char p) x -> URec k Char p #

Generic (URec k Double p) 

Associated Types

type Rep (URec k Double p) :: * -> * #

Methods

from :: URec k Double p -> Rep (URec k Double p) x #

to :: Rep (URec k Double p) x -> URec k Double p #

Generic (URec k Float p) 

Associated Types

type Rep (URec k Float p) :: * -> * #

Methods

from :: URec k Float p -> Rep (URec k Float p) x #

to :: Rep (URec k Float p) x -> URec k Float p #

Generic (URec k Int p) 

Associated Types

type Rep (URec k Int p) :: * -> * #

Methods

from :: URec k Int p -> Rep (URec k Int p) x #

to :: Rep (URec k Int p) x -> URec k Int p #

Generic (URec k Word p) 

Associated Types

type Rep (URec k Word p) :: * -> * #

Methods

from :: URec k Word p -> Rep (URec k Word p) x #

to :: Rep (URec k Word p) x -> URec k Word p #

Generic (a, b, c) 

Associated Types

type Rep (a, b, c) :: * -> * #

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (K1 k i c p) 

Associated Types

type Rep (K1 k i c p) :: * -> * #

Methods

from :: K1 k i c p -> Rep (K1 k i c p) x #

to :: Rep (K1 k i c p) x -> K1 k i c p #

Generic ((:+:) k f g p) 

Associated Types

type Rep ((k :+: f) g p) :: * -> * #

Methods

from :: (k :+: f) g p -> Rep ((k :+: f) g p) x #

to :: Rep ((k :+: f) g p) x -> (k :+: f) g p #

Generic ((:*:) k f g p) 

Associated Types

type Rep ((k :*: f) g p) :: * -> * #

Methods

from :: (k :*: f) g p -> Rep ((k :*: f) g p) x #

to :: Rep ((k :*: f) g p) x -> (k :*: f) g p #

Generic (a, b, c, d) 

Associated Types

type Rep (a, b, c, d) :: * -> * #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (M1 k i c f p) 

Associated Types

type Rep (M1 k i c f p) :: * -> * #

Methods

from :: M1 k i c f p -> Rep (M1 k i c f p) x #

to :: Rep (M1 k i c f p) x -> M1 k i c f p #

Generic ((:.:) k2 k1 f g p) 

Associated Types

type Rep ((k2 :.: k1) f g p) :: * -> * #

Methods

from :: (k2 :.: k1) f g p -> Rep ((k2 :.: k1) f g p) x #

to :: Rep ((k2 :.: k1) f g p) x -> (k2 :.: k1) f g p #

Generic (a, b, c, d, e) 

Associated Types

type Rep (a, b, c, d, e) :: * -> * #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic (a, b, c, d, e, f) 

Associated Types

type Rep (a, b, c, d, e, f) :: * -> * #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (a, b, c, d, e, f, g) 

Associated Types

type Rep (a, b, c, d, e, f, g) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #