Safe Haskell | None |
---|---|
Language | Haskell2010 |
Field Of View scanning.
See https://github.com/LambdaHack/LambdaHack/wiki/Fov-and-los for discussion.
Synopsis
- data FovValid a
- = FovValid a
- | FovInvalid
- type PerValidFid = EnumMap FactionId (EnumMap LevelId Bool)
- newtype PerReachable = PerReachable {}
- data CacheBeforeLucid = CacheBeforeLucid {}
- type PerActor = EnumMap ActorId (FovValid CacheBeforeLucid)
- data PerceptionCache = PerceptionCache {}
- type PerCacheLid = EnumMap LevelId PerceptionCache
- type PerCacheFid = EnumMap FactionId PerCacheLid
- newtype FovShine = FovShine {}
- newtype FovLucid = FovLucid {}
- type FovLucidLid = EnumMap LevelId (FovValid FovLucid)
- newtype FovClear = FovClear {}
- type FovClearLid = EnumMap LevelId FovClear
- newtype FovLit = FovLit {}
- type FovLitLid = EnumMap LevelId FovLit
- perceptionFromPTotal :: FactionId -> LevelId -> FovLucid -> CacheBeforeLucid -> State -> Perception
- perActorFromLevel :: PerActor -> (ActorId -> Actor) -> ActorMaxSkills -> FovClear -> PerActor
- boundSightByCalm :: Int -> Int64 -> Int
- totalFromPerActor :: PerActor -> CacheBeforeLucid
- lucidFromLevel :: FovClearLid -> FovLitLid -> State -> LevelId -> Level -> FovLucid
- perFidInDungeon :: State -> (FovLitLid, FovClearLid, FovLucidLid, PerValidFid, PerCacheFid, PerFid)
- perceptionFromPTotalNoStash :: FovLucid -> CacheBeforeLucid -> Perception
- cacheBeforeLucidFromActor :: FovClear -> Actor -> Skills -> CacheBeforeLucid
- shineFromLevel :: State -> LevelId -> Level -> FovShine
- floorLightSources :: DiscoveryAspect -> Level -> [(Point, Int)]
- lucidFromItems :: FovClear -> [(Point, Int)] -> [FovLucid]
- litFromLevel :: COps -> Level -> FovLit
- litInDungeon :: State -> FovLitLid
- clearFromLevel :: COps -> Level -> FovClear
- clearInDungeon :: State -> FovClearLid
- lucidInDungeon :: FovClearLid -> FovLitLid -> State -> FovLucidLid
- perLidFromFaction :: FovLucidLid -> FovClearLid -> FactionId -> State -> (PerLid, PerCacheLid)
- perceptionCacheFromLevel :: FovClearLid -> FactionId -> LevelId -> State -> PerceptionCache
- type Matrix = (Int, Int, Int, Int)
- fullscan :: Int -> Point -> FovClear -> EnumSet Point
Perception cache
type PerValidFid = EnumMap FactionId (EnumMap LevelId Bool) Source #
Main perception validity map, for all factions.
The inner type is not a set, due to an unbenchmarked theory that a constant shape map is faster.
newtype PerReachable Source #
Visually reachable positions (light passes through them to the actor). They need to be intersected with lucid positions to obtain visible positions.
Instances
Eq PerReachable Source # | |
Defined in Game.LambdaHack.Server.Fov (==) :: PerReachable -> PerReachable -> Bool # (/=) :: PerReachable -> PerReachable -> Bool # | |
Show PerReachable Source # | |
Defined in Game.LambdaHack.Server.Fov showsPrec :: Int -> PerReachable -> ShowS # show :: PerReachable -> String # showList :: [PerReachable] -> ShowS # |
data CacheBeforeLucid Source #
Instances
Eq CacheBeforeLucid Source # | |
Defined in Game.LambdaHack.Server.Fov (==) :: CacheBeforeLucid -> CacheBeforeLucid -> Bool # (/=) :: CacheBeforeLucid -> CacheBeforeLucid -> Bool # | |
Show CacheBeforeLucid Source # | |
Defined in Game.LambdaHack.Server.Fov showsPrec :: Int -> CacheBeforeLucid -> ShowS # show :: CacheBeforeLucid -> String # showList :: [CacheBeforeLucid] -> ShowS # |
data PerceptionCache Source #
Instances
Eq PerceptionCache Source # | |
Defined in Game.LambdaHack.Server.Fov (==) :: PerceptionCache -> PerceptionCache -> Bool # (/=) :: PerceptionCache -> PerceptionCache -> Bool # | |
Show PerceptionCache Source # | |
Defined in Game.LambdaHack.Server.Fov showsPrec :: Int -> PerceptionCache -> ShowS # show :: PerceptionCache -> String # showList :: [PerceptionCache] -> ShowS # |
type PerCacheLid = EnumMap LevelId PerceptionCache Source #
Server cache of perceptions of a single faction, indexed by level identifier.
type PerCacheFid = EnumMap FactionId PerCacheLid Source #
Server cache of perceptions, indexed by faction identifier.
Data used in FOV computation and cached to speed it up
Map from level positions that currently hold item or actor(s) with shine to the maximum of radiuses of the shining lights.
Note that floor and (many projectile) actors light on a single tile
should be additive for FovShine
to be incrementally updated.
FovShine
should not even be kept in StateServer
, because it's cheap
to compute, compared to FovLucid
and invalidated almost as often
(not invalidated only by UpdAlterTile
).
Instances
Level positions with either ambient light or shining items or actors.
Instances
Level positions that pass through light and vision.
Instances
Level positions with tiles that have ambient light.
Operations
perceptionFromPTotal :: FactionId -> LevelId -> FovLucid -> CacheBeforeLucid -> State -> Perception Source #
Compute positions visible (reachable and seen) by the party. A position is lucid, if it's lit by an ambient light or by a weak, portable light source, e.g,, carried by an actor. A reachable and lucid position is visible. Additionally, positions directly adjacent to an actor are assumed to be visible to him (through sound, touch, noctovision, whatever).
perActorFromLevel :: PerActor -> (ActorId -> Actor) -> ActorMaxSkills -> FovClear -> PerActor Source #
lucidFromLevel :: FovClearLid -> FovLitLid -> State -> LevelId -> Level -> FovLucid Source #
Update lights on the level. This is needed every (even enemy) actor move to show thrown torches. We need to update lights even if cmd doesn't change any perception, so that for next cmd that does, but doesn't change lights, and operates on the same level, the lights are up to date. We could make lights lazy to ensure no computation is wasted, but it's rare that cmd changed them, but not the perception (e.g., earthquake in an uninhabited corner of the active arena, but the we'd probably want some feedback, at least sound).
perFidInDungeon :: State -> (FovLitLid, FovClearLid, FovLucidLid, PerValidFid, PerCacheFid, PerFid) Source #
Calculate the perception and its caches for the whole dungeon.
Internal operations
cacheBeforeLucidFromActor :: FovClear -> Actor -> Skills -> CacheBeforeLucid Source #
Compute positions reachable by the actor. Reachable are all fields on a visually unblocked path from the actor position. Also compute positions seen by noctovision and perceived by smell.
floorLightSources :: DiscoveryAspect -> Level -> [(Point, Int)] Source #
lucidFromItems :: FovClear -> [(Point, Int)] -> [FovLucid] Source #
Compute all dynamically lit positions on a level, whether lit by actors or shining floor items. Note that an actor can be blind, in which case he doesn't see his own light (but others, from his or other factions, possibly do).
litInDungeon :: State -> FovLitLid Source #
clearInDungeon :: State -> FovClearLid Source #
lucidInDungeon :: FovClearLid -> FovLitLid -> State -> FovLucidLid Source #
perLidFromFaction :: FovLucidLid -> FovClearLid -> FactionId -> State -> (PerLid, PerCacheLid) Source #
Calculate perception of a faction.
perceptionCacheFromLevel :: FovClearLid -> FactionId -> LevelId -> State -> PerceptionCache Source #