swarm-0.7.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellNone
LanguageHaskell2010

Swarm.Game.Display

Description

Utilities for describing how to display in-game entities in the TUI.

Synopsis

The display record

type Priority = Int Source #

Display priority. Entities with higher priority will be drawn on top of entities with lower priority.

data Attribute Source #

An internal attribute name.

Constructors

ADefault 
ARobot 
AEntity 
AWorld Text 

Instances

Instances details
FromJSON Attribute Source # 
Instance details

Defined in Swarm.Game.Display

ToJSON Attribute Source # 
Instance details

Defined in Swarm.Game.Display

Generic Attribute Source # 
Instance details

Defined in Swarm.Game.Display

Associated Types

type Rep Attribute 
Instance details

Defined in Swarm.Game.Display

type Rep Attribute = D1 ('MetaData "Attribute" "Swarm.Game.Display" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-scenario" 'False) ((C1 ('MetaCons "ADefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ARobot" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AEntity" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AWorld" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))
Show Attribute Source # 
Instance details

Defined in Swarm.Game.Display

Eq Attribute Source # 
Instance details

Defined in Swarm.Game.Display

Ord Attribute Source # 
Instance details

Defined in Swarm.Game.Display

Hashable Attribute Source # 
Instance details

Defined in Swarm.Game.Display

type Rep Attribute Source # 
Instance details

Defined in Swarm.Game.Display

type Rep Attribute = D1 ('MetaData "Attribute" "Swarm.Game.Display" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-scenario" 'False) ((C1 ('MetaCons "ADefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ARobot" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AEntity" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AWorld" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))

data Display Source #

A record explaining how to display an entity in the TUI.

Instances

Instances details
FromJSON Display Source # 
Instance details

Defined in Swarm.Game.Display

ToJSON Display Source # 
Instance details

Defined in Swarm.Game.Display

Monoid Display Source # 
Instance details

Defined in Swarm.Game.Display

Semigroup Display Source # 
Instance details

Defined in Swarm.Game.Display

Generic Display Source # 
Instance details

Defined in Swarm.Game.Display

Associated Types

type Rep Display 
Instance details

Defined in Swarm.Game.Display

type Rep Display = D1 ('MetaData "Display" "Swarm.Game.Display" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-scenario" 'False) (C1 ('MetaCons "Display" 'PrefixI 'True) (((S1 ('MetaSel ('Just "_defaultChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Char) :*: S1 ('MetaSel ('Just "_orientationMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map AbsoluteDir Char))) :*: (S1 ('MetaSel ('Just "_curOrientation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Direction)) :*: S1 ('MetaSel ('Just "_boundaryOverride") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Char)))) :*: ((S1 ('MetaSel ('Just "_displayAttr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attribute) :*: S1 ('MetaSel ('Just "_displayPriority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Priority)) :*: (S1 ('MetaSel ('Just "_invisible") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_childInheritance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ChildInheritance)))))

Methods

from :: Display -> Rep Display x #

to :: Rep Display x -> Display #

Show Display Source # 
Instance details

Defined in Swarm.Game.Display

Eq Display Source # 
Instance details

Defined in Swarm.Game.Display

Methods

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

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

Ord Display Source # 
Instance details

Defined in Swarm.Game.Display

Hashable Display Source # 
Instance details

Defined in Swarm.Game.Display

Methods

hashWithSalt :: Int -> Display -> Int #

hash :: Display -> Int #

FromJSONE Display Display Source # 
Instance details

Defined in Swarm.Game.Display

type Rep Display Source # 
Instance details

Defined in Swarm.Game.Display

type Rep Display = D1 ('MetaData "Display" "Swarm.Game.Display" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-scenario" 'False) (C1 ('MetaCons "Display" 'PrefixI 'True) (((S1 ('MetaSel ('Just "_defaultChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Char) :*: S1 ('MetaSel ('Just "_orientationMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map AbsoluteDir Char))) :*: (S1 ('MetaSel ('Just "_curOrientation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Direction)) :*: S1 ('MetaSel ('Just "_boundaryOverride") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Char)))) :*: ((S1 ('MetaSel ('Just "_displayAttr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attribute) :*: S1 ('MetaSel ('Just "_displayPriority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Priority)) :*: (S1 ('MetaSel ('Just "_invisible") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_childInheritance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ChildInheritance)))))

data ChildInheritance Source #

Instances

Instances details
Generic ChildInheritance Source # 
Instance details

Defined in Swarm.Game.Display

Associated Types

type Rep ChildInheritance 
Instance details

Defined in Swarm.Game.Display

type Rep ChildInheritance = D1 ('MetaData "ChildInheritance" "Swarm.Game.Display" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-scenario" 'False) (C1 ('MetaCons "Invisible" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Inherit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DefaultDisplay" 'PrefixI 'False) (U1 :: Type -> Type)))
Show ChildInheritance Source # 
Instance details

Defined in Swarm.Game.Display

Eq ChildInheritance Source # 
Instance details

Defined in Swarm.Game.Display

Ord ChildInheritance Source # 
Instance details

Defined in Swarm.Game.Display

Hashable ChildInheritance Source # 
Instance details

Defined in Swarm.Game.Display

type Rep ChildInheritance Source # 
Instance details

Defined in Swarm.Game.Display

type Rep ChildInheritance = D1 ('MetaData "ChildInheritance" "Swarm.Game.Display" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-scenario" 'False) (C1 ('MetaCons "Invisible" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Inherit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DefaultDisplay" 'PrefixI 'False) (U1 :: Type -> Type)))

Fields

defaultChar :: Lens' Display Char Source #

The default character to use for display.

orientationMap :: Lens' Display (Map AbsoluteDir Char) Source #

For robots or other entities that have an orientation, this map optionally associates different display characters with different orientations. If an orientation is not in the map, the defaultChar will be used.

curOrientation :: Lens' Display (Maybe Direction) Source #

The display caches the current orientation of the entity, so we know which character to use from the orientation map.

boundaryOverride :: Lens' Display (Maybe Char) Source #

The display character to substitute when neighbor boundaries are present

displayAttr :: Lens' Display Attribute Source #

The attribute to use for display.

displayPriority :: Lens' Display Priority Source #

This entity's display priority. Higher priorities are drawn on top of lower.

invisible :: Lens' Display Bool Source #

Whether the entity is currently invisible.

childInheritance :: Lens' Display ChildInheritance Source #

For robots, whether children of this inherit the parent's display

Rendering

displayChar :: Display -> Char Source #

Look up the character that should be used for a display.

hidden :: Display -> Display Source #

Modify a display to use a ? character for entities that are hidden/unknown.

Neighbor-based boundary rendering

getBoundaryDisplay :: (AbsoluteDir -> Bool) -> Maybe Char Source #

Construction

defaultTerrainDisplay :: Attribute -> Display Source #

The default way to display some terrain using the given character and attribute, with priority 0.

defaultEntityDisplay :: Char -> Display Source #

Construct a default display for an entity that uses only a single display character, the default entity attribute, and priority 1.

defaultRobotDisplay :: Display Source #

Construct a default robot display for a given orientation, with display characters "X^>v<", the default robot attribute, and priority 10.

Note that the defaultChar is used for direction DDown and is overridden for the special base robot.