module State where import Configuration (Probability) import Preferences import Core.Square import Table import Random import qualified Data.Map as MM import Data.Data import Data.Binary import Data.Binary.Generic ------------------------------- -- game state data State = State { preferences :: Preferences -- scores state , userName :: String , scores :: MM.Map Preferences{-x-} [ScoreEntry] , sortOrder :: [ScoreAttr] -- game , initialSeed :: RandomSeed , undo :: [Step] , redo :: [CompressedStep] , game :: GameState -- cached -- status , timer :: Maybe Int , hint :: Maybe HintType -- volatile state , revealing :: [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, Typeable, Data) ------------------------------ data Revealing = Revealing { recursive :: Bool , revSquare :: Square , busyAnimation :: Maybe Int } deriving (Show, Typeable, Data) data Hinting = Hinting { hintResult :: Maybe Int , hintAnimation :: Maybe Int } deriving (Show, Typeable, Data) ---------------------------- data ScoreEntry = ScoreEntry { se_name :: String , se_time :: Int , se_alive :: Probability , se_deaths :: Int , se_history :: [CompressedStep] } deriving (Eq, Ord, Show, Typeable, Data) instance Binary ScoreEntry where put = putGeneric get = getGeneric data ScoreAttr = SA_Time | SA_Alive | SA_Success | SA_Deaths deriving (Eq, Ord, Show, Enum, Typeable, Data) ------------------------------ data GenStep a = Reveal Square | Mark Square | CachedState a deriving (Eq, Ord, Show, Typeable, Data) type Step = GenStep GameState -- cached gamestate before the step type CompressedStep = GenStep () instance Functor GenStep where fmap f (CachedState a) = CachedState (f a) fmap _ (Mark s) = Mark s fmap _ (Reveal s) = Reveal s --------------------------- data Interrupt = ModifyPreferences | ViewScore | OtherApp deriving (Eq, Show, Typeable, Data) ----------------------