{-# LANGUAGE DeriveGeneric #-}
module Game.LambdaHack.Content.ItemKind
( ItemKind(..)
, Effect(..), TimerDice(..)
, Aspect(..), ThrowMod(..)
, Feature(..), EqpSlot(..)
, forApplyEffect, forIdEffect
, toDmg, toVelocity, toLinger, toOrganGameTurn, toOrganActorTurn, toOrganNone
, validateSingleItemKind, validateAllItemKind
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Control.DeepSeq
import Data.Binary
import Data.Hashable (Hashable)
import qualified Data.Set as S
import qualified Data.Text as T
import GHC.Generics (Generic)
import qualified NLP.Miniutter.English as MU
import qualified Game.LambdaHack.Common.Ability as Ability
import qualified Game.LambdaHack.Common.Dice as Dice
import Game.LambdaHack.Common.Flavour
import Game.LambdaHack.Common.Misc
data ItemKind = ItemKind
{ isymbol :: !Char
, iname :: !Text
, ifreq :: !(Freqs ItemKind)
, iflavour :: ![Flavour]
, icount :: !Dice.Dice
, irarity :: !Rarity
, iverbHit :: !MU.Part
, iweight :: !Int
, idamage :: ![(Int, Dice.Dice)]
, iaspects :: ![Aspect]
, ieffects :: ![Effect]
, ifeature :: ![Feature]
, idesc :: !Text
, ikit :: ![(GroupName ItemKind, CStore)]
}
deriving Show
data Effect =
ELabel !Text
| EqpSlot !EqpSlot
| 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 !Int
| DetectActor !Int
| DetectItem !Int
| DetectExit !Int
| DetectHidden !Int
| SendFlying !ThrowMod
| PushActor !ThrowMod
| PullActor !ThrowMod
| DropBestWeapon
| ActivateInv !Char
| ApplyPerfume
| OneOf ![Effect]
| OnSmash !Effect
| Recharging !Effect
| Temporary !Text
| Unique
| Periodic
deriving (Show, Eq, Ord, Generic)
instance NFData Effect
forApplyEffect :: Effect -> Bool
forApplyEffect eff = case eff of
ELabel{} -> False
EqpSlot{} -> False
OnSmash{} -> False
Temporary{} -> False
Unique -> False
Periodic -> False
_ -> True
forIdEffect :: Effect -> Bool
forIdEffect eff = case eff of
ELabel{} -> False
EqpSlot{} -> False
OnSmash{} -> False
Explode{} -> False
Unique -> False
Periodic -> False
_ -> True
data TimerDice =
TimerNone
| TimerGameTurn !Dice.Dice
| TimerActorTurn !Dice.Dice
deriving (Eq, Ord, 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"
instance NFData TimerDice
data Aspect =
Timeout !Dice.Dice
| AddHurtMelee !Dice.Dice
| AddArmorMelee !Dice.Dice
| AddArmorRanged !Dice.Dice
| AddMaxHP !Dice.Dice
| AddMaxCalm !Dice.Dice
| AddSpeed !Dice.Dice
| AddSight !Dice.Dice
| AddSmell !Dice.Dice
| AddShine !Dice.Dice
| AddNocto !Dice.Dice
| AddAggression !Dice.Dice
| AddAbility !Ability.Ability !Dice.Dice
deriving (Show, Eq, Ord, Generic)
data ThrowMod = ThrowMod
{ throwVelocity :: !Int
, throwLinger :: !Int
}
deriving (Show, Eq, Ord, Generic)
instance NFData ThrowMod
data Feature =
Fragile
| Lobable
| Durable
| ToThrow !ThrowMod
| Identified
| Applicable
| Equipable
| Meleeable
| Precious
| Tactic !Tactic
deriving (Show, Eq, Ord, Generic)
data EqpSlot =
EqpSlotMiscBonus
| EqpSlotAddHurtMelee
| EqpSlotAddArmorMelee
| EqpSlotAddArmorRanged
| EqpSlotAddMaxHP
| EqpSlotAddSpeed
| EqpSlotAddSight
| EqpSlotLightSource
| EqpSlotWeapon
| EqpSlotMiscAbility
| EqpSlotAbMove
| EqpSlotAbMelee
| EqpSlotAbDisplace
| EqpSlotAbAlter
| EqpSlotAbProject
| EqpSlotAbApply
| EqpSlotAddMaxCalm
| EqpSlotAddSmell
| EqpSlotAddNocto
| EqpSlotAddAggression
| EqpSlotAbWait
| EqpSlotAbMoveItem
deriving (Show, Eq, Ord, Enum, Bounded, Generic)
instance NFData EqpSlot
instance Hashable Effect
instance Hashable TimerDice
instance Hashable Aspect
instance Hashable ThrowMod
instance Hashable Feature
instance Hashable EqpSlot
instance Binary Effect
instance Binary TimerDice
instance Binary Aspect
instance Binary ThrowMod
instance Binary Feature
instance Binary EqpSlot
toDmg :: Dice.Dice -> [(Int, Dice.Dice)]
toDmg dmg = [(1, dmg)]
toVelocity :: Int -> Feature
toVelocity n = ToThrow $ ThrowMod n 100
toLinger :: Int -> Feature
toLinger n = ToThrow $ ThrowMod 100 n
toOrganGameTurn :: GroupName ItemKind -> Dice.Dice -> Effect
toOrganGameTurn grp nDm = CreateItem COrgan grp (TimerGameTurn nDm)
toOrganActorTurn :: GroupName ItemKind -> Dice.Dice -> Effect
toOrganActorTurn grp nDm = CreateItem COrgan grp (TimerActorTurn nDm)
toOrganNone :: GroupName ItemKind -> Effect
toOrganNone grp = CreateItem COrgan grp TimerNone
validateSingleItemKind :: ItemKind -> [Text]
validateSingleItemKind ik@ItemKind{..} =
[ "iname longer than 23" | T.length iname > 23 ]
++ [ "icount < 0" | icount < 0 ]
++ validateRarity irarity
++ (let timeoutAspect :: Aspect -> Bool
timeoutAspect Timeout{} = True
timeoutAspect _ = False
ts = filter timeoutAspect iaspects
in ["more than one Timeout specification" | length ts > 1])
++ (let f :: Effect -> Bool
f ELabel{} = True
f _ = False
ts = filter f ieffects
in ["more than one ELabel specification" | length ts > 1])
++ (let f :: Effect -> Bool
f EqpSlot{} = True
f _ = False
ts = filter f ieffects
in ["more than one EqpSlot specification" | length ts > 1]
++ [ "EqpSlot specified but not Equipable nor Meleeable"
| length ts > 0 && Equipable `notElem` ifeature
&& Meleeable `notElem` ifeature ])
++ ["Reduntand Equipable or Meleeable" | Equipable `elem` ifeature
&& Meleeable `elem` ifeature]
++ (let f :: Effect -> Bool
f Temporary{} = True
f _ = False
ts = filter f ieffects
in ["more than one Temporary specification" | length ts > 1])
++ (let f :: Effect -> Bool
f Unique = True
f _ = False
ts = filter f ieffects
in ["more than one Unique specification" | length ts > 1])
++ (let f :: Effect -> Bool
f Periodic = True
f _ = False
ts = filter f ieffects
in ["more than one Periodic 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 Tactic{} = True
f _ = False
ts = filter f ifeature
in ["more than one Tactic specification" | length ts > 1])
++ concatMap (validateDups ik)
[ Fragile, Lobable, Durable, Identified, Applicable
, Equipable, Meleeable, Precious ]
validateDups :: ItemKind -> Feature -> [Text]
validateDups ItemKind{..} feat =
let ts = filter (== feat) ifeature
in ["more than one" <+> tshow feat <+> "specification" | length ts > 1]
validateAllItemKind :: [ItemKind] -> [Text]
validateAllItemKind content =
let kindFreq :: S.Set (GroupName ItemKind)
kindFreq = let tuples = [ cgroup
| k <- content
, (cgroup, n) <- ifreq k
, n > 0 ]
in S.fromList tuples
missingGroups = [ cgroup
| k <- content
, (cgroup, _) <- ikit k
, S.notMember cgroup kindFreq ]
errorMsg = case missingGroups of
[] -> []
_ -> ["no groups" <+> tshow missingGroups
<+> "among content that has groups"
<+> tshow (S.elems kindFreq)]
hardwiredAbsent = filter (`S.notMember` kindFreq) hardwiredItemGroups
in errorMsg
++ [ "Hardwired groups not in content:" <+> tshow hardwiredAbsent
| not $ null hardwiredAbsent ]
hardwiredItemGroups :: [GroupName ItemKind]
hardwiredItemGroups =
[ "temporary condition", "treasure", "useful", "any scroll", "any vial"
, "potion", "flask" ]
++ ["bonus HP", "currency", "impressed", "mobile"]