{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving, TupleSections #-}
module Game.LambdaHack.Common.Item
( Item(..), ItemIdentity(..)
, ItemKindIx, ItemDisco(..), ItemFull(..), ItemFullKit
, DiscoveryKind, DiscoveryAspect, ItemIxMap, Benefit(..), DiscoveryBenefit
, ItemTimer, ItemTimers, ItemQuant, ItemBag, ItemDict
, toItemKindIx, quantSingle, itemToFull6, aspectRecordFull, strongestSlot
, itemTimerZero, createItemTimer, shiftItemTimer
, deltaOfItemTimer, charging, ncharges, hasCharge
, strongestMelee, unknownMeleeBonus, unknownSpeedBonus
, conditionMeleeBonus, conditionSpeedBonus, armorHurtCalculation
, mergeItemQuant, listToolsToConsume, subtractIidfromGrps, sortIids
, TileAction (..), parseTileAction
#ifdef EXPOSE_INTERNAL
, valueAtEqpSlot, unknownAspect, countIidConsumed
#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 qualified Data.Ix as Ix
import GHC.Generics (Generic)
import qualified Game.LambdaHack.Common.ItemAspect as IA
import Game.LambdaHack.Common.Kind
import Game.LambdaHack.Common.Time
import Game.LambdaHack.Common.Types
import qualified Game.LambdaHack.Content.ItemKind as IK
import qualified Game.LambdaHack.Content.TileKind as TK
import qualified Game.LambdaHack.Core.Dice as Dice
import Game.LambdaHack.Definition.Ability (EqpSlot (..))
import qualified Game.LambdaHack.Definition.Ability as Ability
import Game.LambdaHack.Definition.Defs
import Game.LambdaHack.Definition.Flavour
data Item = Item
{ Item -> ItemIdentity
jkind :: ItemIdentity
, Item -> Maybe FactionId
jfid :: Maybe FactionId
, Item -> Flavour
jflavour :: Flavour
}
deriving (Int -> Item -> ShowS
[Item] -> ShowS
Item -> String
(Int -> Item -> ShowS)
-> (Item -> String) -> ([Item] -> ShowS) -> Show Item
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Item -> ShowS
showsPrec :: Int -> Item -> ShowS
$cshow :: Item -> String
show :: Item -> String
$cshowList :: [Item] -> ShowS
showList :: [Item] -> ShowS
Show, Item -> Item -> Bool
(Item -> Item -> Bool) -> (Item -> Item -> Bool) -> Eq Item
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Item -> Item -> Bool
== :: Item -> Item -> Bool
$c/= :: Item -> Item -> Bool
/= :: Item -> Item -> Bool
Eq, (forall x. Item -> Rep Item x)
-> (forall x. Rep Item x -> Item) -> Generic Item
forall x. Rep Item x -> Item
forall x. Item -> Rep Item x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Item -> Rep Item x
from :: forall x. Item -> Rep Item x
$cto :: forall x. Rep Item x -> Item
to :: forall x. Rep Item x -> Item
Generic)
instance Binary Item
data ItemIdentity =
IdentityObvious (ContentId IK.ItemKind)
| IdentityCovered ItemKindIx (ContentId IK.ItemKind)
deriving (Int -> ItemIdentity -> ShowS
[ItemIdentity] -> ShowS
ItemIdentity -> String
(Int -> ItemIdentity -> ShowS)
-> (ItemIdentity -> String)
-> ([ItemIdentity] -> ShowS)
-> Show ItemIdentity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ItemIdentity -> ShowS
showsPrec :: Int -> ItemIdentity -> ShowS
$cshow :: ItemIdentity -> String
show :: ItemIdentity -> String
$cshowList :: [ItemIdentity] -> ShowS
showList :: [ItemIdentity] -> ShowS
Show, ItemIdentity -> ItemIdentity -> Bool
(ItemIdentity -> ItemIdentity -> Bool)
-> (ItemIdentity -> ItemIdentity -> Bool) -> Eq ItemIdentity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ItemIdentity -> ItemIdentity -> Bool
== :: ItemIdentity -> ItemIdentity -> Bool
$c/= :: ItemIdentity -> ItemIdentity -> Bool
/= :: ItemIdentity -> ItemIdentity -> Bool
Eq, (forall x. ItemIdentity -> Rep ItemIdentity x)
-> (forall x. Rep ItemIdentity x -> ItemIdentity)
-> Generic ItemIdentity
forall x. Rep ItemIdentity x -> ItemIdentity
forall x. ItemIdentity -> Rep ItemIdentity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ItemIdentity -> Rep ItemIdentity x
from :: forall x. ItemIdentity -> Rep ItemIdentity x
$cto :: forall x. Rep ItemIdentity x -> ItemIdentity
to :: forall x. Rep ItemIdentity x -> ItemIdentity
Generic)
instance Hashable ItemIdentity
instance Binary ItemIdentity
type DiscoveryAspect = EM.EnumMap ItemId IA.AspectRecord
newtype ItemKindIx = ItemKindIx Word16
deriving (Int -> ItemKindIx -> ShowS
[ItemKindIx] -> ShowS
ItemKindIx -> String
(Int -> ItemKindIx -> ShowS)
-> (ItemKindIx -> String)
-> ([ItemKindIx] -> ShowS)
-> Show ItemKindIx
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ItemKindIx -> ShowS
showsPrec :: Int -> ItemKindIx -> ShowS
$cshow :: ItemKindIx -> String
show :: ItemKindIx -> String
$cshowList :: [ItemKindIx] -> ShowS
showList :: [ItemKindIx] -> ShowS
Show, ItemKindIx -> ItemKindIx -> Bool
(ItemKindIx -> ItemKindIx -> Bool)
-> (ItemKindIx -> ItemKindIx -> Bool) -> Eq ItemKindIx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ItemKindIx -> ItemKindIx -> Bool
== :: ItemKindIx -> ItemKindIx -> Bool
$c/= :: ItemKindIx -> ItemKindIx -> Bool
/= :: ItemKindIx -> ItemKindIx -> Bool
Eq, Eq ItemKindIx
Eq ItemKindIx =>
(ItemKindIx -> ItemKindIx -> Ordering)
-> (ItemKindIx -> ItemKindIx -> Bool)
-> (ItemKindIx -> ItemKindIx -> Bool)
-> (ItemKindIx -> ItemKindIx -> Bool)
-> (ItemKindIx -> ItemKindIx -> Bool)
-> (ItemKindIx -> ItemKindIx -> ItemKindIx)
-> (ItemKindIx -> ItemKindIx -> ItemKindIx)
-> Ord ItemKindIx
ItemKindIx -> ItemKindIx -> Bool
ItemKindIx -> ItemKindIx -> Ordering
ItemKindIx -> ItemKindIx -> ItemKindIx
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ItemKindIx -> ItemKindIx -> Ordering
compare :: ItemKindIx -> ItemKindIx -> Ordering
$c< :: ItemKindIx -> ItemKindIx -> Bool
< :: ItemKindIx -> ItemKindIx -> Bool
$c<= :: ItemKindIx -> ItemKindIx -> Bool
<= :: ItemKindIx -> ItemKindIx -> Bool
$c> :: ItemKindIx -> ItemKindIx -> Bool
> :: ItemKindIx -> ItemKindIx -> Bool
$c>= :: ItemKindIx -> ItemKindIx -> Bool
>= :: ItemKindIx -> ItemKindIx -> Bool
$cmax :: ItemKindIx -> ItemKindIx -> ItemKindIx
max :: ItemKindIx -> ItemKindIx -> ItemKindIx
$cmin :: ItemKindIx -> ItemKindIx -> ItemKindIx
min :: ItemKindIx -> ItemKindIx -> ItemKindIx
Ord, Int -> ItemKindIx
ItemKindIx -> Int
ItemKindIx -> [ItemKindIx]
ItemKindIx -> ItemKindIx
ItemKindIx -> ItemKindIx -> [ItemKindIx]
ItemKindIx -> ItemKindIx -> ItemKindIx -> [ItemKindIx]
(ItemKindIx -> ItemKindIx)
-> (ItemKindIx -> ItemKindIx)
-> (Int -> ItemKindIx)
-> (ItemKindIx -> Int)
-> (ItemKindIx -> [ItemKindIx])
-> (ItemKindIx -> ItemKindIx -> [ItemKindIx])
-> (ItemKindIx -> ItemKindIx -> [ItemKindIx])
-> (ItemKindIx -> ItemKindIx -> ItemKindIx -> [ItemKindIx])
-> Enum ItemKindIx
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ItemKindIx -> ItemKindIx
succ :: ItemKindIx -> ItemKindIx
$cpred :: ItemKindIx -> ItemKindIx
pred :: ItemKindIx -> ItemKindIx
$ctoEnum :: Int -> ItemKindIx
toEnum :: Int -> ItemKindIx
$cfromEnum :: ItemKindIx -> Int
fromEnum :: ItemKindIx -> Int
$cenumFrom :: ItemKindIx -> [ItemKindIx]
enumFrom :: ItemKindIx -> [ItemKindIx]
$cenumFromThen :: ItemKindIx -> ItemKindIx -> [ItemKindIx]
enumFromThen :: ItemKindIx -> ItemKindIx -> [ItemKindIx]
$cenumFromTo :: ItemKindIx -> ItemKindIx -> [ItemKindIx]
enumFromTo :: ItemKindIx -> ItemKindIx -> [ItemKindIx]
$cenumFromThenTo :: ItemKindIx -> ItemKindIx -> ItemKindIx -> [ItemKindIx]
enumFromThenTo :: ItemKindIx -> ItemKindIx -> ItemKindIx -> [ItemKindIx]
Enum, Ord ItemKindIx
Ord ItemKindIx =>
((ItemKindIx, ItemKindIx) -> [ItemKindIx])
-> ((ItemKindIx, ItemKindIx) -> ItemKindIx -> Int)
-> ((ItemKindIx, ItemKindIx) -> ItemKindIx -> Int)
-> ((ItemKindIx, ItemKindIx) -> ItemKindIx -> Bool)
-> ((ItemKindIx, ItemKindIx) -> Int)
-> ((ItemKindIx, ItemKindIx) -> Int)
-> Ix ItemKindIx
(ItemKindIx, ItemKindIx) -> Int
(ItemKindIx, ItemKindIx) -> [ItemKindIx]
(ItemKindIx, ItemKindIx) -> ItemKindIx -> Bool
(ItemKindIx, ItemKindIx) -> ItemKindIx -> Int
forall a.
Ord a =>
((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
$crange :: (ItemKindIx, ItemKindIx) -> [ItemKindIx]
range :: (ItemKindIx, ItemKindIx) -> [ItemKindIx]
$cindex :: (ItemKindIx, ItemKindIx) -> ItemKindIx -> Int
index :: (ItemKindIx, ItemKindIx) -> ItemKindIx -> Int
$cunsafeIndex :: (ItemKindIx, ItemKindIx) -> ItemKindIx -> Int
unsafeIndex :: (ItemKindIx, ItemKindIx) -> ItemKindIx -> Int
$cinRange :: (ItemKindIx, ItemKindIx) -> ItemKindIx -> Bool
inRange :: (ItemKindIx, ItemKindIx) -> ItemKindIx -> Bool
$crangeSize :: (ItemKindIx, ItemKindIx) -> Int
rangeSize :: (ItemKindIx, ItemKindIx) -> Int
$cunsafeRangeSize :: (ItemKindIx, ItemKindIx) -> Int
unsafeRangeSize :: (ItemKindIx, ItemKindIx) -> Int
Ix.Ix, Eq ItemKindIx
Eq ItemKindIx =>
(Int -> ItemKindIx -> Int)
-> (ItemKindIx -> Int) -> Hashable ItemKindIx
Int -> ItemKindIx -> Int
ItemKindIx -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> ItemKindIx -> Int
hashWithSalt :: Int -> ItemKindIx -> Int
$chash :: ItemKindIx -> Int
hash :: ItemKindIx -> Int
Hashable, Get ItemKindIx
[ItemKindIx] -> Put
ItemKindIx -> Put
(ItemKindIx -> Put)
-> Get ItemKindIx -> ([ItemKindIx] -> Put) -> Binary ItemKindIx
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
$cput :: ItemKindIx -> Put
put :: ItemKindIx -> Put
$cget :: Get ItemKindIx
get :: Get ItemKindIx
$cputList :: [ItemKindIx] -> Put
putList :: [ItemKindIx] -> Put
Binary)
data ItemDisco =
ItemDiscoFull IA.AspectRecord
| ItemDiscoMean IA.KindMean
deriving (Int -> ItemDisco -> ShowS
[ItemDisco] -> ShowS
ItemDisco -> String
(Int -> ItemDisco -> ShowS)
-> (ItemDisco -> String)
-> ([ItemDisco] -> ShowS)
-> Show ItemDisco
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ItemDisco -> ShowS
showsPrec :: Int -> ItemDisco -> ShowS
$cshow :: ItemDisco -> String
show :: ItemDisco -> String
$cshowList :: [ItemDisco] -> ShowS
showList :: [ItemDisco] -> ShowS
Show, Eq ItemDisco
Eq ItemDisco =>
(ItemDisco -> ItemDisco -> Ordering)
-> (ItemDisco -> ItemDisco -> Bool)
-> (ItemDisco -> ItemDisco -> Bool)
-> (ItemDisco -> ItemDisco -> Bool)
-> (ItemDisco -> ItemDisco -> Bool)
-> (ItemDisco -> ItemDisco -> ItemDisco)
-> (ItemDisco -> ItemDisco -> ItemDisco)
-> Ord ItemDisco
ItemDisco -> ItemDisco -> Bool
ItemDisco -> ItemDisco -> Ordering
ItemDisco -> ItemDisco -> ItemDisco
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ItemDisco -> ItemDisco -> Ordering
compare :: ItemDisco -> ItemDisco -> Ordering
$c< :: ItemDisco -> ItemDisco -> Bool
< :: ItemDisco -> ItemDisco -> Bool
$c<= :: ItemDisco -> ItemDisco -> Bool
<= :: ItemDisco -> ItemDisco -> Bool
$c> :: ItemDisco -> ItemDisco -> Bool
> :: ItemDisco -> ItemDisco -> Bool
$c>= :: ItemDisco -> ItemDisco -> Bool
>= :: ItemDisco -> ItemDisco -> Bool
$cmax :: ItemDisco -> ItemDisco -> ItemDisco
max :: ItemDisco -> ItemDisco -> ItemDisco
$cmin :: ItemDisco -> ItemDisco -> ItemDisco
min :: ItemDisco -> ItemDisco -> ItemDisco
Ord, ItemDisco -> ItemDisco -> Bool
(ItemDisco -> ItemDisco -> Bool)
-> (ItemDisco -> ItemDisco -> Bool) -> Eq ItemDisco
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ItemDisco -> ItemDisco -> Bool
== :: ItemDisco -> ItemDisco -> Bool
$c/= :: ItemDisco -> ItemDisco -> Bool
/= :: ItemDisco -> ItemDisco -> Bool
Eq)
data ItemFull = ItemFull
{ ItemFull -> Item
itemBase :: Item
, ItemFull -> ContentId ItemKind
itemKindId :: ContentId IK.ItemKind
, ItemFull -> ItemKind
itemKind :: IK.ItemKind
, ItemFull -> ItemDisco
itemDisco :: ItemDisco
, ItemFull -> Bool
itemSuspect :: Bool
}
deriving Int -> ItemFull -> ShowS
[ItemFull] -> ShowS
ItemFull -> String
(Int -> ItemFull -> ShowS)
-> (ItemFull -> String) -> ([ItemFull] -> ShowS) -> Show ItemFull
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ItemFull -> ShowS
showsPrec :: Int -> ItemFull -> ShowS
$cshow :: ItemFull -> String
show :: ItemFull -> String
$cshowList :: [ItemFull] -> ShowS
showList :: [ItemFull] -> ShowS
Show
type ItemFullKit = (ItemFull, ItemQuant)
type DiscoveryKind = EM.EnumMap ItemKindIx (ContentId IK.ItemKind)
type ItemIxMap = EM.EnumMap ItemKindIx (ES.EnumSet ItemId)
data Benefit = Benefit
{ Benefit -> Bool
benInEqp :: Bool
, Benefit -> Double
benPickup :: Double
, Benefit -> Double
benApply :: Double
, Benefit -> Double
benMelee :: Double
, Benefit -> Double
benFling :: Double
}
deriving (Int -> Benefit -> ShowS
[Benefit] -> ShowS
Benefit -> String
(Int -> Benefit -> ShowS)
-> (Benefit -> String) -> ([Benefit] -> ShowS) -> Show Benefit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Benefit -> ShowS
showsPrec :: Int -> Benefit -> ShowS
$cshow :: Benefit -> String
show :: Benefit -> String
$cshowList :: [Benefit] -> ShowS
showList :: [Benefit] -> ShowS
Show, (forall x. Benefit -> Rep Benefit x)
-> (forall x. Rep Benefit x -> Benefit) -> Generic Benefit
forall x. Rep Benefit x -> Benefit
forall x. Benefit -> Rep Benefit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Benefit -> Rep Benefit x
from :: forall x. Benefit -> Rep Benefit x
$cto :: forall x. Rep Benefit x -> Benefit
to :: forall x. Rep Benefit x -> Benefit
Generic)
instance Binary Benefit
type DiscoveryBenefit = EM.EnumMap ItemId Benefit
newtype ItemTimer = ItemTimer {ItemTimer -> Time
itemTimer :: Time}
deriving (Int -> ItemTimer -> ShowS
[ItemTimer] -> ShowS
ItemTimer -> String
(Int -> ItemTimer -> ShowS)
-> (ItemTimer -> String)
-> ([ItemTimer] -> ShowS)
-> Show ItemTimer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ItemTimer -> ShowS
showsPrec :: Int -> ItemTimer -> ShowS
$cshow :: ItemTimer -> String
show :: ItemTimer -> String
$cshowList :: [ItemTimer] -> ShowS
showList :: [ItemTimer] -> ShowS
Show, ItemTimer -> ItemTimer -> Bool
(ItemTimer -> ItemTimer -> Bool)
-> (ItemTimer -> ItemTimer -> Bool) -> Eq ItemTimer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ItemTimer -> ItemTimer -> Bool
== :: ItemTimer -> ItemTimer -> Bool
$c/= :: ItemTimer -> ItemTimer -> Bool
/= :: ItemTimer -> ItemTimer -> Bool
Eq, Get ItemTimer
[ItemTimer] -> Put
ItemTimer -> Put
(ItemTimer -> Put)
-> Get ItemTimer -> ([ItemTimer] -> Put) -> Binary ItemTimer
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
$cput :: ItemTimer -> Put
put :: ItemTimer -> Put
$cget :: Get ItemTimer
get :: Get ItemTimer
$cputList :: [ItemTimer] -> Put
putList :: [ItemTimer] -> Put
Binary)
type ItemTimers = [ItemTimer]
type ItemQuant = (Int, ItemTimers)
type ItemBag = EM.EnumMap ItemId ItemQuant
type ItemDict = EM.EnumMap ItemId Item
toItemKindIx :: Word16 -> ItemKindIx
{-# INLINE toItemKindIx #-}
toItemKindIx :: Word16 -> ItemKindIx
toItemKindIx = Word16 -> ItemKindIx
ItemKindIx
quantSingle :: ItemQuant
quantSingle :: ItemQuant
quantSingle = (Int
1, [])
itemToFull6 :: COps -> DiscoveryKind -> DiscoveryAspect -> ItemId -> Item
-> ItemFull
itemToFull6 :: COps
-> DiscoveryKind -> DiscoveryAspect -> ItemId -> Item -> ItemFull
itemToFull6 COps{ContentData ItemKind
coitem :: ContentData ItemKind
coitem :: COps -> ContentData ItemKind
coitem, ItemSpeedup
coItemSpeedup :: ItemSpeedup
coItemSpeedup :: COps -> ItemSpeedup
coItemSpeedup} DiscoveryKind
discoKind DiscoveryAspect
discoAspect ItemId
iid Item
itemBase =
let (ContentId ItemKind
itemKindId, Bool
itemSuspect) = case Item -> ItemIdentity
jkind Item
itemBase of
IdentityObvious ContentId ItemKind
ik -> (ContentId ItemKind
ik, Bool
False)
IdentityCovered ItemKindIx
ix ContentId ItemKind
ik ->
(ContentId ItemKind, Bool)
-> (ContentId ItemKind -> (ContentId ItemKind, Bool))
-> Maybe (ContentId ItemKind)
-> (ContentId ItemKind, Bool)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (ContentId ItemKind
ik, Bool
True) (, Bool
False) (Maybe (ContentId ItemKind) -> (ContentId ItemKind, Bool))
-> Maybe (ContentId ItemKind) -> (ContentId ItemKind, Bool)
forall a b. (a -> b) -> a -> b
$ ItemKindIx
ix ItemKindIx -> DiscoveryKind -> Maybe (ContentId ItemKind)
forall k a. Enum k => k -> EnumMap k a -> Maybe a
`EM.lookup` DiscoveryKind
discoKind
itemKind :: ItemKind
itemKind = ContentData ItemKind -> ContentId ItemKind -> ItemKind
forall a. ContentData a -> ContentId a -> a
okind ContentData ItemKind
coitem ContentId ItemKind
itemKindId
km :: KindMean
km = ContentId ItemKind -> ItemSpeedup -> KindMean
getKindMean ContentId ItemKind
itemKindId ItemSpeedup
coItemSpeedup
itemAspectMean :: KindMean
itemAspectMean | Bool
itemSuspect = KindMean
km {IA.kmConst = False}
| Bool
otherwise = KindMean
km
itemDisco :: ItemDisco
itemDisco = case ItemId -> DiscoveryAspect -> Maybe AspectRecord
forall k a. Enum k => k -> EnumMap k a -> Maybe a
EM.lookup ItemId
iid DiscoveryAspect
discoAspect of
Just AspectRecord
itemAspect -> AspectRecord -> ItemDisco
ItemDiscoFull AspectRecord
itemAspect
Maybe AspectRecord
Nothing -> KindMean -> ItemDisco
ItemDiscoMean KindMean
itemAspectMean
in ItemFull {Bool
ContentId ItemKind
ItemKind
ItemDisco
Item
itemBase :: Item
itemKindId :: ContentId ItemKind
itemKind :: ItemKind
itemDisco :: ItemDisco
itemSuspect :: Bool
itemBase :: Item
itemKindId :: ContentId ItemKind
itemSuspect :: Bool
itemKind :: ItemKind
itemDisco :: ItemDisco
..}
aspectRecordFull :: ItemFull -> IA.AspectRecord
aspectRecordFull :: ItemFull -> AspectRecord
aspectRecordFull ItemFull
itemFull =
case ItemFull -> ItemDisco
itemDisco ItemFull
itemFull of
ItemDiscoFull AspectRecord
itemAspect -> AspectRecord
itemAspect
ItemDiscoMean KindMean
itemAspectMean -> KindMean -> AspectRecord
IA.kmMean KindMean
itemAspectMean
strongestSlot :: DiscoveryBenefit -> Ability.EqpSlot -> [(ItemId, ItemFullKit)]
-> [(Int, (ItemId, ItemFullKit))]
strongestSlot :: DiscoveryBenefit
-> EqpSlot
-> [(ItemId, ItemFullKit)]
-> [(Int, (ItemId, ItemFullKit))]
strongestSlot DiscoveryBenefit
discoBenefit EqpSlot
eqpSlot [(ItemId, ItemFullKit)]
is =
let f :: (ItemId, ItemFullKit) -> Maybe (Int, (ItemId, ItemFullKit))
f (ItemId
iid, (ItemFull
itemFull, ItemQuant
kit)) =
let Benefit{Bool
benInEqp :: Benefit -> Bool
benInEqp :: Bool
benInEqp, Double
benPickup :: Benefit -> Double
benPickup :: Double
benPickup, Double
benMelee :: Benefit -> Double
benMelee :: Double
benMelee} = DiscoveryBenefit
discoBenefit DiscoveryBenefit -> ItemId -> Benefit
forall k a. Enum k => EnumMap k a -> k -> a
EM.! ItemId
iid
in if Bool -> Bool
not Bool
benInEqp
then Maybe (Int, (ItemId, ItemFullKit))
forall a. Maybe a
Nothing
else (Int, (ItemId, ItemFullKit)) -> Maybe (Int, (ItemId, ItemFullKit))
forall a. a -> Maybe a
Just ((Int, (ItemId, ItemFullKit))
-> Maybe (Int, (ItemId, ItemFullKit)))
-> (Int, (ItemId, ItemFullKit))
-> Maybe (Int, (ItemId, ItemFullKit))
forall a b. (a -> b) -> a -> b
$
let ben :: Int
ben = case EqpSlot
eqpSlot of
EqpSlot
EqpSlotWeaponFast ->
Double -> Int
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
ceiling Double
benPickup
EqpSlot
EqpSlotWeaponBig ->
Double -> Int
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (- Double
benMelee)
EqpSlot
_ -> EqpSlot -> AspectRecord -> Int
valueAtEqpSlot EqpSlot
eqpSlot (AspectRecord -> Int) -> AspectRecord -> Int
forall a b. (a -> b) -> a -> b
$ ItemFull -> AspectRecord
aspectRecordFull ItemFull
itemFull
idBonus :: Int
idBonus = if ItemFull -> Bool
itemSuspect ItemFull
itemFull then Int
1000 else Int
0
arItem :: AspectRecord
arItem = ItemFull -> AspectRecord
aspectRecordFull ItemFull
itemFull
uniqueBonus :: Int
uniqueBonus = if Flag -> AspectRecord -> Bool
IA.checkFlag Flag
Ability.Unique AspectRecord
arItem Bool -> Bool -> Bool
&& Int
ben Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
20
then Int
1000
else Int
0
in (Int
ben Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
idBonus Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
uniqueBonus, (ItemId
iid, (ItemFull
itemFull, ItemQuant
kit)))
in ((Int, (ItemId, ItemFullKit))
-> (Int, (ItemId, ItemFullKit)) -> Ordering)
-> [(Int, (ItemId, ItemFullKit))] -> [(Int, (ItemId, ItemFullKit))]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (((Int, (ItemId, ItemFullKit))
-> (Int, (ItemId, ItemFullKit)) -> Ordering)
-> (Int, (ItemId, ItemFullKit))
-> (Int, (ItemId, ItemFullKit))
-> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip (((Int, (ItemId, ItemFullKit))
-> (Int, (ItemId, ItemFullKit)) -> Ordering)
-> (Int, (ItemId, ItemFullKit))
-> (Int, (ItemId, ItemFullKit))
-> Ordering)
-> ((Int, (ItemId, ItemFullKit))
-> (Int, (ItemId, ItemFullKit)) -> Ordering)
-> (Int, (ItemId, ItemFullKit))
-> (Int, (ItemId, ItemFullKit))
-> Ordering
forall a b. (a -> b) -> a -> b
$ ((Int, (ItemId, ItemFullKit)) -> Int)
-> (Int, (ItemId, ItemFullKit))
-> (Int, (ItemId, ItemFullKit))
-> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (Int, (ItemId, ItemFullKit)) -> Int
forall a b. (a, b) -> a
fst) ([(Int, (ItemId, ItemFullKit))] -> [(Int, (ItemId, ItemFullKit))])
-> [(Int, (ItemId, ItemFullKit))] -> [(Int, (ItemId, ItemFullKit))]
forall a b. (a -> b) -> a -> b
$ ((ItemId, ItemFullKit) -> Maybe (Int, (ItemId, ItemFullKit)))
-> [(ItemId, ItemFullKit)] -> [(Int, (ItemId, ItemFullKit))]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (ItemId, ItemFullKit) -> Maybe (Int, (ItemId, ItemFullKit))
f [(ItemId, ItemFullKit)]
is
valueAtEqpSlot :: EqpSlot -> IA.AspectRecord -> Int
valueAtEqpSlot :: EqpSlot -> AspectRecord -> Int
valueAtEqpSlot EqpSlot
eqpSlot arItem :: AspectRecord
arItem@IA.AspectRecord{Int
Maybe EqpSlot
Maybe (GroupName ItemKind)
Text
Flags
Skills
ThrowMod
aTimeout :: Int
aSkills :: Skills
aFlags :: Flags
aELabel :: Text
aToThrow :: ThrowMod
aPresentAs :: Maybe (GroupName ItemKind)
aEqpSlot :: Maybe EqpSlot
aTimeout :: AspectRecord -> Int
aSkills :: AspectRecord -> Skills
aFlags :: AspectRecord -> Flags
aELabel :: AspectRecord -> Text
aToThrow :: AspectRecord -> ThrowMod
aPresentAs :: AspectRecord -> Maybe (GroupName ItemKind)
aEqpSlot :: AspectRecord -> Maybe EqpSlot
..} =
case EqpSlot
eqpSlot of
EqpSlot
EqpSlotMove -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkMove Skills
aSkills
EqpSlot
EqpSlotMelee -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkMelee Skills
aSkills
EqpSlot
EqpSlotDisplace -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkDisplace Skills
aSkills
EqpSlot
EqpSlotAlter -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkAlter Skills
aSkills
EqpSlot
EqpSlotWait -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkWait Skills
aSkills
EqpSlot
EqpSlotMoveItem -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkMoveItem Skills
aSkills
EqpSlot
EqpSlotProject -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkProject Skills
aSkills
EqpSlot
EqpSlotApply -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkApply Skills
aSkills
EqpSlot
EqpSlotSwimming -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkSwimming Skills
aSkills
EqpSlot
EqpSlotFlying -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkFlying Skills
aSkills
EqpSlot
EqpSlotHurtMelee -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkHurtMelee Skills
aSkills
EqpSlot
EqpSlotArmorMelee -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkArmorMelee Skills
aSkills
EqpSlot
EqpSlotArmorRanged -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkArmorRanged Skills
aSkills
EqpSlot
EqpSlotMaxHP -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkMaxHP Skills
aSkills
EqpSlot
EqpSlotSpeed -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkSpeed Skills
aSkills
EqpSlot
EqpSlotSight -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkSight Skills
aSkills
EqpSlot
EqpSlotShine -> Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkShine Skills
aSkills
EqpSlot
EqpSlotMiscBonus ->
Int
aTimeout
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkMaxCalm Skills
aSkills
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkSmell Skills
aSkills
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkNocto Skills
aSkills
EqpSlot
EqpSlotWeaponFast -> String -> Int
forall a. HasCallStack => String -> a
error (String -> Int) -> String -> Int
forall a b. (a -> b) -> a -> b
$ String
"" String -> AspectRecord -> String
forall v. Show v => String -> v -> String
`showFailure` AspectRecord
arItem
EqpSlot
EqpSlotWeaponBig -> String -> Int
forall a. HasCallStack => String -> a
error (String -> Int) -> String -> Int
forall a b. (a -> b) -> a -> b
$ String
"" String -> AspectRecord -> String
forall v. Show v => String -> v -> String
`showFailure` AspectRecord
arItem
itemTimerZero :: ItemTimer
itemTimerZero :: ItemTimer
itemTimerZero = Time -> ItemTimer
ItemTimer Time
timeZero
createItemTimer :: Time -> Delta Time -> ItemTimer
createItemTimer :: Time -> Delta Time -> ItemTimer
createItemTimer Time
localTime Delta Time
delta = Time -> ItemTimer
ItemTimer (Time -> ItemTimer) -> Time -> ItemTimer
forall a b. (a -> b) -> a -> b
$ Time
localTime Time -> Delta Time -> Time
`timeShift` Delta Time
delta
shiftItemTimer :: Delta Time -> ItemTimer -> ItemTimer
shiftItemTimer :: Delta Time -> ItemTimer -> ItemTimer
shiftItemTimer Delta Time
delta ItemTimer
t = Time -> ItemTimer
ItemTimer (Time -> ItemTimer) -> Time -> ItemTimer
forall a b. (a -> b) -> a -> b
$ ItemTimer -> Time
itemTimer ItemTimer
t Time -> Delta Time -> Time
`timeShift` Delta Time
delta
deltaOfItemTimer :: Time -> ItemTimer -> Delta Time
deltaOfItemTimer :: Time -> ItemTimer -> Delta Time
deltaOfItemTimer Time
localTime ItemTimer
t = Time -> Time -> Delta Time
timeDeltaToFrom (ItemTimer -> Time
itemTimer ItemTimer
t) Time
localTime
charging :: Time -> ItemTimer -> Bool
charging :: Time -> ItemTimer -> Bool
charging Time
localTime = (Time -> Time -> Bool
forall a. Ord a => a -> a -> Bool
> Time
localTime) (Time -> Bool) -> (ItemTimer -> Time) -> ItemTimer -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ItemTimer -> Time
itemTimer
ncharges :: Time -> ItemQuant -> Int
ncharges :: Time -> ItemQuant -> Int
ncharges Time
localTime (Int
itemK, [ItemTimer]
itemTimers) =
Int
itemK Int -> Int -> Int
forall a. Num a => a -> a -> a
- [ItemTimer] -> Int
forall a. [a] -> Int
length ((ItemTimer -> Bool) -> [ItemTimer] -> [ItemTimer]
forall a. (a -> Bool) -> [a] -> [a]
filter (Time -> ItemTimer -> Bool
charging Time
localTime) [ItemTimer]
itemTimers)
hasCharge :: Time -> ItemQuant -> Bool
hasCharge :: Time -> ItemQuant -> Bool
hasCharge Time
localTime ItemQuant
kit = Time -> ItemQuant -> Int
ncharges Time
localTime ItemQuant
kit Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
strongestMelee :: Bool -> Maybe DiscoveryBenefit -> Time
-> [(ItemId, ItemFullKit)]
-> [(Double, Bool, Int, Int, ItemId, ItemFullKit)]
strongestMelee :: Bool
-> Maybe DiscoveryBenefit
-> Time
-> [(ItemId, ItemFullKit)]
-> [(Double, Bool, Int, Int, ItemId, ItemFullKit)]
strongestMelee Bool
_ Maybe DiscoveryBenefit
_ Time
_ [] = []
strongestMelee Bool
ignoreCharges Maybe DiscoveryBenefit
mdiscoBenefit Time
localTime [(ItemId, ItemFullKit)]
kitAss =
let f :: (ItemId, ItemFullKit)
-> Maybe (Double, Bool, Int, Int, ItemId, ItemFullKit)
f (ItemId
iid, ifk :: ItemFullKit
ifk@(ItemFull
itemFull, ItemQuant
kit)) =
let rawDmg :: Double
rawDmg = ItemKind -> Double
IK.damageUsefulness (ItemKind -> Double) -> ItemKind -> Double
forall a b. (a -> b) -> a -> b
$ ItemFull -> ItemKind
itemKind ItemFull
itemFull
unIDedBonus :: Double
unIDedBonus = if ItemFull -> Bool
itemSuspect ItemFull
itemFull then Double
1000 else Double
0
totalValue :: Double
totalValue = case Maybe DiscoveryBenefit
mdiscoBenefit of
Just DiscoveryBenefit
discoBenefit ->
let Benefit{Double
benMelee :: Benefit -> Double
benMelee :: Double
benMelee} = DiscoveryBenefit
discoBenefit DiscoveryBenefit -> ItemId -> Benefit
forall k a. Enum k => EnumMap k a -> k -> a
EM.! ItemId
iid
in Double
benMelee Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
unIDedBonus
Maybe DiscoveryBenefit
Nothing -> - Double
rawDmg
arItem :: AspectRecord
arItem = ItemFull -> AspectRecord
aspectRecordFull ItemFull
itemFull
timeout :: Int
timeout = AspectRecord -> Int
IA.aTimeout AspectRecord
arItem
hasEffect :: Bool
hasEffect = (Effect -> Bool) -> [Effect] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Effect -> Bool
IK.forApplyEffect
(ItemKind -> [Effect]
IK.ieffects (ItemKind -> [Effect]) -> ItemKind -> [Effect]
forall a b. (a -> b) -> a -> b
$ ItemFull -> ItemKind
itemKind ItemFull
itemFull)
ncha :: Int
ncha = Time -> ItemQuant -> Int
ncharges Time
localTime ItemQuant
kit
in if Bool
ignoreCharges Bool -> Bool -> Bool
|| Int
ncha Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then (Double, Bool, Int, Int, ItemId, ItemFullKit)
-> Maybe (Double, Bool, Int, Int, ItemId, ItemFullKit)
forall a. a -> Maybe a
Just (Double
totalValue, Bool
hasEffect, Int
timeout, Int
ncha, ItemId
iid, ItemFullKit
ifk)
else Maybe (Double, Bool, Int, Int, ItemId, ItemFullKit)
forall a. Maybe a
Nothing
in ((Double, Bool, Int, Int, ItemId, ItemFullKit)
-> (Double, Bool, Int, ContentId ItemKind))
-> [(Double, Bool, Int, Int, ItemId, ItemFullKit)]
-> [(Double, Bool, Int, Int, ItemId, ItemFullKit)]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (\(Double
value, Bool
hasEffect, Int
timeout, Int
_, ItemId
_, (ItemFull
itemFull, ItemQuant
_)) ->
let timN :: Int
timN = if Int
timeout Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then -Int
99999 else - Int
timeout
in (Double
value, Bool -> Bool
not Bool
hasEffect, Int
timN, ItemFull -> ContentId ItemKind
itemKindId ItemFull
itemFull))
(((ItemId, ItemFullKit)
-> Maybe (Double, Bool, Int, Int, ItemId, ItemFullKit))
-> [(ItemId, ItemFullKit)]
-> [(Double, Bool, Int, Int, ItemId, ItemFullKit)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (ItemId, ItemFullKit)
-> Maybe (Double, Bool, Int, Int, ItemId, ItemFullKit)
f [(ItemId, ItemFullKit)]
kitAss)
unknownAspect :: (IK.Aspect -> [Dice.Dice]) -> ItemFull -> Bool
unknownAspect :: (Aspect -> [Dice]) -> ItemFull -> Bool
unknownAspect Aspect -> [Dice]
f itemFull :: ItemFull
itemFull@ItemFull{itemKind :: ItemFull -> ItemKind
itemKind=IK.ItemKind{[Aspect]
iaspects :: [Aspect]
iaspects :: ItemKind -> [Aspect]
iaspects}, Bool
ContentId ItemKind
ItemDisco
Item
itemBase :: ItemFull -> Item
itemKindId :: ItemFull -> ContentId ItemKind
itemDisco :: ItemFull -> ItemDisco
itemSuspect :: ItemFull -> Bool
itemBase :: Item
itemKindId :: ContentId ItemKind
itemDisco :: ItemDisco
itemSuspect :: Bool
..} =
case ItemDisco
itemDisco of
ItemDiscoMean IA.KindMean{Bool
kmConst :: KindMean -> Bool
kmConst :: Bool
kmConst} ->
let arItem :: AspectRecord
arItem = ItemFull -> AspectRecord
aspectRecordFull ItemFull
itemFull
unknown :: Dice -> Bool
unknown Dice
x = let (Int
minD, Int
maxD) = Dice -> (Int, Int)
Dice.infsupDice Dice
x
in Int
minD Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
maxD
in Bool
itemSuspect Bool -> Bool -> Bool
&& Bool -> Bool
not (Flag -> AspectRecord -> Bool
IA.checkFlag Flag
Ability.MinorAspects AspectRecord
arItem)
Bool -> Bool -> Bool
|| Bool -> Bool
not Bool
kmConst Bool -> Bool -> Bool
&& [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or ((Aspect -> [Bool]) -> [Aspect] -> [Bool]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((Dice -> Bool) -> [Dice] -> [Bool]
forall a b. (a -> b) -> [a] -> [b]
map Dice -> Bool
unknown ([Dice] -> [Bool]) -> (Aspect -> [Dice]) -> Aspect -> [Bool]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Aspect -> [Dice]
f) [Aspect]
iaspects)
ItemDiscoFull{} -> Bool
False
unknownMeleeBonus :: [ItemFull] -> Bool
unknownMeleeBonus :: [ItemFull] -> Bool
unknownMeleeBonus =
let p :: Aspect -> [Dice]
p (IK.AddSkill Skill
Ability.SkHurtMelee Dice
k) = [Dice
k]
p Aspect
_ = []
f :: ItemFull -> Bool -> Bool
f ItemFull
itemFull Bool
b = Bool
b Bool -> Bool -> Bool
|| (Aspect -> [Dice]) -> ItemFull -> Bool
unknownAspect Aspect -> [Dice]
p ItemFull
itemFull
in (ItemFull -> Bool -> Bool) -> Bool -> [ItemFull] -> Bool
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ItemFull -> Bool -> Bool
f Bool
False
unknownSpeedBonus :: [ItemFull] -> Bool
unknownSpeedBonus :: [ItemFull] -> Bool
unknownSpeedBonus =
let p :: Aspect -> [Dice]
p (IK.AddSkill Skill
Ability.SkSpeed Dice
k) = [Dice
k]
p Aspect
_ = []
f :: ItemFull -> Bool -> Bool
f ItemFull
itemFull Bool
b = Bool
b Bool -> Bool -> Bool
|| (Aspect -> [Dice]) -> ItemFull -> Bool
unknownAspect Aspect -> [Dice]
p ItemFull
itemFull
in (ItemFull -> Bool -> Bool) -> Bool -> [ItemFull] -> Bool
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ItemFull -> Bool -> Bool
f Bool
False
conditionMeleeBonus :: [ItemFullKit] -> Int
conditionMeleeBonus :: [ItemFullKit] -> Int
conditionMeleeBonus [ItemFullKit]
kitAss =
let f :: (ItemFull, (Int, b)) -> Int -> Int
f (ItemFull
itemFull, (Int
itemK, b
_)) Int
k =
let arItem :: AspectRecord
arItem = ItemFull -> AspectRecord
aspectRecordFull ItemFull
itemFull
in if Flag -> AspectRecord -> Bool
IA.checkFlag Flag
Ability.Condition AspectRecord
arItem
then Int
k Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
itemK Int -> Int -> Int
forall a. Num a => a -> a -> a
* Skill -> AspectRecord -> Int
IA.getSkill Skill
Ability.SkHurtMelee AspectRecord
arItem
else Int
k
in (ItemFullKit -> Int -> Int) -> Int -> [ItemFullKit] -> Int
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ItemFullKit -> Int -> Int
forall {b}. (ItemFull, (Int, b)) -> Int -> Int
f Int
0 [ItemFullKit]
kitAss
conditionSpeedBonus :: [ItemFullKit] -> Int
conditionSpeedBonus :: [ItemFullKit] -> Int
conditionSpeedBonus [ItemFullKit]
kitAss =
let f :: (ItemFull, (Int, b)) -> Int -> Int
f (ItemFull
itemFull, (Int
itemK, b
_)) Int
k =
let arItem :: AspectRecord
arItem = ItemFull -> AspectRecord
aspectRecordFull ItemFull
itemFull
in if Flag -> AspectRecord -> Bool
IA.checkFlag Flag
Ability.Condition AspectRecord
arItem
then Int
k Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
itemK Int -> Int -> Int
forall a. Num a => a -> a -> a
* Skill -> AspectRecord -> Int
IA.getSkill Skill
Ability.SkSpeed AspectRecord
arItem
else Int
k
in (ItemFullKit -> Int -> Int) -> Int -> [ItemFullKit] -> Int
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ItemFullKit -> Int -> Int
forall {b}. (ItemFull, (Int, b)) -> Int -> Int
f Int
0 [ItemFullKit]
kitAss
armorHurtCalculation :: Bool -> Ability.Skills -> Ability.Skills -> Int
armorHurtCalculation :: Bool -> Skills -> Skills -> Int
armorHurtCalculation Bool
proj Skills
sMaxSk Skills
tMaxSk =
let trim200 :: a -> a
trim200 a
n = a -> a -> a
forall a. Ord a => a -> a -> a
min a
200 (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ a -> a -> a
forall a. Ord a => a -> a -> a
max (-a
200) a
n
itemBonus :: Int
itemBonus =
Int -> Int
forall {a}. (Ord a, Num a) => a -> a
trim200 (Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkHurtMelee Skills
sMaxSk)
Int -> Int -> Int
forall a. Num a => a -> a -> a
- if Bool
proj
then Int -> Int
forall {a}. (Ord a, Num a) => a -> a
trim200 (Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkArmorRanged Skills
tMaxSk)
else Int -> Int
forall {a}. (Ord a, Num a) => a -> a
trim200 (Skill -> Skills -> Int
Ability.getSk Skill
Ability.SkArmorMelee Skills
tMaxSk)
in Int
100 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int -> Int
forall a. Ord a => a -> a -> a
max (-Int
95) Int
itemBonus
mergeItemQuant :: ItemQuant -> ItemQuant -> ItemQuant
mergeItemQuant :: ItemQuant -> ItemQuant -> ItemQuant
mergeItemQuant (Int
k2, [ItemTimer]
it2) (Int
k1, [ItemTimer]
it1) = (Int
k1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
k2, [ItemTimer]
it1 [ItemTimer] -> [ItemTimer] -> [ItemTimer]
forall a. [a] -> [a] -> [a]
++ [ItemTimer]
it2)
listToolsToConsume :: [(ItemId, ItemFullKit)] -> [(ItemId, ItemFullKit)]
-> [((CStore, Bool), (ItemId, ItemFullKit))]
listToolsToConsume :: [(ItemId, ItemFullKit)]
-> [(ItemId, ItemFullKit)]
-> [((CStore, Bool), (ItemId, ItemFullKit))]
listToolsToConsume [(ItemId, ItemFullKit)]
kitAssG [(ItemId, ItemFullKit)]
kitAssE =
let isDurable :: (a, (ItemFull, b)) -> Bool
isDurable = Flag -> AspectRecord -> Bool
IA.checkFlag Flag
Ability.Durable
(AspectRecord -> Bool)
-> ((a, (ItemFull, b)) -> AspectRecord)
-> (a, (ItemFull, b))
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ItemFull -> AspectRecord
aspectRecordFull (ItemFull -> AspectRecord)
-> ((a, (ItemFull, b)) -> ItemFull)
-> (a, (ItemFull, b))
-> AspectRecord
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ItemFull, b) -> ItemFull
forall a b. (a, b) -> a
fst ((ItemFull, b) -> ItemFull)
-> ((a, (ItemFull, b)) -> (ItemFull, b))
-> (a, (ItemFull, b))
-> ItemFull
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, (ItemFull, b)) -> (ItemFull, b)
forall a b. (a, b) -> b
snd
([(ItemId, ItemFullKit)]
kitAssGT, [(ItemId, ItemFullKit)]
kitAssGF) = ((ItemId, ItemFullKit) -> Bool)
-> [(ItemId, ItemFullKit)]
-> ([(ItemId, ItemFullKit)], [(ItemId, ItemFullKit)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (ItemId, ItemFullKit) -> Bool
forall {a} {b}. (a, (ItemFull, b)) -> Bool
isDurable [(ItemId, ItemFullKit)]
kitAssG
([(ItemId, ItemFullKit)]
kitAssET, [(ItemId, ItemFullKit)]
kitAssEF) = ((ItemId, ItemFullKit) -> Bool)
-> [(ItemId, ItemFullKit)]
-> ([(ItemId, ItemFullKit)], [(ItemId, ItemFullKit)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (ItemId, ItemFullKit) -> Bool
forall {a} {b}. (a, (ItemFull, b)) -> Bool
isDurable [(ItemId, ItemFullKit)]
kitAssE
in [(CStore, Bool)]
-> [(ItemId, ItemFullKit)]
-> [((CStore, Bool), (ItemId, ItemFullKit))]
forall a b. [a] -> [b] -> [(a, b)]
zip ((CStore, Bool) -> [(CStore, Bool)]
forall a. a -> [a]
repeat (CStore
CGround, Bool
False)) [(ItemId, ItemFullKit)]
kitAssGF
[((CStore, Bool), (ItemId, ItemFullKit))]
-> [((CStore, Bool), (ItemId, ItemFullKit))]
-> [((CStore, Bool), (ItemId, ItemFullKit))]
forall a. [a] -> [a] -> [a]
++ [(CStore, Bool)]
-> [(ItemId, ItemFullKit)]
-> [((CStore, Bool), (ItemId, ItemFullKit))]
forall a b. [a] -> [b] -> [(a, b)]
zip ((CStore, Bool) -> [(CStore, Bool)]
forall a. a -> [a]
repeat (CStore
CEqp, Bool
False)) [(ItemId, ItemFullKit)]
kitAssEF
[((CStore, Bool), (ItemId, ItemFullKit))]
-> [((CStore, Bool), (ItemId, ItemFullKit))]
-> [((CStore, Bool), (ItemId, ItemFullKit))]
forall a. [a] -> [a] -> [a]
++ [(CStore, Bool)]
-> [(ItemId, ItemFullKit)]
-> [((CStore, Bool), (ItemId, ItemFullKit))]
forall a b. [a] -> [b] -> [(a, b)]
zip ((CStore, Bool) -> [(CStore, Bool)]
forall a. a -> [a]
repeat (CStore
CGround, Bool
True)) [(ItemId, ItemFullKit)]
kitAssGT
[((CStore, Bool), (ItemId, ItemFullKit))]
-> [((CStore, Bool), (ItemId, ItemFullKit))]
-> [((CStore, Bool), (ItemId, ItemFullKit))]
forall a. [a] -> [a] -> [a]
++ [(CStore, Bool)]
-> [(ItemId, ItemFullKit)]
-> [((CStore, Bool), (ItemId, ItemFullKit))]
forall a b. [a] -> [b] -> [(a, b)]
zip ((CStore, Bool) -> [(CStore, Bool)]
forall a. a -> [a]
repeat (CStore
CEqp, Bool
True)) [(ItemId, ItemFullKit)]
kitAssET
countIidConsumed :: ItemFullKit
-> [(Bool, Int, GroupName IK.ItemKind)]
-> (Int, Int, [(Bool, Int, GroupName IK.ItemKind)])
countIidConsumed :: ItemFullKit
-> [(Bool, Int, GroupName ItemKind)]
-> (Int, Int, [(Bool, Int, GroupName ItemKind)])
countIidConsumed (ItemFull{ItemKind
itemKind :: ItemFull -> ItemKind
itemKind :: ItemKind
itemKind}, (Int
k, [ItemTimer]
_)) [(Bool, Int, GroupName ItemKind)]
grps0 =
let hasGroup :: GroupName ItemKind -> Bool
hasGroup GroupName ItemKind
grp =
Bool -> (Int -> Bool) -> Maybe Int -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (Maybe Int -> Bool) -> Maybe Int -> Bool
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> [(GroupName ItemKind, Int)] -> Maybe Int
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup GroupName ItemKind
grp ([(GroupName ItemKind, Int)] -> Maybe Int)
-> [(GroupName ItemKind, Int)] -> Maybe Int
forall a b. (a -> b) -> a -> b
$ ItemKind -> [(GroupName ItemKind, Int)]
IK.ifreq ItemKind
itemKind
matchGroup :: (Int, Int, [(Bool, Int, GroupName ItemKind)])
-> (Bool, Int, GroupName ItemKind)
-> (Int, Int, [(Bool, Int, GroupName ItemKind)])
matchGroup (Int
nToApplyIfDurable, Int
nToDestroyAlways, [(Bool, Int, GroupName ItemKind)]
grps)
(Bool
destroyAlways, Int
n, GroupName ItemKind
grp) =
if GroupName ItemKind -> Bool
hasGroup GroupName ItemKind
grp
then let mkn :: Int
mkn = Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
k Int
n
grps2 :: [(Bool, Int, GroupName ItemKind)]
grps2 = if Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
mkn Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then (Bool
destroyAlways, Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
mkn, GroupName ItemKind
grp) (Bool, Int, GroupName ItemKind)
-> [(Bool, Int, GroupName ItemKind)]
-> [(Bool, Int, GroupName ItemKind)]
forall a. a -> [a] -> [a]
: [(Bool, Int, GroupName ItemKind)]
grps
else [(Bool, Int, GroupName ItemKind)]
grps
in if Bool
destroyAlways
then ( Int
nToApplyIfDurable
, Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
nToDestroyAlways Int
mkn
, [(Bool, Int, GroupName ItemKind)]
grps2 )
else ( Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
nToApplyIfDurable Int
mkn
, Int
nToDestroyAlways
, [(Bool, Int, GroupName ItemKind)]
grps2 )
else ( Int
nToApplyIfDurable
, Int
nToDestroyAlways
, (Bool
destroyAlways, Int
n, GroupName ItemKind
grp) (Bool, Int, GroupName ItemKind)
-> [(Bool, Int, GroupName ItemKind)]
-> [(Bool, Int, GroupName ItemKind)]
forall a. a -> [a] -> [a]
: [(Bool, Int, GroupName ItemKind)]
grps )
in ((Int, Int, [(Bool, Int, GroupName ItemKind)])
-> (Bool, Int, GroupName ItemKind)
-> (Int, Int, [(Bool, Int, GroupName ItemKind)]))
-> (Int, Int, [(Bool, Int, GroupName ItemKind)])
-> [(Bool, Int, GroupName ItemKind)]
-> (Int, Int, [(Bool, Int, GroupName ItemKind)])
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Int, Int, [(Bool, Int, GroupName ItemKind)])
-> (Bool, Int, GroupName ItemKind)
-> (Int, Int, [(Bool, Int, GroupName ItemKind)])
matchGroup (Int
0, Int
0, []) [(Bool, Int, GroupName ItemKind)]
grps0
subtractIidfromGrps :: ( EM.EnumMap CStore ItemBag
, [(CStore, (ItemId, ItemFull))]
, [(Bool, Int, GroupName IK.ItemKind)] )
-> ((CStore, Bool), (ItemId, ItemFullKit))
-> ( EM.EnumMap CStore ItemBag
, [(CStore, (ItemId, ItemFull))]
, [(Bool, Int, GroupName IK.ItemKind)] )
subtractIidfromGrps :: (EnumMap CStore ItemBag, [(CStore, (ItemId, ItemFull))],
[(Bool, Int, GroupName ItemKind)])
-> ((CStore, Bool), (ItemId, ItemFullKit))
-> (EnumMap CStore ItemBag, [(CStore, (ItemId, ItemFull))],
[(Bool, Int, GroupName ItemKind)])
subtractIidfromGrps (EnumMap CStore ItemBag
bagsToLose1, [(CStore, (ItemId, ItemFull))]
iidsToApply1, [(Bool, Int, GroupName ItemKind)]
grps1)
((CStore
store, Bool
durable), (ItemId
iid, itemFullKit :: ItemFullKit
itemFullKit@(ItemFull
itemFull, (Int
_, [ItemTimer]
it)))) =
let (Int
nToApplyIfDurable, Int
nToDestroyAlways, [(Bool, Int, GroupName ItemKind)]
grps2) =
ItemFullKit
-> [(Bool, Int, GroupName ItemKind)]
-> (Int, Int, [(Bool, Int, GroupName ItemKind)])
countIidConsumed ItemFullKit
itemFullKit [(Bool, Int, GroupName ItemKind)]
grps1
(Int
nToApply, Int
nToDestroy) = if Bool
durable
then (Int
nToApplyIfDurable, Int
nToDestroyAlways)
else (Int
0, Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
nToApplyIfDurable Int
nToDestroyAlways)
in ( if Int
nToDestroy Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then EnumMap CStore ItemBag
bagsToLose1
else let kit2 :: ItemQuant
kit2 = (Int
nToDestroy, Int -> [ItemTimer] -> [ItemTimer]
forall a. Int -> [a] -> [a]
take Int
nToDestroy [ItemTimer]
it)
removedBags :: EnumMap CStore ItemBag
removedBags = CStore -> ItemBag -> EnumMap CStore ItemBag
forall k a. Enum k => k -> a -> EnumMap k a
EM.singleton CStore
store (ItemBag -> EnumMap CStore ItemBag)
-> ItemBag -> EnumMap CStore ItemBag
forall a b. (a -> b) -> a -> b
$ ItemId -> ItemQuant -> ItemBag
forall k a. Enum k => k -> a -> EnumMap k a
EM.singleton ItemId
iid ItemQuant
kit2
in (ItemBag -> ItemBag -> ItemBag)
-> EnumMap CStore ItemBag
-> EnumMap CStore ItemBag
-> EnumMap CStore ItemBag
forall a k.
(a -> a -> a) -> EnumMap k a -> EnumMap k a -> EnumMap k a
EM.unionWith ((ItemQuant -> ItemQuant -> ItemQuant)
-> ItemBag -> ItemBag -> ItemBag
forall a k.
(a -> a -> a) -> EnumMap k a -> EnumMap k a -> EnumMap k a
EM.unionWith ItemQuant -> ItemQuant -> ItemQuant
mergeItemQuant)
EnumMap CStore ItemBag
removedBags EnumMap CStore ItemBag
bagsToLose1
, Int
-> (CStore, (ItemId, ItemFull)) -> [(CStore, (ItemId, ItemFull))]
forall a. Int -> a -> [a]
replicate Int
nToApply (CStore
store, (ItemId
iid, ItemFull
itemFull)) [(CStore, (ItemId, ItemFull))]
-> [(CStore, (ItemId, ItemFull))] -> [(CStore, (ItemId, ItemFull))]
forall a. [a] -> [a] -> [a]
++ [(CStore, (ItemId, ItemFull))]
iidsToApply1
, [(Bool, Int, GroupName ItemKind)]
grps2 )
sortIids :: (ItemId -> ItemFull)
-> [(ItemId, ItemQuant)]
-> [(ItemId, ItemQuant)]
sortIids :: (ItemId -> ItemFull)
-> [(ItemId, ItemQuant)] -> [(ItemId, ItemQuant)]
sortIids ItemId -> ItemFull
itemToF =
let kindAndAppearance :: (ItemId, ItemQuant)
-> (Bool, ContentId ItemKind, ItemDisco, Char, Text, Flavour,
Maybe FactionId)
kindAndAppearance (ItemId
iid, ItemQuant
_) =
let ItemFull{itemBase :: ItemFull -> Item
itemBase=Item{Maybe FactionId
Flavour
ItemIdentity
jkind :: Item -> ItemIdentity
jfid :: Item -> Maybe FactionId
jflavour :: Item -> Flavour
jkind :: ItemIdentity
jfid :: Maybe FactionId
jflavour :: Flavour
..}, Bool
ContentId ItemKind
ItemKind
ItemDisco
itemKindId :: ItemFull -> ContentId ItemKind
itemKind :: ItemFull -> ItemKind
itemDisco :: ItemFull -> ItemDisco
itemSuspect :: ItemFull -> Bool
itemKindId :: ContentId ItemKind
itemKind :: ItemKind
itemDisco :: ItemDisco
itemSuspect :: Bool
..} = ItemId -> ItemFull
itemToF ItemId
iid
in ( Bool -> Bool
not Bool
itemSuspect, ContentId ItemKind
itemKindId, ItemDisco
itemDisco
, ItemKind -> Char
IK.isymbol ItemKind
itemKind, ItemKind -> Text
IK.iname ItemKind
itemKind
, Flavour
jflavour, Maybe FactionId
jfid )
in ((ItemId, ItemQuant)
-> (Bool, ContentId ItemKind, ItemDisco, Char, Text, Flavour,
Maybe FactionId))
-> [(ItemId, ItemQuant)] -> [(ItemId, ItemQuant)]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (ItemId, ItemQuant)
-> (Bool, ContentId ItemKind, ItemDisco, Char, Text, Flavour,
Maybe FactionId)
kindAndAppearance
data TileAction =
EmbedAction (ItemId, ItemQuant)
| ToAction (GroupName TK.TileKind)
| WithAction [(Int, GroupName IK.ItemKind)] (GroupName TK.TileKind)
deriving Int -> TileAction -> ShowS
[TileAction] -> ShowS
TileAction -> String
(Int -> TileAction -> ShowS)
-> (TileAction -> String)
-> ([TileAction] -> ShowS)
-> Show TileAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TileAction -> ShowS
showsPrec :: Int -> TileAction -> ShowS
$cshow :: TileAction -> String
show :: TileAction -> String
$cshowList :: [TileAction] -> ShowS
showList :: [TileAction] -> ShowS
Show
parseTileAction :: Bool -> Bool -> [(IK.ItemKind, (ItemId, ItemQuant))]
-> TK.Feature
-> Maybe TileAction
parseTileAction :: Bool
-> Bool
-> [(ItemKind, (ItemId, ItemQuant))]
-> Feature
-> Maybe TileAction
parseTileAction Bool
bproj Bool
underFeet [(ItemKind, (ItemId, ItemQuant))]
embedKindList Feature
feat = case Feature
feat of
TK.Embed GroupName ItemKind
igroup ->
let f :: (ItemKind, (ItemId, ItemQuant)) -> Bool
f (ItemKind
itemKind, (ItemId, ItemQuant)
_) =
Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe (-Int
1) (GroupName ItemKind -> [(GroupName ItemKind, Int)] -> Maybe Int
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup GroupName ItemKind
igroup ([(GroupName ItemKind, Int)] -> Maybe Int)
-> [(GroupName ItemKind, Int)] -> Maybe Int
forall a b. (a -> b) -> a -> b
$ ItemKind -> [(GroupName ItemKind, Int)]
IK.ifreq ItemKind
itemKind) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0
in case ((ItemKind, (ItemId, ItemQuant)) -> Bool)
-> [(ItemKind, (ItemId, ItemQuant))]
-> Maybe (ItemKind, (ItemId, ItemQuant))
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (ItemKind, (ItemId, ItemQuant)) -> Bool
f [(ItemKind, (ItemId, ItemQuant))]
embedKindList of
Maybe (ItemKind, (ItemId, ItemQuant))
Nothing -> Maybe TileAction
forall a. Maybe a
Nothing
Just (ItemKind
_, (ItemId, ItemQuant)
iidkit) -> TileAction -> Maybe TileAction
forall a. a -> Maybe a
Just (TileAction -> Maybe TileAction) -> TileAction -> Maybe TileAction
forall a b. (a -> b) -> a -> b
$ (ItemId, ItemQuant) -> TileAction
EmbedAction (ItemId, ItemQuant)
iidkit
TK.OpenTo GroupName TileKind
tgroup | Bool -> Bool
not (Bool
underFeet Bool -> Bool -> Bool
|| Bool
bproj) -> TileAction -> Maybe TileAction
forall a. a -> Maybe a
Just (TileAction -> Maybe TileAction) -> TileAction -> Maybe TileAction
forall a b. (a -> b) -> a -> b
$ GroupName TileKind -> TileAction
ToAction GroupName TileKind
tgroup
TK.CloseTo GroupName TileKind
tgroup | Bool -> Bool
not (Bool
underFeet Bool -> Bool -> Bool
|| Bool
bproj) -> TileAction -> Maybe TileAction
forall a. a -> Maybe a
Just (TileAction -> Maybe TileAction) -> TileAction -> Maybe TileAction
forall a b. (a -> b) -> a -> b
$ GroupName TileKind -> TileAction
ToAction GroupName TileKind
tgroup
TK.ChangeTo GroupName TileKind
tgroup | Bool -> Bool
not Bool
bproj -> TileAction -> Maybe TileAction
forall a. a -> Maybe a
Just (TileAction -> Maybe TileAction) -> TileAction -> Maybe TileAction
forall a b. (a -> b) -> a -> b
$ GroupName TileKind -> TileAction
ToAction GroupName TileKind
tgroup
TK.OpenWith ProjectileTriggers
proj [(Int, GroupName ItemKind)]
grps GroupName TileKind
tgroup | Bool -> Bool
not Bool
underFeet ->
if ProjectileTriggers
proj ProjectileTriggers -> ProjectileTriggers -> Bool
forall a. Eq a => a -> a -> Bool
== ProjectileTriggers
TK.ProjNo Bool -> Bool -> Bool
&& Bool
bproj
then Maybe TileAction
forall a. Maybe a
Nothing
else TileAction -> Maybe TileAction
forall a. a -> Maybe a
Just (TileAction -> Maybe TileAction) -> TileAction -> Maybe TileAction
forall a b. (a -> b) -> a -> b
$ [(Int, GroupName ItemKind)] -> GroupName TileKind -> TileAction
WithAction [(Int, GroupName ItemKind)]
grps GroupName TileKind
tgroup
TK.CloseWith ProjectileTriggers
proj [(Int, GroupName ItemKind)]
grps GroupName TileKind
tgroup | Bool -> Bool
not Bool
underFeet ->
if ProjectileTriggers
proj ProjectileTriggers -> ProjectileTriggers -> Bool
forall a. Eq a => a -> a -> Bool
== ProjectileTriggers
TK.ProjNo Bool -> Bool -> Bool
&& Bool
bproj
then Maybe TileAction
forall a. Maybe a
Nothing
else TileAction -> Maybe TileAction
forall a. a -> Maybe a
Just (TileAction -> Maybe TileAction) -> TileAction -> Maybe TileAction
forall a b. (a -> b) -> a -> b
$ [(Int, GroupName ItemKind)] -> GroupName TileKind -> TileAction
WithAction [(Int, GroupName ItemKind)]
grps GroupName TileKind
tgroup
TK.ChangeWith ProjectileTriggers
proj [(Int, GroupName ItemKind)]
grps GroupName TileKind
tgroup ->
if ProjectileTriggers
proj ProjectileTriggers -> ProjectileTriggers -> Bool
forall a. Eq a => a -> a -> Bool
== ProjectileTriggers
TK.ProjNo Bool -> Bool -> Bool
&& Bool
bproj
then Maybe TileAction
forall a. Maybe a
Nothing
else TileAction -> Maybe TileAction
forall a. a -> Maybe a
Just (TileAction -> Maybe TileAction) -> TileAction -> Maybe TileAction
forall a b. (a -> b) -> a -> b
$ [(Int, GroupName ItemKind)] -> GroupName TileKind -> TileAction
WithAction [(Int, GroupName ItemKind)]
grps GroupName TileKind
tgroup
Feature
_ -> Maybe TileAction
forall a. Maybe a
Nothing