[Haskell-cafe] Functional GUIs again

Fraser Wilson blancolioni at gmail.com
Mon Feb 16 15:21:11 EST 2009


Oh, cheers!  Newtype deriving is more general than I expected.  Thanks for
the comment.

I've requested a hackage account, so I expect it to be there shortly :-)

cheers,
Fraser.

On Mon, Feb 16, 2009 at 9:12 PM, Ryan Ingram <ryani.spam at gmail.com> wrote:

> Tiny code-review comment:
>
> > data Style = Style [(String, StyleValue)]
> >            deriving (Read, Show)
>
> > instance Monoid Style where
> >    mempty = Style []
> >    mappend (Style xs) (Style ys) = Style (xs ++ ys)
>
> =>
>
> > {-# LANGUAGE GeneralizedNewtypeDeriving #-}
> >
> > newtype Style = Style [(String, StyleValue)]
> >            deriving (Read, Show, Monoid)
>
> Also, put it on hackage! :)  It looks pretty cool.
>
>  -- ryan
>
> 2009/2/16 Fraser Wilson <blancolioni at gmail.com>:
> > Since I'm congenitally lazy, and writing a GUI by hand in the IO monad is
> > ... not what I expect from a beautiful program, and because what I often
> > need is a GUI that manipulates a state, and because I don't understand
> > arrows, and having been intrigued by a recent cafe thread, I threw
> together
> > a prototype GUI library with the following features:
> >
> >   - the GUI is defined on three levels: gadgets, widgets and styles
> >   - gadgets are functions on a state
> >   - widgets are data structures which define the layout
> >   - styles are ways to modify the appearance of widgets
> >
> > The following quick example shows a text box and a button.  Clicking on
> the
> > button reverses the text in the text box.
> >
> >> module Main where
> >
> >> import Barrie
> >
> >> demoWidget :: Widget
> >> demoWidget = vbox [ui "demo entry" textBox,
> >>                    ui "demo command" (labelButton "click me")]
> >
> >> type DemoState = String
> >
> >> type DemoGadget = Gadget DemoState
> >
> >> demoGUI :: DemoGadget
> >> demoGUI = localG "demo gui" [editorG "demo entry" id const,
> >>                              commandG "demo command" reverse]
> >
> >> main = gtkMain demoGUI demoWidget "Hello, world"
> >
> > Two gadgets are used:
> >
> > editorG :: String -> (a -> b) -> (b -> a -> a) -> Gadget a
> > commandG :: String -> (a -> a) -> Gadget a
> >
> > The editor gadget can show a value from a state, and update a state with
> a
> > value.  The command gadget can transform a state to a new state.  gtkMain
> > connects the gadgets to a widget, which specifies layout using the vbox,
> > attaching the editor gadget to a text box, and the command gadget to a
> > button.
> >
> > Well, that's all pretty trivial.  The key thing for me was that I can
> easily
> > slap a GUI onto the the front of a class of applications, which happen to
> be
> > the sort of applications I've been writing lately.  Also, arbitrary parts
> of
> > the GUI can respond to things that happen miles away, without really
> having
> > to worry about it too much.  In barrie-0.1 and 0.2, which used
> stream-based
> > approaches, the problem of getting state from one end of the application
> to
> > the other was non-trivial.
> >
> > I'll sketch another quick example:
> >
> >> data BridgeGame = ...
> >
> > And a bunch of things you can do with the state:
> >
> >> makeBid :: Bid -> BridgeGame -> BridgeGame
> >> playCard :: Card -> BridgeGame -> BridgeGame
> >
> > For bidding, each bid is represented by a gadget:
> >
> >> bidG :: Bid -> Gadget BridgeGame
> >> bidG bid = enabled (bidOK bid) $ CommandG (show bid) (makeBid bid)
> >
> > 'enabled' switches the gadget on if its first argument returns true when
> > applied to the current state.  However, the decision about what to do
> with a
> > disabled gadget is made by its corresponding widget.
> >
> > We get one button for each bid:
> >
> >> biddingG :: Gadget BridgeGame
> >> biddingG = localG "bidding" (map bidG allBids)
> >
> > And they can be displayed in any old order using a widget:
> >
> >> biddingW :: Widget
> >> biddingW = vbox (map suitBids [Club, Diamond, Heart, Spade] ++ [ntBids])
> >>    where suitBids suit = hbox $ map (bidButton . flip Bid suit) [1 .. 7]
> >>          ntBids = hbox $ map (bidButton . NT) [1 .. 7]
> >>          bidButton bid = ui (show bid) $ labelButton (show bid)
> >
> > (You're right, double, redouble and pass are not represented.  They make
> the
> > lines too long).
> >
> > Screenshot here: http://thewhitelion.org/images/4D.png
> >
> > I've just bid four diamonds, so everything lower than that is
> automatically
> > disabled.
> >
> > Currently, Barrie implements buttons, text boxes, labels,
> > vertical/horizontal layout, single-column lists and drop lists.  It
> current
> > uses Gtk2hs for rendering, but it's GUI-agnostic (in fact, the first
> > renderer was putStrLn/getLine).
> >
> > You can have a look by using darcs:
> >    darcs get http://thewhitelion.org/darcs/barrie
> >
> > Or get the tarball at
> > http://thewhitelion.org/haskell/barrie-0.3.0-src.tar.gz
> >
> > One note: this is not intended to be a theoretically sound approach,
> merely
> > a way of getting something done quickly.  I would expect it to be most
> > useful in putting a GUI front-end onto an existing application, in
> > particular, an application that is driven by user actions which update a
> > state; e.g. a calculator, a bridge game, a 4th edition D&D character
> creator
> > (but that leads to a critical mass of nerdiness, so it's off the table
> for
> > now)
> >
> > cheers,
> > Fraser.
> >
> > --
> > http://thewhitelion.org/mysister
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> >
>



-- 
http://thewhitelion.org/mysister
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090216/55b5164a/attachment.htm


More information about the Haskell-Cafe mailing list