module State where import Configuration import Core.Square import Core.Constraints import Step import Data.ChangeMap import Data.ChangeSet import Control.Monad import Data.Binary import Data.DeriveTH import Data.Derive.Binary import System.Random import System.Random.Instances import qualified Data.Map ------------------------------- -- játékállapot data State = State { -- configuration :: Configuration -- game , seed :: StdGen , game :: GameState -- cached , undo :: [(GameState, Step)] , redo :: [Step] -- preferences , userName :: String , undoChangesSeed :: Bool -- scores state , scores :: Data.Map.Map Configuration [ScoreEntry] -- normál map , sortOrder :: [ScoreAttr] -- status , hint :: Maybe HintType , timer :: Maybe Int -- state , revealing :: Maybe Revealing -- , hinting :: Maybe Hinting , interrupt :: Maybe (Bool, Interrupt) -- visible -- GUI state , focus :: Square , mouseFocus :: Maybe Square -- Nothing: mouse is outside , redness :: [(Square, Int)] -- 0-100 } deriving (Show) ------------------------------ data Revealing = Revealing { recursive :: Bool , revSquare :: Square , revResult :: Maybe RevealResult -- maybe for easier saving -- keep lazy! , recRevealing :: [Square] , busyAnimation :: Maybe Int } deriving (Show) data Hinting = Hinting { hintResult :: Maybe Int , hintAnimation :: Maybe Int } deriving (Show) ---------------------------- data ScoreEntry = ScoreEntry { se_name :: String , se_time :: Int , se_alive :: Probability , se_deaths :: Int , se_history :: [Step] } deriving (Eq, Ord, Show) data ScoreAttr = SA_Time | SA_Alive | SA_Success | SA_Deaths deriving (Eq, Ord, Show, Enum) ---------------------------- data GameState = GameState { constraints :: Constraints , marked :: Set Square , alive :: Probability , revealResults :: Map Square (Maybe Int) -- a tartalom cachelve van -- cached , constraintsProb :: Probability -- ebből lesz information , maxHiddenProb :: Maybe Int -- 0-100 , hiddenProbs :: Map Square Int -- 0-100 , noHiddenProbs :: [Square] -- empty squares to be hinted } deriving (Show) ------------------------------ data Step = Reveal StdGen [Square] | Mark Square deriving (Eq, Ord, Show) --------------------------- data Interrupt = ModifyPreferences | ViewScore | OtherApp deriving (Eq, Show) ---------------------- $( derive makeBinary ''Interrupt ) $( derive makeBinary ''Revealing ) $( derive makeBinary ''ScoreAttr ) $( derive makeBinary ''ScoreEntry ) $( derive makeBinary ''Step ) $( derive makeBinary ''GameState ) $( derive makeBinary ''State )