{-# LANGUAGE DeriveGeneric #-}
module Game.LambdaHack.Common.ReqFailure
( ReqFailure(..)
, impossibleReqFailure, showReqFailure
, permittedPrecious, permittedProject, permittedProjectAI, permittedApply
#ifdef EXPOSE_INTERNAL
#endif
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Data.Binary
import GHC.Generics (Generic)
import Game.LambdaHack.Common.Item
import qualified Game.LambdaHack.Common.ItemAspect as IA
import Game.LambdaHack.Common.Time
import qualified Game.LambdaHack.Content.ItemKind as IK
data ReqFailure =
MoveNothing
| MeleeSelf
| MeleeDistant
| DisplaceDistant
| DisplaceAccess
| DisplaceProjectiles
| DisplaceDying
| DisplaceBraced
| DisplaceImmobile
| DisplaceSupported
| AlterUnskilled
| AlterUnwalked
| AlterDistant
| AlterBlockActor
| AlterBlockItem
| AlterNothing
| EqpOverfull
| EqpStackFull
| ApplyUnskilled
| ApplyRead
| ApplyOutOfReach
| ApplyCharging
| ApplyNoEffects
| ItemNothing
| ItemNotCalm
| NotCalmPrecious
| ProjectUnskilled
| ProjectAimOnself
| ProjectBlockTerrain
| ProjectBlockActor
| ProjectLobable
| ProjectOutOfReach
| TriggerNothing
| NoChangeDunLeader
deriving (Show, Eq, Generic)
instance Binary ReqFailure
impossibleReqFailure :: ReqFailure -> Bool
impossibleReqFailure reqFailure = case reqFailure of
MoveNothing -> True
MeleeSelf -> True
MeleeDistant -> True
DisplaceDistant -> True
DisplaceAccess -> True
DisplaceProjectiles -> True
DisplaceDying -> True
DisplaceBraced -> True
DisplaceImmobile -> False
DisplaceSupported -> False
AlterUnskilled -> False
AlterUnwalked -> False
AlterDistant -> True
AlterBlockActor -> True
AlterBlockItem -> True
AlterNothing -> True
EqpOverfull -> True
EqpStackFull -> True
ApplyUnskilled -> False
ApplyRead -> False
ApplyOutOfReach -> True
ApplyCharging -> False
ApplyNoEffects -> False
ItemNothing -> True
ItemNotCalm -> False
NotCalmPrecious -> False
ProjectUnskilled -> False
ProjectAimOnself -> True
ProjectBlockTerrain -> True
ProjectBlockActor -> True
ProjectLobable -> False
ProjectOutOfReach -> True
TriggerNothing -> True
NoChangeDunLeader -> True
showReqFailure :: ReqFailure -> Text
showReqFailure reqFailure = case reqFailure of
MoveNothing -> "wasting time on moving into obstacle"
MeleeSelf -> "trying to melee oneself"
MeleeDistant -> "trying to melee a distant foe"
DisplaceDistant -> "trying to displace a distant actor"
DisplaceAccess -> "switching places without access"
DisplaceProjectiles -> "trying to displace multiple projectiles"
DisplaceDying -> "trying to displace a dying foe"
DisplaceBraced -> "trying to displace a braced foe"
DisplaceImmobile -> "trying to displace an immobile foe"
DisplaceSupported -> "trying to displace a supported foe"
AlterUnskilled -> "unskilled actors cannot alter tiles"
AlterUnwalked -> "unskilled actors cannot enter tiles"
AlterDistant -> "trying to alter a distant tile"
AlterBlockActor -> "blocked by an actor"
AlterBlockItem -> "jammed by an item"
AlterNothing -> "wasting time on altering nothing"
EqpOverfull -> "cannot equip any more items"
EqpStackFull -> "cannot equip the whole item stack"
ApplyUnskilled -> "unskilled actors cannot apply items"
ApplyRead -> "activating this kind of items requires skill level 2"
ApplyOutOfReach -> "cannot apply an item out of reach"
ApplyCharging -> "cannot apply an item that is still charging"
ApplyNoEffects -> "cannot apply an item that produces no effects"
ItemNothing -> "wasting time on void item manipulation"
ItemNotCalm -> "you are too alarmed to use the shared stash"
NotCalmPrecious -> "you are too alarmed to handle such an exquisite item"
ProjectUnskilled -> "unskilled actors cannot aim"
ProjectAimOnself -> "cannot aim at oneself"
ProjectBlockTerrain -> "aiming obstructed by terrain"
ProjectBlockActor -> "aiming blocked by an actor"
ProjectLobable -> "lobbing an item requires fling skill 3"
ProjectOutOfReach -> "cannot aim an item out of reach"
TriggerNothing -> "wasting time on triggering nothing"
NoChangeDunLeader -> "no manual level change for your team"
permittedPrecious :: Bool -> Bool -> ItemFull -> Either ReqFailure Bool
permittedPrecious forced calmE ItemFull{itemKind, itemDisco} =
let isPrecious = IK.Precious `elem` IK.ifeature itemKind
in if not forced && not calmE && isPrecious
then Left NotCalmPrecious
else Right $ IK.Durable `elem` IK.ifeature itemKind
|| case itemDisco of
ItemDiscoFull{} -> True
_ -> not isPrecious
permittedPreciousAI :: Bool -> ItemFull -> Bool
permittedPreciousAI calmE ItemFull{itemKind, itemDisco} =
let isPrecious = IK.Precious `elem` IK.ifeature itemKind
in if not calmE && isPrecious
then False
else IK.Durable `elem` IK.ifeature itemKind
|| case itemDisco of
ItemDiscoFull{} -> True
_ -> not isPrecious
permittedProject :: Bool -> Int -> Bool -> ItemFull -> Either ReqFailure Bool
permittedProject forced skill calmE itemFull@ItemFull{itemKind} =
if | not forced && skill < 1 -> Left ProjectUnskilled
| not forced
&& IK.Lobable `elem` IK.ifeature itemKind
&& skill < 3 -> Left ProjectLobable
| otherwise ->
let badSlot = case IK.getEqpSlot itemKind of
Just IA.EqpSlotLightSource -> False
Just _ -> True
Nothing -> IK.goesIntoEqp itemKind
in if badSlot
then Right False
else permittedPrecious forced calmE itemFull
permittedProjectAI :: Int -> Bool -> ItemFull -> Bool
permittedProjectAI skill calmE itemFull@ItemFull{itemKind} =
if | skill < 1 -> False
| IK.Lobable `elem` IK.ifeature itemKind
&& skill < 3 -> False
| otherwise -> permittedPreciousAI calmE itemFull
permittedApply :: Time -> Int -> Bool-> ItemFull -> ItemQuant
-> Either ReqFailure Bool
permittedApply localTime skill calmE
itemFull@ItemFull{itemKind, itemSuspect} kit =
if | IK.isymbol itemKind == '?' && skill < 2 -> Left ApplyRead
| skill < 1 -> Left ApplyUnskilled
| not $ hasCharge localTime itemFull kit -> Left ApplyCharging
| otherwise ->
if null (IK.ieffects itemKind) && not itemSuspect
then Left ApplyNoEffects
else permittedPrecious False calmE itemFull