Implement combat

Put a bunch of gormlaks randomly on the level, and implement combat via
damaging those gormlaks by one point.
This commit is contained in:
Griffin Smith 2019-09-21 12:43:54 -04:00
parent dd16166665
commit d632a30d05
7 changed files with 96 additions and 35 deletions

View file

@ -36,6 +36,8 @@ import qualified Xanthous.Entities.Character as Character
import Xanthous.Entities.Character (characterName) import Xanthous.Entities.Character (characterName)
import Xanthous.Entities import Xanthous.Entities
import Xanthous.Entities.Item (Item) import Xanthous.Entities.Item (Item)
import Xanthous.Entities.Creature (Creature)
import qualified Xanthous.Entities.Creature as Creature
import Xanthous.Entities.Environment (Door, open, locked) import Xanthous.Entities.Environment (Door, open, locked)
import Xanthous.Entities.Character import Xanthous.Entities.Character
import Xanthous.Generators import Xanthous.Generators
@ -64,18 +66,25 @@ runAppM appm = fmap fst . runAppT appm
startEvent :: AppM () startEvent :: AppM ()
startEvent = do startEvent = do
level <- initLevel
generateLevel SCaveAutomata CaveAutomata.defaultParams
$ Dimensions 80 80
entities <>= (SomeEntity <$> level ^. levelWalls)
entities <>= (SomeEntity <$> level ^. levelItems)
characterPosition .= level ^. levelCharacterPosition
modify updateCharacterVision modify updateCharacterVision
prompt_ @'StringPrompt ["character", "namePrompt"] Uncancellable prompt_ @'StringPrompt ["character", "namePrompt"] Uncancellable
$ \(StringResult s) -> do $ \(StringResult s) -> do
character . characterName ?= s character . characterName ?= s
say ["welcome"] =<< use character say ["welcome"] =<< use character
initLevel :: AppM ()
initLevel = do
level <-
generateLevel SCaveAutomata CaveAutomata.defaultParams
$ Dimensions 80 80
entities <>= (SomeEntity <$> level ^. levelWalls)
entities <>= (SomeEntity <$> level ^. levelItems)
entities <>= (SomeEntity <$> level ^. levelCreatures)
characterPosition .= level ^. levelCharacterPosition
handleEvent :: BrickEvent Name () -> AppM (Next GameState) handleEvent :: BrickEvent Name () -> AppM (Next GameState)
handleEvent ev = use promptState >>= \case handleEvent ev = use promptState >>= \case
NoPrompt -> handleNoPromptEvent ev NoPrompt -> handleNoPromptEvent ev
@ -98,7 +107,7 @@ handleCommand (Move dir) = do
characterPosition .= newPos characterPosition .= newPos
describeEntitiesAt newPos describeEntitiesAt newPos
modify updateCharacterVision modify updateCharacterVision
Just Combat -> undefined Just Combat -> attackAt newPos
Just Stop -> pure () Just Stop -> pure ()
continue continue
@ -214,3 +223,22 @@ describeEntitiesAt pos =
let descriptions = description <$> ents let descriptions = description <$> ents
in say ["entities", "description"] $ object in say ["entities", "description"] $ object
["entityDescriptions" A..= toSentence descriptions] ["entityDescriptions" A..= toSentence descriptions]
attackAt :: Position -> AppM ()
attackAt pos =
uses entities (entitiesAtPositionWithType @Creature pos) >>= \case
Empty -> say_ ["combat", "nothingToAttack"]
(creature :< Empty) -> attackCreature creature
creatures -> undefined
where
attackCreature (creatureID, creature) = do
charDamage <- use $ character . characterDamage
let creature' = Creature.damage charDamage creature
msgParams = object ["creature" A..= creature']
if Creature.isDead creature'
then do
say ["combat", "killed"] msgParams
entities . at creatureID .= Nothing
else do
say ["combat", "hit"] msgParams
entities . ix creatureID . positioned .= SomeEntity creature'

View file

@ -3,6 +3,7 @@ module Xanthous.Entities.Character
( Character(..) ( Character(..)
, characterName , characterName
, inventory , inventory
, characterDamage
, mkCharacter , mkCharacter
, pickUpItem , pickUpItem
) where ) where
@ -22,6 +23,7 @@ import Xanthous.Entities.Item
data Character = Character data Character = Character
{ _inventory :: !(Vector Item) { _inventory :: !(Vector Item)
, _characterName :: !(Maybe Text) , _characterName :: !(Maybe Text)
, _characterDamage :: !Word
} }
deriving stock (Show, Eq, Generic) deriving stock (Show, Eq, Generic)
deriving anyclass (CoArbitrary, Function) deriving anyclass (CoArbitrary, Function)
@ -50,6 +52,7 @@ mkCharacter :: Character
mkCharacter = Character mkCharacter = Character
{ _inventory = mempty { _inventory = mempty
, _characterName = Nothing , _characterName = Nothing
, _characterDamage = 1
} }
pickUpItem :: Item -> Character -> Character pickUpItem :: Item -> Character -> Character

View file

@ -7,12 +7,14 @@ module Xanthous.Entities.Creature
, hitpoints , hitpoints
, newWithType , newWithType
, damage , damage
, isDead
) where ) where
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Xanthous.Prelude import Xanthous.Prelude
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Data.Word
import Test.QuickCheck.Arbitrary.Generic import Test.QuickCheck.Arbitrary.Generic
import Data.Aeson.Generic.DerivingVia
import Data.Aeson (ToJSON, FromJSON)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Xanthous.Entities.RawTypes hiding (Creature, description) import Xanthous.Entities.RawTypes hiding (Creature, description)
import qualified Xanthous.Entities.RawTypes as Raw import qualified Xanthous.Entities.RawTypes as Raw
@ -21,10 +23,13 @@ import Xanthous.Entities (Draw(..), Entity(..), DrawRawChar(..))
data Creature = Creature data Creature = Creature
{ _creatureType :: CreatureType { _creatureType :: CreatureType
, _hitpoints :: Word16 , _hitpoints :: Word
} }
deriving stock (Eq, Show, Generic) deriving stock (Eq, Show, Generic)
deriving Draw via DrawRawChar "_creatureType" Creature deriving Draw via DrawRawChar "_creatureType" Creature
deriving (ToJSON, FromJSON)
via WithOptions '[ FieldLabelModifier '[Drop 1] ]
Creature
makeLenses ''Creature makeLenses ''Creature
instance Arbitrary Creature where instance Arbitrary Creature where
@ -39,8 +44,11 @@ newWithType _creatureType =
let _hitpoints = _creatureType ^. maxHitpoints let _hitpoints = _creatureType ^. maxHitpoints
in Creature {..} in Creature {..}
damage :: Word16 -> Creature -> Creature damage :: Word -> Creature -> Creature
damage amount = hitpoints %~ \hp -> damage amount = hitpoints %~ \hp ->
if hp <= amount if hp <= amount
then 0 then 0
else hp - amount else hp - amount
isDead :: Creature -> Bool
isDead = views hitpoints (== 0)

View file

@ -19,7 +19,6 @@ import Test.QuickCheck
import Test.QuickCheck.Arbitrary.Generic 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 Data.Word
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Xanthous.Entities (EntityChar, HasChar(..)) import Xanthous.Entities (EntityChar, HasChar(..))
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -27,12 +26,12 @@ data CreatureType = CreatureType
{ _name :: Text { _name :: Text
, _description :: Text , _description :: Text
, _char :: EntityChar , _char :: EntityChar
, _maxHitpoints :: Word16 , _maxHitpoints :: Word
, _friendly :: Bool , _friendly :: Bool
} }
deriving stock (Show, Eq, Generic) deriving stock (Show, Eq, Generic)
deriving anyclass (NFData) deriving anyclass (NFData)
deriving (FromJSON) deriving (ToJSON, FromJSON)
via WithOptions '[ FieldLabelModifier '[Drop 1] ] via WithOptions '[ FieldLabelModifier '[Drop 1] ]
CreatureType CreatureType
makeFieldsNoPrefix ''CreatureType makeFieldsNoPrefix ''CreatureType

View file

@ -12,6 +12,7 @@ module Xanthous.Generators
, Level(..) , Level(..)
, levelWalls , levelWalls
, levelItems , levelItems
, levelCreatures
, levelCharacterPosition , levelCharacterPosition
, generateLevel , generateLevel
) where ) where
@ -29,7 +30,8 @@ import Xanthous.Data (Dimensions, Position(Position))
import Xanthous.Data.EntityMap (EntityMap) import Xanthous.Data.EntityMap (EntityMap)
import qualified Xanthous.Data.EntityMap as EntityMap import qualified Xanthous.Data.EntityMap as EntityMap
import Xanthous.Entities.Environment import Xanthous.Entities.Environment
import Xanthous.Entities.Item import Xanthous.Entities.Item (Item)
import Xanthous.Entities.Creature (Creature)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
data Generator = CaveAutomata data Generator = CaveAutomata
@ -38,9 +40,6 @@ data Generator = CaveAutomata
data SGenerator (gen :: Generator) where data SGenerator (gen :: Generator) where
SCaveAutomata :: SGenerator 'CaveAutomata SCaveAutomata :: SGenerator 'CaveAutomata
data AGenerator where
AGenerator :: forall gen. SGenerator gen -> AGenerator
type family Params (gen :: Generator) :: Type where type family Params (gen :: Generator) :: Type where
Params 'CaveAutomata = CaveAutomata.Params Params 'CaveAutomata = CaveAutomata.Params
@ -89,9 +88,10 @@ cellsToWalls cells = foldl' maybeInsertWall mempty . assocs $ cells
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
data Level = Level data Level = Level
{ _levelWalls :: EntityMap Wall { _levelWalls :: !(EntityMap Wall)
, _levelItems :: EntityMap Item , _levelItems :: !(EntityMap Item)
, _levelCharacterPosition :: Position , _levelCreatures :: !(EntityMap Creature)
, _levelCharacterPosition :: !Position
} }
makeLenses ''Level makeLenses ''Level
@ -101,5 +101,6 @@ generateLevel gen ps dims = do
let cells = generate gen ps dims rand let cells = generate gen ps dims rand
_levelWalls = cellsToWalls cells _levelWalls = cellsToWalls cells
_levelItems <- randomItems cells _levelItems <- randomItems cells
_levelCreatures <- randomCreatures cells
_levelCharacterPosition <- chooseCharacterPosition cells _levelCharacterPosition <- chooseCharacterPosition cells
pure Level {..} pure Level {..}

View file

@ -2,6 +2,7 @@
module Xanthous.Generators.LevelContents module Xanthous.Generators.LevelContents
( chooseCharacterPosition ( chooseCharacterPosition
, randomItems , randomItems
, randomCreatures
) where ) where
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Xanthous.Prelude import Xanthous.Prelude
@ -13,28 +14,40 @@ import Xanthous.Generators.Util
import Xanthous.Random import Xanthous.Random
import Xanthous.Data (Position, positionFromPair) import Xanthous.Data (Position, positionFromPair)
import Xanthous.Data.EntityMap (EntityMap, _EntityMap) import Xanthous.Data.EntityMap (EntityMap, _EntityMap)
import Xanthous.Entities.Item (Item(..)) import Xanthous.Entities.Raws (rawsWithType, RawType)
import Xanthous.Entities.Raws
import Xanthous.Entities.RawTypes
import qualified Xanthous.Entities.Item as Item import qualified Xanthous.Entities.Item as Item
import Xanthous.Entities.Item (Item)
import qualified Xanthous.Entities.Creature as Creature
import Xanthous.Entities.Creature (Creature)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
chooseCharacterPosition :: MonadRandom m => Cells -> m Position chooseCharacterPosition :: MonadRandom m => Cells -> m Position
chooseCharacterPosition = randomPosition chooseCharacterPosition = randomPosition
randomItems :: MonadRandom m => Cells -> m (EntityMap Item) randomItems :: MonadRandom m => Cells -> m (EntityMap Item)
randomItems cells = do randomItems = randomEntities Item.newWithType (0.0004, 0.001)
let len = rangeSize $ bounds cells
(numItems :: Int) <- floor . (* fromIntegral len) randomCreatures :: MonadRandom m => Cells -> m (EntityMap Creature)
<$> getRandomR @_ @Float (0.0004, 0.001) randomCreatures = randomEntities Creature.newWithType (0.0007, 0.003)
items <- for [0..numItems] $ const $ do
pos <- randomPosition cells randomEntities
itemType <- fmap (fromMaybe (error "no item raws!")) :: forall entity raw m. (MonadRandom m, RawType raw)
. choose . ChooseElement => (raw -> entity)
$ rawsWithType @ItemType -> (Float, Float)
let item = Item.newWithType itemType -> Cells
pure (pos, item) -> m (EntityMap entity)
pure $ _EntityMap # items randomEntities newWithType sizeRange cells =
case fromNullable $ rawsWithType @raw of
Nothing -> pure mempty
Just raws -> do
let len = rangeSize $ bounds cells
(numEntities :: Int) <- floor . (* fromIntegral len) <$> getRandomR sizeRange
entities <- for [0..numEntities] $ const $ do
pos <- randomPosition cells
raw <- choose raws
let entity = newWithType raw
pure (pos, entity)
pure $ _EntityMap # entities
randomPosition :: MonadRandom m => Cells -> m Position randomPosition :: MonadRandom m => Cells -> m Position
randomPosition cells = fmap positionFromPair . choose $ impureNonNull candidates randomPosition cells = fmap positionFromPair . choose $ impureNonNull candidates

View file

@ -15,3 +15,12 @@ open:
character: character:
namePrompt: "What's your name? " namePrompt: "What's your name? "
combat:
nothingToAttack: There's nothing to attack there
hit:
- You hit the {{creature.creatureType.name}}
- You attack the {{creature.creatureType.name}}
killed:
- You kill the {{creature.creatureType.name}}!
- You've killed the {{creature.creatureType.name}}!