Difference between revisions of "Phooey"

From HaskellWiki
Jump to navigation Jump to search
Line 94: Line 94:
 
ui1y = title "Shopping List" $ fruit >>= total
 
ui1y = title "Shopping List" $ fruit >>= total
 
</haskell>
 
</haskell>
d
 
   
 
=== Arrow ===
 
=== Arrow ===

Revision as of 19:10, 30 March 2007

Abstract

Phooey is a functional UI library for Haskell. Beside this page, here are some ways to explore Phooey:

Phooey is also used in GuiTV, a library for composable interfaces and "tangible values".

Introduction

GUIs are usually programmed in an unnatural style, in that implementation dependencies are inverted, relative to logical dependencies. This reversal results directly from the push (data-driven) orientation of most GUI libraries. While outputs depend on inputs from a user and semantic point of view, the push style imposes an implementation dependence of inputs on outputs.

A second drawback of the push style is that it is imperative rather than declarative. A GUI program describes actions to update a model and and view in reaction to user input. In contrast to the how-to-update style of an imperative program, a functional GUI program would express what-it-is of a model in terms of the inputs and of the view in terms of the model.

The questions of push-vs-pull and imperative-vs-declarative are related. While an imperative GUI program could certainly be written to pull (poll) values from input to model and model to view, thus eliminating the dependency inversion, I don't know how a declarative program could be written in the inverted-dependency style. (Do you?).

A important reason for using push rather than pull in a GUI implementation is that push is typically much more efficient. A simple pull implementation would either waste time recomputing an unchanging model and view (pegging your CPU for no benefit), or deal with the complexity of avoiding that recomputation. The push style computes only when inputs change. (Animation negates this advantage of push.)

Phooey ("Phunctional ooser ynterfaces") adopts the declarative style, in which outputs are expressed in terms of inputs. Under the hood, however, the implementation is push-based (data-driven). Phooey performs the dependency inversion invisibly, so that programmers may express GUIs simply and declaratively while still getting an efficient implementation. I have taken care to structure Phooey's implementation as simply as possible to make clear how this dependency inversion works (subject of paper in progress). In addition, Phooey supports dynamic input bounds, flexible layout, and mutually-referential widgets. (The last feature is currently broken.)

Phooey came out of Pajama and Eros. Pan is a re-implementation of the Pan language and compiler for function synthesis of interactive, continuous, infinite images. Pan and Pajama use a monadic style for specifying GUIs and are able to do so because they use the implementation trick of Compiling Embedded Languages, in which one manipulates expressions rather than values. (This trick is mostly transparent, but the illusion shows through in places.)

One example, three interfaces

As an example, below is a simple shopping list GUI. The total displayed at the bottom of the window always shows the sum of the values of the apples and bananas input sliders. When a user changes the inputs, the output updates accordingly.

Ui1.png

Phooey presents three styles of functional GUI interfaces, structured as a monad, an arrow, and an applicative functor. Below we present code for the shopping list example in each of the three functional styles.

The examples below are all found under src/Examples/ in the phooey distribution, in the modules Monad.hs, Arrow.hs, and Monad.hs. In each case, the example is run by loading the corresponding example module into ghci and typing "runUI ui1".

Monad

Here is a definition for the GUI shown above, formulated in terms of Phooey's monadic interface.

ui1 :: UI (Source ())
ui1 = title "Shopping List" $
      do a <- title "apples"  $ islider (0,10) 3
         b <- title "bananas" $ islider (0,10) 7
         title "total" $ showDisplay (liftA2 (+) a b)

The relevant library declarations:

-- Input widget type (with initial value)
type IWidget  a =        a -> UI (Source a)
-- Output widget type
type OWidget  a = Source a -> UI (Source ())

islider     :: (Int,Int) -> IWidget Int
showDisplay :: Show a => OWidget a
title       :: String -> UI a -> UI a

The Source type is a data-driven computation. By using Source Int instead of Int for the type of a and b above, we do not have to rebuild the GUI every time an input value changes.

The down side of using source types is seen in the showDisplay line above, which requires lifting. We could partially hide the lifting behind overloadings of Num and other classes (as in Fran, Pan, and other systems). Some methods, however, do not not have sufficiently flexible types (e.g., (==)), and the illusion becomes awkward. The Arrow and Applicative interfaces hide the source types.

Before we move on to other interface styles, let's look at some refactorings. First pull out the slider minus initial value:

sl0 :: IWidget Int
sl0 = islider (0,10)

Then the titled widgets:

apples, bananas :: UI (Source Int)
apples  = title "apples"  $ sl0 3
bananas = title "bananas" $ sl0 7

total :: Num a => OWidget a
total = title "total" . showDisplay

And use them:

ui1x :: UI (Source ())
ui1x = title "Shopping List" $
       do a <- apples
          b <- bananas
          total (liftA2 (+) a b)

We can go point-free by using liftM2 and (>>=):

fruit :: UI (Source Int)
fruit = liftM2 (liftA2 (+)) apples bananas

ui1y :: UI (Source ())
ui1y = title "Shopping List" $ fruit >>= total

Arrow

Using source types allows the monadic style to capture the static nature of the input GUI while giving access to a source of dynamic values. Alternatively, we can solve the problem by replacing the Monad abstraction with one that separates static and dynamic aspects. Getting that separation is the point of the Arrow abstraction, and thus Phooey provides an arrow interface as well. Moreover, the UI arrow is implemented on top of its UI monad using a simple, reusable pattern. See the Arrow module doc and its source code.

The example:

ui1 :: UI () ()
ui1 = title "Shopping List" $
      proc () -> do
	a <- title "apples"  $ islider (0,10) 3 -< ()
	b <- title "bananas" $ islider (0,10) 7 -< ()
	title "total"  showDisplay              -< a+b

Note the simplicity of a+b. Also, the slider bounds have been moved to a dynamic position, which will be discussed below.

The types of islider, showDisplay, and title as as in the monadic version, with these new definitions of input and output widget types:

type IWidget  a = a -> UI () a
type OWidget  a = UI a ()

Applicative Functor

Applicative functors provide still another approach to separating static and dynamic information. Here is our example, showing just the changes relative to the monadic version.

ui1 :: UI (IO ())
ui1 = title "Shopping List" $ fruit <**> total

fruit :: UI Int
fruit = liftA2 (+) apples bananas

total :: Num a => OWidget a
total = title "total" showDisplay

The UI-building functions again have the same types as before, relative to these new definitions:

type IWidget a = a -> UI a
type OWidget a = UI (a -> IO ())

Notes:

  • Output widgets are function-valued UI.
  • fruit has a simpler definition, requiring only one lifting instead of two.
  • total is subtly different, because output widgets are now function-valued.
  • ui1 uses the reverse application operator (<**>). This reversal causes the function to appear after (below) the argument.
  • ui1 is an IO-valued UI.

Dynamic bounds

Phooey sliders may have dynamic bounds, taking a source of bounds instead of static bounds. In the following example, the first two sliders determine the bounds of the third slider.

Ui2.png

Of course, one would want a prettier interface, but this example will serve to illustrate a point.

Dynamic bounds, monad version

In the Monad version, the new function is

isliderDyn :: Source (Int,Int) -> IWidget Int

Example code:

ui2 :: UI (Source ())
ui2 = do  l <- title "lo"    $ sl0 3
          h <- title "hi"    $ sl0 8
          v <- title "val"   $ isliderDyn (pair l h) 5
          title "factorial"  $ showDisplay (liftA fact v)

Factoring:

lo,hi :: UI (Source Int)
lo = title "lo" $ sl0 3
hi = title "hi" $ sl0 8

bounds :: UI (Source (Int,Int))
bounds = liftM2 pair lo hi

val :: UI (Source Int)
val = do b <- bounds
         title "val" $ isliderDyn b 5

ui2 = do v <- val
         title "factorial"  $ showDisplay (liftA fact v)

As a variation, we might prefer to wrap the "val" title is around the lo & hi sliders as well the val slider. This layout reflects the purpose of the "lo" and "hi" sliders.

Ui2-app.png

The only change:

val = title "val" $
      do b <- bounds
         isliderDyn b 5


Dynamic bounds, arrow version

Example code:

ui2 = proc () -> do
        l <- lo -< ()
        h <- hi -< ()
        v <- title "val" $ isliderDyn 5 -< (l,h)
        title "factorial" showDisplay   -< fact v

Here's an arrow variation using isliderDyn even with static bounds:

ui2 = proc () -> do
        lo  <- title "lo"  $ isliderDyn 3 -< (0,10)
        hi  <- title "hi"  $ isliderDyn 8 -< (0,10)
        val <- title "val" $ isliderDyn 5 -< (lo,hi)
        title "factorial" showDisplay     -< fact val

We can also do some factoring. The bounds come out very simply:

bounds :: UI () (Int,Int)
bounds = lo &&& hi

Then

val = bounds >>> title "val" (isliderDyn 5)

ui2 = (fact ^<< val') >>> title "factorial" showDisplay

Spelling out (^<<):

ui2 = val >>> pure fact >>> title "factorial" showDisplay

If we want the "val" title around the bounds, redefine val:

val = title "val" $ (lo &&& hi) >>> isliderDyn 5


Dynamic bounds, applicative functor version

The example code is very simple:

val = title "val" $ isliderDyn (pair lo hi) 5

ui2 = (fact <$> val) <**> title "factorial" showDisplay

This version includes the bounds within the "val" title. I don't know how to get a "val" title on just the dynamically-bounded slider.

Layout

By default, UI layout follows the order of the specification, with earlier-specified components above later-specified ones. This layout may be overridden by explicit layout functions. For instance, the following definitions form variations of ui1 laid out from bottom to top and from left to right.

GUIs & code:

UiB1.png
UiL1.png
uiB1 = fromBottom ui1
uiL1 = fromLeft   ui1


We can also lay out a sub-assembly, as in ui3 below

Ui3.png
ui3 = fromBottom $
      title "Shopping  List" $
      fromRight fruit >>= total

Recursive GUIs

Next is a recursive example. It is like ui2, but the lo and hi sliders are used to bound each other. The specification enforces the constraint that lo <= hi.

Ui4.png

Monad version:

uir1 :: UI (Source ())
uir1 = mdo l <- title "lo"   $ isliderDyn (pair (pure 0)  h) 3
           h <- title "hi"   $ isliderDyn (pair l (pure 10)) 8
           v <- title "val"  $ isliderDyn (pair l h) 5
           title "factorial" $ showDisplay (liftA fact v)

Refactoring,

boundsR :: UI (Source (Int,Int))
boundsR = mfix boundsF
 where
   boundsF lh = liftM2 pair
                  (title "lo" $ isliderDyn (pair (pure 0) h) 3)
                  (title "hi" $ isliderDyn (pair l (pure 10)) 8)
     where
       (l,h) = unPair lh

unPair :: Functor f => f (a, b) -> (f a, f b)
unPair p = (fmap fst p, fmap snd p)

Then continue as with ui1:

valR :: UI (Source Int)
valR = do b <- boundsR
          title "val" $ isliderDyn b 5

uir1' = do v <- valR
           title "factorial"  $ showDisplay (liftA fact v)

The next example is tightly recursive. A slider is used to bound itself, so that the range is always the current value ±5.

Ui5.png
uir2 = mdo v <- title "val" (isliderDyn (liftA (plusMinus 5) v) 6)
           title "squared" (showDisplay (liftA square v))
 where
   plusMinus n x = (x-n,x+n)
   square y      = y*y

The arrow and applicative functor versions of these examples exhaust stack space.

Portability

Phooey is built on wxHaskell. Quoting from the wxHaskell home page,

wxHaskell is therefore built on top of wxWidgets -- a comprehensive C++ library that is portable across all major GUI platforms; including GTK, Windows, X11, and MacOS X.

So I expect that Phooey runs on all of these platforms. That said, I have only tried Phooey on Windows. Please give it a try and leave a message on the Talk page ("Discuss this page").

Known problems

  • Recursive examples don't work (consumes memory) in the Arrow or Applicative interface.

Plans

  • Use Javascript and HTML in place wxHaskell, and hook it up with Yhc/Javascript.