module Event where import Core.Square import Configuration (Configuration) import State (ScoreAttr, ScoreEntry) -------------------------------------- input ------------- type MousePos = Maybe Square data Event = RevealEvent MousePos -- Nothing: by keyboard | MarkEvent MousePos -- Nothing: by keyboard | MouseMotion MousePos -- Nothing: mouse is outside | NewEvent | LeftEvent | RightEvent | UpEvent | DownEvent | UndoEvent | RedoEvent | HintEvent | FullHintEvent | ShowScores | OpenPreferences | PreferencesClosed (Maybe Configuration) | NewScoreClosed (Maybe String) [ScoreAttr] | 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 | SquareHintDone | Tick | FadeTick | BusyTick | InterruptVisible -- better name: LongInterrupt deriving (Eq, Ord, Show) ---------------------------- output -------------------- type Responses = [Response] data Response = DrawSquares Board [(Square, SquareState)] | ShowTime String -- gyorsulna szerkezetváltással | ShowInfo String -- gyorsulna szerkezetváltással | PopUpPreferences Configuration | PopUpNewScore Configuration (Maybe Int) [ScoreEntry] [ScoreAttr] deriving (Eq, Ord, Show) 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