-- | The type of cave kinds. Every level in the game is an instantiated
-- cave kind.
module Game.LambdaHack.Content.CaveKind
  ( pattern DEFAULT_RANDOM
  , CaveKind(..), makeData
#ifdef EXPOSE_INTERNAL
    -- * Internal operations
  , validateSingle, validateAll, mandatoryGroups
#endif
  ) where

import Prelude ()

import Game.LambdaHack.Core.Prelude

import qualified Data.Text as T

import           Game.LambdaHack.Content.ItemKind (ItemKind)
import           Game.LambdaHack.Content.PlaceKind (PlaceKind)
import           Game.LambdaHack.Content.TileKind (TileKind)
import qualified Game.LambdaHack.Core.Dice as Dice
import           Game.LambdaHack.Core.Random
import           Game.LambdaHack.Definition.ContentData
import           Game.LambdaHack.Definition.Defs

-- | Parameters for the generation of dungeon levels.
-- Warning: for efficiency, avoid embedded items in any of the common tiles.
data CaveKind = CaveKind
  { CaveKind -> Char
csymbol         :: Char             -- ^ a symbol
  , CaveKind -> Text
cname           :: Text             -- ^ short description
  , CaveKind -> Freqs CaveKind
cfreq           :: Freqs CaveKind   -- ^ frequency within groups
  , CaveKind -> X
cXminSize       :: X                -- ^ minimal X size of the whole cave
  , CaveKind -> X
cYminSize       :: Y                -- ^ minimal Y size of the whole cave
  , CaveKind -> DiceXY
ccellSize       :: Dice.DiceXY      -- ^ size of a map cell holding a place
  , CaveKind -> DiceXY
cminPlaceSize   :: Dice.DiceXY      -- ^ minimal size of places; for merging
  , CaveKind -> DiceXY
cmaxPlaceSize   :: Dice.DiceXY      -- ^ maximal size of places; for growing
  , CaveKind -> Dice
cdarkOdds       :: Dice.Dice        -- ^ the odds a place is dark
                                        --   (level-scaled dice roll > 50)
  , CaveKind -> Dice
cnightOdds      :: Dice.Dice        -- ^ the odds the cave is dark
                                        --   (level-scaled dice roll > 50)
  , CaveKind -> Rational
cauxConnects    :: Rational         -- ^ a proportion of extra connections
  , CaveKind -> Rational
cmaxVoid        :: Rational
      -- ^ at most this proportion of rooms may be void
  , CaveKind -> Rational
cdoorChance     :: Chance           -- ^ the chance of a door in an opening
  , CaveKind -> Rational
copenChance     :: Chance           -- ^ if there's a door, is it open?
  , CaveKind -> X
chidden         :: Int              -- ^ if not open, hidden one in n times
  , CaveKind -> X
cactorCoeff     :: Int              -- ^ the lower, the more monsters spawn
  , CaveKind -> Freqs ItemKind
cactorFreq      :: Freqs ItemKind   -- ^ actor groups to consider
  , CaveKind -> Dice
citemNum        :: Dice.Dice        -- ^ number of initial items in the cave
  , CaveKind -> Freqs ItemKind
citemFreq       :: Freqs ItemKind   -- ^ item groups to consider
  , CaveKind -> Freqs PlaceKind
cplaceFreq      :: Freqs PlaceKind  -- ^ place groups to consider
  , CaveKind -> Bool
cpassable       :: Bool
      -- ^ are passable default tiles permitted
  , CaveKind -> Bool
labyrinth       :: Bool                -- ^ waste of time for AI to explore
  , CaveKind -> GroupName TileKind
cdefTile        :: GroupName TileKind  -- ^ the default cave tile
  , CaveKind -> GroupName TileKind
cdarkCorTile    :: GroupName TileKind  -- ^ the dark cave corridor tile
  , CaveKind -> GroupName TileKind
clitCorTile     :: GroupName TileKind  -- ^ the lit cave corridor tile
  , CaveKind -> GroupName TileKind
cwallTile       :: GroupName TileKind  -- ^ the tile used for @FWall@ fence
  , CaveKind -> GroupName TileKind
ccornerTile     :: GroupName TileKind  -- ^ tile used for the fence corners
  , CaveKind -> GroupName TileKind
cfenceTileN     :: GroupName TileKind  -- ^ the outer fence N wall
  , CaveKind -> GroupName TileKind
cfenceTileE     :: GroupName TileKind  -- ^ the outer fence E wall
  , CaveKind -> GroupName TileKind
cfenceTileS     :: GroupName TileKind  -- ^ the outer fence S wall
  , CaveKind -> GroupName TileKind
cfenceTileW     :: GroupName TileKind  -- ^ the outer fence W wall
  , CaveKind -> Bool
cfenceApart     :: Bool                -- ^ are places touching fence banned
  , CaveKind -> GroupName TileKind
clegendDarkTile :: GroupName TileKind  -- ^ the dark place plan legend
  , CaveKind -> GroupName TileKind
clegendLitTile  :: GroupName TileKind  -- ^ the lit place plan legend
  , CaveKind -> X
cminStairDist   :: Int                 -- ^ minimal distance between stairs
  , CaveKind -> Dice
cmaxStairsNum   :: Dice.Dice           -- ^ maximum number of stairs
  , CaveKind -> Freqs PlaceKind
cescapeFreq     :: Freqs PlaceKind     -- ^ escape groups, if any
  , CaveKind -> Freqs PlaceKind
cstairFreq      :: Freqs PlaceKind     -- ^ place groups for created stairs
  , CaveKind -> Freqs PlaceKind
cstairAllowed   :: Freqs PlaceKind     -- ^ extra groups for inherited
  , CaveKind -> [X]
cskip           :: [Int]  -- ^ which faction starting positions to skip
  , CaveKind -> Text
cdesc           :: Text   -- ^ full cave description
  }
  deriving X -> CaveKind -> ShowS
[CaveKind] -> ShowS
CaveKind -> String
(X -> CaveKind -> ShowS)
-> (CaveKind -> String) -> ([CaveKind] -> ShowS) -> Show CaveKind
forall a.
(X -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CaveKind] -> ShowS
$cshowList :: [CaveKind] -> ShowS
show :: CaveKind -> String
$cshow :: CaveKind -> String
showsPrec :: X -> CaveKind -> ShowS
$cshowsPrec :: X -> CaveKind -> ShowS
Show  -- No Eq and Ord to make extending logically sound

-- | Catch caves with not enough space for all the places. Check the size
-- of the cave descriptions to make sure they fit on screen. Etc.
validateSingle :: CaveKind -> [Text]
validateSingle :: CaveKind -> [Text]
validateSingle CaveKind{..} =
  let (minCellSizeX :: X
minCellSizeX, minCellSizeY :: X
minCellSizeY) = DiceXY -> (X, X)
Dice.infDiceXY DiceXY
ccellSize
      (minMinSizeX :: X
minMinSizeX, minMinSizeY :: X
minMinSizeY) = DiceXY -> (X, X)
Dice.infDiceXY DiceXY
cminPlaceSize
      (maxMinSizeX :: X
maxMinSizeX, maxMinSizeY :: X
maxMinSizeY) = DiceXY -> (X, X)
Dice.supDiceXY DiceXY
cminPlaceSize
      (minMaxSizeX :: X
minMaxSizeX, minMaxSizeY :: X
minMaxSizeY) = DiceXY -> (X, X)
Dice.infDiceXY DiceXY
cmaxPlaceSize
  in [ "cname longer than 25" | Text -> X
T.length Text
cname X -> X -> Bool
forall a. Ord a => a -> a -> Bool
> 25 ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "cXminSize < 20" | X
cXminSize X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 20 ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "cYminSize < 20" | X
cYminSize X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 20 ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "minCellSizeX < 1" | X
minCellSizeX X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 1 ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "minCellSizeY < 1" | X
minCellSizeY X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 1 ]
     -- The following four are heuristics, so not too restrictive:
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "minCellSizeX < 6 && non-trivial stairs"
        | X
minCellSizeX X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 6 Bool -> Bool -> Bool
&& Bool -> Bool
not (Freqs PlaceKind -> X
forall a. [a] -> X
length Freqs PlaceKind
cstairFreq X -> X -> Bool
forall a. Ord a => a -> a -> Bool
<= 1 Bool -> Bool -> Bool
&& Freqs PlaceKind -> Bool
forall a. [a] -> Bool
null Freqs PlaceKind
cescapeFreq) ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "minCellSizeY < 4 && non-trivial stairs"
        | X
minCellSizeY X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 4 Bool -> Bool -> Bool
&& Bool -> Bool
not (Freqs PlaceKind -> X
forall a. [a] -> X
length Freqs PlaceKind
cstairFreq X -> X -> Bool
forall a. Ord a => a -> a -> Bool
<= 1 Bool -> Bool -> Bool
&& Freqs PlaceKind -> Bool
forall a. [a] -> Bool
null Freqs PlaceKind
cescapeFreq) ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "minMinSizeX < 5 && non-trivial stairs"
        | X
minMinSizeX X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 5 Bool -> Bool -> Bool
&& Bool -> Bool
not (Freqs PlaceKind -> X
forall a. [a] -> X
length Freqs PlaceKind
cstairFreq X -> X -> Bool
forall a. Ord a => a -> a -> Bool
<= 1 Bool -> Bool -> Bool
&& Freqs PlaceKind -> Bool
forall a. [a] -> Bool
null Freqs PlaceKind
cescapeFreq) ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "minMinSizeY < 3 && non-trivial stairs"
        | X
minMinSizeY X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 3 Bool -> Bool -> Bool
&& Bool -> Bool
not (Freqs PlaceKind -> X
forall a. [a] -> X
length Freqs PlaceKind
cstairFreq X -> X -> Bool
forall a. Ord a => a -> a -> Bool
<= 1 Bool -> Bool -> Bool
&& Freqs PlaceKind -> Bool
forall a. [a] -> Bool
null Freqs PlaceKind
cescapeFreq) ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "minMinSizeX < 1" | X
minMinSizeX X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 1 ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "minMinSizeY < 1" | X
minMinSizeY X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 1 ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "minMaxSizeX < maxMinSizeX" | X
minMaxSizeX X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< X
maxMinSizeX ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "minMaxSizeY < maxMinSizeY" | X
minMaxSizeY X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< X
maxMinSizeY ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "chidden < 0" | X
chidden X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 0 ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "cactorCoeff < 0" | X
cactorCoeff X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 0 ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "citemNum < 0" | Dice -> X
Dice.infDice Dice
citemNum X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 0 ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "cmaxStairsNum < 0" | Dice -> X
Dice.infDice Dice
cmaxStairsNum X -> X -> Bool
forall a. Ord a => a -> a -> Bool
< 0 ]
     [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ "stairs suggested, but not defined"
        | Dice -> X
Dice.supDice Dice
cmaxStairsNum X -> X -> Bool
forall a. Ord a => a -> a -> Bool
> 0 Bool -> Bool -> Bool
&& Freqs PlaceKind -> Bool
forall a. [a] -> Bool
null Freqs PlaceKind
cstairFreq ]

-- | Validate all cave kinds.
-- Note that names don't have to be unique: we can have several variants
-- of a cave with a given name.
validateAll :: [CaveKind] -> ContentData CaveKind -> [Text]
validateAll :: [CaveKind] -> ContentData CaveKind -> [Text]
validateAll _ _ = []  -- so far, always valid

-- * Mandatory item groups

mandatoryGroups :: [GroupName CaveKind]
mandatoryGroups :: [GroupName CaveKind]
mandatoryGroups =
       [GroupName CaveKind
DEFAULT_RANDOM]

pattern DEFAULT_RANDOM :: GroupName CaveKind

pattern $bDEFAULT_RANDOM :: GroupName CaveKind
$mDEFAULT_RANDOM :: forall r. GroupName CaveKind -> (Void# -> r) -> (Void# -> r) -> r
DEFAULT_RANDOM = GroupName "default random"

makeData :: [CaveKind] -> [GroupName CaveKind] -> [GroupName CaveKind]
         -> ContentData CaveKind
makeData :: [CaveKind]
-> [GroupName CaveKind]
-> [GroupName CaveKind]
-> ContentData CaveKind
makeData content :: [CaveKind]
content groupNamesSingleton :: [GroupName CaveKind]
groupNamesSingleton groupNames :: [GroupName CaveKind]
groupNames =
  String
-> (CaveKind -> Text)
-> (CaveKind -> Freqs CaveKind)
-> (CaveKind -> [Text])
-> ([CaveKind] -> ContentData CaveKind -> [Text])
-> [CaveKind]
-> [GroupName CaveKind]
-> [GroupName CaveKind]
-> ContentData CaveKind
forall c.
Show c =>
String
-> (c -> Text)
-> (c -> Freqs c)
-> (c -> [Text])
-> ([c] -> ContentData c -> [Text])
-> [c]
-> [GroupName c]
-> [GroupName c]
-> ContentData c
makeContentData "CaveKind" CaveKind -> Text
cname CaveKind -> Freqs CaveKind
cfreq CaveKind -> [Text]
validateSingle [CaveKind] -> ContentData CaveKind -> [Text]
validateAll [CaveKind]
content
                  [GroupName CaveKind]
groupNamesSingleton
                  ([GroupName CaveKind]
mandatoryGroups [GroupName CaveKind]
-> [GroupName CaveKind] -> [GroupName CaveKind]
forall a. [a] -> [a] -> [a]
++ [GroupName CaveKind]
groupNames)