module Transition.Graphics where import State import Configuration import State.Functions import Event import Core.Square import Numeric import Data.Maybe import qualified Data.ChangeMap as M import qualified Data.ChangeSet as S ------------------------------------------------------------- squareState :: State -> Square -> SquareState squareState st p | Just r <- revealing st , p == revSquare r , Just i <- busyAnimation r = BusySign focused prelight i | Just h <- hint st , Just max <- maxHiddenProb g , Just x <- M.lookup p $ hiddenProbs g , h == FullHint || x == max || x == 0 || marked' = (if marked' then HintedBomb else Hint) focused prelight x | marked' = Bomb focused prelight | Just Nothing <- revealed = Death | Just (Just i) <- revealed = if hiddenTable st then HiddenSign else Clear focused i dangerousness | otherwise = NoSign focused prelight where g = game st focused = p == focus st && focusMoves st prelight = maybe False (== p) (mouseFocus st) && mouseFocusShown st revealed = M.lookup p $ revealResults g marked' = S.member p $ marked g dangerousness = head $ [x | (q,x)<-redness st, q==p] ++ [0] infoString st | playerWins st = "Congratulations! You won with " ++ show_ 2 (luck st) ++ " luck." | alive (game st) == 0 = "Sorry, you died of necessity." | isFinished st = "Sorry, you died by accident." | otherwise = "Mines left: " ++ show (mines_left st) ++ " " ++ "Information: " ++ show_ 1 (100 * information st) ++ "%" ++ " " ++ "Luck: " ++ show_ 2 (luck st) where show_ :: RealFloat a => Int -> a -> [Char] show_ i x = showFFloat (Just i) x "" timeString st | Just t <- timer st = showSeconds t | isNew st = "Timer will start" | otherwise = "Timer stopped" where showSeconds :: Int -> String showSeconds s = f h ++ ":" ++ f m' ++ ":" ++ f s' where (m, s') = divMod s 60 (h, m') = divMod m 60 f :: Int -> String f i = reverse $ take 2 $ reverse $ "0" ++ show i