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

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

Documentation

module Aztecs.ECS

load :: (ArrowQuery q, ArrowSystem q arr, Asset a) => AssetLoader a o -> arr () o Source #

data Camera Source #

Camera component.

Constructors

Camera 

Fields

Instances

Instances details
Component Camera Source # 
Instance details

Defined in Aztecs.Camera

Associated Types

type StorageT Camera Source #

Generic Camera Source # 
Instance details

Defined in Aztecs.Camera

Associated Types

type Rep Camera :: Type -> Type #

Methods

from :: Camera -> Rep Camera x #

to :: Rep Camera x -> Camera #

Show Camera Source # 
Instance details

Defined in Aztecs.Camera

NFData Camera Source # 
Instance details

Defined in Aztecs.Camera

Methods

rnf :: Camera -> () #

type StorageT Camera Source # 
Instance details

Defined in Aztecs.Camera

type Rep Camera Source # 
Instance details

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

Instances details
Component CameraTarget Source # 
Instance details

Defined in Aztecs.Camera

Associated Types

type StorageT CameraTarget Source #

Generic CameraTarget Source # 
Instance details

Defined in Aztecs.Camera

Associated Types

type Rep CameraTarget :: Type -> Type #

Show CameraTarget Source # 
Instance details

Defined in Aztecs.Camera

NFData CameraTarget Source # 
Instance details

Defined in Aztecs.Camera

Methods

rnf :: CameraTarget -> () #

Eq CameraTarget Source # 
Instance details

Defined in Aztecs.Camera

type StorageT CameraTarget Source # 
Instance details

Defined in Aztecs.Camera

type Rep CameraTarget Source # 
Instance details

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)))

data Key Source #

Instances

Instances details
Bounded Key Source # 
Instance details

Defined in Aztecs.Input

Methods

minBound :: Key #

maxBound :: Key #

Enum Key Source # 
Instance details

Defined in Aztecs.Input

Methods

succ :: Key -> Key #

pred :: Key -> Key #

toEnum :: Int -> Key #

fromEnum :: Key -> Int #

enumFrom :: Key -> [Key] #

enumFromThen :: Key -> Key -> [Key] #

enumFromTo :: Key -> Key -> [Key] #

enumFromThenTo :: Key -> Key -> Key -> [Key] #

Generic Key Source # 
Instance details

Defined in Aztecs.Input

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Show Key Source # 
Instance details

Defined in Aztecs.Input

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

NFData Key Source # 
Instance details

Defined in Aztecs.Input

Methods

rnf :: Key -> () #

Eq Key Source # 
Instance details

Defined in Aztecs.Input

Methods

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

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

Ord Key Source # 
Instance details

Defined in Aztecs.Input

Methods

compare :: Key -> Key -> Ordering #

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

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

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

type Rep Key Source # 
Instance details

Defined in Aztecs.Input

type Rep Key = D1 ('MetaData "Key" "Aztecs.Input" "aztecs-0.8.0-5YWGoxTs0Vw9iciqZAe9GO" 'False) ((((((C1 ('MetaCons "KeyA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyB" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KeyC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyE" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KeyF" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyG" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyH" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyI" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyJ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyK" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "KeyL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyM" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyN" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyO" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyQ" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KeyR" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyU" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyV" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyW" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "KeyX" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyZ" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Key0" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Key1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Key2" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Key3" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Key4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Key5" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Key6" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Key7" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Key8" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Key9" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyF1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyF2" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyF3" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyF4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyF5" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KeyF6" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyF7" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyF8" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyF9" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyF10" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyF11" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "KeyF12" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyEscape" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyEnter" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeySpace" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyBackspace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyTab" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KeyCapsLock" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyShift" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyCtrl" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyAlt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyRight" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "KeyUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyHome" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyPageUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyPageDown" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KeyInsert" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyDelete" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyMinus" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyEquals" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyBracketLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyBracketRight" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "KeyBackslash" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeySemicolon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyComma" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyPeriod" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeySlash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyNumLock" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KeyNumpad0" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyNumpad1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyNumpad2" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyNumpad3" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyNumpad4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyNumpad5" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "KeyNumpad6" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyNumpad7" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyNumpad8" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyNumpad9" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyNumpadDivide" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyNumpadMultiply" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KeyNumpadMinus" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyNumpadPlus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyNumpadEnter" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KeyNumpadPeriod" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeySuper" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyMenu" 'PrefixI 'False) (U1 :: Type -> Type))))))))

data KeyboardInput Source #

Keyboard input component.

Constructors

KeyboardInput 

Fields

Instances

Instances details
Component KeyboardInput Source # 
Instance details

Defined in Aztecs.Input

Associated Types

type StorageT KeyboardInput Source #

Generic KeyboardInput Source # 
Instance details

Defined in Aztecs.Input

Associated Types

type Rep KeyboardInput :: Type -> Type #

Show KeyboardInput Source # 
Instance details

Defined in Aztecs.Input

NFData KeyboardInput Source # 
Instance details

Defined in Aztecs.Input

Methods

rnf :: KeyboardInput -> () #

type StorageT KeyboardInput Source # 
Instance details

Defined in Aztecs.Input

type Rep KeyboardInput Source # 
Instance details

Defined in Aztecs.Input

type Rep KeyboardInput = D1 ('MetaData "KeyboardInput" "Aztecs.Input" "aztecs-0.8.0-5YWGoxTs0Vw9iciqZAe9GO" 'False) (C1 ('MetaCons "KeyboardInput" 'PrefixI 'True) (S1 ('MetaSel ('Just "keyboardEvents") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map Key InputMotion)) :*: S1 ('MetaSel ('Just "keyboardPressed") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set Key))))

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

Instances details
Component MouseInput Source # 
Instance details

Defined in Aztecs.Input

Associated Types

type StorageT MouseInput Source #

Generic MouseInput Source # 
Instance details

Defined in Aztecs.Input

Associated Types

type Rep MouseInput :: Type -> Type #

Show MouseInput Source # 
Instance details

Defined in Aztecs.Input

NFData MouseInput Source # 
Instance details

Defined in Aztecs.Input

Methods

rnf :: MouseInput -> () #

type StorageT MouseInput Source # 
Instance details

Defined in Aztecs.Input

type Rep MouseInput Source # 
Instance details

Defined in Aztecs.Input

type Rep MouseInput = D1 ('MetaData "MouseInput" "Aztecs.Input" "aztecs-0.8.0-5YWGoxTs0Vw9iciqZAe9GO" 'False) (C1 ('MetaCons "MouseInput" 'PrefixI 'True) (S1 ('MetaSel ('Just "mousePosition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 Int)) :*: (S1 ('MetaSel ('Just "mouseOffset") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 Int)) :*: S1 ('MetaSel ('Just "mouseButtons") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map MouseButton InputMotion)))))

newtype Time Source #

Time component.

Constructors

Time 

Fields

Instances

Instances details
Component Time Source # 
Instance details

Defined in Aztecs.Time

Associated Types

type StorageT Time Source #

Generic Time Source # 
Instance details

Defined in Aztecs.Time

Associated Types

type Rep Time :: Type -> Type #

Methods

from :: Time -> Rep Time x #

to :: Rep Time x -> Time #

Num Time Source # 
Instance details

Defined in Aztecs.Time

Methods

(+) :: Time -> Time -> Time #

(-) :: Time -> Time -> Time #

(*) :: Time -> Time -> Time #

negate :: Time -> Time #

abs :: Time -> Time #

signum :: Time -> Time #

fromInteger :: Integer -> Time #

Show Time Source # 
Instance details

Defined in Aztecs.Time

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

NFData Time Source # 
Instance details

Defined in Aztecs.Time

Methods

rnf :: Time -> () #

Eq Time Source # 
Instance details

Defined in Aztecs.Time

Methods

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

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

Ord Time Source # 
Instance details

Defined in Aztecs.Time

Methods

compare :: Time -> Time -> Ordering #

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

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

(>) :: Time -> Time -> Bool #

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

max :: Time -> Time -> Time #

min :: Time -> Time -> Time #

type StorageT Time Source # 
Instance details

Defined in Aztecs.Time

type StorageT Time = [Time]
type Rep Time Source # 
Instance details

Defined in Aztecs.Time

type Rep Time = D1 ('MetaData "Time" "Aztecs.Time" "aztecs-0.8.0-5YWGoxTs0Vw9iciqZAe9GO" 'True) (C1 ('MetaCons "Time" 'PrefixI 'True) (S1 ('MetaSel ('Just "elapsedMS") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

data Transform v r Source #

Transform component.

Constructors

Transform 

Instances

Instances details
Component (Transform (V2 Int) Int) Source # 
Instance details

Defined in Aztecs.Transform

Associated Types

type StorageT (Transform (V2 Int) Int) Source #

(Num v, Num r) => Monoid (Transform v r) Source # 
Instance details

Defined in Aztecs.Transform

Methods

mempty :: Transform v r #

mappend :: Transform v r -> Transform v r -> Transform v r #

mconcat :: [Transform v r] -> Transform v r #

(Num v, Num r) => Semigroup (Transform v r) Source # 
Instance details

Defined in Aztecs.Transform

Methods

(<>) :: Transform v r -> Transform v r -> Transform v r #

sconcat :: NonEmpty (Transform v r) -> Transform v r #

stimes :: Integral b => b -> Transform v r -> Transform v r #

Generic (Transform v r) Source # 
Instance details

Defined in Aztecs.Transform

Associated Types

type Rep (Transform v r) :: Type -> Type #

Methods

from :: Transform v r -> Rep (Transform v r) x #

to :: Rep (Transform v r) x -> Transform v r #

(Show r, Show v) => Show (Transform v r) Source # 
Instance details

Defined in Aztecs.Transform

Methods

showsPrec :: Int -> Transform v r -> ShowS #

show :: Transform v r -> String #

showList :: [Transform v r] -> ShowS #

(NFData v, NFData r) => NFData (Transform v r) Source # 
Instance details

Defined in Aztecs.Transform

Methods

rnf :: Transform v r -> () #

(Eq r, Eq v) => Eq (Transform v r) Source # 
Instance details

Defined in Aztecs.Transform

Methods

(==) :: Transform v r -> Transform v r -> Bool #

(/=) :: Transform v r -> Transform v r -> Bool #

type StorageT (Transform (V2 Int) Int) Source # 
Instance details

Defined in Aztecs.Transform

type Rep (Transform v r) Source # 
Instance details

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))))

type Transform2D = Transform (V2 Int) Int Source #

2D transform component.

transform2d :: Transform2D Source #

Empty transform.

newtype Size v Source #

Size component.

Constructors

Size 

Fields

Instances

Instances details
Component (Size (V2 Int)) Source # 
Instance details

Defined in Aztecs.Transform

Associated Types

type StorageT (Size (V2 Int)) Source #

Generic (Size v) Source # 
Instance details

Defined in Aztecs.Transform

Associated Types

type Rep (Size v) :: Type -> Type #

Methods

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

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

NFData v => NFData (Size v) Source # 
Instance details

Defined in Aztecs.Transform

Methods

rnf :: Size v -> () #

type StorageT (Size (V2 Int)) Source # 
Instance details

Defined in Aztecs.Transform

type StorageT (Size (V2 Int)) = [Size (V2 Int)]
type Rep (Size v) Source # 
Instance details

Defined in Aztecs.Transform

type Rep (Size v) = D1 ('MetaData "Size" "Aztecs.Transform" "aztecs-0.8.0-5YWGoxTs0Vw9iciqZAe9GO" 'True) (C1 ('MetaCons "Size" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v)))

data Window Source #

Window component.

Constructors

Window 

Fields

Instances

Instances details
Component Window Source # 
Instance details

Defined in Aztecs.Window

Associated Types

type StorageT Window Source #

Generic Window Source # 
Instance details

Defined in Aztecs.Window

Associated Types

type Rep Window :: Type -> Type #

Methods

from :: Window -> Rep Window x #

to :: Rep Window x -> Window #

Show Window Source # 
Instance details

Defined in Aztecs.Window

NFData Window Source # 
Instance details

Defined in Aztecs.Window

Methods

rnf :: Window -> () #

type StorageT Window Source # 
Instance details

Defined in Aztecs.Window

type Rep Window Source # 
Instance details

Defined in Aztecs.Window

type Rep Window = D1 ('MetaData "Window" "Aztecs.Window" "aztecs-0.8.0-5YWGoxTs0Vw9iciqZAe9GO" 'False) (C1 ('MetaCons "Window" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowTitle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)))