Link up messages to the overall game
Add a "say" function for saying messages within an app monad to the user, and link everything up to display them and track their history
This commit is contained in:
parent
2fd3e4c9ad
commit
adb3b74c0c
9 changed files with 155 additions and 39 deletions
|
@ -12,6 +12,6 @@ ui = str "Hello, world!"
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
app <- makeApp
|
app <- makeApp
|
||||||
let initialState = getInitialState
|
initialState <- getInitialState
|
||||||
_ <- defaultMain app initialState
|
_ <- defaultMain app initialState
|
||||||
pure ()
|
pure ()
|
||||||
|
|
|
@ -1,35 +1,46 @@
|
||||||
module Xanthous.App (makeApp) where
|
module Xanthous.App (makeApp) where
|
||||||
|
|
||||||
import Xanthous.Prelude
|
import Xanthous.Prelude
|
||||||
import Brick hiding (App)
|
import Brick hiding (App, halt, continue)
|
||||||
import qualified Brick
|
import qualified Brick
|
||||||
import Graphics.Vty.Attributes (defAttr)
|
import Graphics.Vty.Attributes (defAttr)
|
||||||
import Graphics.Vty.Input.Events (Event(EvKey))
|
import Graphics.Vty.Input.Events (Event(EvKey))
|
||||||
|
import Control.Monad.State (get)
|
||||||
|
|
||||||
import Xanthous.Game
|
import Xanthous.Game
|
||||||
import Xanthous.Game.Draw (drawGame)
|
import Xanthous.Game.Draw (drawGame)
|
||||||
import Xanthous.Resource (Name)
|
import Xanthous.Resource (Name)
|
||||||
import Xanthous.Command
|
import Xanthous.Command
|
||||||
import Xanthous.Data (move)
|
import Xanthous.Data (move)
|
||||||
|
import Xanthous.Monad
|
||||||
|
|
||||||
type App = Brick.App GameState () Name
|
type App = Brick.App GameState () Name
|
||||||
|
type AppM a = AppT (EventM Name) a
|
||||||
|
|
||||||
makeApp :: IO App
|
makeApp :: IO App
|
||||||
makeApp = pure $ Brick.App
|
makeApp = pure $ Brick.App
|
||||||
{ appDraw = drawGame
|
{ appDraw = drawGame
|
||||||
, appChooseCursor = const headMay
|
, appChooseCursor = const headMay
|
||||||
, appHandleEvent = handleEvent
|
, appHandleEvent = \state event -> runAppM (handleEvent event) state
|
||||||
, appStartEvent = pure
|
, appStartEvent = runAppM $ startEvent >> get
|
||||||
, appAttrMap = const $ attrMap defAttr []
|
, appAttrMap = const $ attrMap defAttr []
|
||||||
}
|
}
|
||||||
|
|
||||||
handleEvent :: GameState -> BrickEvent Name () -> EventM Name (Next GameState)
|
runAppM :: AppM a -> GameState -> EventM Name a
|
||||||
handleEvent game (VtyEvent (EvKey k mods))
|
runAppM appm = fmap fst . runAppT appm
|
||||||
| Just command <- commandFromKey k mods
|
|
||||||
= handleCommand command game
|
|
||||||
handleEvent game _ = continue game
|
|
||||||
|
|
||||||
handleCommand :: Command -> GameState -> EventM Name (Next GameState)
|
startEvent :: AppM ()
|
||||||
|
startEvent = say ["welcome"]
|
||||||
|
|
||||||
|
handleEvent :: BrickEvent Name () -> AppM (Next GameState)
|
||||||
|
handleEvent (VtyEvent (EvKey k mods))
|
||||||
|
| Just command <- commandFromKey k mods
|
||||||
|
= handleCommand command
|
||||||
|
handleEvent _ = continue
|
||||||
|
|
||||||
|
handleCommand :: Command -> AppM (Next GameState)
|
||||||
handleCommand Quit = halt
|
handleCommand Quit = halt
|
||||||
handleCommand (Move dir) = continue . (characterPosition %~ move dir)
|
handleCommand (Move dir) = do
|
||||||
|
characterPosition %= move dir
|
||||||
|
continue
|
||||||
handleCommand _ = error "unimplemented"
|
handleCommand _ = error "unimplemented"
|
||||||
|
|
|
@ -3,46 +3,82 @@
|
||||||
module Xanthous.Game
|
module Xanthous.Game
|
||||||
( GameState(..)
|
( GameState(..)
|
||||||
, entities
|
, entities
|
||||||
|
, messageHistory
|
||||||
|
, randomGen
|
||||||
|
|
||||||
, getInitialState
|
, getInitialState
|
||||||
|
|
||||||
, positionedCharacter
|
, positionedCharacter
|
||||||
, character
|
, character
|
||||||
, characterPosition
|
, characterPosition
|
||||||
|
|
||||||
|
, MessageHistory(..)
|
||||||
|
, pushMessage
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Xanthous.Prelude
|
import Data.List.NonEmpty ( NonEmpty((:|)))
|
||||||
import Test.QuickCheck.Arbitrary
|
import qualified Data.List.NonEmpty as NonEmpty
|
||||||
|
import System.Random
|
||||||
|
import Test.QuickCheck
|
||||||
|
import Test.QuickCheck.Arbitrary.Generic
|
||||||
|
import Xanthous.Prelude
|
||||||
|
|
||||||
import Xanthous.Data.EntityMap (EntityMap, EntityID)
|
import Xanthous.Data.EntityMap (EntityMap, EntityID)
|
||||||
import qualified Xanthous.Data.EntityMap as EntityMap
|
import qualified Xanthous.Data.EntityMap as EntityMap
|
||||||
import Xanthous.Data (Positioned, Position(..), positioned, position)
|
import Xanthous.Data (Positioned, Position(..), positioned, position)
|
||||||
import Xanthous.Entities.SomeEntity
|
import Xanthous.Entities.SomeEntity
|
||||||
import Xanthous.Entities.Character
|
import Xanthous.Entities.Character
|
||||||
|
import Xanthous.Orphans ()
|
||||||
|
|
||||||
|
data MessageHistory
|
||||||
|
= NoMessageHistory
|
||||||
|
| MessageHistory (NonEmpty Text) Bool
|
||||||
|
deriving stock (Show, Eq, Generic)
|
||||||
|
deriving anyclass (NFData, CoArbitrary, Function)
|
||||||
|
|
||||||
|
instance Arbitrary MessageHistory where
|
||||||
|
arbitrary = genericArbitrary
|
||||||
|
|
||||||
|
pushMessage :: Text -> MessageHistory -> MessageHistory
|
||||||
|
pushMessage msg NoMessageHistory = MessageHistory (msg :| []) True
|
||||||
|
pushMessage msg (MessageHistory msgs _) = MessageHistory (NonEmpty.cons msg msgs) True
|
||||||
|
|
||||||
data GameState = GameState
|
data GameState = GameState
|
||||||
{ _entities :: EntityMap SomeEntity
|
{ _entities :: EntityMap SomeEntity
|
||||||
, _characterEntityID :: EntityID
|
, _characterEntityID :: EntityID
|
||||||
|
, _messageHistory :: MessageHistory
|
||||||
|
, _randomGen :: StdGen
|
||||||
}
|
}
|
||||||
deriving stock (Show, Eq)
|
deriving stock (Show)
|
||||||
makeLenses ''GameState
|
makeLenses ''GameState
|
||||||
|
|
||||||
|
instance Eq GameState where
|
||||||
|
(GameState es₁ ceid₁ mh₁ _) == (GameState es₂ ceid₂ mh₂ _)
|
||||||
|
= es₁ == es₂
|
||||||
|
&& ceid₁ == ceid₂
|
||||||
|
&& mh₁ == mh₂
|
||||||
|
|
||||||
instance Arbitrary GameState where
|
instance Arbitrary GameState where
|
||||||
arbitrary = do
|
arbitrary = do
|
||||||
ents <- arbitrary
|
char <- arbitrary @Character
|
||||||
char <- arbitrary
|
charPos <- arbitrary
|
||||||
pure $ getInitialState
|
_messageHistory <- arbitrary
|
||||||
& entities .~ ents
|
(_characterEntityID, _entities) <- arbitrary <&>
|
||||||
& positionedCharacter .~ char
|
EntityMap.insertAtReturningID charPos (SomeEntity char)
|
||||||
|
_randomGen <- mkStdGen <$> arbitrary
|
||||||
|
pure $ GameState {..}
|
||||||
|
|
||||||
getInitialState :: GameState
|
getInitialState :: IO GameState
|
||||||
getInitialState =
|
getInitialState = do
|
||||||
|
_randomGen <- getStdGen
|
||||||
let char = mkCharacter
|
let char = mkCharacter
|
||||||
(_characterEntityID, _entities)
|
(_characterEntityID, _entities)
|
||||||
= EntityMap.insertAtReturningID
|
= EntityMap.insertAtReturningID
|
||||||
(Position 0 0)
|
(Position 0 0)
|
||||||
(SomeEntity char)
|
(SomeEntity char)
|
||||||
mempty
|
mempty
|
||||||
in GameState {..}
|
_messageHistory = NoMessageHistory
|
||||||
|
pure GameState {..}
|
||||||
|
|
||||||
positionedCharacter :: Lens' GameState (Positioned Character)
|
positionedCharacter :: Lens' GameState (Positioned Character)
|
||||||
positionedCharacter = lens getPositionedCharacter setPositionedCharacter
|
positionedCharacter = lens getPositionedCharacter setPositionedCharacter
|
||||||
|
|
|
@ -8,15 +8,25 @@ import Xanthous.Prelude
|
||||||
import Brick hiding (loc)
|
import Brick hiding (loc)
|
||||||
import Brick.Widgets.Border
|
import Brick.Widgets.Border
|
||||||
import Brick.Widgets.Border.Style
|
import Brick.Widgets.Border.Style
|
||||||
|
import Data.List.NonEmpty(NonEmpty((:|)))
|
||||||
|
|
||||||
import Xanthous.Data (Position(Position), x, y, loc)
|
import Xanthous.Data (Position(Position), x, y, loc)
|
||||||
import Xanthous.Data.EntityMap
|
import Xanthous.Data.EntityMap
|
||||||
import Xanthous.Entities
|
import Xanthous.Entities
|
||||||
import Xanthous.Game (GameState(..), entities, characterPosition)
|
import Xanthous.Game
|
||||||
|
( GameState(..)
|
||||||
|
, entities
|
||||||
|
, characterPosition
|
||||||
|
, MessageHistory(..)
|
||||||
|
, messageHistory
|
||||||
|
)
|
||||||
import Xanthous.Resource (Name(..))
|
import Xanthous.Resource (Name(..))
|
||||||
|
import Xanthous.Orphans ()
|
||||||
|
|
||||||
drawMessages :: GameState -> Widget Name
|
drawMessages :: MessageHistory -> Widget Name
|
||||||
drawMessages _ = str "Welcome to Xanthous! It's dangerous out there, why not stay inside?"
|
drawMessages NoMessageHistory = emptyWidget
|
||||||
|
drawMessages (MessageHistory _ False) = emptyWidget
|
||||||
|
drawMessages (MessageHistory (lastMessage :| _) True) = str $ unpack lastMessage
|
||||||
|
|
||||||
drawEntities :: (Draw a, Show a) => EntityMap a -> Widget Name
|
drawEntities :: (Draw a, Show a) => EntityMap a -> Widget Name
|
||||||
drawEntities em@(fromNullable . positions -> Just entityPositions)
|
drawEntities em@(fromNullable . positions -> Just entityPositions)
|
||||||
|
@ -41,5 +51,5 @@ drawGame :: GameState -> [Widget Name]
|
||||||
drawGame game
|
drawGame game
|
||||||
= pure
|
= pure
|
||||||
. withBorderStyle unicode
|
. withBorderStyle unicode
|
||||||
$ drawMessages game
|
$ drawMessages (game ^. messageHistory)
|
||||||
<=> border (drawMap game)
|
<=> border (drawMap game)
|
||||||
|
|
|
@ -9,19 +9,19 @@ module Xanthous.Messages
|
||||||
, messages
|
, messages
|
||||||
, message
|
, message
|
||||||
) where
|
) where
|
||||||
|
--------------------------------------------------------------------------------
|
||||||
import Xanthous.Prelude
|
import Xanthous.Prelude
|
||||||
|
|
||||||
|
import Control.Monad.Random.Class (MonadRandom)
|
||||||
|
import Data.Aeson (FromJSON, ToJSON, toJSON)
|
||||||
|
import Data.Aeson.Generic.DerivingVia
|
||||||
|
import Data.FileEmbed
|
||||||
import Data.List.NonEmpty
|
import Data.List.NonEmpty
|
||||||
import Test.QuickCheck hiding (choose)
|
import Test.QuickCheck hiding (choose)
|
||||||
import Test.QuickCheck.Arbitrary.Generic
|
import Test.QuickCheck.Arbitrary.Generic
|
||||||
import Test.QuickCheck.Instances.UnorderedContainers ()
|
import Test.QuickCheck.Instances.UnorderedContainers ()
|
||||||
import Text.Mustache
|
import Text.Mustache
|
||||||
import Data.Aeson (FromJSON, ToJSON)
|
|
||||||
import Data.Aeson.Generic.DerivingVia
|
|
||||||
import Data.FileEmbed
|
|
||||||
import qualified Data.Yaml as Yaml
|
import qualified Data.Yaml as Yaml
|
||||||
import Data.Aeson (toJSON)
|
|
||||||
import Control.Monad.Random.Class (MonadRandom)
|
|
||||||
|
|
||||||
import Xanthous.Random
|
import Xanthous.Random
|
||||||
import Xanthous.Orphans ()
|
import Xanthous.Orphans ()
|
||||||
|
|
58
src/Xanthous/Monad.hs
Normal file
58
src/Xanthous/Monad.hs
Normal file
|
@ -0,0 +1,58 @@
|
||||||
|
module Xanthous.Monad
|
||||||
|
( AppT(..)
|
||||||
|
, runAppT
|
||||||
|
, continue
|
||||||
|
, halt
|
||||||
|
, say
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Xanthous.Prelude
|
||||||
|
import Control.Monad.Random
|
||||||
|
import Control.Monad.State
|
||||||
|
import qualified Brick
|
||||||
|
import Brick (EventM, Next)
|
||||||
|
import Data.Aeson
|
||||||
|
|
||||||
|
import Xanthous.Game
|
||||||
|
import Xanthous.Messages (message)
|
||||||
|
|
||||||
|
newtype AppT m a
|
||||||
|
= AppT { unAppT :: StateT GameState m a }
|
||||||
|
deriving ( Functor
|
||||||
|
, Applicative
|
||||||
|
, Monad
|
||||||
|
, MonadState GameState
|
||||||
|
)
|
||||||
|
via (StateT GameState m)
|
||||||
|
|
||||||
|
instance MonadTrans AppT where
|
||||||
|
lift = AppT . lift
|
||||||
|
|
||||||
|
instance (Monad m) => MonadRandom (AppT m) where
|
||||||
|
getRandomR rng = randomGen %%= randomR rng
|
||||||
|
getRandom = randomGen %%= random
|
||||||
|
getRandomRs rng = uses randomGen $ randomRs rng
|
||||||
|
getRandoms = uses randomGen randoms
|
||||||
|
|
||||||
|
runAppT :: Monad m => AppT m a -> GameState -> m (a, GameState)
|
||||||
|
runAppT appt initialState = flip runStateT initialState . unAppT $ appt
|
||||||
|
|
||||||
|
halt :: AppT (EventM n) (Next GameState)
|
||||||
|
halt = lift . Brick.halt =<< get
|
||||||
|
|
||||||
|
continue :: AppT (EventM n) (Next GameState)
|
||||||
|
continue = lift . Brick.continue =<< get
|
||||||
|
|
||||||
|
-- say :: [Text] -> AppT m ()
|
||||||
|
-- say :: [Text] -> params -> AppT m ()
|
||||||
|
|
||||||
|
class SayR a where
|
||||||
|
say :: [Text] -> a
|
||||||
|
|
||||||
|
instance Monad m => SayR (AppT m ()) where
|
||||||
|
say msgPath = say msgPath $ object []
|
||||||
|
|
||||||
|
instance (Monad m, ToJSON params) => SayR (params -> AppT m ()) where
|
||||||
|
say msgPath params = do
|
||||||
|
msg <- message msgPath params
|
||||||
|
messageHistory %= pushMessage msg
|
|
@ -8,7 +8,7 @@ module Xanthous.Prelude
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import ClassyPrelude hiding
|
import ClassyPrelude hiding
|
||||||
(return, (<|), unsnoc, uncons, cons, snoc, index, (<.>), Index)
|
(return, (<|), unsnoc, uncons, cons, snoc, index, (<.>), Index, say)
|
||||||
import Data.Kind
|
import Data.Kind
|
||||||
import GHC.TypeLits hiding (Text)
|
import GHC.TypeLits hiding (Text)
|
||||||
import Control.Lens
|
import Control.Lens
|
||||||
|
|
|
@ -8,7 +8,6 @@ module Xanthous.Random
|
||||||
|
|
||||||
import Xanthous.Prelude
|
import Xanthous.Prelude
|
||||||
import Data.List.NonEmpty (NonEmpty)
|
import Data.List.NonEmpty (NonEmpty)
|
||||||
import System.Random
|
|
||||||
import Control.Monad.Random.Class (MonadRandom(getRandomR))
|
import Control.Monad.Random.Class (MonadRandom(getRandomR))
|
||||||
|
|
||||||
class Choose a where
|
class Choose a where
|
||||||
|
|
|
@ -4,7 +4,7 @@ cabal-version: 1.12
|
||||||
--
|
--
|
||||||
-- see: https://github.com/sol/hpack
|
-- see: https://github.com/sol/hpack
|
||||||
--
|
--
|
||||||
-- hash: d86e44c1f3fe890c699f9af19ae10b013973d1cb6e79cc403d6e1c35a74c99c1
|
-- hash: 5d750bf0bb5c6d278928f6c9606427754a444344fd769f50c02b776dedf0e771
|
||||||
|
|
||||||
name: xanthous
|
name: xanthous
|
||||||
version: 0.1.0.0
|
version: 0.1.0.0
|
||||||
|
@ -40,6 +40,7 @@ library
|
||||||
Xanthous.Game
|
Xanthous.Game
|
||||||
Xanthous.Game.Draw
|
Xanthous.Game.Draw
|
||||||
Xanthous.Messages
|
Xanthous.Messages
|
||||||
|
Xanthous.Monad
|
||||||
Xanthous.Orphans
|
Xanthous.Orphans
|
||||||
Xanthous.Prelude
|
Xanthous.Prelude
|
||||||
Xanthous.Random
|
Xanthous.Random
|
||||||
|
@ -95,6 +96,7 @@ executable xanthous
|
||||||
Xanthous.Game
|
Xanthous.Game
|
||||||
Xanthous.Game.Draw
|
Xanthous.Game.Draw
|
||||||
Xanthous.Messages
|
Xanthous.Messages
|
||||||
|
Xanthous.Monad
|
||||||
Xanthous.Orphans
|
Xanthous.Orphans
|
||||||
Xanthous.Prelude
|
Xanthous.Prelude
|
||||||
Xanthous.Random
|
Xanthous.Random
|
||||||
|
|
Loading…
Add table
Reference in a new issue