Safe Haskell | None |
---|---|
Language | Haskell2010 |
Game.LambdaHack.Common.Tile
Description
Operations concerning dungeon level tiles.
Unlike for many other content types, there is no type Tile
,
of particular concrete tiles in the dungeon,
corresponding to TileKind
(the type of kinds of terrain tiles).
This is because the tiles are too numerous and there's not enough
storage space for a well-rounded Tile
type, on one hand,
and on the other hand, tiles are accessed
too often in performance critical code
to try to compress their representation and/or recompute them.
Instead, of defining a Tile
type, we express various properties
of concrete tiles by arrays or sparse EnumMaps, as appropriate.
Actors at normal speed (2 m/s) take one turn to move one tile (1 m by 1 m).
Synopsis
- data TileSpeedup = TileSpeedup {
- isClearTab :: Tab Bool
- isLitTab :: Tab Bool
- isHideoutTab :: Tab Bool
- isWalkableTab :: Tab Bool
- isDoorTab :: Tab Bool
- isOpenableTab :: Tab Bool
- isClosableTab :: Tab Bool
- isChangableTab :: Tab Bool
- isModifiableWithTab :: Tab Bool
- isSuspectTab :: Tab Bool
- isHideAsTab :: Tab Bool
- consideredByAITab :: Tab Bool
- isVeryOftenItemTab :: Tab Bool
- isCommonItemTab :: Tab Bool
- isOftenActorTab :: Tab Bool
- isNoItemTab :: Tab Bool
- isNoActorTab :: Tab Bool
- isEasyOpenTab :: Tab Bool
- isEmbedTab :: Tab Bool
- isAquaticTab :: Tab Bool
- alterMinSkillTab :: Tab Word8
- alterMinWalkTab :: Tab Word8
- newtype Tab a = Tab (Vector a)
- speedupTile :: Bool -> ContentData TileKind -> TileSpeedup
- isClear :: TileSpeedup -> ContentId TileKind -> Bool
- isLit :: TileSpeedup -> ContentId TileKind -> Bool
- isHideout :: TileSpeedup -> ContentId TileKind -> Bool
- isWalkable :: TileSpeedup -> ContentId TileKind -> Bool
- isDoor :: TileSpeedup -> ContentId TileKind -> Bool
- isChangable :: TileSpeedup -> ContentId TileKind -> Bool
- isSuspect :: TileSpeedup -> ContentId TileKind -> Bool
- isHideAs :: TileSpeedup -> ContentId TileKind -> Bool
- consideredByAI :: TileSpeedup -> ContentId TileKind -> Bool
- isExplorable :: TileSpeedup -> ContentId TileKind -> Bool
- isVeryOftenItem :: TileSpeedup -> ContentId TileKind -> Bool
- isCommonItem :: TileSpeedup -> ContentId TileKind -> Bool
- isOftenActor :: TileSpeedup -> ContentId TileKind -> Bool
- isNoItem :: TileSpeedup -> ContentId TileKind -> Bool
- isNoActor :: TileSpeedup -> ContentId TileKind -> Bool
- isEasyOpen :: TileSpeedup -> ContentId TileKind -> Bool
- isEmbed :: TileSpeedup -> ContentId TileKind -> Bool
- isAquatic :: TileSpeedup -> ContentId TileKind -> Bool
- alterMinSkill :: TileSpeedup -> ContentId TileKind -> Int
- alterMinWalk :: TileSpeedup -> ContentId TileKind -> Int
- kindHasFeature :: Feature -> TileKind -> Bool
- openTo :: ContentData TileKind -> ContentId TileKind -> Rnd (ContentId TileKind)
- closeTo :: ContentData TileKind -> ContentId TileKind -> Rnd (ContentId TileKind)
- embeddedItems :: ContentData TileKind -> ContentId TileKind -> [GroupName ItemKind]
- revealAs :: ContentData TileKind -> ContentId TileKind -> Rnd (ContentId TileKind)
- obscureAs :: ContentData TileKind -> ContentId TileKind -> Rnd (ContentId TileKind)
- hideAs :: ContentData TileKind -> ContentId TileKind -> Maybe (ContentId TileKind)
- buildAs :: ContentData TileKind -> ContentId TileKind -> ContentId TileKind
- isEasyOpenKind :: TileKind -> Bool
- isOpenable :: TileSpeedup -> ContentId TileKind -> Bool
- isClosable :: TileSpeedup -> ContentId TileKind -> Bool
- isModifiable :: TileSpeedup -> ContentId TileKind -> Bool
- createTab :: Unbox a => ContentData TileKind -> (TileKind -> a) -> Tab a
- createTabWithKey :: Unbox a => ContentData TileKind -> (ContentId TileKind -> TileKind -> a) -> Tab a
- accessTab :: Unbox a => Tab a -> ContentId TileKind -> a
- alterMinSkillKind :: ContentId TileKind -> TileKind -> Word8
- alterMinWalkKind :: ContentId TileKind -> TileKind -> Word8
Tile property lookup speedup tables and their construction
data TileSpeedup Source #
A lot of tabulated maps from tile kind identifier to a property of the tile kind.
Constructors
TileSpeedup | |
Fields
|
speedupTile :: Bool -> ContentData TileKind -> TileSpeedup Source #
Speedup property lookups
isClear :: TileSpeedup -> ContentId TileKind -> Bool Source #
Whether a tile does not block vision. Essential for efficiency of FOV, hence tabulated.
isLit :: TileSpeedup -> ContentId TileKind -> Bool Source #
Whether a tile has ambient light --- is lit on its own. Essential for efficiency of Perception, hence tabulated.
isHideout :: TileSpeedup -> ContentId TileKind -> Bool Source #
Whether a tile is a good hideout: walkable and dark.
isWalkable :: TileSpeedup -> ContentId TileKind -> Bool Source #
Whether actors can walk into a tile. Essential for efficiency of pathfinding, hence tabulated.
isDoor :: TileSpeedup -> ContentId TileKind -> Bool Source #
Whether a tile is a door, open or closed. Essential for efficiency of pathfinding, hence tabulated.
isChangable :: TileSpeedup -> ContentId TileKind -> Bool Source #
Whether a tile is changable.
isSuspect :: TileSpeedup -> ContentId TileKind -> Bool Source #
Whether a tile is suspect. Essential for efficiency of pathfinding, hence tabulated.
consideredByAI :: TileSpeedup -> ContentId TileKind -> Bool Source #
isExplorable :: TileSpeedup -> ContentId TileKind -> Bool Source #
Whether one can easily explore a tile, possibly finding a treasure, either spawned there or dropped there by a (dying from poison) foe. Doors can't be explorable since revealing a secret tile should not change it's explorable status. Also, door explorable status should not depend on whether they are open or not, so that a foe opening a door doesn't force us to backtrack to explore it. Still, a foe that digs through a wall will affect our exploration counter and if content lets walls contain threasure, such backtraking makes sense.
isVeryOftenItem :: TileSpeedup -> ContentId TileKind -> Bool Source #
isCommonItem :: TileSpeedup -> ContentId TileKind -> Bool Source #
isOftenActor :: TileSpeedup -> ContentId TileKind -> Bool Source #
isEasyOpen :: TileSpeedup -> ContentId TileKind -> Bool Source #
Whether a tile kind (specified by its id) has an OpenTo
feature
or is walkable even without opening.
alterMinSkill :: TileSpeedup -> ContentId TileKind -> Int Source #
alterMinWalk :: TileSpeedup -> ContentId TileKind -> Int Source #
Slow property lookups
embeddedItems :: ContentData TileKind -> ContentId TileKind -> [GroupName ItemKind] Source #
isEasyOpenKind :: TileKind -> Bool Source #
isOpenable :: TileSpeedup -> ContentId TileKind -> Bool Source #
Whether a tile kind (specified by its id) has an OpenTo
feature.
isClosable :: TileSpeedup -> ContentId TileKind -> Bool Source #
Whether a tile kind (specified by its id) has a CloseTo
feature.
isModifiable :: TileSpeedup -> ContentId TileKind -> Bool Source #
Internal operations
createTabWithKey :: Unbox a => ContentData TileKind -> (ContentId TileKind -> TileKind -> a) -> Tab a Source #