Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Aztecs
Description
Aztecs is a type-safe and friendly ECS for games and more.
An ECS is a modern approach to organizing your application state as a database, providing patterns for data-oriented design and parallel processing.
The ECS architecture is composed of three main concepts:
Entities
An entity is an object comprised of zero or more components.
In Aztecs, entities are represented by their EntityID
, a unique identifier.
Components
A Component
holds the data for a particular aspect of an entity.
For example, a zombie entity might have a Health
and a Transform
component.
newtype Position = Position Int deriving (Show) instance Component Position newtype Velocity = Velocity Int deriving (Show) instance Component Velocity
Systems
A System
is a pipeline that processes entities and their components.
Systems in Aztecs either run in sequence or in parallel automatically based on the components they access.
Systems can access game state in two ways:
Access
An Access
can be queued for full access to the World
, after a system is complete.
Access
allows for spawning, inserting, and removing components.
setup :: System () () setup = S.queue . const . A.spawn_ $ bundle (Position 0) <> bundle (Velocity 1)
Queries
A Query
can read and write matching components.
move :: System () () move = S.map ( proc () -> do Velocity v <- Q.fetch -< () Position p <- Q.fetch -< () Q.set -< Position $ p + v ) >>> S.run print
Finally, systems can be run on a World
to produce a result.
main :: IO () main = runSystem_ $ setup >>> S.forever move
Synopsis
- module Aztecs.ECS
- asset :: MonadAssetLoader a m => FilePath -> AssetConfig a -> m (Handle a)
- load :: (ArrowQuery q, ArrowSystem q arr, Asset a) => AssetLoader a o -> arr () o
- data Camera = Camera {
- cameraViewport :: !(V2 Int)
- cameraScale :: !(V2 Float)
- newtype CameraTarget = CameraTarget {}
- data Key
- = KeyA
- | KeyB
- | KeyC
- | KeyD
- | KeyE
- | KeyF
- | KeyG
- | KeyH
- | KeyI
- | KeyJ
- | KeyK
- | KeyL
- | KeyM
- | KeyN
- | KeyO
- | KeyP
- | KeyQ
- | KeyR
- | KeyS
- | KeyT
- | KeyU
- | KeyV
- | KeyW
- | KeyX
- | KeyY
- | KeyZ
- | Key0
- | Key1
- | Key2
- | Key3
- | Key4
- | Key5
- | Key6
- | Key7
- | Key8
- | Key9
- | KeyF1
- | KeyF2
- | KeyF3
- | KeyF4
- | KeyF5
- | KeyF6
- | KeyF7
- | KeyF8
- | KeyF9
- | KeyF10
- | KeyF11
- | KeyF12
- | KeyEscape
- | KeyEnter
- | KeySpace
- | KeyBackspace
- | KeyTab
- | KeyCapsLock
- | KeyShift
- | KeyCtrl
- | KeyAlt
- | KeyLeft
- | KeyRight
- | KeyUp
- | KeyDown
- | KeyHome
- | KeyEnd
- | KeyPageUp
- | KeyPageDown
- | KeyInsert
- | KeyDelete
- | KeyMinus
- | KeyEquals
- | KeyBracketLeft
- | KeyBracketRight
- | KeyBackslash
- | KeySemicolon
- | KeyComma
- | KeyPeriod
- | KeySlash
- | KeyNumLock
- | KeyNumpad0
- | KeyNumpad1
- | KeyNumpad2
- | KeyNumpad3
- | KeyNumpad4
- | KeyNumpad5
- | KeyNumpad6
- | KeyNumpad7
- | KeyNumpad8
- | KeyNumpad9
- | KeyNumpadDivide
- | KeyNumpadMultiply
- | KeyNumpadMinus
- | KeyNumpadPlus
- | KeyNumpadEnter
- | KeyNumpadPeriod
- | KeySuper
- | KeyMenu
- data KeyboardInput = KeyboardInput {
- keyboardEvents :: !(Map Key InputMotion)
- keyboardPressed :: !(Set Key)
- isKeyPressed :: Key -> KeyboardInput -> Bool
- wasKeyPressed :: Key -> KeyboardInput -> Bool
- wasKeyReleased :: Key -> KeyboardInput -> Bool
- data MouseInput = MouseInput {
- mousePosition :: !(Point V2 Int)
- mouseOffset :: !(V2 Int)
- mouseButtons :: !(Map MouseButton InputMotion)
- newtype Time = Time {}
- data Transform v r = Transform {
- transformTranslation :: !v
- transformRotation :: !r
- transformScale :: !v
- type Transform2D = Transform (V2 Int) Int
- transform2d :: Transform2D
- newtype Size v = Size {
- unSize :: v
- type Size2D = Size (V2 Int)
- size2D :: Size (V2 Integer)
- data Window = Window {
- windowTitle :: !String
Documentation
module Aztecs.ECS
asset :: MonadAssetLoader a m => FilePath -> AssetConfig a -> m (Handle a) Source #
load :: (ArrowQuery q, ArrowSystem q arr, Asset a) => AssetLoader a o -> arr () o Source #
Camera component.
Constructors
Camera | |
Fields
|
Instances
Component Camera Source # | |
Defined in Aztecs.Camera | |
Generic Camera Source # | |
Show Camera Source # | |
NFData Camera Source # | |
Defined in Aztecs.Camera | |
type StorageT Camera Source # | |
Defined in Aztecs.Camera | |
type Rep Camera Source # | |
Defined in Aztecs.Camera type Rep Camera = D1 ('MetaData "Camera" "Aztecs.Camera" "aztecs-0.8.0-5YWGoxTs0Vw9iciqZAe9GO" 'False) (C1 ('MetaCons "Camera" 'PrefixI 'True) (S1 ('MetaSel ('Just "cameraViewport") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 Int)) :*: S1 ('MetaSel ('Just "cameraScale") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 Float)))) |
newtype CameraTarget Source #
Camera target component.
Constructors
CameraTarget | |
Fields
|
Instances
Component CameraTarget Source # | |
Defined in Aztecs.Camera Associated Types type StorageT CameraTarget Source # | |
Generic CameraTarget Source # | |
Defined in Aztecs.Camera Associated Types type Rep CameraTarget :: Type -> Type # | |
Show CameraTarget Source # | |
Defined in Aztecs.Camera Methods showsPrec :: Int -> CameraTarget -> ShowS # show :: CameraTarget -> String # showList :: [CameraTarget] -> ShowS # | |
NFData CameraTarget Source # | |
Defined in Aztecs.Camera Methods rnf :: CameraTarget -> () # | |
Eq CameraTarget Source # | |
Defined in Aztecs.Camera | |
type StorageT CameraTarget Source # | |
Defined in Aztecs.Camera | |
type Rep CameraTarget Source # | |
Defined in Aztecs.Camera type Rep CameraTarget = D1 ('MetaData "CameraTarget" "Aztecs.Camera" "aztecs-0.8.0-5YWGoxTs0Vw9iciqZAe9GO" 'True) (C1 ('MetaCons "CameraTarget" 'PrefixI 'True) (S1 ('MetaSel ('Just "cameraTargetWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EntityID))) |
Constructors
Instances
data KeyboardInput Source #
Keyboard input component.
Constructors
KeyboardInput | |
Fields
|
Instances
isKeyPressed :: Key -> KeyboardInput -> Bool Source #
True
if this key is currently pressed.
wasKeyPressed :: Key -> KeyboardInput -> Bool Source #
True
if this key was pressed this frame.
wasKeyReleased :: Key -> KeyboardInput -> Bool Source #
True
if this key was released this frame.
data MouseInput Source #
Mouse input component.
Constructors
MouseInput | |
Fields
|
Instances
Time component.
Transform component.
Constructors
Transform | |
Fields
|
Instances
Component (Transform (V2 Int) Int) Source # | |
(Num v, Num r) => Monoid (Transform v r) Source # | |
(Num v, Num r) => Semigroup (Transform v r) Source # | |
Generic (Transform v r) Source # | |
(Show r, Show v) => Show (Transform v r) Source # | |
(NFData v, NFData r) => NFData (Transform v r) Source # | |
Defined in Aztecs.Transform | |
(Eq r, Eq v) => Eq (Transform v r) Source # | |
type StorageT (Transform (V2 Int) Int) Source # | |
type Rep (Transform v r) Source # | |
Defined in Aztecs.Transform type Rep (Transform v r) = D1 ('MetaData "Transform" "Aztecs.Transform" "aztecs-0.8.0-5YWGoxTs0Vw9iciqZAe9GO" 'False) (C1 ('MetaCons "Transform" 'PrefixI 'True) (S1 ('MetaSel ('Just "transformTranslation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 v) :*: (S1 ('MetaSel ('Just "transformRotation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 r) :*: S1 ('MetaSel ('Just "transformScale") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 v)))) |
transform2d :: Transform2D Source #
Empty transform.
Size component.
Window component.
Constructors
Window | |
Fields
|