{-# LANGUAGE TypeFamilies #-}
module Game.LambdaHack.Common.Level
(
LevelId, Dungeon
, ascendInBranch, whereTo
, ItemFloor, ActorMap, TileMap, SmellMap, Level(..)
, updateFloor, updateEmbed, updateActorMap, updateTile, updateSmell
, at, findPoint, findPos, findPosTry, findPosTry2
#ifdef EXPOSE_INTERNAL
, assertSparseItems, assertSparseActors
#endif
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Data.Binary
import qualified Data.EnumMap.Strict as EM
import Game.LambdaHack.Common.Actor
import Game.LambdaHack.Common.ContentData
import qualified Game.LambdaHack.Common.Dice as Dice
import Game.LambdaHack.Common.Item
import Game.LambdaHack.Common.Misc
import Game.LambdaHack.Common.Point
import qualified Game.LambdaHack.Common.PointArray as PointArray
import Game.LambdaHack.Common.Random
import Game.LambdaHack.Common.Time
import Game.LambdaHack.Content.CaveKind (CaveKind)
import Game.LambdaHack.Content.TileKind (TileKind)
type Dungeon = EM.EnumMap LevelId Level
ascendInBranch :: Dungeon -> Bool -> LevelId -> [LevelId]
ascendInBranch dungeon up lid =
let (minD, maxD) =
case (EM.minViewWithKey dungeon, EM.maxViewWithKey dungeon) of
(Just ((s, _), _), Just ((e, _), _)) -> (s, e)
_ -> error $ "null dungeon" `showFailure` dungeon
ln = max minD $ min maxD $ toEnum $ fromEnum lid + if up then 1 else -1
in case EM.lookup ln dungeon of
Just _ | ln /= lid -> [ln]
_ | ln == lid -> []
_ -> ascendInBranch dungeon up ln
whereTo :: LevelId
-> Point
-> Maybe Bool
-> Dungeon
-> (LevelId, Point)
whereTo lid pos mup dungeon =
let lvl = dungeon EM.! lid
(up, i) = case elemIndex pos $ fst $ lstair lvl of
Just ifst -> (True, ifst)
Nothing -> case elemIndex pos $ snd $ lstair lvl of
Just isnd -> (False, isnd)
Nothing -> case mup of
Just forcedUp -> (forcedUp, 0)
Nothing -> error $ "no stairs at" `showFailure` (lid, pos)
!_A = assert (maybe True (== up) mup) ()
in case ascendInBranch dungeon up lid of
[] | isJust mup -> (lid, pos)
[] -> error $ "no dungeon level to go to" `showFailure` (lid, pos)
ln : _ -> let lvlDest = dungeon EM.! ln
stairsDest = (if up then snd else fst) (lstair lvlDest)
in if length stairsDest < i + 1
then error $ "no stairs at index" `showFailure` (lid, pos)
else (ln, stairsDest !! i)
type ItemFloor = EM.EnumMap Point ItemBag
type ActorMap = EM.EnumMap Point [ActorId]
type TileMap = PointArray.Array (ContentId TileKind)
type SmellMap = EM.EnumMap Point Time
data Level = Level
{ lkind :: ContentId CaveKind
, ldepth :: Dice.AbsDepth
, lfloor :: ItemFloor
, lembed :: ItemFloor
, lactor :: ActorMap
, ltile :: TileMap
, lxsize :: X
, lysize :: Y
, lsmell :: SmellMap
, lstair :: ([Point], [Point])
, lescape :: [Point]
, lseen :: Int
, lexpl :: Int
, ltime :: Time
, lnight :: Bool
}
deriving (Show, Eq)
assertSparseItems :: ItemFloor -> ItemFloor
assertSparseItems m =
assert (EM.null (EM.filter EM.null m)
`blame` "null floors found" `swith` m) m
assertSparseActors :: ActorMap -> ActorMap
assertSparseActors m =
assert (EM.null (EM.filter null m)
`blame` "null actor lists found" `swith` m) m
updateFloor :: (ItemFloor -> ItemFloor) -> Level -> Level
updateFloor f lvl = lvl {lfloor = f (lfloor lvl)}
updateEmbed :: (ItemFloor -> ItemFloor) -> Level -> Level
updateEmbed f lvl = lvl {lembed = f (lembed lvl)}
updateActorMap :: (ActorMap -> ActorMap) -> Level -> Level
updateActorMap f lvl = lvl {lactor = f (lactor lvl)}
updateTile :: (TileMap -> TileMap) -> Level -> Level
updateTile f lvl = lvl {ltile = f (ltile lvl)}
updateSmell :: (SmellMap -> SmellMap) -> Level -> Level
updateSmell f lvl = lvl {lsmell = f (lsmell lvl)}
at :: Level -> Point -> ContentId TileKind
{-# INLINE at #-}
at Level{ltile} p = ltile PointArray.! p
findPoint :: X -> Y -> (Point -> Maybe Point) -> Rnd Point
findPoint x y f =
let search = do
pxy <- randomR (0, (x - 1) * (y - 1))
let pos = PointArray.punindex x pxy
case f pos of
Just p -> return p
Nothing -> search
in search
findPos :: TileMap -> (Point -> ContentId TileKind -> Bool) -> Rnd Point
findPos ltile p =
let (x, y) = PointArray.sizeA ltile
search = do
pxy <- randomR (0, (x - 1) * (y - 1))
let tile = ContentId $ ltile `PointArray.accessI` pxy
pos = PointArray.punindex x pxy
if p pos tile
then return $! pos
else search
in search
findPosTry :: Int
-> TileMap
-> (Point -> ContentId TileKind -> Bool)
-> [Point -> ContentId TileKind -> Bool]
-> Rnd Point
{-# INLINE findPosTry #-}
findPosTry numTries ltile m = findPosTry2 numTries ltile m [] undefined
findPosTry2 :: Int
-> TileMap
-> (Point -> ContentId TileKind -> Bool)
-> [Point -> ContentId TileKind -> Bool]
-> (Point -> ContentId TileKind -> Bool)
-> [Point -> ContentId TileKind -> Bool]
-> Rnd Point
findPosTry2 numTries ltile m0 l g r = assert (numTries > 0) $
let (x, y) = PointArray.sizeA ltile
accomodate fallback _ [] = fallback
accomodate fallback m (hd : tl) =
let search 0 = accomodate fallback m tl
search !k = do
pxy <- randomR (0, (x - 1) * (y - 1))
let tile = ContentId $ ltile `PointArray.accessI` pxy
pos = PointArray.punindex x pxy
if m pos tile && hd pos tile
then return $! pos
else search (k - 1)
in search numTries
in accomodate (accomodate (findPos ltile m0) m0 r)
(\pos tile -> m0 pos tile && g pos tile)
l
instance Binary Level where
put Level{..} = do
put lkind
put ldepth
put (assertSparseItems lfloor)
put (assertSparseItems lembed)
put (assertSparseActors lactor)
put ltile
put lxsize
put lysize
put lsmell
put lstair
put lescape
put lseen
put lexpl
put ltime
put lnight
get = do
lkind <- get
ldepth <- get
lfloor <- get
lembed <- get
lactor <- get
ltile <- get
lxsize <- get
lysize <- get
lsmell <- get
lstair <- get
lescape <- get
lseen <- get
lexpl <- get
ltime <- get
lnight <- get
return $! Level{..}