about summary refs log blame commit diff
path: root/src/Xanthous/Entities/Character.hs
blob: 0bb5867ee5e1b127a7131ce94424c7663b7a3e3e (plain) (tree)
1
2
3
4
5
6
7
8
9
                                

                                  

                 
                   
                      
               
              
          
         
                                                                                

                       

                                          
            

                                     
                                                                                
                        
                             
                                                                                
 
                          
                                
                                   
                             
                                

                                    
                                           


                                                        
                      



                   




                                                                
 


                                                        

                               
                            
 
                                  
                              
 


                        

                        
                       
                            
                        
                                          

   


                                         


                                            
{-# LANGUAGE TemplateHaskell #-}
module Xanthous.Entities.Character
  ( Character(..)
  , characterName
  , inventory
  , characterDamage
  , characterHitpoints
  , mkCharacter
  , pickUpItem
  , isDead
  ) where
--------------------------------------------------------------------------------
import Xanthous.Prelude
import Test.QuickCheck
import Test.QuickCheck.Instances.Vector ()
import Test.QuickCheck.Arbitrary.Generic
import Brick
import Data.Aeson.Generic.DerivingVia
import Data.Aeson (ToJSON, FromJSON)
--------------------------------------------------------------------------------
import Xanthous.Entities
import Xanthous.Entities.Item
--------------------------------------------------------------------------------

data Character = Character
  { _inventory :: !(Vector Item)
  , _characterName :: !(Maybe Text)
  , _characterDamage :: !Word
  , _characterHitpoints :: !Word
  }
  deriving stock (Show, Eq, Generic)
  deriving anyclass (CoArbitrary, Function)
  deriving (ToJSON, FromJSON)
       via WithOptions '[ FieldLabelModifier '[Drop 1] ]
           Character
makeLenses ''Character

scrollOffset :: Int
scrollOffset = 5

instance Draw Character where
  draw _ = visibleRegion rloc rreg $ str "@"
    where
      rloc = Location (negate scrollOffset, negate scrollOffset)
      rreg = (2 * scrollOffset, 2 * scrollOffset)

-- the character does not (yet) have a mind of its own
instance Brain Character where step = brainVia Brainless

instance Entity Character where
  blocksVision _ = False
  description _ = "yourself"

instance Arbitrary Character where
  arbitrary = genericArbitrary

initialHitpoints :: Word
initialHitpoints = 10

mkCharacter :: Character
mkCharacter = Character
  { _inventory = mempty
  , _characterName = Nothing
  , _characterDamage = 1
  , _characterHitpoints = initialHitpoints
  }

isDead :: Character -> Bool
isDead = (== 0) . view characterHitpoints

pickUpItem :: Item -> Character -> Character
pickUpItem item = inventory %~ (item <|)