{-# LANGUAGE DeriveGeneric #-}
module Game.LambdaHack.Content.ItemKind
( ItemKind(..), makeData
, Aspect(..), Effect(..), DetectKind(..), TimerDice, ThrowMod(..)
, boostItemKindList, forApplyEffect
, strengthOnSmash, getDropOrgans, getMandatoryHideAsFromKind, isEffEscape
, isEffEscapeOrAscend, timeoutAspect, onSmashEffect, damageUsefulness
, verbMsgNoLonger, verbMsgLess, toVelocity, toLinger
, timerNone, isTimerNone, foldTimer, toOrganBad, toOrganGood, toOrganNoTimer
#ifdef EXPOSE_INTERNAL
, boostItemKind, validateSingle, validateAll, validateDups, validateDamage
, hardwiredItemGroups
#endif
) where
import Prelude ()
import Game.LambdaHack.Core.Prelude
import Data.Binary
import Data.Hashable (Hashable)
import qualified Data.Text as T
import GHC.Generics (Generic)
import qualified System.Random as R
import qualified Game.LambdaHack.Core.Dice as Dice
import qualified Game.LambdaHack.Definition.Ability as Ability
import Game.LambdaHack.Definition.ContentData
import Game.LambdaHack.Definition.Defs
import Game.LambdaHack.Definition.Flavour
data ItemKind = ItemKind
{ isymbol :: Char
, iname :: Text
, ifreq :: Freqs ItemKind
, iflavour :: [Flavour]
, icount :: Dice.Dice
, irarity :: Rarity
, iverbHit :: Text
, iweight :: Int
, idamage :: Dice.Dice
, iaspects :: [Aspect]
, ieffects :: [Effect]
, ikit :: [(GroupName ItemKind, CStore)]
, idesc :: Text
}
deriving (Show, Generic)
data Aspect =
Timeout Dice.Dice
| AddSkill Ability.Skill Dice.Dice
| SetFlag Ability.Flag
| ELabel Text
| ToThrow ThrowMod
| HideAs (GroupName ItemKind)
| EqpSlot Ability.EqpSlot
| Odds Dice.Dice [Aspect] [Aspect]
deriving (Show, Eq, Generic)
data Effect =
Burn Dice.Dice
| Explode (GroupName ItemKind)
| RefillHP Int
| RefillCalm Int
| Dominate
| Impress
| PutToSleep
| Yell
| Summon (GroupName ItemKind) Dice.Dice
| Ascend Bool
| Escape
| Paralyze Dice.Dice
| ParalyzeInWater Dice.Dice
| InsertMove Dice.Dice
| Teleport Dice.Dice
| CreateItem CStore (GroupName ItemKind) TimerDice
| DropItem Int Int CStore (GroupName ItemKind)
| PolyItem
| RerollItem
| DupItem
| Identify
| Detect DetectKind Int
| SendFlying ThrowMod
| PushActor ThrowMod
| PullActor ThrowMod
| DropBestWeapon
| ActivateInv Char
| ApplyPerfume
| OneOf [Effect]
| OnSmash Effect
| Composite [Effect]
| VerbNoLonger Text
| VerbMsg Text
deriving (Show, Eq, Generic)
data DetectKind =
DetectAll
| DetectActor
| DetectLoot
| DetectExit
| DetectHidden
| DetectEmbed
deriving (Show, Eq, Generic)
data TimerDice =
TimerNone
| TimerGameTurn Dice.Dice
| TimerActorTurn Dice.Dice
deriving (Eq, Generic)
instance Show TimerDice where
show TimerNone = "0"
show (TimerGameTurn nDm) =
show nDm ++ " " ++ if nDm == 1 then "turn" else "turns"
show (TimerActorTurn nDm) =
show nDm ++ " " ++ if nDm == 1 then "move" else "moves"
data ThrowMod = ThrowMod
{ throwVelocity :: Int
, throwLinger :: Int
, throwHP :: Int
}
deriving (Show, Eq, Ord, Generic)
instance Binary Effect
instance Binary DetectKind
instance Binary TimerDice
instance Binary ThrowMod
instance Hashable ThrowMod
boostItemKindList :: R.StdGen -> [ItemKind] -> [ItemKind]
boostItemKindList _ [] = []
boostItemKindList initialGen l =
let (r, _) = R.randomR (0, length l - 1) initialGen
in case splitAt r l of
(pre, i : post) -> pre ++ boostItemKind i : post
_ -> error $ "" `showFailure` l
boostItemKind :: ItemKind -> ItemKind
boostItemKind i =
let mainlineLabel (label, _) =
label `elem` ["common item", "curious item", "treasure"]
in if any mainlineLabel (ifreq i)
then i { ifreq = ("common item", 10000) : filter (not . mainlineLabel) (ifreq i)
, iaspects = delete (SetFlag Ability.Unique) $ iaspects i
}
else i
forApplyEffect :: Effect -> Bool
forApplyEffect eff = case eff of
OnSmash{} -> False
Composite effs -> any forApplyEffect effs
VerbNoLonger{} -> False
VerbMsg{} -> False
ParalyzeInWater{} -> False
_ -> True
isEffEscape :: Effect -> Bool
isEffEscape Escape{} = True
isEffEscape (OneOf l) = any isEffEscape l
isEffEscape (Composite l) = any isEffEscape l
isEffEscape _ = False
isEffEscapeOrAscend :: Effect -> Bool
isEffEscapeOrAscend Ascend{} = True
isEffEscapeOrAscend Escape{} = True
isEffEscapeOrAscend (OneOf l) = any isEffEscapeOrAscend l
isEffEscapeOrAscend (Composite l) = any isEffEscapeOrAscend l
isEffEscapeOrAscend _ = False
timeoutAspect :: Aspect -> Bool
timeoutAspect Timeout{} = True
timeoutAspect _ = False
onSmashEffect :: Effect -> Bool
onSmashEffect OnSmash{} = True
onSmashEffect _ = False
strengthOnSmash :: ItemKind -> [Effect]
strengthOnSmash =
let f (OnSmash eff) = [eff]
f _ = []
in concatMap f . ieffects
getDropOrgans :: ItemKind -> [GroupName ItemKind]
getDropOrgans =
let f (DropItem _ _ COrgan grp) = [grp]
f Impress = ["impressed"]
f (OneOf l) = concatMap f l
f (Composite l) = concatMap f l
f _ = []
in concatMap f . ieffects
getMandatoryHideAsFromKind :: ItemKind -> Maybe (GroupName ItemKind)
getMandatoryHideAsFromKind itemKind =
let f (HideAs grp) = [grp]
f _ = []
in listToMaybe $ concatMap f (iaspects itemKind)
damageUsefulness :: ItemKind -> Double
damageUsefulness itemKind =
let v = min 1000 (10 * Dice.meanDice (idamage itemKind))
in assert (v >= 0) v
verbMsgNoLonger :: Text -> Effect
verbMsgNoLonger name = VerbNoLonger $ "be no longer" <+> name
verbMsgLess :: Text -> Effect
verbMsgLess name = VerbMsg $ "look less" <+> name
toVelocity :: Int -> Aspect
toVelocity n = ToThrow $ ThrowMod n 100 1
toLinger :: Int -> Aspect
toLinger n = ToThrow $ ThrowMod 100 n 1
timerNone :: TimerDice
timerNone = TimerNone
isTimerNone :: TimerDice -> Bool
isTimerNone tim = tim == TimerNone
foldTimer :: a -> (Dice.Dice -> a) -> (Dice.Dice -> a) -> TimerDice -> a
foldTimer a fgame factor tim = case tim of
TimerNone -> a
TimerGameTurn nDm -> fgame nDm
TimerActorTurn nDm -> factor nDm
toOrganBad :: GroupName ItemKind -> Dice.Dice -> Effect
toOrganBad grp nDm =
assert (Dice.infDice nDm > 0
`blame` "dice at organ creation should always roll above zero"
`swith` (grp, nDm))
$ CreateItem COrgan grp (TimerGameTurn nDm)
toOrganGood :: GroupName ItemKind -> Dice.Dice -> Effect
toOrganGood grp nDm =
assert (Dice.infDice nDm > 0
`blame` "dice at organ creation should always roll above zero"
`swith` (grp, nDm))
$ CreateItem COrgan grp (TimerActorTurn nDm)
toOrganNoTimer :: GroupName ItemKind -> Effect
toOrganNoTimer grp = CreateItem COrgan grp TimerNone
validateSingle :: ItemKind -> [Text]
validateSingle ik@ItemKind{..} =
["iname longer than 23" | T.length iname > 23]
++ ["icount < 0" | Dice.infDice icount < 0]
++ validateRarity irarity
++ validateDamage idamage
++ (let ts = filter timeoutAspect iaspects
in ["more than one Timeout specification" | length ts > 1])
++ [ "Conflicting Fragile and Durable"
| SetFlag Ability.Fragile `elem` iaspects
&& SetFlag Ability.Durable `elem` iaspects ]
++ (let f :: Aspect -> Bool
f EqpSlot{} = True
f _ = False
ts = filter f iaspects
in [ "EqpSlot specified but not Equipable nor Meleeable"
| length ts > 0 && SetFlag Ability.Equipable `notElem` iaspects
&& SetFlag Ability.Meleeable `notElem` iaspects ])
++ [ "Redundant Equipable or Meleeable"
| SetFlag Ability.Equipable `elem` iaspects
&& SetFlag Ability.Meleeable `elem` iaspects ]
++ [ "Conflicting Durable and Blast"
| SetFlag Ability.Durable `elem` iaspects
&& SetFlag Ability.Blast `elem` iaspects ]
++ [ "Conflicting Durable and Condition"
| SetFlag Ability.Durable `elem` iaspects
&& SetFlag Ability.Condition `elem` iaspects ]
++ [ "Conflicting Blast and Condition"
| SetFlag Ability.Blast `elem` iaspects
&& SetFlag Ability.Condition `elem` iaspects ]
++ (let f :: Aspect -> Bool
f ELabel{} = True
f _ = False
ts = filter f iaspects
in ["more than one ELabel specification" | length ts > 1])
++ (let f :: Aspect -> Bool
f ToThrow{} = True
f _ = False
ts = filter f iaspects
in ["more than one ToThrow specification" | length ts > 1])
++ (let f :: Aspect -> Bool
f HideAs{} = True
f _ = False
ts = filter f iaspects
in ["more than one HideAs specification" | length ts > 1])
++ concatMap (validateDups ik) (map SetFlag [minBound .. maxBound])
++ (let f :: Effect -> Bool
f VerbMsg{} = True
f _ = False
in validateOnlyOne ieffects "VerbMsg" f)
++ (let f :: Effect -> Bool
f VerbNoLonger{} = True
f _ = False
in validateOnlyOne ieffects "VerbNoLonger" f)
++ (validateNotNested ieffects "OnSmash" onSmashEffect)
validateOnlyOne :: [Effect] -> Text -> (Effect -> Bool) -> [Text]
validateOnlyOne effs t f =
let ts = filter f effs
in ["more than one" <+> t <+> "specification" | length ts > 1]
validateNotNested :: [Effect] -> Text -> (Effect -> Bool) -> [Text]
validateNotNested effs t f =
let g (OneOf l) = any f l || any g l
g (OnSmash effect) = f effect || g effect
g (Composite l) = any f l || any g l
g _ = False
ts = filter g effs
in [ "effect" <+> t <+> "should be specified at top level, not nested"
| length ts > 0 ]
validateDups :: ItemKind -> Aspect -> [Text]
validateDups ItemKind{..} feat =
let ts = filter (== feat) iaspects
in ["more than one" <+> tshow feat <+> "specification" | length ts > 1]
validateDamage :: Dice.Dice -> [Text]
validateDamage dice = [ "potentially negative dice:" <+> tshow dice
| Dice.infDice dice < 0]
validateAll :: [ItemKind] -> ContentData ItemKind -> [Text]
validateAll content coitem =
let missingKitGroups = [ cgroup
| k <- content
, (cgroup, _) <- ikit k
, not $ omemberGroup coitem cgroup ]
f :: Aspect -> Bool
f HideAs{} = True
f _ = False
wrongHideAsGroups =
[ cgroup
| k <- content
, let (cgroup, notSingleton) = case find f (iaspects k) of
Just (HideAs grp) | not $ oisSingletonGroup coitem grp ->
(grp, True)
_ -> (undefined, False)
, notSingleton
]
g :: Effect -> Maybe (GroupName ItemKind)
g (Explode grp) = Just grp
g (Summon grp _) = Just grp
g (CreateItem _ grp _) = Just grp
g (DropItem _ _ _ grp) = Just grp
g _ = Nothing
missingEffectGroups =
[ (iname k, absGroups)
| k <- content
, let grps = mapMaybe g $ ieffects k
absGroups = filter (not . omemberGroup coitem) grps
, not $ null absGroups
]
missingHardwiredGroups =
filter (not . omemberGroup coitem) hardwiredItemGroups
in [ "no ikit groups in content:" <+> tshow missingKitGroups
| not $ null missingKitGroups ]
++ [ "HideAs groups not singletons:" <+> tshow wrongHideAsGroups
| not $ null wrongHideAsGroups ]
++ [ "mentioned groups not in content:" <+> tshow missingEffectGroups
| not $ null missingEffectGroups ]
++ [ "hardwired groups not in content:" <+> tshow missingHardwiredGroups
| not $ null missingHardwiredGroups ]
hardwiredItemGroups :: [GroupName ItemKind]
hardwiredItemGroups =
["condition", "common item"]
++ ["bonus HP", "braced", "asleep", "impressed", "currency", "mobile"]
makeData :: [ItemKind] -> ContentData ItemKind
makeData = makeContentData "ItemKind" iname ifreq validateSingle validateAll