{-# LANGUAGE DeriveGeneric #-}
module Game.LambdaHack.Content.CaveKind
( CaveKind(..), makeData
#ifdef EXPOSE_INTERNAL
, validateSingle, validateAll
#endif
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Control.DeepSeq
import qualified Data.Text as T
import GHC.Generics (Generic)
import Game.LambdaHack.Common.ContentData
import qualified Game.LambdaHack.Common.Dice as Dice
import Game.LambdaHack.Common.Misc
import Game.LambdaHack.Common.Point
import Game.LambdaHack.Common.Random
import Game.LambdaHack.Content.ItemKind (ItemKind)
import Game.LambdaHack.Content.PlaceKind (PlaceKind)
import Game.LambdaHack.Content.TileKind (TileKind)
data CaveKind = CaveKind
{ csymbol :: Char
, cname :: Text
, cfreq :: Freqs CaveKind
, cxsize :: X
, cysize :: Y
, cgrid :: Dice.DiceXY
, cminPlaceSize :: Dice.DiceXY
, cmaxPlaceSize :: Dice.DiceXY
, cdarkChance :: Dice.Dice
, cnightChance :: Dice.Dice
, cauxConnects :: Rational
, cmaxVoid :: Rational
, cminStairDist :: Int
, cextraStairs :: Dice.Dice
, cdoorChance :: Chance
, copenChance :: Chance
, chidden :: Int
, cactorCoeff :: Int
, cactorFreq :: Freqs ItemKind
, citemNum :: Dice.Dice
, citemFreq :: Freqs ItemKind
, cplaceFreq :: Freqs PlaceKind
, cpassable :: Bool
, cdefTile :: GroupName TileKind
, cdarkCorTile :: GroupName TileKind
, clitCorTile :: GroupName TileKind
, cfillerTile :: GroupName TileKind
, couterFenceTile :: GroupName TileKind
, clegendDarkTile :: GroupName TileKind
, clegendLitTile :: GroupName TileKind
, cescapeGroup :: Maybe (GroupName PlaceKind)
, cstairFreq :: Freqs PlaceKind
, cdesc :: Text
}
deriving (Show, Generic)
instance NFData CaveKind
validateSingle :: CaveKind -> [Text]
validateSingle CaveKind{..} =
let (minGridX, minGridY) = Dice.minDiceXY cgrid
(maxGridX, maxGridY) = Dice.maxDiceXY cgrid
(minMinSizeX, minMinSizeY) = Dice.minDiceXY cminPlaceSize
(maxMinSizeX, maxMinSizeY) = Dice.maxDiceXY cminPlaceSize
(minMaxSizeX, minMaxSizeY) = Dice.minDiceXY cmaxPlaceSize
xborder = if couterFenceTile /= "basic outer fence" then 2 else 0
yborder = if couterFenceTile /= "basic outer fence" then 2 else 0
in [ "cname longer than 25" | T.length cname > 25 ]
++ [ "cxsize < 7" | cxsize < 7 ]
++ [ "cysize < 7" | cysize < 7 ]
++ [ "minGridX < 1" | minGridX < 1 ]
++ [ "minGridY < 1" | minGridY < 1 ]
++ [ "minMinSizeX < 1" | minMinSizeX < 1 ]
++ [ "minMinSizeY < 1" | minMinSizeY < 1 ]
++ [ "minMaxSizeX < maxMinSizeX" | minMaxSizeX < maxMinSizeX ]
++ [ "minMaxSizeY < maxMinSizeY" | minMaxSizeY < maxMinSizeY ]
++ [ "cxsize too small"
| maxGridX * (maxMinSizeX - 4) + xborder >= cxsize ]
++ [ "cysize too small"
| maxGridY * maxMinSizeY + yborder >= cysize ]
++ [ "cextraStairs < 0" | Dice.minDice cextraStairs < 0 ]
++ [ "chidden < 0" | chidden < 0 ]
++ [ "cactorCoeff < 0" | cactorCoeff < 0 ]
++ [ "citemNum < 0" | Dice.minDice citemNum < 0 ]
validateAll :: ContentData ItemKind
-> ContentData PlaceKind
-> ContentData TileKind
-> [CaveKind]
-> ContentData CaveKind
-> [Text]
validateAll coitem coplace cotile content cocave =
let missingActorFreq = filter (not . omemberGroup coitem)
$ concatMap (map fst . cactorFreq) content
missingItemFreq = filter (not . omemberGroup coitem)
$ concatMap (map fst . citemFreq) content
missingPlaceFreq = filter (not . omemberGroup coplace)
$ concatMap (map fst . cplaceFreq) content
missingEscapeGroup = filter (not . omemberGroup coplace)
$ mapMaybe cescapeGroup content
missingStairFreq = filter (not . omemberGroup coplace)
$ concatMap (map fst . cstairFreq) content
tileGroupFuns = [ cdefTile, cdarkCorTile, clitCorTile, cfillerTile
, couterFenceTile, clegendDarkTile, clegendLitTile ]
g kind = map (\f -> f kind) tileGroupFuns
missingTileFreq = filter (not . omemberGroup cotile)
$ concatMap g content
in [ "cactorFreq item groups not in content:" <+> tshow missingActorFreq
| not $ null missingActorFreq ]
++ [ "citemFreq item groups not in content:" <+> tshow missingItemFreq
| not $ null missingItemFreq ]
++ [ "cplaceFreq place groups not in content:" <+> tshow missingPlaceFreq
| not $ null missingPlaceFreq ]
++ [ "cescapeGroup place groups not in content:"
<+> tshow missingEscapeGroup
| not $ null missingEscapeGroup ]
++ [ "cstairFreq place groups not in content:" <+> tshow missingStairFreq
| not $ null missingStairFreq ]
++ [ "tile groups not in content:" <+> tshow missingTileFreq
| not $ null missingTileFreq ]
++ [ "no cave defined for \"default random\""
| not $ omemberGroup cocave "default random" ]
makeData :: ContentData ItemKind
-> ContentData PlaceKind
-> ContentData TileKind
-> [CaveKind]
-> ContentData CaveKind
makeData coitem coplace cotile =
makeContentData "CaveKind" cname cfreq validateSingle
(validateAll coitem coplace cotile)