2021-11-07 21:44:57 +01:00
|
|
|
{-# LANGUAGE RecordWildCards #-}
|
|
|
|
--------------------------------------------------------------------------------
|
2019-09-13 21:24:05 +02:00
|
|
|
module Main ( main ) where
|
|
|
|
--------------------------------------------------------------------------------
|
2019-10-12 18:59:42 +02:00
|
|
|
import Xanthous.Prelude hiding (finally)
|
2019-09-13 21:24:05 +02:00
|
|
|
import Brick
|
2020-05-12 05:03:21 +02:00
|
|
|
import qualified Brick.BChan
|
|
|
|
import qualified Graphics.Vty as Vty
|
2019-09-07 20:49:59 +02:00
|
|
|
import qualified Options.Applicative as Opt
|
2019-09-13 21:24:05 +02:00
|
|
|
import System.Random
|
2019-10-12 18:59:42 +02:00
|
|
|
import Control.Monad.Random (getRandom)
|
|
|
|
import Control.Exception (finally)
|
2019-11-29 20:33:52 +01:00
|
|
|
import System.Exit (die)
|
2019-09-13 21:24:05 +02:00
|
|
|
--------------------------------------------------------------------------------
|
2019-10-12 18:59:42 +02:00
|
|
|
import qualified Xanthous.Game as Game
|
2020-05-12 05:03:21 +02:00
|
|
|
import Xanthous.Game.Env (GameEnv(..))
|
2021-11-07 21:44:57 +01:00
|
|
|
import qualified Xanthous.Game.Env as Game
|
2020-02-17 19:24:31 +01:00
|
|
|
import Xanthous.App
|
2021-06-12 20:57:30 +02:00
|
|
|
import Xanthous.Generators.Level
|
2019-10-12 18:59:42 +02:00
|
|
|
( GeneratorInput
|
|
|
|
, parseGeneratorInput
|
|
|
|
, generateFromInput
|
|
|
|
, showCells
|
|
|
|
)
|
|
|
|
import qualified Xanthous.Entities.Character as Character
|
2021-06-12 20:57:30 +02:00
|
|
|
import Xanthous.Generators.Level.Util (regions)
|
|
|
|
import Xanthous.Generators.Level.LevelContents
|
2019-09-13 21:24:05 +02:00
|
|
|
import Xanthous.Data (Dimensions, Dimensions'(Dimensions))
|
|
|
|
import Data.Array.IArray ( amap )
|
|
|
|
--------------------------------------------------------------------------------
|
2019-10-12 18:59:42 +02:00
|
|
|
|
2021-11-07 21:44:57 +01:00
|
|
|
parseGameConfig :: Opt.Parser Game.Config
|
|
|
|
parseGameConfig = Game.Config
|
|
|
|
<$> Opt.switch
|
|
|
|
( Opt.long "disable-saving"
|
|
|
|
<> Opt.help "Disallow saving games"
|
|
|
|
)
|
|
|
|
|
2019-10-12 18:59:42 +02:00
|
|
|
data RunParams = RunParams
|
|
|
|
{ seed :: Maybe Int
|
|
|
|
, characterName :: Maybe Text
|
2021-11-07 21:44:57 +01:00
|
|
|
, gameConfig :: Game.Config
|
2019-10-12 18:59:42 +02:00
|
|
|
}
|
|
|
|
deriving stock (Show, Eq)
|
|
|
|
|
|
|
|
parseRunParams :: Opt.Parser RunParams
|
|
|
|
parseRunParams = RunParams
|
|
|
|
<$> optional (Opt.option Opt.auto
|
|
|
|
( Opt.long "seed"
|
|
|
|
<> Opt.help "Random seed for the game."
|
|
|
|
))
|
|
|
|
<*> optional (Opt.strOption
|
|
|
|
( Opt.short 'n'
|
|
|
|
<> Opt.long "name"
|
|
|
|
<> Opt.help
|
|
|
|
( "Name for the character. If not set on the command line, "
|
|
|
|
<> "will be prompted for at runtime"
|
|
|
|
)
|
|
|
|
))
|
2021-11-07 21:44:57 +01:00
|
|
|
<*> parseGameConfig
|
2019-10-12 18:59:42 +02:00
|
|
|
|
2019-09-07 20:49:59 +02:00
|
|
|
data Command
|
2019-10-12 18:59:42 +02:00
|
|
|
= Run RunParams
|
2019-11-29 20:33:52 +01:00
|
|
|
| Load FilePath
|
2019-12-30 17:31:56 +01:00
|
|
|
| Generate GeneratorInput Dimensions (Maybe Int)
|
2019-08-25 19:28:10 +02:00
|
|
|
|
2019-09-07 20:49:59 +02:00
|
|
|
parseDimensions :: Opt.Parser Dimensions
|
|
|
|
parseDimensions = Dimensions
|
|
|
|
<$> Opt.option Opt.auto
|
|
|
|
( Opt.short 'w'
|
|
|
|
<> Opt.long "width"
|
2019-12-30 17:31:56 +01:00
|
|
|
<> Opt.metavar "TILES"
|
2019-09-07 20:49:59 +02:00
|
|
|
)
|
|
|
|
<*> Opt.option Opt.auto
|
|
|
|
( Opt.short 'h'
|
|
|
|
<> Opt.long "height"
|
2019-12-30 17:31:56 +01:00
|
|
|
<> Opt.metavar "TILES"
|
2019-09-07 20:49:59 +02:00
|
|
|
)
|
|
|
|
|
2019-12-30 17:31:56 +01:00
|
|
|
|
2019-09-07 20:49:59 +02:00
|
|
|
parseCommand :: Opt.Parser Command
|
2019-10-12 18:59:42 +02:00
|
|
|
parseCommand = (<|> Run <$> parseRunParams) $ Opt.subparser
|
2019-09-07 20:49:59 +02:00
|
|
|
$ Opt.command "run"
|
|
|
|
(Opt.info
|
2019-10-12 18:59:42 +02:00
|
|
|
(Run <$> parseRunParams)
|
2019-09-07 20:49:59 +02:00
|
|
|
(Opt.progDesc "Run the game"))
|
2019-11-29 20:33:52 +01:00
|
|
|
<> Opt.command "load"
|
|
|
|
(Opt.info
|
|
|
|
(Load <$> Opt.argument Opt.str (Opt.metavar "FILE"))
|
|
|
|
(Opt.progDesc "Load a saved game"))
|
2019-09-07 20:49:59 +02:00
|
|
|
<> Opt.command "generate"
|
|
|
|
(Opt.info
|
|
|
|
(Generate
|
|
|
|
<$> parseGeneratorInput
|
|
|
|
<*> parseDimensions
|
2019-12-30 17:31:56 +01:00
|
|
|
<*> optional
|
|
|
|
(Opt.option Opt.auto (Opt.long "seed"))
|
2019-09-07 20:49:59 +02:00
|
|
|
<**> Opt.helper
|
|
|
|
)
|
|
|
|
(Opt.progDesc "Generate a sample level"))
|
|
|
|
|
|
|
|
optParser :: Opt.ParserInfo Command
|
|
|
|
optParser = Opt.info
|
|
|
|
(parseCommand <**> Opt.helper)
|
|
|
|
(Opt.header "Xanthous: a WIP TUI RPG")
|
|
|
|
|
2019-11-29 20:33:52 +01:00
|
|
|
thanks :: IO ()
|
|
|
|
thanks = putStr "\n\n" >> putStrLn "Thanks for playing Xanthous!"
|
|
|
|
|
2020-05-12 05:03:21 +02:00
|
|
|
newGame :: RunParams -> IO ()
|
|
|
|
newGame rparams = do
|
2019-10-12 18:59:42 +02:00
|
|
|
gameSeed <- maybe getRandom pure $ seed rparams
|
2019-12-30 17:31:56 +01:00
|
|
|
when (isNothing $ seed rparams)
|
|
|
|
. putStrLn
|
|
|
|
$ "Seed: " <> tshow gameSeed
|
2019-10-12 18:59:42 +02:00
|
|
|
let initialState = Game.initialStateFromSeed gameSeed &~ do
|
|
|
|
for_ (characterName rparams) $ \cn ->
|
|
|
|
Game.character . Character.characterName ?= cn
|
2021-11-07 21:44:57 +01:00
|
|
|
runGame NewGame (gameConfig rparams) initialState `finally` do
|
2020-05-12 05:03:21 +02:00
|
|
|
thanks
|
2019-10-12 18:59:42 +02:00
|
|
|
when (isNothing $ seed rparams)
|
|
|
|
. putStrLn
|
|
|
|
$ "Seed: " <> tshow gameSeed
|
|
|
|
putStr "\n\n"
|
2019-09-07 20:49:59 +02:00
|
|
|
|
2019-11-29 20:33:52 +01:00
|
|
|
loadGame :: FilePath -> IO ()
|
|
|
|
loadGame saveFile = do
|
2021-11-06 16:44:14 +01:00
|
|
|
gameState <- maybe (die "Invalid save file!") pure . Game.loadGame . fromStrict
|
|
|
|
=<< readFile @IO saveFile
|
2021-11-07 21:44:57 +01:00
|
|
|
gameState `deepseq` runGame (LoadGame saveFile) Game.defaultConfig gameState
|
2019-11-29 20:33:52 +01:00
|
|
|
|
2021-11-07 21:44:57 +01:00
|
|
|
runGame :: RunType -> Game.Config -> Game.GameState -> IO ()
|
|
|
|
runGame rt _config gameState = do
|
|
|
|
_eventChan <- Brick.BChan.newBChan 10
|
|
|
|
let gameEnv = GameEnv {..}
|
2020-05-12 05:03:21 +02:00
|
|
|
app <- makeApp gameEnv rt
|
|
|
|
let buildVty = Vty.mkVty Vty.defaultConfig
|
|
|
|
initialVty <- buildVty
|
|
|
|
_game' <- customMain
|
|
|
|
initialVty
|
|
|
|
buildVty
|
2021-11-07 21:44:57 +01:00
|
|
|
(Just _eventChan)
|
2020-05-12 05:03:21 +02:00
|
|
|
app
|
|
|
|
gameState
|
|
|
|
pure ()
|
2019-11-29 20:33:52 +01:00
|
|
|
|
2019-12-30 17:31:56 +01:00
|
|
|
runGenerate :: GeneratorInput -> Dimensions -> Maybe Int -> IO ()
|
|
|
|
runGenerate input dims mSeed = do
|
|
|
|
putStrLn "Generating..."
|
|
|
|
genSeed <- maybe getRandom pure mSeed
|
|
|
|
let randGen = mkStdGen genSeed
|
|
|
|
res = generateFromInput input dims randGen
|
2019-09-13 21:24:05 +02:00
|
|
|
rs = regions $ amap not res
|
2019-12-30 17:31:56 +01:00
|
|
|
when (isNothing mSeed)
|
|
|
|
. putStrLn
|
|
|
|
$ "Seed: " <> tshow genSeed
|
2019-09-13 21:24:05 +02:00
|
|
|
putStr "num regions: "
|
|
|
|
print $ length rs
|
|
|
|
putStr "region lengths: "
|
|
|
|
print $ length <$> rs
|
|
|
|
putStr "character position: "
|
|
|
|
print =<< chooseCharacterPosition res
|
2019-09-07 20:49:59 +02:00
|
|
|
putStrLn $ showCells res
|
|
|
|
|
|
|
|
runCommand :: Command -> IO ()
|
2020-05-12 05:03:21 +02:00
|
|
|
runCommand (Run runParams) = newGame runParams
|
2019-11-29 20:33:52 +01:00
|
|
|
runCommand (Load saveFile) = loadGame saveFile
|
2019-12-30 17:31:56 +01:00
|
|
|
runCommand (Generate input dims mSeed) = runGenerate input dims mSeed
|
2019-09-07 20:49:59 +02:00
|
|
|
|
|
|
|
main :: IO ()
|
|
|
|
main = runCommand =<< Opt.execParser optParser
|