> module Barrie.Render where > import Data.List > import Data.Maybe > import Barrie.Gadgets > import Barrie.Style > import Barrie.Trace > import Barrie.Widgets RenderF is the type of rendering functions. A rendering function should be implmeneted for each backend. Currently, we have Gtk and IO. > type RenderF a b = String -- name of the gui element type > -> [RunnableGUI a b] -- children of this gui element > -> Style > -> Maybe (Gadget b) -- corresponding implementation > -> Maybe Widget -- possible popup > -> IO (RunnableGUI a b) RunnableGUI is a type representing a rendered set of gadgets, widgets, and styles. A rendering function retuns a single RunnableGUI, which represents the top level gui element. Each of the inner elements is also a RunnableGUI, and they are rendered in the same way. Anything that can be rendered can be used as a top level element, either in the main application, or in a pop-up. Of course, this isn't enforced by this module, but the RenderF functions should make sure it's true, because we rely on it. A RunnableGUI contains three fields. First is the GUI, which is of a type chosen by the renderer (e.g. Gtk uses Gtk.Widget). Second is an update from state function. When the state changes, this is called for each widget, causing it to display according to the latest state. Finally comes a function which, give a function to extract state from IO should call when the state is updated, which allows everything else to be kept up to date. The final field is a function which, given a way of extracting the current state from IO, and a way of putting it back, can update it via its gadget functionality. One will rightly point out that this is all very ugly and procedural, but luckily, anybody using Barrie doesn't have to worry about it. It's the sewer of side-effects beneath the cathedral of functional gui-ness. > type RunnableGUI gui state = > (gui, -- the GUI > state -> IO (), -- update from state > IO state -> (state -> IO ()) -> IO ()) -- state update function The updates function extracts all the update functions from a runnable gui. This is convenient for the implementation of renderers. > updates :: [RunnableGUI gui state] -> [state -> IO ()] > updates = map (\ (_, update, _) -> update) A behaviour is just a flat list of gadgets. Gadgets are defined in a hierarchical way, but are flattened for rendering. Note that the gadget hierarchy is only tangentially related to the widget layout. The hierarchy is intended to be a functional grouping, although in practice it will often look similar to the widget layout. > renderWidget :: Behaviour w -> Widget -> RenderF r w > -> IO (RunnableGUI r w) > renderWidget behaviour widget render = go widget > where -- go :: StyleSheet -> Layout -> RunnableGUI r w > go w = do let elmt = widgetElementName w > style = widgetStyle w > gadget = findGadget (uiElementName w) behaviour > traceMessage ("rendering element: " ++ elmt); > traceMessage ("ui name = " ++ > intercalate "." (uiElementName w)) > traceMessage ("gadget = " ++ > maybe "Nothing" (gadgetName) gadget) > ws <- mapM go $ widgetChildren w > render elmt ws style gadget (widgetPopupChild w)