Skip to content

Commit

Permalink
Parsing JSON players file with Aeson
Browse files Browse the repository at this point in the history
  • Loading branch information
dsaenztagarro committed Jun 8, 2015
1 parent f4010b9 commit cb6cb51
Show file tree
Hide file tree
Showing 5 changed files with 64 additions and 20 deletions.
3 changes: 2 additions & 1 deletion hs-pathfinder.cabal
Expand Up @@ -28,7 +28,8 @@ library
-- other-modules:
-- other-extensions:
build-depends:
base
base,
aeson >= 0.6.1.0

hs-source-dirs:
src
Expand Down
39 changes: 21 additions & 18 deletions src/Main.hs
@@ -1,46 +1,49 @@
module Main where

import Paizo.Core.Types (Player)
import Paizo.Plugin.FileLoader (getPlayers)

import Control.Monad (when)
import Control.Monad.State
import System.IO (stdin, stdout, hSetEcho, hSetBuffering, BufferMode(..))

data AppConfig = AppConfig
{ crRound :: Int
} deriving (Show)
data AppConfig =
AppConfig { players :: [Player]
, crRound :: Int
} deriving (Show)

type App = StateT AppConfig IO

loadEngine :: App ()
loadEngine = liftIO $ do
hSetEcho stdin False
hSetBuffering stdin NoBuffering
hSetBuffering stdout NoBuffering
initGUI :: App ()
initGUI = liftIO $ do
hSetEcho stdin False
hSetBuffering stdin NoBuffering
hSetBuffering stdout NoBuffering

printT :: (MonadIO m) => String -> m ()
printT s = liftIO . putStrLn $ s

loadGame :: App ()
loadGame = printT "Loading game"
loadGame = do
printT "Loading game"
players <- liftIO getPlayers
put AppConfig { players = players, crRound = 0 }

gameLoop :: App ()
gameLoop = do
printT "Play round"
config <- get
put $ AppConfig { crRound = crRound config + 1 }
put $ AppConfig { players = players config, crRound = crRound config + 1 }
char <- liftIO getChar
when (char == 'c') gameLoop

main2 :: App ()
main2 = do
loadEngine
loadGame
gameLoop
main2 = initGUI >> loadGame >> gameLoop

main :: IO ()
main = do
putStrLn "hello world"
--main :: IO ()
main = runApp main2

runApp :: App a -> IO (a, AppConfig)
runApp k =
let config = AppConfig 0
let config = AppConfig [] 0
in runStateT k config
12 changes: 11 additions & 1 deletion src/Paizo/Core/Types.hs
@@ -1,9 +1,19 @@
{-# LANGUAGE DeriveGeneric #-}

module Paizo.Core.Types (
-- * Player
Player(..)
) where

import Data.Aeson
import GHC.Generics

data Player = Player {
hitPoints :: Int
, consScore :: Int
} deriving (Show)
} deriving (Show, Generic)

-- Instances to convert our type to/from JSON.

instance FromJSON Player
instance ToJSON Player
26 changes: 26 additions & 0 deletions src/Paizo/Plugin/FileLoader.hs
@@ -0,0 +1,26 @@
module Paizo.Plugin.FileLoader (
-- * Functions
getPlayers
) where

import Paizo.Core.Types (Player)

import Control.Monad.IO.Class (liftIO)
import Data.Aeson (eitherDecode)
import qualified Data.ByteString.Lazy as B

-- | Location of the players file
jsonFile :: FilePath
jsonFile = "players.json"

-- | Read the local copy of the JSON file.
getJSON :: IO B.ByteString
getJSON = B.readFile jsonFile

-- | Returns the list of players from JSON file
getPlayers :: IO [Player]
getPlayers = do
d <- (eitherDecode <$> getJSON) :: IO (Either String [Player])
case d of
Left err -> return []
Right players -> return players
4 changes: 4 additions & 0 deletions src/players.json
@@ -0,0 +1,4 @@
[
{ "hitPoints": 20, "consScore": 5 },
{ "hitPoints": 15, "consScore": 7 }
]

0 comments on commit cb6cb51

Please sign in to comment.