{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving #-}
module Game.LambdaHack.Definition.Ability
( Skill(..), Skills, Flag(..), Flags(..), Tactic(..), EqpSlot(..)
, getSk, addSk, checkFl, skillsToList
, zeroSkills, addSkills, sumScaledSkills
, nameTactic, describeTactic, tacticSkills
, blockOnly, meleeAdjacent, meleeAndRanged, ignoreItems
#ifdef EXPOSE_INTERNAL
, compactSkills, scaleSkills
#endif
) where
import Prelude ()
import Game.LambdaHack.Core.Prelude
import Data.Binary
import qualified Data.EnumMap.Strict as EM
import qualified Data.EnumSet as ES
import Data.Hashable (Hashable)
import GHC.Generics (Generic)
data Skill =
SkMove
| SkMelee
| SkDisplace
| SkAlter
| SkWait
| SkMoveItem
| SkProject
| SkApply
| SkSwimming
| SkFlying
| SkHurtMelee
| SkArmorMelee
| SkArmorRanged
| SkMaxHP
| SkMaxCalm
| SkSpeed
| SkSight
| SkSmell
| SkShine
| SkNocto
| SkHearing
| SkAggression
| SkOdor
deriving (Show, Eq, Ord, Generic, Enum, Bounded)
newtype Skills = Skills {skills :: EM.EnumMap Skill Int}
deriving (Show, Eq, Ord, Generic, Hashable, Binary)
data Flag =
Fragile
| Lobable
| Durable
| Equipable
| Meleeable
| Precious
| Blast
| Condition
| Unique
| Periodic
| MinorEffects
deriving (Show, Eq, Ord, Generic, Enum, Bounded)
newtype Flags = Flags {flags :: ES.EnumSet Flag}
deriving (Show, Eq, Ord, Generic, Hashable, Binary)
data Tactic =
TExplore
| TFollow
| TFollowNoItems
| TMeleeAndRanged
| TMeleeAdjacent
| TBlock
| TRoam
| TPatrol
deriving (Show, Eq, Ord, Enum, Bounded, Generic)
instance Binary Tactic
instance Hashable Tactic
data EqpSlot =
EqpSlotMove
| EqpSlotMelee
| EqpSlotDisplace
| EqpSlotAlter
| EqpSlotWait
| EqpSlotMoveItem
| EqpSlotProject
| EqpSlotApply
| EqpSlotSwimming
| EqpSlotFlying
| EqpSlotHurtMelee
| EqpSlotArmorMelee
| EqpSlotArmorRanged
| EqpSlotMaxHP
| EqpSlotSpeed
| EqpSlotSight
| EqpSlotShine
| EqpSlotMiscBonus
| EqpSlotWeaponFast
| EqpSlotWeaponBig
deriving (Show, Eq, Ord, Enum, Bounded, Generic)
instance Binary Skill where
put = putWord8 . toEnum . fromEnum
get = fmap (toEnum . fromEnum) getWord8
instance Binary Flag where
put = putWord8 . toEnum . fromEnum
get = fmap (toEnum . fromEnum) getWord8
instance Binary EqpSlot where
put = putWord8 . toEnum . fromEnum
get = fmap (toEnum . fromEnum) getWord8
instance Hashable Skill
instance Hashable Flag
instance Hashable EqpSlot
getSk :: Skill -> Skills -> Int
{-# INLINE getSk #-}
getSk sk (Skills skills) = EM.findWithDefault 0 sk skills
addSk :: Skill -> Int -> Skills -> Skills
addSk sk n = addSkills (Skills $ EM.singleton sk n)
checkFl :: Flag -> Flags -> Bool
{-# INLINE checkFl #-}
checkFl flag (Flags flags) = flag `ES.member` flags
skillsToList :: Skills -> [(Skill, Int)]
skillsToList (Skills sk) = EM.assocs sk
zeroSkills :: Skills
zeroSkills = Skills EM.empty
compactSkills :: EM.EnumMap Skill Int -> EM.EnumMap Skill Int
compactSkills = EM.filter (/= 0)
addSkills :: Skills -> Skills -> Skills
addSkills (Skills sk1) (Skills sk2) =
Skills $ compactSkills $ EM.unionWith (+) sk1 sk2
scaleSkills :: Int -> EM.EnumMap Skill Int -> EM.EnumMap Skill Int
scaleSkills n = EM.map (n *)
sumScaledSkills :: [(Skills, Int)] -> Skills
sumScaledSkills l = Skills $ compactSkills $ EM.unionsWith (+)
$ map (\(Skills sk, k) -> scaleSkills k sk) l
nameTactic :: Tactic -> Text
nameTactic TExplore = "explore"
nameTactic TFollow = "follow freely"
nameTactic TFollowNoItems = "follow only"
nameTactic TMeleeAndRanged = "fight only"
nameTactic TMeleeAdjacent = "melee only"
nameTactic TBlock = "block only"
nameTactic TRoam = "roam freely"
nameTactic TPatrol = "patrol area"
describeTactic :: Tactic -> Text
describeTactic TExplore = "investigate unknown positions, chase targets"
describeTactic TFollow = "follow leader's target or position, grab items"
describeTactic TFollowNoItems =
"follow leader's target or position, ignore items"
describeTactic TMeleeAndRanged =
"engage in both melee and ranged combat, don't move"
describeTactic TMeleeAdjacent = "engage exclusively in melee, don't move"
describeTactic TBlock = "block and wait, don't move"
describeTactic TRoam = "move freely, chase targets"
describeTactic TPatrol = "find and patrol an area (WIP)"
tacticSkills :: Tactic -> Skills
tacticSkills TExplore = zeroSkills
tacticSkills TFollow = zeroSkills
tacticSkills TFollowNoItems = ignoreItems
tacticSkills TMeleeAndRanged = meleeAndRanged
tacticSkills TMeleeAdjacent = meleeAdjacent
tacticSkills TBlock = blockOnly
tacticSkills TRoam = zeroSkills
tacticSkills TPatrol = zeroSkills
minusTen, blockOnly, meleeAdjacent, meleeAndRanged, ignoreItems :: Skills
minusTen = Skills $ EM.fromDistinctAscList
$ zip [SkMove .. SkApply] (repeat (-10))
blockOnly = Skills $ EM.delete SkWait $ skills minusTen
meleeAdjacent = Skills $ EM.delete SkMelee $ skills blockOnly
meleeAndRanged = Skills $ EM.delete SkProject $ skills meleeAdjacent
ignoreItems = Skills $ EM.fromList
$ zip [SkMoveItem, SkProject, SkApply] (repeat (-10))