hannah/src/Session.hs

43 lines
1008 B
Haskell

{-# LANGUAGE NamedFieldPuns #-}
module Session (
State(..)
, initial
, store
) where
import Config (libDir)
import Data.Map (Map)
import qualified Data.Map as Map (empty)
import Hanafuda.KoiKoi (GameID, PlayerID)
import qualified Hanafuda.Message as Message (PublicGame)
import System.Directory (createDirectoryIfMissing, doesFileExist)
import System.FilePath ((</>))
data State =
New
| Connected {
playerID :: PlayerID
, games :: Map GameID Message.PublicGame
}
deriving Show
stateFile :: FilePath
stateFile = libDir </> "state"
ifM :: IO Bool -> IO a -> IO a -> IO a
ifM condition caseTrue caseFalse =
condition >>= (\b -> if b then caseTrue else caseFalse)
initial :: IO State
initial = do
createDirectoryIfMissing True libDir
ifM (doesFileExist stateFile)
(do
playerID <- read <$> readFile stateFile
return $ Connected {playerID, games = Map.empty}
)
(return New)
store :: PlayerID -> IO ()
store = writeFile stateFile . show