Add wielded, wieldable items

Split the character's inventory up into wielded items (in one or both
hands) and the backpack, and display wielded items when drawing the
inventory panel. Currently there's no way to actually *wield* items
though, so this is all unused/untested.

Also, add the ability for items to be "wieldable", which gives specific
descriptions for when attacking with them and also modified damage.
This commit is contained in:
Griffin Smith 2019-12-22 22:46:43 -05:00
parent 0f754eb2a0
commit 5b1c7799a7
8 changed files with 270 additions and 49 deletions

View file

@ -143,8 +143,8 @@ handleCommand PickUp = do
uses entities (entitiesAtPositionWithType @Item pos) >>= \case uses entities (entitiesAtPositionWithType @Item pos) >>= \case
[] -> say_ ["pickUp", "nothingToPickUp"] [] -> say_ ["pickUp", "nothingToPickUp"]
[item] -> pickUpItem item [item] -> pickUpItem item
items -> items' ->
menu_ ["pickUp", "menu"] Cancellable (entityMenu_ items) menu_ ["pickUp", "menu"] Cancellable (entityMenu_ items')
$ \(MenuResult item) -> pickUpItem item $ \(MenuResult item) -> pickUpItem item
continue continue
where where
@ -185,7 +185,7 @@ handleCommand Look = do
handleCommand Wait = stepGame >> continue handleCommand Wait = stepGame >> continue
handleCommand Eat = do handleCommand Eat = do
uses (character . inventory) uses (character . inventory . backpack)
(V.mapMaybe (\item -> (item,) <$> item ^. Item.itemType . edible)) (V.mapMaybe (\item -> (item,) <$> item ^. Item.itemType . edible))
>>= \case >>= \case
Empty -> say_ ["eat", "noFood"] Empty -> say_ ["eat", "noFood"]
@ -197,7 +197,7 @@ handleCommand Eat = do
menuItems = mkMenuItems $ imap foodMenuItem food menuItems = mkMenuItems $ imap foodMenuItem food
in menu_ ["eat", "menuPrompt"] Cancellable menuItems in menu_ ["eat", "menuPrompt"] Cancellable menuItems
$ \(MenuResult (idx, item, edibleItem)) -> do $ \(MenuResult (idx, item, edibleItem)) -> do
character . inventory %= \inv -> character . inventory . backpack %= \inv ->
let (before, after) = V.splitAt idx inv let (before, after) = V.splitAt idx inv
in before <> fromMaybe Empty (tailMay after) in before <> fromMaybe Empty (tailMay after)
let msg = fromMaybe (Messages.lookup ["eat", "eat"]) let msg = fromMaybe (Messages.lookup ["eat", "eat"])
@ -231,7 +231,7 @@ handleCommand Read = do
in readAndContinue msgs in readAndContinue msgs
continue continue
handleCommand Inventory = showPanel InventoryPanel >> continue handleCommand ShowInventory = showPanel InventoryPanel >> continue
handleCommand Save = do handleCommand Save = do
-- TODO default save locations / config file? -- TODO default save locations / config file?
@ -280,8 +280,8 @@ handlePromptEvent _ (Prompt _ SDirectionPrompt _ _ _) _ = continue
handlePromptEvent _ (Prompt _ SContinue _ _ _) _ = continue handlePromptEvent _ (Prompt _ SContinue _ _ _) _ = continue
handlePromptEvent _ (Prompt _ SMenu _ items cb) (VtyEvent (EvKey (KChar chr) [])) handlePromptEvent _ (Prompt _ SMenu _ items' cb) (VtyEvent (EvKey (KChar chr) []))
| Just (MenuOption _ res) <- items ^. at chr | Just (MenuOption _ res) <- items' ^. at chr
= cb (MenuResult res) >> clearPrompt = cb (MenuResult res) >> clearPrompt
| otherwise | otherwise
= continue = continue
@ -350,9 +350,9 @@ menu :: forall (a :: Type) (params :: Type).
-> Map Char (MenuOption a) -- ^ Menu items -> Map Char (MenuOption a) -- ^ Menu items
-> (PromptResult ('Menu a) -> AppM ()) -- ^ Menu promise handler -> (PromptResult ('Menu a) -> AppM ()) -- ^ Menu promise handler
-> AppM () -> AppM ()
menu msgPath params cancellable items cb = do menu msgPath params cancellable items' cb = do
msg <- Messages.message msgPath params msg <- Messages.message msgPath params
let p = mkMenu cancellable items cb let p = mkMenu cancellable items' cb
promptState .= WaitingPrompt msg p promptState .= WaitingPrompt msg p
menu_ :: forall (a :: Type). menu_ :: forall (a :: Type).
@ -419,7 +419,8 @@ attackAt pos =
say ["combat", "killed"] msgParams say ["combat", "killed"] msgParams
entities . at creatureID .= Nothing entities . at creatureID .= Nothing
else do else do
say ["combat", "hit"] msgParams -- TODO attack messages
say ["combat", "hit", "generic"] msgParams
entities . ix creatureID . positioned .= SomeEntity creature' entities . ix creatureID . positioned .= SomeEntity creature'
stepGame -- TODO stepGame -- TODO

View file

@ -20,7 +20,7 @@ data Command
| Look | Look
| Save | Save
| Read | Read
| Inventory | ShowInventory
-- | TODO replace with `:` commands -- | TODO replace with `:` commands
| ToggleRevealAll | ToggleRevealAll
@ -36,7 +36,7 @@ commandFromKey (KChar ';') [] = Just Look
commandFromKey (KChar 'e') [] = Just Eat commandFromKey (KChar 'e') [] = Just Eat
commandFromKey (KChar 'S') [] = Just Save commandFromKey (KChar 'S') [] = Just Save
commandFromKey (KChar 'r') [] = Just Read commandFromKey (KChar 'r') [] = Just Read
commandFromKey (KChar 'i') [] = Just Inventory commandFromKey (KChar 'i') [] = Just ShowInventory
commandFromKey (KChar 'r') [MMeta] = Just ToggleRevealAll commandFromKey (KChar 'r') [MMeta] = Just ToggleRevealAll

View file

@ -10,6 +10,22 @@ module Xanthous.Entities.Character
, hitpointRecoveryRate , hitpointRecoveryRate
, speed , speed
-- * Inventory
, Inventory(..)
, backpack
, wielded
, items
-- ** Wielded items
, Wielded(..)
, hands
, leftHand
, rightHand
, doubleHanded
, wieldedItems
, WieldedItem(..)
, wieldedItem
, wieldableItem
-- * -- *
, mkCharacter , mkCharacter
, pickUpItem , pickUpItem
@ -27,13 +43,148 @@ import Data.Aeson.Generic.DerivingVia
import Data.Aeson (ToJSON, FromJSON) import Data.Aeson (ToJSON, FromJSON)
import Data.Coerce (coerce) import Data.Coerce (coerce)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Xanthous.Util.QuickCheck
import Xanthous.Game.State import Xanthous.Game.State
import Xanthous.Entities.Item import Xanthous.Entities.Item
import Xanthous.Data (TicksPerTile, Hitpoints, Per, Ticks, (|*|), positioned) import Xanthous.Data
(TicksPerTile, Hitpoints, Per, Ticks, (|*|), positioned, Positioned(..))
import Xanthous.Entities.RawTypes (WieldableItem, wieldable)
--------------------------------------------------------------------------------
data WieldedItem = WieldedItem
{ _wieldedItem :: Item
, _wieldableItem :: WieldableItem
-- ^ Invariant: item ^. itemType . wieldable ≡ Just wieldableItem
}
deriving stock (Eq, Show, Ord, Generic)
deriving anyclass (NFData, CoArbitrary, Function)
deriving (ToJSON, FromJSON)
via WithOptions '[ FieldLabelModifier '[Drop 1] ]
WieldedItem
makeFieldsNoPrefix ''WieldedItem
instance Brain WieldedItem where
step ticks (Positioned p wi) =
over positioned (\i -> WieldedItem i $ wi ^. wieldableItem)
<$> step ticks (Positioned p $ wi ^. wieldedItem)
instance Draw WieldedItem where
draw = draw . view wieldedItem
instance Entity WieldedItem where
blocksVision = blocksVision . view wieldedItem
description = description . view wieldedItem
entityChar = entityChar . view wieldedItem
instance Arbitrary WieldedItem where
arbitrary = genericArbitrary <&> \wi ->
wi & wieldedItem . itemType . wieldable ?~ wi ^. wieldableItem
data Wielded
= DoubleHanded WieldedItem
| Hands { _leftHand :: !(Maybe WieldedItem)
, _rightHand :: !(Maybe WieldedItem)
}
deriving stock (Eq, Show, Ord, Generic)
deriving anyclass (NFData, CoArbitrary, Function)
deriving Arbitrary via GenericArbitrary Wielded
deriving (ToJSON, FromJSON)
via WithOptions '[ 'SumEnc 'ObjWithSingleField ]
Wielded
hands :: Prism' Wielded (Maybe WieldedItem, Maybe WieldedItem)
hands = prism' (uncurry Hands) $ \case
Hands l r -> Just (l, r)
_ -> Nothing
leftHand :: Traversal' Wielded WieldedItem
leftHand = hands . _1 . _Just
rightHand :: Traversal' Wielded WieldedItem
rightHand = hands . _2 . _Just
doubleHanded :: Prism' Wielded WieldedItem
doubleHanded = prism' DoubleHanded $ \case
DoubleHanded i -> Just i
_ -> Nothing
wieldedItems :: Traversal' Wielded Item
wieldedItems k (DoubleHanded wielded) = DoubleHanded <$> wieldedItem k wielded
wieldedItems k (Hands l r) = Hands
<$> (_Just . wieldedItem) k l
<*> (_Just . wieldedItem) k r
data Inventory = Inventory
{ _backpack :: Vector Item
, _wielded :: Wielded
}
deriving stock (Eq, Show, Ord, Generic)
deriving anyclass (NFData, CoArbitrary, Function)
deriving Arbitrary via GenericArbitrary Inventory
deriving (ToJSON, FromJSON)
via WithOptions '[ FieldLabelModifier '[Drop 1] ]
Inventory
makeFieldsNoPrefix ''Inventory
items :: Traversal' Inventory Item
items k (Inventory bp w) = Inventory
<$> traversed k bp
<*> wieldedItems k w
type instance Element Inventory = Item
instance MonoFunctor Inventory where
omap = over items
instance MonoFoldable Inventory where
ofoldMap = foldMapOf items
ofoldr = foldrOf items
ofoldl' = foldlOf' items
otoList = toListOf items
oall = allOf items
oany = anyOf items
onull = nullOf items
ofoldr1Ex = foldr1Of items
ofoldl1Ex' = foldl1Of' items
headEx = headEx . toListOf items
lastEx = lastEx . toListOf items
instance MonoTraversable Inventory where
otraverse = traverseOf items
instance Semigroup Inventory where
inv <> inv =
let backpack' = inv ^. backpack <> inv ^. backpack
(wielded', backpack'') = case (inv ^. wielded, inv ^. wielded) of
(wielded, wielded@(DoubleHanded _)) ->
(wielded, backpack' <> fromList (wielded ^.. wieldedItems))
(wielded, wielded@(Hands (Just _) (Just _))) ->
(wielded, backpack' <> fromList (wielded ^.. wieldedItems))
(wielded, Hands Nothing Nothing) -> (wielded, backpack')
(Hands Nothing Nothing, wielded) -> (wielded, backpack')
(Hands (Just l) Nothing, Hands Nothing (Just r)) ->
(Hands (Just l) (Just r), backpack')
(wielded@(DoubleHanded _), wielded) ->
(wielded, backpack' <> fromList (wielded ^.. wieldedItems))
(Hands Nothing (Just r), Hands Nothing (Just r)) ->
(Hands Nothing (Just r), r ^. wieldedItem <| backpack')
(Hands Nothing r, Hands (Just l) Nothing) ->
(Hands (Just l) r, backpack')
(Hands (Just l) Nothing, Hands (Just l) Nothing) ->
(Hands (Just l) Nothing, l ^. wieldedItem <| backpack')
(Hands (Just l) (Just r), Hands Nothing (Just r)) ->
(Hands (Just l) (Just r), r ^. wieldedItem <| backpack')
(Hands (Just l) (Just r), Hands (Just l) Nothing) ->
(Hands (Just l) (Just r), l ^. wieldedItem <| backpack')
in Inventory backpack'' wielded'
instance Monoid Inventory where
mempty = Inventory mempty $ Hands Nothing Nothing
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
data Character = Character data Character = Character
{ _inventory :: !(Vector Item) { _inventory :: !Inventory
, _characterName :: !(Maybe Text) , _characterName :: !(Maybe Text)
, _characterDamage :: !Hitpoints , _characterDamage :: !Hitpoints
, _characterHitpoints' :: !Double , _characterHitpoints' :: !Double
@ -95,7 +246,7 @@ isDead :: Character -> Bool
isDead = (== 0) . characterHitpoints isDead = (== 0) . characterHitpoints
pickUpItem :: Item -> Character -> Character pickUpItem :: Item -> Character -> Character
pickUpItem item = inventory %~ (item <|) pickUpItem it = inventory . backpack %~ (it <|)
damage :: Hitpoints -> Character -> Character damage :: Hitpoints -> Character -> Character
damage (fromIntegral -> amount) = characterHitpoints' %~ \case damage (fromIntegral -> amount) = characterHitpoints' %~ \case

View file

@ -34,7 +34,8 @@ import Test.QuickCheck.Arbitrary.Generic
import Data.Aeson.Generic.DerivingVia import Data.Aeson.Generic.DerivingVia
import Data.Aeson (ToJSON, FromJSON) import Data.Aeson (ToJSON, FromJSON)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Xanthous.Entities.RawTypes hiding (Creature, description) import Xanthous.Entities.RawTypes
hiding (Creature, description, damage)
import Xanthous.Game.State import Xanthous.Game.State
import Xanthous.Data import Xanthous.Data
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------

View file

@ -2,36 +2,51 @@
{-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE DuplicateRecordFields #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
module Xanthous.Entities.RawTypes module Xanthous.Entities.RawTypes
( CreatureType(..) (
, EdibleItem(..) EntityRaw(..)
, ItemType(..)
, isEdible
, EntityRaw(..)
, _Creature , _Creature
, _Item
-- * Creatures
, CreatureType(..)
-- * Items
, ItemType(..)
-- ** Item sub-types
-- *** Edible
, EdibleItem(..)
, isEdible
-- *** Wieldable
, WieldableItem(..)
, isWieldable
-- * Lens classes -- * Lens classes
, HasAttackMessage(..)
, HasChar(..) , HasChar(..)
, HasName(..) , HasDamage(..)
, HasDescription(..) , HasDescription(..)
, HasEatMessage(..)
, HasEdible(..)
, HasFriendly(..)
, HasHitpointsHealed(..)
, HasLongDescription(..) , HasLongDescription(..)
, HasMaxHitpoints(..) , HasMaxHitpoints(..)
, HasFriendly(..) , HasName(..)
, HasEatMessage(..)
, HasHitpointsHealed(..)
, HasEdible(..)
, HasSpeed(..) , HasSpeed(..)
, HasWieldable(..)
) where ) where
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Xanthous.Prelude import Xanthous.Prelude
import Test.QuickCheck import Test.QuickCheck
import Test.QuickCheck.Arbitrary.Generic
import Data.Aeson.Generic.DerivingVia import Data.Aeson.Generic.DerivingVia
import Data.Aeson (ToJSON, FromJSON) import Data.Aeson (ToJSON, FromJSON)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Xanthous.Messages (Message(..)) import Xanthous.Messages (Message(..))
import Xanthous.Data (TicksPerTile, Hitpoints) import Xanthous.Data (TicksPerTile, Hitpoints)
import Xanthous.Data.EntityChar import Xanthous.Data.EntityChar
import Xanthous.Util.QuickCheck
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
data CreatureType = CreatureType data CreatureType = CreatureType
{ _name :: !Text { _name :: !Text
, _description :: !Text , _description :: !Text
@ -42,14 +57,12 @@ data CreatureType = CreatureType
} }
deriving stock (Show, Eq, Ord, Generic) deriving stock (Show, Eq, Ord, Generic)
deriving anyclass (NFData, CoArbitrary, Function) deriving anyclass (NFData, CoArbitrary, Function)
deriving Arbitrary via GenericArbitrary CreatureType
deriving (ToJSON, FromJSON) deriving (ToJSON, FromJSON)
via WithOptions '[ FieldLabelModifier '[Drop 1] ] via WithOptions '[ FieldLabelModifier '[Drop 1] ]
CreatureType CreatureType
makeFieldsNoPrefix ''CreatureType makeFieldsNoPrefix ''CreatureType
instance Arbitrary CreatureType where
arbitrary = genericArbitrary
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
data EdibleItem = EdibleItem data EdibleItem = EdibleItem
@ -58,13 +71,25 @@ data EdibleItem = EdibleItem
} }
deriving stock (Show, Eq, Ord, Generic) deriving stock (Show, Eq, Ord, Generic)
deriving anyclass (NFData, CoArbitrary, Function) deriving anyclass (NFData, CoArbitrary, Function)
deriving Arbitrary via GenericArbitrary EdibleItem
deriving (ToJSON, FromJSON) deriving (ToJSON, FromJSON)
via WithOptions '[ FieldLabelModifier '[Drop 1] ] via WithOptions '[ FieldLabelModifier '[Drop 1] ]
EdibleItem EdibleItem
makeFieldsNoPrefix ''EdibleItem makeFieldsNoPrefix ''EdibleItem
instance Arbitrary EdibleItem where data WieldableItem = WieldableItem
arbitrary = genericArbitrary { _damage :: !Hitpoints
, _attackMessage :: !(Maybe Message)
}
deriving stock (Show, Eq, Ord, Generic)
deriving anyclass (NFData, CoArbitrary, Function)
deriving Arbitrary via GenericArbitrary WieldableItem
deriving (ToJSON, FromJSON)
via WithOptions '[ FieldLabelModifier '[Drop 1] ]
WieldableItem
makeFieldsNoPrefix ''WieldableItem
--------------------------------------------------------------------------------
data ItemType = ItemType data ItemType = ItemType
{ _name :: Text { _name :: Text
@ -72,20 +97,24 @@ data ItemType = ItemType
, _longDescription :: Text , _longDescription :: Text
, _char :: EntityChar , _char :: EntityChar
, _edible :: Maybe EdibleItem , _edible :: Maybe EdibleItem
, _wieldable :: Maybe WieldableItem
} }
deriving stock (Show, Eq, Ord, Generic) deriving stock (Show, Eq, Ord, Generic)
deriving anyclass (NFData, CoArbitrary, Function) deriving anyclass (NFData, CoArbitrary, Function)
deriving Arbitrary via GenericArbitrary ItemType
deriving (ToJSON, FromJSON) deriving (ToJSON, FromJSON)
via WithOptions '[ FieldLabelModifier '[Drop 1] ] via WithOptions '[ FieldLabelModifier '[Drop 1] ]
ItemType ItemType
makeFieldsNoPrefix ''ItemType makeFieldsNoPrefix ''ItemType
instance Arbitrary ItemType where -- | Can this item be eaten?
arbitrary = genericArbitrary
isEdible :: ItemType -> Bool isEdible :: ItemType -> Bool
isEdible = has $ edible . _Just isEdible = has $ edible . _Just
-- | Can this item be used as a weapon?
isWieldable :: ItemType -> Bool
isWieldable = has $ wieldable . _Just
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
data EntityRaw data EntityRaw
@ -93,9 +122,9 @@ data EntityRaw
| Item ItemType | Item ItemType
deriving stock (Show, Eq, Generic) deriving stock (Show, Eq, Generic)
deriving anyclass (NFData) deriving anyclass (NFData)
deriving Arbitrary via GenericArbitrary EntityRaw
deriving (FromJSON) deriving (FromJSON)
via WithOptions '[ SumEnc ObjWithSingleField ] via WithOptions '[ SumEnc ObjWithSingleField ]
EntityRaw EntityRaw
makePrisms ''EntityRaw makePrisms ''EntityRaw
{-# ANN module ("HLint: ignore Use newtype instead of data" :: String) #-}

View file

@ -0,0 +1,14 @@
Item:
name: stick
description: a wooden stick
longDescription: A sturdy branch broken off from some sort of tree
char:
char:
style:
foreground: yellow
wieldable:
damage: 2
attackMessage:
- You bonk the {{creature.creatureType.name}} over the head with your stick.
- You bash the {{creature.creatureType.name}} on the noggin with your stick.
- You whack the {{creature.creatureType.name}} with your stick.

View file

@ -14,6 +14,7 @@ import Xanthous.Data.EntityMap (EntityMap, atPosition)
import qualified Xanthous.Data.EntityMap as EntityMap import qualified Xanthous.Data.EntityMap as EntityMap
import Xanthous.Game.State import Xanthous.Game.State
import Xanthous.Entities.Character import Xanthous.Entities.Character
import Xanthous.Entities.Item (Item)
import Xanthous.Game import Xanthous.Game
( GameState(..) ( GameState(..)
, entities , entities
@ -105,16 +106,36 @@ drawPanel game panel
. viewport (Resource.Panel panel) Vertical . viewport (Resource.Panel panel) Vertical
$ case panel of $ case panel of
InventoryPanel -> InventoryPanel ->
let items = game ^. character . inventory drawWielded (game ^. character . inventory . wielded)
in if null items <=> drawBackpack (game ^. character . inventory . backpack)
then txtWrap "Your inventory is empty right now." where
else drawWielded :: Wielded -> Widget Name
txtWrap "You are currently carrying the following items:" drawWielded (Hands Nothing Nothing) = emptyWidget
<=> txt " " drawWielded (DoubleHanded i) =
<=> foldl' (<=>) emptyWidget txt $ "You are holding " <> description i <> " in both hands"
(map drawWielded (Hands l r) =
(txtWrap . ((bullet <| " ") <>) . description) maybe
items) emptyWidget
(\i ->
txt $ "You are holding " <> description i <> " in your left hand")
l
<=>
maybe
emptyWidget
(\i ->
txt $ "You are holding " <> description i <> " in your right hand")
r
drawBackpack :: Vector Item -> Widget Name
drawBackpack Empty = txtWrap "Your backpack is empty right now."
drawBackpack backpackItems
= txtWrap ( "You are currently carrying the following items in your "
<> "backpack:")
<=> txt " "
<=> foldl' (<=>) emptyWidget
(map
(txtWrap . ((bullet <| " ") <>) . description)
backpackItems)
drawCharacterInfo :: Character -> Widget Name drawCharacterInfo :: Character -> Widget Name
drawCharacterInfo ch = txt " " <+> charName <+> charHitpoints drawCharacterInfo ch = txt " " <+> charName <+> charHitpoints

View file

@ -37,8 +37,12 @@ combat:
nothingToAttack: There's nothing to attack there. nothingToAttack: There's nothing to attack there.
menu: Which creature would you like to attack? menu: Which creature would you like to attack?
hit: hit:
- You hit the {{creature.creatureType.name}}. fists:
- You attack the {{creature.creatureType.name}}. - You punch the {{creature.creatureType.name}} with your bare fists! It hurts. A lot.
- You strike the {{creature.creatureType.name}} with your bare fists! It leaves a bit of a bruise on your knuckles.
generic:
- You hit the {{creature.creatureType.name}}.
- You attack the {{creature.creatureType.name}}.
creatureAttack: creatureAttack:
- The {{creature.creatureType.name}} hits you! - The {{creature.creatureType.name}} hits you!
- The {{creature.creatureType.name}} attacks you! - The {{creature.creatureType.name}} attacks you!