swarm-0.1.0.0: 2D resource gathering game with programmable robots
CopyrightBrent Yorgey
LicenseBSD-3-Clause
Maintainerbyorgey@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Swarm.Game.World

Description

A world refers to the grid on which the game takes place, and the things in it (besides robots). A world has a base, immutable terrain layer, where each cell contains a terrain type, and a mutable entity layer, with at most one entity per cell.

A world is technically finite but practically infinite (worlds are indexed by 64-bit signed integers, so they correspond to a \( 2^{64} \times 2^{64} \) torus).

Synopsis

World coordinates

newtype Coords Source #

World coordinates use (row,column) format, with the row increasing as we move down the screen. This format plays nicely with drawing the screen.

Constructors

Coords 

Fields

Instances

Instances details
Generic Coords Source # 
Instance details

Defined in Swarm.Game.World

Associated Types

type Rep Coords :: Type -> Type #

Methods

from :: Coords -> Rep Coords x #

to :: Rep Coords x -> Coords #

Ix Coords Source # 
Instance details

Defined in Swarm.Game.World

Show Coords Source # 
Instance details

Defined in Swarm.Game.World

Eq Coords Source # 
Instance details

Defined in Swarm.Game.World

Methods

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

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

Ord Coords Source # 
Instance details

Defined in Swarm.Game.World

Wrapped Coords Source # 
Instance details

Defined in Swarm.Game.World

Associated Types

type Unwrapped Coords #

Rewrapped Coords t Source # 
Instance details

Defined in Swarm.Game.World

type Rep Coords Source # 
Instance details

Defined in Swarm.Game.World

type Rep Coords = D1 ('MetaData "Coords" "Swarm.Game.World" "swarm-0.1.0.0-CFIPFkeeTOhKLDsfeG4aYn" 'True) (C1 ('MetaCons "Coords" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoords") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int64, Int64))))
type Unwrapped Coords Source # 
Instance details

Defined in Swarm.Game.World

type Unwrapped Coords = GUnwrapped (Rep Coords)

locToCoords :: V2 Int64 -> Coords Source #

Convert an (x,y) location to a Coords value.

coordsToLoc :: Coords -> V2 Int64 Source #

Convert Coords to an (x,y) location.

Worlds

newtype WorldFun t e Source #

A WorldFun t e represents a 2D world with terrain of type t (exactly one per cell) and entities of type e (at most one per cell).

Constructors

WF 

Fields

Instances

Instances details
Bifunctor WorldFun Source # 
Instance details

Defined in Swarm.Game.World

Methods

bimap :: (a -> b) -> (c -> d) -> WorldFun a c -> WorldFun b d #

first :: (a -> b) -> WorldFun a c -> WorldFun b c #

second :: (b -> c) -> WorldFun a b -> WorldFun a c #

worldFunFromArray :: Array (Int64, Int64) (t, Maybe e) -> (t, Maybe e) -> WorldFun t e Source #

Create a world function from a finite array of specified cells plus a single default cell to use everywhere else.

data World t e Source #

A World consists of a WorldFun that specifies the initial world, a cache of loaded square tiles to make lookups faster, and a map storing locations whose entities have changed from their initial values.

Right now the World simply holds on to all the tiles it has ever loaded. Ideally it would use some kind of LRU caching scheme to keep memory usage bounded, but it would be a bit tricky, and in any case it's probably not going to matter much for a while. Once tile loads can trigger robots to spawn, it would also make for some difficult decisions in terms of how to handle respawning.

Tile management

loadCell :: IArray UArray t => Coords -> World t e -> World t e Source #

Load the tile containing a specific cell.

loadRegion :: forall t e. IArray UArray t => (Coords, Coords) -> World t e -> World t e Source #

Load all the tiles which overlap the given rectangular region (specified as an upper-left and lower-right corner).

World functions

newWorld :: WorldFun t e -> World t e Source #

Create a new World from a WorldFun.

emptyWorld :: t -> World t e Source #

Create a new empty World consisting of nothing but the given terrain.

lookupTerrain :: IArray UArray t => Coords -> World t e -> t Source #

Look up the terrain value at certain coordinates: try looking it up in the tile cache first, and fall back to running the WorldFun otherwise.

This function does not ensure that the tile containing the given coordinates is loaded. For that, see lookupTerrainM.

lookupEntity :: Coords -> World t e -> Maybe e Source #

Look up the entity at certain coordinates: first, see if it is in the map of locations with changed entities; then try looking it up in the tile cache first; and finally fall back to running the WorldFun.

This function does not ensure that the tile containing the given coordinates is loaded. For that, see lookupEntityM.

update :: Coords -> (Maybe e -> Maybe e) -> World t e -> World t e Source #

Update the entity (or absence thereof) at a certain location, returning an updated World. See also updateM.

Monadic variants

lookupTerrainM :: forall t e sig m. (Has (State (World t e)) sig m, IArray UArray t) => Coords -> m t Source #

A stateful variant of lookupTerrain, which first loads the tile containing the given coordinates if it is not already loaded, then looks up the terrain value.

lookupEntityM :: forall t e sig m. (Has (State (World t e)) sig m, IArray UArray t) => Coords -> m (Maybe e) Source #

A stateful variant of lookupTerrain, which first loads the tile containing the given coordinates if it is not already loaded, then looks up the terrain value.

updateM :: forall t e sig m. (Has (State (World t e)) sig m, IArray UArray t) => Coords -> (Maybe e -> Maybe e) -> m () Source #

A stateful variant of update, which also ensures the tile containing the given coordinates is loaded.