Difference between revisions of "Phooey"

From HaskellWiki
Jump to navigation Jump to search
m (change in capitalization of yet non-existent user interfaces category)
 
(29 intermediate revisions by 4 users not shown)
Line 1: Line 1:
 
== Abstract ==
 
== Abstract ==
   
'''Phooey''' is a functional UI library for [[Haskell]]. Beside this page, here are some ways to explore Phooey:
+
'''Phooey''' is a functional UI library for [[Haskell]]. Or it's two of them, as it provides a <hask>Monad</hask> interface ''and'' an <hask>Applicative</hask> interface. The simplicity of Phooey's implementation is due to its use of [[Reactive]] for applicative, data-driven computation. (Before version 2.0, Phooey used the [[DataDriven]] library.)
   
  +
Besides this wiki page, here are more ways to find out about Phooey:
* Read [http://darcs.haskell.org/packages/phooey/doc/html the Haddock docs] (with source code, additional examples, and Comment/Talk links).
 
  +
* Read [http://hackage.haskell.org/package/phooey-2.0 the Haddock docs] (with source code, additional examples, and Comment/Talk links).
* Get the code repository: '''<tt>darcs get http://darcs.haskell.org/packages/phooey</tt>''', or
 
  +
* Get the code repository: '''<tt>darcs get http://conal.net/repos/phooey</tt>'''.
* Grab a [http://darcs.haskell.org/packages/phooey/dist distribution tarball].
 
  +
* See the [http://darcs.haskell.org/packages/phooey/CHANGES version changes].
 
  +
The package can be installed from [[Hackage]], using [[cabal-install]]:
  +
cabal install phooey
   
 
Phooey is also used in [[GuiTV]], a library for composable interfaces and "tangible values".
 
Phooey is also used in [[GuiTV]], a library for composable interfaces and "tangible values".
  +
  +
Since Reactive is currently broken (as of February 2010), Phooey is also broken.
   
 
== Introduction ==
 
== Introduction ==
Line 14: Line 18:
 
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.
 
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.
+
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 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. ([[Talk:Phooey|Do you?]]).
 
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. ([[Talk:Phooey|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.)
+
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. (Continuous change, i.e. animation, negates this advantage of push.)
   
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 uses the [[Reactive]] library to perform the dependency inversion invisibly, so that programmers may express GUIs simply and declaratively while still getting an efficient implementation.
   
Phooey came out of [http://conal.net/Pajama Pajama] and [http://conal.net/papers/Eros 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.)
+
Phooey came out of [http://conal.net/Pajama Pajama] and [http://conal.net/papers/Eros Eros]. Pajama 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.)
   
== One example, three interfaces ==
+
== One example, two interfaces ==
   
 
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.
 
: [[Image:ui1.png]]
 
: [[Image: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.
+
Phooey presents two styles of functional GUI interfaces, structured as a [[monad]] and as an [[applicative functor]]. (I have removed the original [[arrow]] interface.) Below you can see the code for the shopping list example in each of these styles.
   
The examples below are all found under [http://darcs.haskell.org/packages/phooey/src/Examples <code>src/Examples/</code>] in the phooey distribution, in the modules [http://darcs.haskell.org/packages/phooey/src/Examples/Monad.hs <code>Monad.hs</code>], [http://darcs.haskell.org/packages/phooey/src/Examples/Arrow.hs <code>Arrow.hs</code>], and [http://darcs.haskell.org/packages/phooey/src/Examples/Monad.hs <code>Monad.hs</code>]. In each case, the example is run by loading the corresponding example module into ghci and typing "<hask>runUI ui1</hask>".
+
The examples below are all found under [http://darcs.haskell.org/packages/phooey/src/Examples <code>src/Examples/</code>] in the phooey distribution, in the modules [http://darcs.haskell.org/packages/phooey/src/Examples/Monad.hs <code>Monad.hs</code>], and [http://darcs.haskell.org/packages/phooey/src/Examples/Applicative.hs <code>Applicative.hs</code>]. In each case, the example is run by loading the corresponding example module into ghci and typing <hask>runUI ui1</hask>.
   
 
=== Monad ===
 
=== Monad ===
Line 38: Line 42:
   
 
<haskell>
 
<haskell>
ui1 :: UI (Source ())
+
ui1 :: UI ()
 
ui1 = title "Shopping List" $
 
ui1 = title "Shopping List" $
 
do a <- title "apples" $ islider (0,10) 3
 
do a <- title "apples" $ islider (0,10) 3
Line 50: Line 54:
 
type IWidget a = a -> UI (Source a)
 
type IWidget a = a -> UI (Source a)
 
-- Output widget type
 
-- Output widget type
type OWidget a = Source a -> UI (Source ())
+
type OWidget a = Source a -> UI ()
   
 
islider :: (Int,Int) -> IWidget Int
 
islider :: (Int,Int) -> IWidget Int
Line 57: Line 61:
 
</haskell>
 
</haskell>
   
The <hask>Source</hask> type is a [[TypeCompose#Data-driven_computation|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 <hask>Source</hask> type is a (data-driven) source of [[Reactive|time-varying values]]. (<hask>Source</hask> is a synonym for <hask>Reactive</hask>.) 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. We could partially hide the lifting behind overloadings of <hask>Num</hask> and other classes (as in [http://conal.net/Fran Fran], [http://conal.net/Pan Pan], and other systems). Some methods, however, do not not have sufficiently flexible types (e.g., <hask>(==)</hask>), and the illusion becomes awkward. The <hask>Arrow</hask> and <hask>Applicative</hask> interfaces hide the source types.
 
The down side of using source types is seen in the <hask>showDisplay</hask> line above, which requires lifting. We could partially hide the lifting behind overloadings of <hask>Num</hask> and other classes (as in [http://conal.net/Fran Fran], [http://conal.net/Pan Pan], and other systems). Some methods, however, do not not have sufficiently flexible types (e.g., <hask>(==)</hask>), and the illusion becomes awkward. The <hask>Arrow</hask> and <hask>Applicative</hask> interfaces hide the source types.
Line 79: Line 83:
 
And use them:
 
And use them:
 
<haskell>
 
<haskell>
ui1x :: UI (Source ())
+
ui1x :: UI ()
 
ui1x = title "Shopping List" $
 
ui1x = title "Shopping List" $
 
do a <- apples
 
do a <- apples
Line 88: Line 92:
 
We can go point-free by using <hask>liftM2</hask> and <hask>(>>=)</hask>:
 
We can go point-free by using <hask>liftM2</hask> and <hask>(>>=)</hask>:
 
<haskell>
 
<haskell>
  +
-- Sum UIs
  +
infixl 6 .+.
  +
  +
(.+.) :: Num a => UIS a -> UIS a -> UIS a
  +
(.+.) = liftA2 (liftA2 (+))
  +
 
fruit :: UI (Source Int)
 
fruit :: UI (Source Int)
fruit = liftM2 (liftA2 (+)) apples bananas
+
fruit = apples .+. bananas
   
ui1y :: UI (Source ())
+
ui1y :: UI ()
 
ui1y = title "Shopping List" $ fruit >>= total
 
ui1y = title "Shopping List" $ fruit >>= total
</haskell>
 
 
=== 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 interface doc]
 
and its [http://darcs.haskell.org/packages/phooey/doc/html/src.Graphics.UI.Phooey.Arrow.hs.html source code].
 
 
The example:
 
<haskell>
 
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
 
</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.
 
 
The types of <hask>islider</hask>, <hask>showDisplay</hask>, and <hask>title</hask> as as in the monadic version, with these new definitions of input and output widget types:
 
<haskell>
 
type IWidget a = a -> UI () a
 
type OWidget a = UI a ()
 
 
</haskell>
 
</haskell>
   
 
=== Applicative Functor ===
 
=== Applicative Functor ===
   
[[Applicative functor]]s provide still another approach to separating static and dynamic information. Here is our example, showing just the changes relative to the [[#Monad|monadic]] version. (See the
+
[[Applicative functor]]s (AFs) provide still another approach to separating static and dynamic information. Here is our example, showing just the changes relative to the [[#Monad|monadic]] version. (See the
[http://darcs.haskell.org/packages/phooey/doc/html/Graphics-UI-Phooey-Applicative.html Applicative interface doc]
+
[http://darcs.haskell.org/packages/phooey/doc/html/Graphics-UI-Phooey-Applicative.html Applicative interface doc] and its [http://darcs.haskell.org/packages/phooey/doc/html/src.Graphics.UI.Phooey.Applicative.hs.html source code].)
and its [http://darcs.haskell.org/packages/phooey/doc/html/src.Graphics.UI.Phooey.Applicative.hs.html source code].)
 
 
<haskell>
 
<haskell>
 
ui1 :: UI (IO ())
 
ui1 :: UI (IO ())
Line 133: Line 119:
 
total = title "total" showDisplay
 
total = title "total" showDisplay
 
</haskell>
 
</haskell>
  +
I chose reversed AF application <hask>(<**>)</hask> rather than <hask>(<*>)</hask> so the fruit (argument) would be displayed above the total (function).
   
 
The UI-building functions again have the same types as before, relative to these new definitions:
 
The UI-building functions again have the same types as before, relative to these new definitions:
Line 147: Line 134:
 
* <hask>ui1</hask> is an IO-valued UI.
 
* <hask>ui1</hask> is an IO-valued UI.
   
  +
The applicative UI interface (<hask>Graphics.UI.Phooey.Applicative</hask>) is implemented as a very simple layer on top of the monadic interface, using type composition (from [[TypeCompose]]):
== Dynamic bounds ==
 
  +
<haskell>
  +
type UI = M.UI :. Source
  +
</haskell>
  +
Thanks to properties of <hask>O</hask>, this definition suffices to make <hask>UI</hask> an AF.
   
  +
== Layout ==
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.
 
: [[Image:Ui2.png]]
 
Of course, one would want a prettier interface, but this example will serve to illustrate a point.
 
   
  +
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 <hask>ui1</hask> laid out from bottom to top and from left to right.
=== Dynamic bounds, monad version ===
 
   
  +
GUIs & code:
In the Monad version, the new function is
 
  +
<haskell>
 
  +
: [[Image:UiB1.png]]
isliderDyn :: Source (Int,Int) -> IWidget Int
 
  +
: [[Image:UiL1.png]]
</haskell>
 
   
Example code:
 
 
<haskell>
 
<haskell>
  +
uiB1 = fromBottom ui1
ui2 :: UI (Source ())
 
  +
uiL1 = fromLeft ui1
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)
 
 
</haskell>
 
</haskell>
   
Factoring:
 
<haskell>
 
lo,hi :: UI (Source Int)
 
lo = title "lo" $ sl0 3
 
hi = title "hi" $ sl0 8
 
   
  +
We can also lay out a sub-assembly, as in <hask>ui3</hask> below
bounds :: UI (Source (Int,Int))
 
bounds = liftM2 pair lo hi
 
   
  +
: [[Image:Ui3.png]]
val :: UI (Source Int)
 
val = do b <- bounds
 
title "val" $ isliderDyn b 5
 
   
  +
<haskell>
ui2 = do v <- val
 
  +
ui3 = fromBottom $
title "factorial" $ showDisplay (liftA fact v)
 
  +
title "Shopping List" $
  +
fromRight fruit >>= total
 
</haskell>
 
</haskell>
   
  +
== Event Examples ==
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.
 
: [[Image:Ui2-app.png]]
 
   
  +
The shopping examples above demonstrate the simple case of outputs (<hask>total</hask>) as functions of varying inputs (<hask>apples</hask> and <hask>bananas</hask>). Events were hidden inside the implementation of [[Reactive#Data.Reactive|reactive values]].
The only change:
 
<haskell>
 
val = title "val" $
 
do b <- bounds
 
isliderDyn b 5
 
</haskell>
 
   
  +
This section shows two classic functional GUI examples involving a visible notion of [[Reactive#Data.Reactive|events]].
   
=== Dynamic bounds, arrow version ===
+
=== Counter ===
   
  +
Here is simple counter, which increments or decrements when the "up" or "down" button is pressed. The example is from "[http://www.citeulike.org/user/conal/article/1617415 Structuring Graphical Paradigms in TkGofer]"
Example code:
 
<haskell>
 
ui2 = proc () -> do
 
l <- lo -< ()
 
h <- hi -< ()
 
v <- title "val" $ isliderDyn 5 -< (l,h)
 
title "factorial" showDisplay -< fact v
 
</haskell>
 
   
  +
: [[Image:Phooey-UpDown.png]]
Here's an arrow variation using <hask>isliderDyn</hask> even with static bounds:
 
<haskell>
 
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
 
</haskell>
 
   
  +
The first piece in making this counter is a button, having a specified value and a label. The button GUI's value is an ''event'' rather than a source:
We can also do some factoring. The bounds come out very simply:
 
 
<haskell>
 
<haskell>
bounds :: UI () (Int,Int)
+
smallButton :: a -> String -> UI (Event a)
bounds = lo &&& hi
 
 
</haskell>
 
</haskell>
  +
To make the up/down counter, we'll want two such buttons, labeled "up" and "down". But with what values? The buttons won't know what the counter value is, but they will know how to change the value, so the events will be function-valued. The two events resulting from the two buttons are then merged into a single function-valued event via <hask>mappend</hask>. (If you're curious about events at this point, take a detour and [[Reactive#Data.Reactive|read about them]].)
   
  +
The pair of buttons and combined event could be written as follows:
Then
 
 
<haskell>
 
<haskell>
  +
upDown :: Num a => UIE (a -> a)
val = bounds >>> title "val" (isliderDyn 5)
 
  +
upDown = do up <- smallButton (+ 1) "up"
 
  +
down <- smallButton (subtract 1) "down"
ui2 = (fact ^<< val') >>> title "factorial" showDisplay
 
  +
return (up `mappend` down)
 
</haskell>
 
</haskell>
  +
If you've been hanging around with monad hipsters, you'll know that we can write this definition more simply:
 
Spelling out <hask>(^<<)</hask>:
 
 
<haskell>
 
<haskell>
  +
upDown = liftM2 mappend (smallButton (+ 1) "up")
ui2 = val >>> pure fact >>> title "factorial" showDisplay
 
  +
(smallButton (subtract 1) "down")
 
</haskell>
 
</haskell>
  +
Personally, I'm on an <hask>Applicative</hask> kick lately, so I prefer <hask>liftA2</hask> in place of <hask>liftM2</hask>.
   
  +
Still more sleekly, let's hide the <hask>liftM2</hask> (or <hask>liftA2</hask>) by using the <hask>Monoid (UI o) </hask> instance, which holds whenever <hask>Monoid o</hask>.
If we want the "val" title around the bounds, redefine <hask>val</hask>:
 
 
<haskell>
 
<haskell>
  +
upDown = smallButton (+ 1) "up" `mappend`
val = title "val" $ (lo &&& hi) >>> isliderDyn 5
 
  +
smallButton (subtract 1) "down"
 
</haskell>
 
</haskell>
   
  +
To finish the counter, use the <hask>accumR</hask> function, which makes a source from an initial value and an function-valued event. The source begins as the initial value and grows by applying the functions generated by the event.
 
 
=== Dynamic bounds, applicative functor version ===
 
 
The example code is very simple:
 
 
<haskell>
 
<haskell>
  +
accumR :: a -> UI (Event (a -> a)) -> UI (Source a)
val = title "val" $ isliderDyn (pair lo hi) 5
 
   
  +
counter :: UI ()
ui2 = (fact <$> val) <**> title "factorial" showDisplay
 
  +
counter = title "Counter" $ fromLeft $
  +
do e <- upDown
  +
showDisplay (0 `accumR` e)
 
</haskell>
 
</haskell>
   
  +
=== Calculator ===
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.
 
   
  +
The second event example is a calculator, as taken from "[http://citeseer.ist.psu.edu/vullinghs95lightweight.html Lightweight GUIs for Functional Programming]".
== Layout ==
 
   
  +
: [[Image:Calc.png]]
   
  +
The basic structure of this example is just like the previous one. Each key has a function-valued event, and the keys are combined (visually and semantically) using <hask>mappend</hask>.
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 <hask>ui1</hask> laid out from bottom to top and from left to right.
 
 
GUIs & code:
 
 
: [[Image:UiB1.png]]
 
: [[Image:UiL1.png]]
 
   
  +
First a single key. For variety, we'll postpone interpreting the key's event as a function.
 
<haskell>
 
<haskell>
  +
key :: Char -> UIE Char
uiB1 = fromBottom ui1
 
  +
key c = button' c [c]
uiL1 = fromLeft ui1
 
 
</haskell>
 
</haskell>
   
  +
We'll combine keys with the help of a friend of <hask>concatMap</hask>:
 
We can also lay out a sub-assembly, as in <hask>ui3</hask> below
 
 
: [[Image:Ui3.png]]
 
 
 
<haskell>
 
<haskell>
  +
mconcatMap :: Monoid b => (a -> b) -> [a] -> b
ui3 = fromBottom $
 
  +
mconcatMap f = mconcat . map f
title "Shopping List" $
 
fromRight fruit >>= total
 
 
</haskell>
 
</haskell>
   
  +
With this helper, it's especially easy to turn several keys into a row and several rows into a keyboard.
== Recursive GUIs ==
 
  +
<haskell>
  +
row :: [Char] -> UIE Char
  +
row = fromLeft . mconcatMap key
   
  +
rows :: [[Char]] -> UIE Char
Next is a recursive example. It is like <hask>ui2</hask>, but the <hask>lo</hask> and <hask>hi</hask> sliders are used to bound each other. The specification enforces the constraint that <hask>lo <= hi</hask>.
 
  +
rows = fromTop . mconcatMap row
   
  +
calcKeys :: UIE Char
: [[Image:Ui4.png]]
 
  +
calcKeys = rows [ "123+"
  +
, "456-"
  +
, "789*"
  +
, "C0=/" ]
  +
</haskell>
   
  +
Next, let's turn <hask>calcKeys</hask>'s character-valued event into a function-valued event. While the state of the [[Phooey#Counter|counter]] was a single number, the calculator state is a little more complicated. It consists of a number being formed and a continuation.
Monad version:
 
 
<haskell>
 
<haskell>
  +
type CState = (Int, Int -> Int)
uir1 :: UI (Source ())
 
  +
uir1 = mdo l <- title "lo" $ isliderDyn (pair (pure 0) h) 3
 
  +
startCS :: CState
h <- title "hi" $ isliderDyn (pair l (pure 10)) 8
 
  +
startCS = (0, id)
v <- title "val" $ isliderDyn (pair l h) 5
 
title "factorial" $ showDisplay (liftA fact v)
 
 
</haskell>
 
</haskell>
   
  +
Keyboard characters have interpretations as state transitions.
Refactoring,
 
 
<haskell>
 
<haskell>
  +
cmd :: Char -> CState -> CState
boundsR :: UI (Source (Int,Int))
 
  +
cmd 'C' _ = startCS
boundsR = mfix boundsF
 
  +
cmd '=' (d,k) = (k d, const (k d))
  +
cmd c (d,k) | isDigit c = (10*d + ord c - ord '0', k)
  +
| otherwise = (0, op c (k d))
  +
  +
op :: Char -> Int -> Int -> Int
  +
op c = fromJust (lookup c ops)
 
where
 
where
boundsF lh = liftM2 pair
+
ops :: [(Char, Binop Int)]
  +
ops = [('+',(+)), ('-',(-)), ('*',(*)), ('/',div)]
(title "lo" $ isliderDyn (pair (pure 0) h) 3)
 
  +
</haskell>
(title "hi" $ isliderDyn (pair l (pure 10)) 8)
 
where
 
(l,h) = unPair lh
 
   
  +
To compute the (reactive) value, from a key-generating event, accumulate transitions, starting with the initial state, and extract the value.
unPair :: Functor f => f (a, b) -> (f a, f b)
 
  +
<haskell>
unPair p = (fmap fst p, fmap snd p)
 
  +
compCalc :: Event Char -> Source Int
  +
compCalc key = fmap fst (startCS `accumR` fmap cmd key)
 
</haskell>
 
</haskell>
  +
Show the result:
Then continue as with <hask>ui1</hask>:
 
 
<haskell>
 
<haskell>
valR :: UI (Source Int)
+
showCalc :: Event Char -> UI ()
  +
showCalc = title "result" . showDisplay . compCalc
valR = do b <- boundsR
 
title "val" $ isliderDyn b 5
 
 
uir1' = do v <- valR
 
title "factorial" $ showDisplay (liftA fact v)
 
 
</haskell>
 
</haskell>
   
  +
The whole calculator then snaps together:
The next example is tightly recursive. A slider is used to bound ''itself'', so that the range is always the current value &plusmn;5.
 
: [[Image:Ui5.png]]
 
 
 
<haskell>
 
<haskell>
  +
calc :: UI ()
uir2 = mdo v <- title "val" (isliderDyn (liftA (plusMinus 5) v) 6)
 
  +
calc = title "Calculator" $ calcKeys >>= showCalc
title "squared" (showDisplay (liftA square v))
 
where
 
plusMinus n x = (x-n,x+n)
 
square y = y*y
 
 
</haskell>
 
</haskell>
 
The arrow and applicative functor versions of these examples exhaust stack space.
 
   
 
== Portability ==
 
== Portability ==
Line 337: Line 294:
 
wxHaskell is therefore built on top of [http://www.wxwidgets.org wxWidgets] -- a comprehensive C++ library that is portable across all major GUI platforms; including GTK, Windows, X11, and MacOS X.
 
wxHaskell is therefore built on top of [http://www.wxwidgets.org wxWidgets] -- a comprehensive C++ library that is portable across all major GUI platforms; including GTK, Windows, X11, and MacOS X.
 
</blockquote>
 
</blockquote>
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").
+
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:Phooey|talk page]].
   
 
== Known problems ==
 
== Known problems ==
Line 350: Line 307:
 
[[Category:Libraries]]
 
[[Category:Libraries]]
 
[[Category:Packages]]
 
[[Category:Packages]]
  +
[[Category:wxHaskell]]

Latest revision as of 14:34, 3 April 2012

Abstract

Phooey is a functional UI library for Haskell. Or it's two of them, as it provides a Monad interface and an Applicative interface. The simplicity of Phooey's implementation is due to its use of Reactive for applicative, data-driven computation. (Before version 2.0, Phooey used the DataDriven library.)

Besides this wiki page, here are more ways to find out about Phooey:

The package can be installed from Hackage, using cabal-install:

 cabal install phooey

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

Since Reactive is currently broken (as of February 2010), Phooey is also broken.

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 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. (Continuous change, i.e. 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 uses the Reactive library to perform the dependency inversion invisibly, so that programmers may express GUIs simply and declaratively while still getting an efficient implementation.

Phooey came out of Pajama and Eros. Pajama 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, two 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 two styles of functional GUI interfaces, structured as a monad and as an applicative functor. (I have removed the original arrow interface.) Below you can see the code for the shopping list example in each of these styles.

The examples below are all found under src/Examples/ in the phooey distribution, in the modules Monad.hs, and Applicative.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. See the monad interface and its source code.

ui1 :: UI ()
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 ()

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

The Source type is a (data-driven) source of time-varying values. (Source is a synonym for Reactive.) 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 ()
ui1x = title "Shopping List" $
       do a <- apples
          b <- bananas
          total (liftA2 (+) a b)

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

-- Sum UIs
infixl 6  .+.

(.+.) :: Num a => UIS a -> UIS a -> UIS a
(.+.) = liftA2 (liftA2 (+))

fruit :: UI (Source Int)
fruit = apples .+. bananas

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

Applicative Functor

Applicative functors (AFs) provide still another approach to separating static and dynamic information. Here is our example, showing just the changes relative to the monadic version. (See the Applicative interface doc and its source code.)

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

I chose reversed AF application (<**>) rather than (<*>) so the fruit (argument) would be displayed above the total (function).

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.

The applicative UI interface (Graphics.UI.Phooey.Applicative) is implemented as a very simple layer on top of the monadic interface, using type composition (from TypeCompose):

type UI = M.UI :. Source

Thanks to properties of O, this definition suffices to make UI an AF.

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

Event Examples

The shopping examples above demonstrate the simple case of outputs (total) as functions of varying inputs (apples and bananas). Events were hidden inside the implementation of reactive values.

This section shows two classic functional GUI examples involving a visible notion of events.

Counter

Here is simple counter, which increments or decrements when the "up" or "down" button is pressed. The example is from "Structuring Graphical Paradigms in TkGofer"

Phooey-UpDown.png

The first piece in making this counter is a button, having a specified value and a label. The button GUI's value is an event rather than a source:

smallButton :: a -> String -> UI (Event a)

To make the up/down counter, we'll want two such buttons, labeled "up" and "down". But with what values? The buttons won't know what the counter value is, but they will know how to change the value, so the events will be function-valued. The two events resulting from the two buttons are then merged into a single function-valued event via mappend. (If you're curious about events at this point, take a detour and read about them.)

The pair of buttons and combined event could be written as follows:

upDown :: Num a => UIE (a -> a)
upDown = do up   <- smallButton (+ 1)        "up"
            down <- smallButton (subtract 1) "down"
            return (up `mappend` down)

If you've been hanging around with monad hipsters, you'll know that we can write this definition more simply:

upDown = liftM2 mappend (smallButton (+ 1)        "up")
	                (smallButton (subtract 1) "down")

Personally, I'm on an Applicative kick lately, so I prefer liftA2 in place of liftM2.

Still more sleekly, let's hide the liftM2 (or liftA2) by using the Monoid (UI o) instance, which holds whenever Monoid o.

upDown = smallButton (+ 1)        "up"   `mappend`
	 smallButton (subtract 1) "down"

To finish the counter, use the accumR function, which makes a source from an initial value and an function-valued event. The source begins as the initial value and grows by applying the functions generated by the event.

accumR :: a -> UI (Event (a -> a)) -> UI (Source a)

counter :: UI ()
counter = title "Counter" $ fromLeft $
          do e <- upDown
             showDisplay (0 `accumR` e)

Calculator

The second event example is a calculator, as taken from "Lightweight GUIs for Functional Programming".

Calc.png

The basic structure of this example is just like the previous one. Each key has a function-valued event, and the keys are combined (visually and semantically) using mappend.

First a single key. For variety, we'll postpone interpreting the key's event as a function.

key :: Char -> UIE Char
key c = button' c [c]

We'll combine keys with the help of a friend of concatMap:

mconcatMap :: Monoid b => (a -> b) -> [a] -> b
mconcatMap f = mconcat . map f

With this helper, it's especially easy to turn several keys into a row and several rows into a keyboard.

row :: [Char] -> UIE Char
row = fromLeft . mconcatMap key

rows :: [[Char]] -> UIE Char
rows = fromTop . mconcatMap row

calcKeys :: UIE Char
calcKeys =  rows [ "123+"
                 , "456-"
                 , "789*"
                 , "C0=/" ]

Next, let's turn calcKeys's character-valued event into a function-valued event. While the state of the counter was a single number, the calculator state is a little more complicated. It consists of a number being formed and a continuation.

type CState = (Int, Int -> Int)

startCS :: CState
startCS = (0, id)

Keyboard characters have interpretations as state transitions.

cmd :: Char -> CState -> CState
cmd 'C' _                 = startCS
cmd '=' (d,k)             = (k d, const (k d))
cmd  c  (d,k) | isDigit c = (10*d + ord c - ord '0', k)
              | otherwise = (0, op c (k d))

op :: Char -> Int -> Int -> Int
op c = fromJust (lookup c ops)
 where
   ops :: [(Char, Binop Int)]
   ops = [('+',(+)), ('-',(-)), ('*',(*)), ('/',div)]

To compute the (reactive) value, from a key-generating event, accumulate transitions, starting with the initial state, and extract the value.

compCalc :: Event Char -> Source Int
compCalc key = fmap fst (startCS `accumR` fmap cmd key)

Show the result:

showCalc :: Event Char -> UI ()
showCalc = title "result" . showDisplay . compCalc

The whole calculator then snaps together:

calc :: UI ()
calc = title "Calculator" $ calcKeys >>= showCalc

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.

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.