{-# LANGUAGE DeriveGeneric #-}
module Game.LambdaHack.Content.RuleKind
( RuleKind(..), 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 Data.Version
import GHC.Generics (Generic)
import Game.LambdaHack.Common.ContentData
data RuleKind = RuleKind
{ rsymbol :: Char
, rname :: Text
, rfreq :: Freqs RuleKind
, rtitle :: Text
, rfontDir :: FilePath
, rexeVersion :: Version
, rcfgUIName :: FilePath
, rcfgUIDefault :: String
, rmainMenuArt :: Text
, rintroScreen :: [String]
, rfirstDeathEnds :: Bool
, rwriteSaveClips :: Int
, rleadLevelClips :: Int
, rscoresFile :: FilePath
, rnearby :: Int
}
deriving Generic
instance Show RuleKind where
show _ = "The game ruleset specification."
instance NFData RuleKind
validateSingle :: RuleKind -> [Text]
validateSingle RuleKind{rmainMenuArt} =
let ts = T.lines rmainMenuArt
tsNot110 = filter ((/= 110) . T.length) ts
in case tsNot110 of
[] -> [ "rmainMenuArt doesn't have 60 lines, but " <> tshow (length ts)
| length ts /= 60]
tNot110 : _ ->
["rmainMenuArt has a line with length other than 110:" <> tNot110]
validateAll :: [RuleKind] -> ContentData RuleKind -> [Text]
validateAll _ _ = []
makeData :: [RuleKind] -> ContentData RuleKind
makeData = makeContentData "RuleKind" rname rfreq validateSingle validateAll