module Event where import Numeric import Core.Square import Step (RevealResult) import Preferences (Preferences) import State (ScoreAttr, ScoreEntry) -------------------------------------- input ------------- type MousePos = Maybe Square data Event = NewEvent -- new game | RevealEvent MousePos -- Nothing: by keyboard | MarkEvent MousePos -- Nothing: by keyboard | UndoEvent | RedoEvent | HintEvent | FullHintEvent | ShowScores | OpenPreferences | PreferencesClosed (Maybe Preferences) | NewScoreClosed (Maybe String) [ScoreAttr] | MouseMotion MousePos -- Nothing: mouse is outside | LeftEvent | RightEvent | UpEvent | DownEvent | FocusOut | FocusIn MousePos -- Nothing: mouse is outside | UpdateTable -- jóváhagyások (legyen mindenről?) | DrawingDone | InfoDrawingDone | Init -- triggered? | Triggered Triggered -- nem kéne beágyazni ide deriving (Eq, Ord, Show) data Triggered = RevealDone RevealResult | SquareHintDone | Tick | FadeTick | BusyTick | InterruptVisible -- better name: LongInterrupt deriving (Eq, Ord, Show) ---------------------------- output -------------------- type Responses = [Response] data Response = DrawSquares BoardSize [(Square, SquareState)] | ShowTime TimeInfo | ShowInfo Info | PopUpPreferences Preferences | PopUpNewScore Preferences (Maybe Int) [ScoreEntry] [ScoreAttr] deriving (Eq, Ord, Show) data Info = InfoWin Double | InfoLoose Bool -- True: of necessity, False: by accident | InfoPlay Int{-mines-} Double{-information-} Double{-luck-} deriving (Eq, Ord) instance Show Info where show (InfoWin luck) = "Congratulations! You won with " ++ show_ 2 luck ++ " luck." show (InfoLoose n) = "Sorry, you died " ++ if n then "of necessity." else "by accident." show (InfoPlay m i l) = "Mines left: " ++ show m ++ " " ++ "Information: " ++ show_ 1 (100 * i) ++ "%" ++ " " ++ "Luck: " ++ show_ 2 l show_ :: RealFloat a => Int -> a -> [Char] show_ i x = showFFloat (Just i) x "" data TimeInfo = TimerInit | TimerStopped | TimerAt Int deriving (Eq, Ord) instance Show TimeInfo where show TimerInit = "Timer will start" show TimerStopped = "Timer stopped" show (TimerAt 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 data SquareState = HiddenSign | Death | Clear Focused Int Dangerousness -- ^ 0-8 | NoSign Focused Prelight | Hint Focused Prelight Int -- ^ 0-100 | BusySign Focused Prelight Int -- ^ phase 0-100 | Bomb Focused Prelight | HintedBomb Focused Prelight Int -- ^ 0-100 deriving (Eq, Ord, Show) type Focused = Bool type Prelight = Bool type Dangerousness = Int -- ^ 0-100 focused HiddenSign = False focused Death = False focused (Clear f _ _) = f focused (NoSign f _) = f focused (Hint f _ _) = f focused (BusySign f _ _) = f focused (Bomb f _) = f focused (HintedBomb f _ _) = f prelight HiddenSign = False prelight Death = False prelight (Clear _ _ _) = False prelight (NoSign _ p) = p prelight (Hint _ p _) = p prelight (BusySign _ p _) = p prelight (Bomb _ p) = p prelight (HintedBomb _ p _) = p isBomb (Bomb _ _) = True isBomb (HintedBomb _ _ _) = True isBomb _ = False