Skip to content

Commit

Permalink
Parse FovMode using Read
Browse files Browse the repository at this point in the history
  • Loading branch information
Mikolaj committed Dec 9, 2012
1 parent 9c843f1 commit ed0cf2f
Show file tree
Hide file tree
Showing 7 changed files with 40 additions and 47 deletions.
3 changes: 1 addition & 2 deletions Game/LambdaHack/Action/ConfigIO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -125,8 +125,7 @@ parseConfigRules cp =
let configSelfString = let CP conf = cp in CF.to_string conf
configCaves = map (\(n, t) -> (T.pack n, T.pack t)) $ getItems cp "caves"
configDepth = get cp "dungeon" "depth"
configFovMode = T.pack $ get cp "engine" "fovMode"
configFovRadius = get cp "engine" "fovRadius"
configFovMode = get cp "engine" "fovMode"
configSmellTimeout = get cp "engine" "smellTimeout"
configBaseHP = get cp "heroes" "baseHP"
configExtraHeroes = get cp "heroes" "extraHeroes"
Expand Down
31 changes: 26 additions & 5 deletions Game/LambdaHack/Config.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,23 @@
-- | Personal game configuration file type definitions.
module Game.LambdaHack.Config
( Config(..), ConfigUI(..)
( Config(..), ConfigUI(..), FovMode(..)
) where

import Data.Text (Text)
import Data.Binary

import qualified Game.LambdaHack.Key as K

-- TODO: should Blind really be a FovMode, or a modifier? Let's decide
-- when other similar modifiers are added.
-- | Field Of View scanning mode.
data FovMode =
Shadow -- ^ restrictive shadow casting
| Permissive -- ^ permissive FOV
| Digital Int -- ^ digital FOV with the given radius
| Blind -- ^ only feeling out adjacent tiles by touch
deriving (Show, Read)

-- | Fully typed contents of the rules config file.
data Config = Config
{ configSelfString :: !String
Expand All @@ -16,8 +26,7 @@ data Config = Config
-- dungeon
, configDepth :: !Int
-- engine
, configFovMode :: !Text -- TODO
, configFovRadius :: !Int
, configFovMode :: !FovMode
, configSmellTimeout :: !Int
-- heroes
, configBaseHP :: !Int
Expand Down Expand Up @@ -47,13 +56,26 @@ data ConfigUI = ConfigUI
, configHistoryMax :: !Int
} deriving Show

instance Binary FovMode where
put Shadow = putWord8 0
put Permissive = putWord8 1
put (Digital r) = putWord8 2 >> put r
put Blind = putWord8 3
get = do
tag <- getWord8
case tag of
0 -> return Shadow
1 -> return Permissive
2 -> fmap Digital get
3 -> return Blind
_ -> fail "no parse (FovMode)"

instance Binary Config where
put Config{..} = do
put configSelfString
put configCaves
put configDepth
put configFovMode
put configFovRadius
put configSmellTimeout
put configBaseHP
put configExtraHeroes
Expand All @@ -64,7 +86,6 @@ instance Binary Config where
configCaves <- get
configDepth <- get
configFovMode <- get
configFovRadius <- get
configSmellTimeout <- get
configBaseHP <- get
configExtraHeroes <- get
Expand Down
2 changes: 1 addition & 1 deletion Game/LambdaHack/Draw.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,9 +32,9 @@ import Game.LambdaHack.Content.ItemKind
import qualified Game.LambdaHack.Item as Item
import Game.LambdaHack.Random
import qualified Game.LambdaHack.Kind as Kind
import Game.LambdaHack.FOV
import qualified Game.LambdaHack.Feature as F
import Game.LambdaHack.Time
import Game.LambdaHack.Config

-- | Color mode for the display.
data ColorMode =
Expand Down
13 changes: 2 additions & 11 deletions Game/LambdaHack/FOV.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
-- See <https://github.com/kosmikus/LambdaHack/wiki/Fov-and-los>
-- for discussion.
module Game.LambdaHack.FOV
( FovMode(..), fullscan
( fullscan
) where

import qualified Data.List as L
Expand All @@ -18,16 +18,7 @@ import Game.LambdaHack.Level
import qualified Game.LambdaHack.Kind as Kind
import Game.LambdaHack.Content.TileKind
import qualified Game.LambdaHack.Tile as Tile

-- TODO: should Blind really be a FovMode, or a modifier? Let's decide
-- when other similar modifiers are added.
-- | Field Of View scanning mode.
data FovMode =
Shadow -- ^ restrictive shadow casting
| Permissive -- ^ permissive FOV
| Digital Int -- ^ digital FOV with the given radius
| Blind -- ^ only feeling out adjacent tiles by touch
deriving Show
import Game.LambdaHack.Config

-- | Perform a full scan for a given location. Returns the locations
-- that are currently in the field of view. The Field of View
Expand Down
28 changes: 6 additions & 22 deletions Game/LambdaHack/Perception.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,9 +11,7 @@ import qualified Data.List as L
import qualified Data.IntMap as IM
import Data.Maybe
import Control.Monad
import Data.Text (Text)

import Game.LambdaHack.Utils.Assert
import Game.LambdaHack.Point
import Game.LambdaHack.State
import Game.LambdaHack.Level
Expand All @@ -26,7 +24,6 @@ import Game.LambdaHack.Config
import qualified Game.LambdaHack.Tile as Tile
import qualified Game.LambdaHack.Kind as Kind
import Game.LambdaHack.Content.TileKind
import Game.LambdaHack.Msg

newtype PerceptionReachable = PerceptionReachable
{ preachable :: IS.IntSet
Expand Down Expand Up @@ -126,27 +123,18 @@ levelPerception cops@Kind.COps{cotile}
, sdebug = DebugMode{smarkVision}
}
lvl@Level{lactor} =
let Config{ configFovMode
, configFovRadius } = sconfig
radius = if configFovRadius < 1
then assert `failure`
"FOV radius is"
<+> showT configFovRadius
<> ", should be >= 1"
else configFovRadius
let Config{configFovMode} = sconfig
-- Perception for a player-controlled monster on the current level.
mLocPer =
if not (isAHero state splayer) && IM.member splayer lactor
then let m = getPlayerBody state
in Just (bloc m,
computeReachable cops radius configFovMode
smarkVision m lvl)
computeReachable cops configFovMode smarkVision m lvl)
else Nothing
(mLoc, mPer) = (fmap fst mLocPer, fmap snd mLocPer)
hs = IM.filter (\ m -> bfaction m == sfaction && not (bproj m)) lactor
pers = IM.map (\ h ->
computeReachable cops radius configFovMode
smarkVision h lvl) hs
computeReachable cops configFovMode smarkVision h lvl) hs
locs = map bloc $ IM.elems hs
lpers = maybeToList mPer ++ IM.elems pers
reachable = PerceptionReachable $ IS.unions (map preachable lpers)
Expand Down Expand Up @@ -191,20 +179,16 @@ isVisible cotile PerceptionReachable{preachable}

-- | Reachable are all fields on an unblocked path from the hero position.
-- The player's own position is considred reachable by him.
computeReachable :: Kind.COps -> Int -> Text -> Maybe FovMode
computeReachable :: Kind.COps -> FovMode -> Maybe FovMode
-> Actor -> Level -> PerceptionReachable
computeReachable Kind.COps{cotile, coactor=Kind.Ops{okind}}
radius mode smarkVision actor lvl =
configFovMode smarkVision actor lvl =
let fovMode m =
if not $ asight $ okind $ bkind m
then Blind
else case smarkVision of
Just fm -> fm
Nothing -> case mode of
"shadow" -> Shadow
"permissive" -> Permissive
"digital" -> Digital radius
_ -> assert `failure` "Unknown FOV mode:" <+> showT mode
Nothing -> configFovMode
ploc = bloc actor
in PerceptionReachable $
IS.insert ploc $ IS.fromList $ fullscan cotile (fovMode actor) ploc lvl
3 changes: 1 addition & 2 deletions Game/LambdaHack/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,6 @@ module Game.LambdaHack.State

import qualified Data.Set as S
import Data.Binary
import Game.LambdaHack.Config
import qualified System.Random as R
import System.Time
import Data.Text (Text)
Expand All @@ -33,13 +32,13 @@ import Game.LambdaHack.Level
import qualified Game.LambdaHack.Dungeon as Dungeon
import Game.LambdaHack.Item
import Game.LambdaHack.Msg
import Game.LambdaHack.FOV
import Game.LambdaHack.Time
import qualified Game.LambdaHack.Kind as Kind
import Game.LambdaHack.Content.FactionKind
import Game.LambdaHack.Content.ItemKind
import Game.LambdaHack.Effect
import Game.LambdaHack.Flavour
import Game.LambdaHack.Config

-- | The diary contains all the player data that carries over
-- from game to game, even across playing sessions. That includes
Expand Down
7 changes: 3 additions & 4 deletions config.rules.default
Original file line number Diff line number Diff line change
Expand Up @@ -15,10 +15,9 @@
; LambdaCave_10: caveNoise

; [engine]
; fovMode: digital
; ;fovMode: permissive
; ;fovMode: shadow
; fovRadius: 12
; fovMode: Digital 12
; ;fovMode: Permissive
; ;fovMode: Shadow
; ;startingRandomGenerator: 42
; ;dungeonRandomGenerator: 42
; smellTimeout: 100
Expand Down

0 comments on commit ed0cf2f

Please sign in to comment.