Hi

It was great to see XRC being added to wxHaskell. Nonetheless, it seems
to have less type safety than the "traditional" way of creating widgets.
There seems to be two static guaranties we are now missing:

1) The naming of widgets is by strings which can be misspelled.

2) One can accidentally use a wrong *res function for accessing the
widget. E.g. using radioBoxRes for a button.

Fortunately, it could easily be remedied by parsing the xrc.xml file and
generating the necessary functions.

Would people think this is a good idea? Would you use it?

I have made a _very_ rudimentary proof of concept:


module Main where

import Text.HTML.TagSoup
import Text.HTML.TagSoup.Parser
import Data.Char

main = do
  makeSelectorModule "controls.xrc"


makeSelectorModule :: String -> IO ()
makeSelectorModule filename = do
  xml <- readFile filename
  let out = outputModule filename
  writeFile (out ++ ".hs") (header out ++ makeSelectors xml)

outputModule :: String -> String
outputModule filename =
    toUpper (head filename) : takeWhile (/= '.') (drop 1 filename) ++ "Selector"


makeSelectors :: String -> String
makeSelectors xs = unlines $ map makeSelector $ concat $ map process $ 
parseTags xs

process (TagOpen "object" [("class", t), ("name", name)]) = [Widget t name]
process _ = []

data Widget = Widget String String 
              deriving Show

header name = "module " ++ name ++ " where\n" ++
              "import Graphics.UI.WX\n"

makeSelector :: Widget -> String
makeSelector (Widget "wxButton" name) = name ++ "Button f = buttonRes f \"" ++ 
name ++ "\""
makeSelector _ = ""


Which for the "controls.xrc" file in the sample directory generates a
file named "ControlsSelector.hs" containing:


module ControlsSelector where
import Graphics.UI.WX

okButton f = buttonRes f "ok"
quitButton f = buttonRes f "quit"
rb1Button f = buttonRes f "rb1"
cb1Button f = buttonRes f "cb1"


If people are interested, I would gladly volunteer to turn the proof of
concept into "real" code.


Greetings

Mads Lindstrøm






------------------------------------------------------------------------------
SF.Net email is Sponsored by MIX09, March 18-20, 2009 in Las Vegas, Nevada.
The future of the web can't happen without you.  Join us at MIX09 to help
pave the way to the Next Web now. Learn more and register at
http://ad.doubleclick.net/clk;208669438;13503038;i?http://2009.visitmix.com/
_______________________________________________
wxhaskell-devel mailing list
wxhaskell-devel@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/wxhaskell-devel

Reply via email to