Difference between revisions of "Phooey"

From HaskellWiki
Jump to navigation Jump to search
m (→‎Introduction: added sections)
m (part-way through big changes)
Line 1: Line 1:
  +
''This page is in flux. I am preparing a new release (1.0) with some major changes.''
  +
 
== Abstract ==
 
== Abstract ==
   
Line 7: Line 9:
 
* Grab a [http://darcs.haskell.org/packages/phooey/dist distribution tarball].
 
* Grab a [http://darcs.haskell.org/packages/phooey/dist distribution tarball].
 
* See the [http://darcs.haskell.org/packages/phooey/CHANGES version changes].
 
* See the [http://darcs.haskell.org/packages/phooey/CHANGES version changes].
  +
 
Phooey is also used in [[GuiTV]], a library for composable interfaces and "tangible values".
   
 
== Introduction ==
 
== Introduction ==
Line 19: Line 23:
   
 
Phooey ("'''Ph'''unctional '''oo'''s'''e'''r '''y'''nterfaces") 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 ("'''Ph'''unctional '''oo'''s'''e'''r '''y'''nterfaces") 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 [http://conal.net/Pajama Pajama] and [http://conal.net/papers/Eros]. Pan is a
  +
re-implementation of the [http://conal.net/Pan 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 [http://conal.net/papers/jfp-saig
  +
Compiling Embedded Languages], in which one manipulates expressions rather than values. (This trick
  +
is mostly transparent, but the illusion shows through in places.)
   
 
As an example, below is a simple shopping list GUI. The <hask>total</hask> displayed at the bottom of the window always shows the sum of the values of the <hask>apples</hask> and <hask>bananas</hask> input sliders. When a user changes the inputs, the output updates accordingly.
 
As an example, below is a simple shopping list GUI. The <hask>total</hask> displayed at the bottom of the window always shows the sum of the values of the <hask>apples</hask> and <hask>bananas</hask> input sliders. When a user changes the inputs, the output updates accordingly.
Line 25: Line 36:
 
Phooey presents three styles of functional GUI interfaces, structured as a [[monad]], an [[arrow]], and an [[applicative functor]].
 
Phooey presents three styles of functional GUI interfaces, structured as a [[monad]], an [[arrow]], and an [[applicative functor]].
   
  +
== One example, three interfaces ==
== Monad ==
 
   
 
=== Monad ===
Here is a definition for the GUI shown above, formulated in terms of [http://darcs.haskell.org/packages/phooey/doc/html/Graphics-UI-Phooey-Monad.html Phooey's monadic interface].
 
  +
 
Here is a definition for the GUI shown above, formulated in terms of [http://darcs.haskell.org/packages/phooey/doc/html/Graphics-UI-Phooey-Monad.html Phooey's [[monad]]ic interface].
   
 
<haskell>
 
<haskell>
Line 38: Line 51:
   
 
The relevant library declarations:
 
The relevant library declarations:
 
 
<haskell>
 
<haskell>
 
-- Input widget type (with initial value)
 
-- Input widget type (with initial value)
Line 50: Line 62:
 
</haskell>
 
</haskell>
   
The <hask>Source</hask> type is a [[TypeCompose#Data_driven_computations|data-driven computation]].
+
The <hask>Source</hask> type is a [[TypeCompose#Data_driven_computations|data-driven computation]]. By using <hask>Source Int</hask> instead of <hask>Int</hask> for the type of <hask>a</hask> and <hask>b</hask> 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 <hask>showDisplay</hask> line above, which requires lifting.
== Arrow ==
 
   
 
=== 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
  +
[http://darcs.haskell.org/packages/phooey/doc/html/Graphics-UI-Phooey-Arrow.html Arrow module doc]
  +
and its [http://darcs.haskell.org/packages/phooey/doc/html/src/Graphics/UI/Phooey/Arrow.hs.html
  +
source code].
  +
  +
The example:
 
<haskell>
 
<haskell>
 
ui1 :: UI () ()
 
ui1 :: UI () ()
 
ui1 = title "Shopping List" $
 
ui1 = title "Shopping List" $
 
proc () -> do
 
proc () -> do
a <- title "apples" (islider 3) -< (0,10)
+
a <- title "apples" $ islider (0,10) 3 -< ()
b <- title "bananas" (islider 7) -< (0,10)
+
b <- title "bananas" $ islider (0,10) 7 -< ()
title "total" showDisplay -< a+b
+
title "total" showDisplay -< a+b
 
</haskell>
 
</haskell>
  +
Note the simplicity of <hask>a+b</hask>. Also, the slider bounds have been moved to a ''dynamic'' position, which will be discussed below.
   
  +
Relevant library declarations:
== Applicative Functor ==
 
 
<haskell>
  +
type IWidget a = a -> UI () a
  +
type OWidget a = UI a ()
   
  +
islider :: (Int,Int) -> IWidget Int
== Motivation ==
 
  +
showDisplay :: Show a => OWidget a
  +
title :: String -> UI a b -> UI a b
  +
</haskell>
   
 
=== Applicative Functor ===
Phooey came out of [http://conal.net/Pajama Pajama] and [http://conal.net/papers/Eros]. Pan is a re-implementation of the [http://conal.net/Pan 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 [http://conal.net/papers/jfp-saig Compiling Embedded Languages], in which one manipulates expressions rather than values. (This trick is mostly transparent, but the illusion shows through in places.)
 
   
  +
Example:
Switching from expressions to values raises a challenge for a declarative [[monad]]ic approach. For instance, consider this (problematic) monadic UI.
 
 
<haskell>
 
<haskell>
factOopsUI :: UIM ()
+
ui1 :: UI Upd
  +
ui1 = title "Shopping List" $
factOopsUI = do n <- title "n" (islider 3 (0,20))
 
  +
(liftA2 (+) apples bananas) <**> total
title "factorial" (showDisplay (fact n))
 
  +
  +
apples, bananas :: UI Int
 
apples = title "apples" $ islider (0,10) 3
  +
bananas = title "bananas" $ islider (0,10) 7
  +
  +
total :: Num a => UI a ()
  +
total = title "total" showDisplay
 
</haskell>
 
</haskell>
  +
If <hask>n :: Int</hask>, then the second half of the GUI depends on the dynamic run-time values flowing out of the first half, and so must be constructed for each new value of <hask>n</hask>. The problem is a failure to separate a GUI into its static and dynamic parts. A solution with the monadic framework would be to give <hask>n</hask> a different type, such as <hask>Source Int</hask>, which captures the static nature of the input GUI while giving access to a ''source'' of dynamic values. Phooey provides this monadic solution in its [http://darcs.haskell.org/packages/phooey/doc/html/Graphics-UI-Phooey-MonadUI.html MonadUI] module. The awkwardness is that we can no longer use such simple formulations as <hask>factOopsUI</hask> above, since expressions like <hask>product [1..n]</hask> won't type-check. (We can play overloading tricks as in [http://conal.net/Fran Fran], Pan, and Pajama, but they don't always work.) Instead, we could use <hask>return</hask>, <hask>liftM</hask>, <hask>liftM2</hask>, etc.
 
  +
Relevant library declarations:
 
<haskell>
 
<haskell>
  +
type Snk a = a -> IO ()
factUI :: UIM ()
 
factUI = do n <- title "n" (islider 3 (return (0,20)))
 
title "factorial" (showDisplay (liftM fact n))
 
</haskell>
 
   
  +
type IWidget a = a -> UI a
Rather than introducing the complexity of the <hask>Source</hask> type and the need for explicit lifting, 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's primary interface is formulated as an arrow rather than a monad. Phooey's UI arrow is implemented on top of its UI monad using a simple, reusable pattern. See the [http://darcs.haskell.org/packages/phooey/doc/html/Graphics-UI-Phooey-ArrowUI.html ArrowUI module doc] and its [http://darcs.haskell.org/packages/phooey/doc/html/src/Graphics/UI/Phooey/ArrowUI.hs.html source code].
 
  +
type OWidget a = UI (Snk a)
  +
  +
islider :: (Int,Int) -> IWidget Int
  +
showDisplay :: Show a => OWidget a
  +
title :: String -> UI a -> UI a
  +
</haskell>
   
  +
''WORKING HERE''
Phooey is also used in [[TV]], a library for composable interfaces and "tangible values".
 
   
 
== Portability ==
 
== Portability ==

Revision as of 03:27, 28 March 2007

This page is in flux. I am preparing a new release (1.0) with some major changes.

Abstract

Phooey is an arrow-based functional UI library for Haskell.

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 [1]. 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 [http://conal.net/papers/jfp-saig Compiling Embedded Languages], in which one manipulates expressions rather than values. (This trick is mostly transparent, but the illusion shows through in places.)

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.

One example, three interfaces

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.

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 [http://darcs.haskell.org/packages/phooey/doc/html/src/Graphics/UI/Phooey/Arrow.hs.html 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.

Relevant library declarations:

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

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

Applicative Functor

Example:

ui1 :: UI Upd
ui1 = title "Shopping List" $
      (liftA2 (+) apples bananas) <**> total

apples, bananas :: UI Int
apples  = title "apples"  $ islider (0,10) 3
bananas = title "bananas" $ islider (0,10) 7

total :: Num a => UI a ()
total = title "total" showDisplay

Relevant library declarations:

type Snk a = a -> IO ()

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

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

WORKING HERE

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

  • When two sliders are placed side-by-side, the right one doesn't stretch as expected. I've asked for help on wxHaskell-users.

Plans

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