{-# LANGUAGE TemplateHaskell #-}
-- | Game rules and assorted game setup data.
module Content.RuleKind
  ( standardRules
  ) where

import Prelude ()

import Game.LambdaHack.Core.Prelude

import qualified Data.Ini.Reader as Ini
import           Instances.TH.Lift ()
import           Language.Haskell.TH.Syntax
import           System.FilePath
import           System.IO
  (IOMode (ReadMode), hGetContents, hSetEncoding, openFile, utf8)

-- Cabal
import qualified Paths_LambdaHack as Self (version)

import Game.LambdaHack.Content.RuleKind

standardRules :: RuleContent
standardRules :: RuleContent
standardRules = $WRuleContent :: String
-> X
-> X
-> Version
-> String
-> (String, Config)
-> X
-> X
-> String
-> X
-> [Text]
-> Char
-> RuleContent
RuleContent
  { rtitle :: String
rtitle = "LambdaHack"
  , rXmax :: X
rXmax = 80
  , rYmax :: X
rYmax = 21
  , rexeVersion :: Version
rexeVersion = Version
Self.version
  -- The strings containing the default configuration file
  -- included from config.ui.default.
  , rcfgUIName :: String
rcfgUIName = "config.ui" String -> String -> String
<.> "ini"
  , rcfgUIDefault :: (String, Config)
rcfgUIDefault = $(do
      let path = "GameDefinition" </> "config.ui" <.> "default"
      qAddDependentFile path
      s <- qRunIO $ do
        inputHandle <- openFile path ReadMode
        hSetEncoding inputHandle utf8
        hGetContents inputHandle
      let cfgUIDefault =
            either (error . ("Ini.parse of default config" `showFailure`)) id
            $ Ini.parse s
      lift (s, cfgUIDefault))
  , rwriteSaveClips :: X
rwriteSaveClips = 1000
  , rleadLevelClips :: X
rleadLevelClips = 50
  , rscoresFile :: String
rscoresFile = "LambdaHack.scores"
  , rnearby :: X
rnearby = 20
  , rstairWordCarried :: [Text]
rstairWordCarried = ["staircase"]  -- only one, so inert
  , rsymbolProjectile :: Char
rsymbolProjectile = '|'
  }