aztecs-0.14.0: A modular game engine and Entity-Component-System (ECS) for Haskell.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Aztecs.ECS.Schedule.Internal

Documentation

class Schedule (m :: k) s where Source #

Associated Types

type Scheduled (m :: k) s Source #

Methods

schedule :: s -> Scheduled m s Source #

Instances

Instances details
Schedule (m :: k) (HSet ('[] :: [Type])) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Associated Types

type Scheduled (m :: k) (HSet ('[] :: [Type])) 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

type Scheduled (m :: k) (HSet ('[] :: [Type])) = HSet ('[] :: [Type])

Methods

schedule :: HSet ('[] :: [Type]) -> Scheduled m (HSet ('[] :: [Type])) Source #

System m sys => Schedule (m :: Type -> Type) (HSet '[sys]) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Associated Types

type Scheduled (m :: Type -> Type) (HSet '[sys]) 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

type Scheduled (m :: Type -> Type) (HSet '[sys]) = HSet (GroupsToNestedHSet m (GroupSystems m '[sys]))
type Scheduled (m :: Type -> Type) (HSet (sys ': rest)) 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

type Scheduled (m :: Type -> Type) (HSet (sys ': rest)) = HSet (GroupsToNestedHSet m (GroupSystems m (sys ': rest)))

Methods

schedule :: HSet '[sys] -> Scheduled m (HSet '[sys]) Source #

(System m sys, AllSystems m rest, rest ~ (sys2 ': rest'), CompileGroups m (GroupSystems m (sys ': rest)) (sys ': rest)) => Schedule (m :: Type -> Type) (HSet (sys ': rest)) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Associated Types

type Scheduled (m :: Type -> Type) (HSet (sys ': rest)) 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

type Scheduled (m :: Type -> Type) (HSet (sys ': rest)) = HSet (GroupsToNestedHSet m (GroupSystems m (sys ': rest)))

Methods

schedule :: HSet (sys ': rest) -> Scheduled m (HSet (sys ': rest)) Source #

type family SystemInOf (m :: Type -> Type) sys :: [Type] where ... Source #

Equations

SystemInOf m sys = AccessType (SystemIn m sys) 

type family HasInputOverlap (inputs1 :: [Type]) (inputs2 :: [Type]) :: Bool where ... Source #

type family HasComponentOverlap (components1 :: [Type]) (components2 :: [Type]) :: Bool where ... Source #

Equations

HasComponentOverlap ('[] :: [Type]) components2 = 'False 
HasComponentOverlap (c ': rest) components2 = Or (Contains c components2) (HasComponentOverlap rest components2) 

type family GroupSystems (m :: Type -> Type) (systems :: [Type]) :: [[Type]] where ... Source #

Equations

GroupSystems m ('[] :: [Type]) = '[] :: [[Type]] 
GroupSystems m '[sys] = '['[sys]] 
GroupSystems m (sys1 ': (sys2 ': rest)) = If (HasInputOverlap (SystemInOf m sys1) (SystemInOf m sys2)) (GroupSystemsConflict m (sys1 ': (sys2 ': rest))) (GroupSystemsNoConflict m (sys1 ': (sys2 ': rest))) 

type family GroupSystemsConflict (m :: Type -> Type) (systems :: [Type]) :: [[Type]] where ... Source #

Equations

GroupSystemsConflict m (sys ': rest) = '[sys] ': GroupSystems m rest 

type family GroupSystemsNoConflict (m :: Type -> Type) (systems :: [Type]) :: [[Type]] where ... Source #

Equations

GroupSystemsNoConflict m (sys1 ': (sys2 ': rest)) = MergeCompatibleSystems m '[sys1, sys2] rest 

type family MergeCompatibleSystems (m :: Type -> Type) (group :: [Type]) (remaining :: [Type]) :: [[Type]] where ... Source #

Equations

MergeCompatibleSystems m group ('[] :: [Type]) = '[group] 
MergeCompatibleSystems m group (sys ': rest) = If (CanAddSystemToGroup m sys group) (MergeCompatibleSystems m (AppendToGroup sys group) rest) (group ': GroupSystems m (sys ': rest)) 

type family CanAddSystemToGroup (m :: Type -> Type) sys (group :: [Type]) :: Bool where ... Source #

Equations

CanAddSystemToGroup m sys ('[] :: [Type]) = 'True 
CanAddSystemToGroup m sys (groupSys ': rest) = And (Not (HasInputOverlap (SystemInOf m sys) (SystemInOf m groupSys))) (CanAddSystemToGroup m sys rest) 

type family AppendToGroup sys (group :: [Type]) :: [Type] where ... Source #

Equations

AppendToGroup sys group = sys ': group 

type family If (condition :: Bool) (then_ :: k) (else_ :: k) :: k where ... Source #

Equations

If 'True (then_ :: k) (else_ :: k) = then_ 
If 'False (then_ :: k) (else_ :: k) = else_ 

type family GroupsToNestedHSet (m :: k) (groups :: [[Type]]) :: [Type] where ... Source #

Equations

GroupsToNestedHSet (m :: k) ('[] :: [[Type]]) = '[] :: [Type] 
GroupsToNestedHSet (m :: k) (group ': rest) = HSet (MapToIdentityT m group) ': GroupsToNestedHSet m rest 

class AllSystems (m :: k) (systems :: k1) Source #

Instances

Instances details
AllSystems (m :: k) ('[] :: [a]) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

(System m (Run constraints sys), AllSystems m rest) => AllSystems (m :: Type -> Type) (Run constraints sys ': rest :: [Type]) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

(System m sys, AllSystems m rest) => AllSystems (m :: Type -> Type) (sys ': rest :: [Type]) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

class CompileGroups (m :: k) (groups :: [[Type]]) (systems :: [Type]) where Source #

Methods

compileGroups :: HSet systems -> HSet (GroupsToNestedHSet m groups) Source #

Instances

Instances details
CompileGroups (m :: k) ('[] :: [[Type]]) systems Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Methods

compileGroups :: HSet systems -> HSet (GroupsToNestedHSet m ('[] :: [[Type]])) Source #

CompileGroup m group systems => CompileGroups (m :: k) '[group] systems Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Methods

compileGroups :: HSet systems -> HSet (GroupsToNestedHSet m '[group]) Source #

(CompileGroup m group systems, CompileGroups m rest systems) => CompileGroups (m :: k) (group ': rest) systems Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Methods

compileGroups :: HSet systems -> HSet (GroupsToNestedHSet m (group ': rest)) Source #

class CompileGroup (m :: k) (group :: [Type]) (systems :: [Type]) where Source #

Methods

compileGroup :: HSet systems -> HSet (MapToIdentityT m group) Source #

Instances

Instances details
CompileGroup (m :: k) ('[] :: [Type]) systems Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Methods

compileGroup :: HSet systems -> HSet (MapToIdentityT m ('[] :: [Type])) Source #

ExtractSystem m sys systems => CompileGroup (m :: k) '[sys] systems Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Methods

compileGroup :: HSet systems -> HSet (MapToIdentityT m '[sys]) Source #

(ExtractSystem m sys systems, CompileGroup m rest systems) => CompileGroup (m :: k) (sys ': rest) systems Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Methods

compileGroup :: HSet systems -> HSet (MapToIdentityT m (sys ': rest)) Source #

type family MapToIdentityT (m :: k) (systems :: [Type]) :: [Type] where ... Source #

Equations

MapToIdentityT (m :: k) ('[] :: [Type]) = '[] :: [Type] 
MapToIdentityT (m :: k) (sys ': rest) = sys ': MapToIdentityT m rest 

class ExtractSystem (m :: k) sys (systems :: [Type]) where Source #

Methods

extractSystem :: HSet systems -> sys Source #

Instances

Instances details
ExtractSystem m sys rest => ExtractSystem (m :: k) sys (other ': rest) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Methods

extractSystem :: HSet (other ': rest) -> sys Source #

ExtractSystem (m :: k) sys (sys ': rest) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Methods

extractSystem :: HSet (sys ': rest) -> sys Source #

data Before sys Source #

data After sys Source #

data Run (constraints :: [Type]) sys where Source #

Constructors

Run :: forall sys (constraints :: [Type]). sys -> Run constraints sys 

Instances

Instances details
System m sys => System m (Run constraints sys) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Associated Types

type SystemIn m (Run constraints sys) 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

type SystemIn m (Run constraints sys) = SystemIn m sys

Methods

runSystem :: Run constraints sys -> SystemIn m (Run constraints sys) -> m () Source #

RemainingAfterExtract sys (Run constraints sys ': rest) ~ rest => ExtractFromHSet sys (Run constraints sys ': rest) Source # 
Instance details

Defined in Aztecs.ECS.Scheduler.Internal

Methods

extractFromHSet :: HSet (Run constraints sys ': rest) -> (sys, HSet (RemainingAfterExtract sys (Run constraints sys ': rest))) Source #

Show sys => Show (Run constraints sys) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

Methods

showsPrec :: Int -> Run constraints sys -> ShowS #

show :: Run constraints sys -> String #

showList :: [Run constraints sys] -> ShowS #

(System m (Run constraints sys), AllSystems m rest) => AllSystems (m :: Type -> Type) (Run constraints sys ': rest :: [Type]) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

type SystemIn m (Run constraints sys) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Internal

type SystemIn m (Run constraints sys) = SystemIn m sys

type family UnwrapSystem runSys where ... Source #

Equations

UnwrapSystem (Run constraints sys) = sys 
UnwrapSystem sys = sys 

type family GetConstraints runSys :: [Type] where ... Source #

Equations

GetConstraints (Run constraints sys) = constraints 
GetConstraints sys = '[] :: [Type]