GUI data structure experiments
This commit is contained in:
parent
be0da410a0
commit
d4b4f706b6
@ -1,14 +1,22 @@
|
||||
{-# LANGUAGE ExistentialQuantification #-}
|
||||
|
||||
module UI.Callbacks where
|
||||
|
||||
import Control.Monad.Trans (liftIO)
|
||||
import Types
|
||||
import UI.UITypes
|
||||
|
||||
data Pixel = Pixel Int Int
|
||||
|
||||
getGUI :: [GUIAny]
|
||||
getGUI = (GUIAny $ GUIContainer 0 0 120 80 [] 1):(GUIAny $ GUIContainer 50 60 300 700 [(GUIAny $ GUIContainer 55 65 200 400 [] 5)] 1):[]
|
||||
|
||||
-- | Handler for UI-Inputs.
|
||||
-- Indicates a primary click on something (e.g. left-click, touch on Touchpad, fire on Gamepad, ...
|
||||
clickHandler :: Pixel -> Pioneers ()
|
||||
clickHandler (Pixel x y) = liftIO $ putStrLn $ unwords ["button press on (",show x,",",show y,")"]
|
||||
clickHandler (Pixel x y) = case concat $ map (isInside x y) getGUI of
|
||||
[] -> liftIO $ putStrLn $ unwords ["button press on (",show x,",",show y,")"]
|
||||
hit -> liftIO $ putStrLn $ unwords $ foldl (++) ["hitting"] ([map (\w -> (show.getBoundary) w ++ ' ':(show.getPriority) w) hit])
|
||||
|
||||
-- | Handler for UI-Inputs.
|
||||
-- Indicates an alternate click on something (e.g. right-click, touch&hold on Touchpad, ...
|
||||
|
@ -5,9 +5,11 @@ import Graphics.UI.SDL.Surface
|
||||
import Graphics.UI.SDL.Color
|
||||
import Graphics.UI.SDL.Rect
|
||||
import Graphics.UI.SDL.Types
|
||||
import UI.UITypes
|
||||
|
||||
--createRGBSurface :: Int32 -> Int32 -> Int32 -> Word32 -> Word32 -> Word32 -> Word32 -> IO Surface
|
||||
-- width height depth rFilter gFilter bFilter aFilter
|
||||
-- createRGBSurface width height 32 0xFF000000 0x00FF0000 0x0000FF00 0x000000FF
|
||||
|
||||
updateGUI :: Int32 -> Int32 -> IO Surface
|
||||
updateGUI width height = do
|
||||
|
Loading…
Reference in New Issue
Block a user