{-# LANGUAGE DeriveGeneric #-}
module Game.LambdaHack.Content.ItemKind
( ItemKind(..), makeData
, Effect(..), DetectKind(..), TimerDice, ThrowMod(..), Feature(..)
, ItemSpeedup, emptyItemSpeedup, getKindMean, speedupItem
, boostItemKindList, forApplyEffect, onlyMinorEffects
, filterRecharging, stripRecharging, stripOnSmash
, strengthOnSmash, getDropOrgans, getToThrow, getHideAs, getEqpSlot
, isEffEscape, isEffAscend, isEffEscapeOrAscend
, isMelee, isTmpCondition, isBlast, isHumanTrinket
, goesIntoEqp, goesIntoInv, goesIntoSha
, itemTrajectory, totalRange, damageUsefulness
, tmpNoLonger, tmpLess, toVelocity, toLinger
, timerNone, isTimerNone, foldTimer
, toOrganBad, toOrganGood, toOrganNoTimer
#ifdef EXPOSE_INTERNAL
, meanAspect, boostItemKind, majorEffect
, validateSingle, validateAll, validateDups, validateDamage
, hardwiredItemGroups
#endif
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Control.DeepSeq
import Data.Binary
import qualified Data.Text as T
import qualified Data.Vector as V
import GHC.Generics (Generic)
import qualified NLP.Miniutter.English as MU
import qualified System.Random as R
import Game.LambdaHack.Common.ContentData
import qualified Game.LambdaHack.Common.Dice as Dice
import Game.LambdaHack.Common.Flavour
import qualified Game.LambdaHack.Common.ItemAspect as IA
import Game.LambdaHack.Common.Misc
import Game.LambdaHack.Common.Point
import Game.LambdaHack.Common.Time
import Game.LambdaHack.Common.Vector
data ItemKind = ItemKind
{ isymbol :: Char
, iname :: Text
, ifreq :: Freqs ItemKind
, iflavour :: [Flavour]
, icount :: Dice.Dice
, irarity :: Rarity
, iverbHit :: MU.Part
, iweight :: Int
, idamage :: Dice.Dice
, iaspects :: [IA.Aspect]
, ieffects :: [Effect]
, ifeature :: [Feature]
, idesc :: Text
, ikit :: [(GroupName ItemKind, CStore)]
}
deriving (Show, Generic)
data Effect =
Burn Dice.Dice
| Explode (GroupName ItemKind)
| RefillHP Int
| RefillCalm Int
| Dominate
| Impress
| Summon (GroupName ItemKind) Dice.Dice
| Ascend Bool
| Escape
| Paralyze Dice.Dice
| InsertMove Dice.Dice
| Teleport Dice.Dice
| CreateItem CStore (GroupName ItemKind) TimerDice
| DropItem Int Int CStore (GroupName ItemKind)
| PolyItem
| Identify
| Detect DetectKind Int
| SendFlying ThrowMod
| PushActor ThrowMod
| PullActor ThrowMod
| DropBestWeapon
| ActivateInv Char
| ApplyPerfume
| OneOf [Effect]
| OnSmash Effect
| Recharging Effect
| Composite [Effect]
| Temporary Text
deriving (Show, Eq, Generic)
data DetectKind =
DetectAll
| DetectActor
| DetectItem
| 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
}
deriving (Show, Eq, Ord, Generic)
data Feature =
ELabel Text
| Fragile
| Lobable
| Durable
| ToThrow ThrowMod
| HideAs (GroupName ItemKind)
| Equipable
| Meleeable
| Precious
| Tactic Tactic
| Blast
| EqpSlot IA.EqpSlot
| Unique
| Periodic
| MinorEffects
deriving (Show, Eq, Ord, Generic)
newtype ItemSpeedup = ItemSpeedup (V.Vector IA.KindMean)
deriving (Show, Eq, Generic)
instance NFData ItemKind
instance NFData Effect
instance NFData DetectKind
instance NFData TimerDice
instance NFData ThrowMod
instance NFData Feature
instance Binary Effect
instance Binary DetectKind
instance Binary TimerDice
instance Binary ThrowMod
emptyItemSpeedup :: ItemSpeedup
emptyItemSpeedup = ItemSpeedup V.empty
getKindMean :: ContentId ItemKind -> ItemSpeedup -> IA.KindMean
getKindMean kindId (ItemSpeedup is) = is V.! contentIdIndex kindId
speedupItem :: ContentData ItemKind -> ItemSpeedup
speedupItem coitem =
let f !kind =
let kmMean = meanAspect kind
kmConst = not $ IA.aspectsRandom (iaspects kind)
in IA.KindMean{..}
in ItemSpeedup $! omapVector coitem f
meanAspect :: ItemKind -> IA.AspectRecord
meanAspect kind = foldl' IA.addMeanAspect IA.emptyAspectRecord (iaspects kind)
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)
, ifeature = delete Unique $ ifeature i
}
else i
forApplyEffect :: Effect -> Bool
forApplyEffect eff = case eff of
OnSmash{} -> False
Recharging eff2 -> forApplyEffect eff2
Composite effs -> any forApplyEffect effs
Temporary{} -> False
_ -> True
majorEffect :: Effect -> Bool
majorEffect eff = case eff of
OnSmash{} -> False
Recharging eff2 -> majorEffect eff2
Composite (eff1 : _) -> majorEffect eff1
_ -> True
onlyMinorEffects :: ItemKind -> Bool
onlyMinorEffects kind =
MinorEffects `elem` ifeature kind
|| not (any majorEffect $ ieffects kind)
isEffEscape :: Effect -> Bool
isEffEscape Escape{} = True
isEffEscape (OneOf l) = any isEffEscapeOrAscend l
isEffEscape (Recharging eff) = isEffEscapeOrAscend eff
isEffEscape (Composite l) = any isEffEscapeOrAscend l
isEffEscape _ = False
isEffAscend :: Effect -> Bool
isEffAscend Ascend{} = True
isEffAscend (OneOf l) = any isEffEscapeOrAscend l
isEffAscend (Recharging eff) = isEffEscapeOrAscend eff
isEffAscend (Composite l) = any isEffEscapeOrAscend l
isEffAscend _ = False
isEffEscapeOrAscend :: Effect -> Bool
isEffEscapeOrAscend Ascend{} = True
isEffEscapeOrAscend Escape{} = True
isEffEscapeOrAscend (OneOf l) = any isEffEscapeOrAscend l
isEffEscapeOrAscend (Recharging eff) = isEffEscapeOrAscend eff
isEffEscapeOrAscend (Composite l) = any isEffEscapeOrAscend l
isEffEscapeOrAscend _ = False
filterRecharging :: [Effect] -> [Effect]
filterRecharging effs =
let getRechargingEffect :: Effect -> Maybe Effect
getRechargingEffect e@Recharging{} = Just e
getRechargingEffect _ = Nothing
in mapMaybe getRechargingEffect effs
stripRecharging :: [Effect] -> [Effect]
stripRecharging effs =
let getRechargingEffect :: Effect -> Maybe Effect
getRechargingEffect (Recharging e) = Just e
getRechargingEffect _ = Nothing
in mapMaybe getRechargingEffect effs
stripOnSmash :: [Effect] -> [Effect]
stripOnSmash effs =
let getOnSmashEffect :: Effect -> Maybe Effect
getOnSmashEffect (OnSmash e) = Just e
getOnSmashEffect _ = Nothing
in mapMaybe getOnSmashEffect effs
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 (Recharging eff) = f eff
f (Composite l) = concatMap f l
f _ = []
in concatMap f . ieffects
getToThrow :: ItemKind -> ThrowMod
getToThrow itemKind =
let f (ToThrow tmod) = [tmod]
f _ = []
in case concatMap f (ifeature itemKind) of
[] -> ThrowMod 100 100
x : _ -> x
getHideAs :: ItemKind -> Maybe (GroupName ItemKind)
getHideAs itemKind =
let f (HideAs grp) = [grp]
f _ = []
in case concatMap f (ifeature itemKind) of
[] -> Nothing
x : _ -> Just x
getEqpSlot :: ItemKind -> Maybe IA.EqpSlot
getEqpSlot itemKind =
let f (EqpSlot eqpSlot) = [eqpSlot]
f _ = []
in case concatMap f (ifeature itemKind) of
[] -> Nothing
x : _ -> Just x
isMelee :: ItemKind -> Bool
isMelee itemKind = Meleeable `elem` ifeature itemKind
isTmpCondition :: ItemKind -> Bool
isTmpCondition itemKind = Fragile `elem` ifeature itemKind
&& Durable `elem` ifeature itemKind
isBlast :: ItemKind -> Bool
isBlast itemKind = Blast `elem` ifeature itemKind
isHumanTrinket :: ItemKind -> Bool
isHumanTrinket itemKind =
Precious `elem` ifeature itemKind
&& Equipable `notElem` ifeature itemKind
goesIntoEqp :: ItemKind -> Bool
goesIntoEqp itemKind = Equipable `elem` ifeature itemKind
|| Meleeable `elem` ifeature itemKind
goesIntoInv :: ItemKind -> Bool
goesIntoInv itemKind = Precious `notElem` ifeature itemKind
&& not (goesIntoEqp itemKind)
goesIntoSha :: ItemKind -> Bool
goesIntoSha itemKind = Precious `elem` ifeature itemKind
&& not (goesIntoEqp itemKind)
itemTrajectory :: ItemKind -> [Point] -> ([Vector], (Speed, Int))
itemTrajectory itemKind path =
let ThrowMod{..} = getToThrow itemKind
in computeTrajectory (iweight itemKind) throwVelocity throwLinger path
totalRange :: ItemKind -> Int
totalRange itemKind = snd $ snd $ itemTrajectory itemKind []
damageUsefulness :: ItemKind -> Double
damageUsefulness itemKind =
let v = min 1000 (10 * Dice.meanDice (idamage itemKind))
in assert (v >= 0) v
tmpNoLonger :: Text -> Effect
tmpNoLonger name = Temporary $ "be no longer" <+> name
tmpLess :: Text -> Effect
tmpLess name = Temporary $ "become less" <+> name
toVelocity :: Int -> Feature
toVelocity n = ToThrow $ ThrowMod n 100
toLinger :: Int -> Feature
toLinger n = ToThrow $ ThrowMod 100 n
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.minDice 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.minDice 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.minDice icount < 0 ]
++ validateRarity irarity
++ validateDamage idamage
++ (let timeoutAspect :: IA.Aspect -> Bool
timeoutAspect IA.Timeout{} = True
timeoutAspect _ = False
ts = filter timeoutAspect iaspects
in ["more than one Timeout specification" | length ts > 1])
++ (let f :: Feature -> Bool
f EqpSlot{} = True
f _ = False
ts = filter f ifeature
in [ "EqpSlot specified but not Equipable nor Meleeable"
| length ts > 0 && Equipable `notElem` ifeature
&& Meleeable `notElem` ifeature ])
++ ["Redundant Equipable or Meleeable" | Equipable `elem` ifeature
&& Meleeable `elem` ifeature]
++ (let f :: Effect -> Bool
f OnSmash{} = True
f _ = False
in validateNotNested ieffects "OnSmash" f)
++ (let f :: Effect -> Bool
f Recharging{} = True
f _ = False
in validateNotNested ieffects "Recharging" f)
++ (let f :: Effect -> Bool
f Temporary{} = True
f _ = False
in validateOnlyOne ieffects "Temporary" f)
++ (let f :: Feature -> Bool
f ELabel{} = True
f _ = False
ts = filter f ifeature
in ["more than one ELabel specification" | length ts > 1])
++ (let f :: Feature -> Bool
f ToThrow{} = True
f _ = False
ts = filter f ifeature
in ["more than one ToThrow specification" | length ts > 1])
++ (let f :: Feature -> Bool
f HideAs{} = True
f _ = False
ts = filter f ifeature
in ["more than one HideAs specification" | length ts > 1])
++ (let f :: Feature -> Bool
f Tactic{} = True
f _ = False
ts = filter f ifeature
in ["more than one Tactic specification" | length ts > 1])
++ concatMap (validateDups ik)
[ Fragile, Lobable, Durable, Equipable, Meleeable, Precious, Blast
, Unique, Periodic]
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 (Recharging 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 -> Feature -> [Text]
validateDups ItemKind{..} feat =
let ts = filter (== feat) ifeature
in ["more than one" <+> tshow feat <+> "specification" | length ts > 1]
validateDamage :: Dice.Dice -> [Text]
validateDamage dice = [ "potentially negative dice:" <+> tshow dice
| Dice.minDice dice < 0]
validateAll :: [ItemKind] -> ContentData ItemKind -> [Text]
validateAll content coitem =
let missingKitGroups = [ cgroup
| k <- content
, (cgroup, _) <- ikit k
, not $ omemberGroup coitem cgroup ]
f :: Feature -> Bool
f HideAs{} = True
f _ = False
wrongHideAsGroups =
[ cgroup
| k <- content
, let (cgroup, notSingleton) = case find f (ifeature 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", "currency", "impressed", "mobile"]
makeData :: [ItemKind] -> ContentData ItemKind
makeData = makeContentData "ItemKind" iname ifreq validateSingle validateAll