-- | Establish a class for all things that are utterly required to be part of -- the program state for the interactive renderer. These will all be set -- by the interactive system for you, so they just must be defined in your -- state object. -- -- [@Author@] Jeff Heard -- -- [@Copyright@] © 2008 Renaissance Computing Institute -- module Graphics.Rendering.Hieroglyph.UIState where import Graphics.Rendering.Hieroglyph.Primitives import qualified Graphics.UI.Gtk as Gtk import Data.Map (Map, empty) import Control.Concurrent import Graphics.UI.Gtk.Gdk.Pixbuf (Pixbuf) import System.Mem.Weak type ImageCache = MVar (Map String (Weak Pixbuf)) initImageCache = newMVar empty -- | A keystroke data Key = Character Char | Enter | Tab | BackSpace | Insert | Delete | Home | End | PgUp | PgDown | PF1 | PF2 | PF3 | PF4 | PF5 | PF6 | PF7 | PF8 | PF9 | PF10 | PF11 | PF12 -- | The basic UI state. This will get passed to all scene elements class UIState a where mousePosition :: a -> Point -- ^ The current mouse position mouseLeftButtonDown :: a -> Bool -- ^ Mouse left button. Is it down? mouseRightButtonDown :: a -> Bool -- ^ Mouse right button, is it down? mouseMiddleButtonDown :: a -> Bool -- ^ Mouse middle button, is it down? mouseWheel :: a -> Int -- ^ Moues wheel, has it moved? keyCtrl :: a -> Bool -- ^ Is the control key down? keyShift :: a -> Bool -- ^ Is the shift key down? keyAlt :: a -> Bool -- ^ Is the alt key down? key :: a -> Key -- ^ Is there a real key down? drawing :: a -> Maybe Gtk.Widget -- ^ The draw window sizeX :: a -> Double -- ^ The width of the drawing area sizeY :: a -> Double -- ^ The height of the drawing area imageCache :: a -> Maybe ImageCache setMousePosition :: Point -> a-> a -- ^ Set the mouse position (do not call in your own code) setMouseLeftButtonDown :: Bool -> a-> a -- ^ Set the left button (do not call in your own code) setMouseRightButtonDown :: Bool -> a-> a -- ^ Set the right button (do not call in your own code) setMouseMiddleButtonDown :: Bool -> a-> a -- ^ Set the middle button (do not call in your own code) setMouseWheel :: Int -> a-> a -- ^ Set the mouse wheel delta (do not call in your own code) setKeyCtrl :: Bool -> a-> a -- ^ Set the control modifier state (do not call in your own code) setKeyShift :: Bool -> a-> a -- ^ Set the shift modifier state (do not call in your own code) setKeyAlt :: Bool -> a-> a -- ^ Set the alt modifier state (do not call in your own code) setKey :: Key -> a-> a -- ^ Set the key that is pressed (do not call in your own code) setDrawing :: Maybe Gtk.Widget -> a-> a -- ^ Set the draw window (do not call in your own code) setSizeX :: Double -> a -> a -- ^ Set the drawing area width (do not call in your own code) setSizeY :: Double -> a -> a -- ^ Set the drawing area height (do not call in your own code) setImageCache :: Maybe ImageCache -> a -> a