An @-sign in a box, in haskell

Initial commit of a Haskell version of Xanthous, written using Brick and
built with Nix.

This is so much nicer and so much easier
This commit is contained in:
Griffin Smith 2019-08-25 13:28:10 -04:00
parent fb0d1b3e66
commit d3f3890dc5
17 changed files with 1075 additions and 3 deletions

17
src/Main.hs Normal file
View file

@ -0,0 +1,17 @@
module Main where
import Xanthous.Prelude
import Brick
import Xanthous.Game (getInitialState)
import Xanthous.App (makeApp)
ui :: Widget ()
ui = str "Hello, world!"
main :: IO ()
main = do
app <- makeApp
initialState <- getInitialState
_ <- defaultMain app initialState
pure ()

21
src/Xanthous/App.hs Normal file
View file

@ -0,0 +1,21 @@
module Xanthous.App (makeApp) where
import Xanthous.Prelude
import Brick hiding (App)
import qualified Brick
import Graphics.Vty.Attributes (defAttr)
import Xanthous.Game
import Xanthous.Game.Draw (drawGame)
import Xanthous.Resource (Name)
type App = Brick.App GameState () Name
makeApp :: IO App
makeApp = pure $ Brick.App
{ appDraw = drawGame
, appChooseCursor = const headMay
, appHandleEvent = resizeOrQuit
, appStartEvent = pure
, appAttrMap = const $ attrMap defAttr []
}

12
src/Xanthous/Game.hs Normal file
View file

@ -0,0 +1,12 @@
module Xanthous.Game
( GameState(..)
, getInitialState
) where
import Xanthous.Prelude
data GameState = GameState
{ }
getInitialState :: IO GameState
getInitialState = pure GameState

28
src/Xanthous/Game/Draw.hs Normal file
View file

@ -0,0 +1,28 @@
module Xanthous.Game.Draw
( drawGame
) where
import Xanthous.Prelude
import Brick
import Brick.Widgets.Border
import Brick.Widgets.Border.Style
import Xanthous.Game (GameState(..))
import Xanthous.Resource (Name(..))
drawMessages :: GameState -> Widget Name
drawMessages _ = str "Welcome to Xanthous! It's dangerous out there, why not stay inside?"
drawMap :: GameState -> Widget Name
drawMap _game
= viewport MapViewport Both
$ vBox mapRows
where
-- TODO
firstRow = [str "@"] <> replicate 79 (str " ")
mapRows = firstRow <> (replicate 20 . hBox . replicate 80 $ str " ")
drawGame :: GameState -> [Widget Name]
drawGame game = pure . withBorderStyle unicode
$ drawMessages game
<=> border (drawMap game)

10
src/Xanthous/Prelude.hs Normal file
View file

@ -0,0 +1,10 @@
module Xanthous.Prelude
( module ClassyPrelude
, Type
, Constraint
, module GHC.TypeLits
) where
import ClassyPrelude hiding (return)
import Data.Kind
import GHC.TypeLits hiding (Text)

11
src/Xanthous/Resource.hs Normal file
View file

@ -0,0 +1,11 @@
module Xanthous.Resource
( Name(..)
) where
import Xanthous.Prelude
data Name = MapViewport
-- ^ The main viewport where we display the game content
| MessageBox
-- ^ The box where we display messages to the user
deriving stock (Show, Eq, Ord)