module GUI where import qualified Game import qualified Configuration as Config import qualified Graphics.UI.WX as WX import Graphics.UI.WX (Prop((:=)), text, command, on, close, container, widget, layout, margin, row, column, ) import Control.Monad (forM) data T = Cons { frame :: WX.Frame (), panel :: WX.Panel (), message :: WX.StaticText (), scoreA, scoreB :: WX.Gauge (), matrix :: [[((Int,Int), WX.Button ())]], restart :: WX.Button (), maxScore :: Int } create :: Config.T -> IO T create cfg = do f <- WX.frame [text := "Midimory"] p <- WX.panel f [] message_ <- WX.staticText p [ text := Game.makeMessage Game.PlayerA Game.First ] let maxScore_ = div (Config.rows cfg * Config.columns cfg) 2 scoreA_ <- WX.vgauge p maxScore_ [] scoreB_ <- WX.vgauge p maxScore_ [] matrix_ <- forM (zip [0..] (Config.texts cfg)) $ \(r,ln) -> forM (zip [0..] ln) $ \(c,label) -> do b <- WX.button p [ text := label ] return ((r,c),b) restart_ <- WX.button p [ text := "Restart" ] quit_ <- WX.button p [ text := "Quit", on command := close f ] WX.set f [layout := container p $ margin 10 $ row 5 $ WX.vfill (widget scoreA_) : (column 5 $ WX.hfill (widget message_) : WX.grid (Config.columns cfg) (Config.rows cfg) (map (map (WX.fill . widget . snd)) matrix_) : row 5 [WX.hfill (widget restart_), WX.hfill (widget quit_)] : []) : WX.vfill (widget scoreB_) : [] ] return $ Cons { frame = f, panel = p, message = message_, scoreA = scoreA_, scoreB = scoreB_, matrix = matrix_, restart = restart_, maxScore = maxScore_ }