Talk:Phooey
Getting Phooey to Run
This is very interesting. Getting this apparently simple proof of concept working is difficult for me. I've tried on Suse 10.2 and Windows XP. files I used on XP:
wxMSW-2.4.2-setup.zip
ghc-6-4-bld2.msi
wxhaskell-bin-msw2.4.2-ghc6.4-0.9.4-1.zip
The recommended wxwindows 2.4.2 requires a wxhaskell dependent on ghc640. The problem is that arrows require base >=2.0 I could update Cabal to 1.1.7 using darcs etc. But I find no instructions on how to update the base-1.0 which comes with GHC 6.4.0. Even with instructions I think it requires a C compiler or more?
I use WinXP, GHC 6.6, and wxWidgets 2.4.2. I compiled wxWidgets and wxHaskell from sources. Conal 23:47, 20 February 2007 (UTC)
Yes, this looks nice; I can report partiual success on linux. I was able to build using ghc6.6 on Fedora 5, using wxGTK version 2.6.3 (built from source) and then wxHaskell. Phooey examples ran, however titles (window and panel) did not appear correctly, nor did text output, e.g. on the "shopping list" example the "total" field remains blank. On checking the wxHaskell demos, it seems the problem is in there. User:Djd 04:54, 14 May 2007
Thanks for the report. I expected wxHaskell to take care of cross-platform compatibility, but I guess not. Hm. Conal 17:26, 14 May 2007 (UTC)
- Just an update on this. On MacOS X, the slider stuff works, but the text widgets don't seem to notice any updates. Then again, I'm also using wxWidgets 2.6 (and you're using 2.4). Maybe it's related to that and not the cross-platform stuff. We'll need somebody on Windows to test in order to be sure. -- kowey 22:27, 21 March 2008 (UTC)
I got phooey working on Ubuntu 8.04 by compiling wxhaskell against the standard libwxgtk2.6-dev package. There are some problems, though. I tried compiling the standard shopping list, monadic style example with
- ghc -package phoeey test.hs -o test
The GUI shows up, but dragging the sliders doesn't cause the "total" field to be updated. If I instead do
- runhaskell test.hs
everything works fine, but the application crashes frequently. --Auders 13:33, 25 October 2008 (UTC)
Adding additional compound widgets
Hi Conal, I am looking to extend Phooey to include a record editor widget, a record list widget, as well as a tree widget. The first two being based on Grid. This is so that I can continue my work on HGene. i.e. the record editor would allow users to edit Person records, the list widget would show the children of a person and the tree to allow them to view a tree of Persons. For the editor I have so far (in the imperative world so far)
-- List of field name, field getter, field setter
type EditorProps a = [ ( String, a -> String, a -> String -> a )]
-- Create an editor for 'a'.
-- Returns a grid, a means of reseting the record being edited, an extractor and notifier
mkEditor :: Show a => Window b -> EditorProps a -> a -> IO ( (Grid (), a -> IO(), IO a, IO () -> IO () ))
Is this in line with where you think Phooey can go and is this on the right track? Mark_Wassell
- Hi Mark. Your design looks good to me. I'd love so hear/see how it goes. Conal 15:39, 14 August 2007 (UTC)
- Hi Conal, Take a look at Extending Phooey for what I have so far. Mark_Wassell
- Wonderful! Hey, I see you're using Phooey's Monad interface. Have you tried doing your extensions with the Applicative interface? I'm planning to eliminate the Monad & Arrow interfaces and just leave Applicative. I can instead keep Monad and continue to layer Applicative on top of it (
A.UI = M.UI `O` Source
), if there's value in doing so. Conal 14:53, 18 August 2007 (UTC)
- Wonderful! Hey, I see you're using Phooey's Monad interface. Have you tried doing your extensions with the Applicative interface? I'm planning to eliminate the Monad & Arrow interfaces and just leave Applicative. I can instead keep Monad and continue to layer Applicative on top of it (
- I see your UI is defined recursively (
mdo
), which works for the monadic interface, but not for the applicative one. I don't even know what the interface for would be for applicatives. Perhapsafix :: f (a -> a) -> f a
. Conal 16:07, 18 August 2007 (UTC)
- I see your UI is defined recursively (
Hi, My first reason for using Monad was wanting to avoid conceptual overload. I have now tried it and hit the following problems:
- Since A.UI includes Source, I cannot see a way of returning more than one source as I was previously doing. I would like to be able to return multiple sources from a widget.
- I also tried the following
uiapp pd = let pers = showTree pd
in ((editPerson pers) `iPair` (showChildren pd pers)) <**> showPerson
And get *two* occurrences of the tree, one above editPerson and one above showChildren. In the world of my example 'pers' is the selected Person in the tree and editPerson displays the property editor for the person and showChildren displays the list of children for the Person. (This is obviously not really the case as pers is a lot more).
This does raise the conceptual question of whether my GUI can actually be represented in the AF style. Thinking about tangible values etc, is there a function which when made visible would look like my GUI?
Having said all the above this isn't a show stopper - I am quite happy with Monadic style. Maybe I can get the benefits of both.
Mark_Wassell 09:38, 20 August 2007 (UTC)
Intermediate results and self-updating widgets
Hi Conal, I have been experimenting with Phooey for a little bit now. I think it is very cool how you separate the layout of elements and the wiring of which widgets affects other widgets, while keeping the library functional (as opposed to imperative). Thus, if I sound negative below it is just because I am playing the devils advocate.
There seem to be no easy way of representing intermediate results. For example, if you have apples, bananas, shovels, and spades. And you want to have two intermediate results, namely fruits and tools. I came up with the following program:
-- Have to make phantom1 & phantom2, otherwise the intermediate results are not shown. We also -- need to reference them from the last line in the UI-monad. basket :: UI (Source ()) basket = title "Shopping List" $ do a <- apples b <- bananas let fruitsTotal = liftA2 (+) a b phantom1 <- title "Fruit" $ showDisplay fruitsTotal c <- shovels d <- spades let toolsTotal = liftA2 (+) c d phantom2 <- title "Tools" $ showDisplay toolsTotal title "Basket" $ showDisplay $ liftA2 (+) fruitsTotal (liftA3 (const . const) toolsTotal phantom1 phantom2) -- The code below is not enough to show the intermediate results: -- title "Basket" $ showDisplay $ liftA2 (+) fruitsTotal toolsTotal apples, bananas, shovels, spades :: UI (Source Int) apples = title "apples" $ sl0 3 bananas = title "bananas" $ sl0 7 shovels = title "shovels" $ sl0 2 spades = title "spades" $ sl0 5
It seems to be more troublesome than it should be.
I was thinking that if we had an intermediate result widget defined as:
type IRWidget a = a -> Source a -> UI (Source a)
then we could make the basket program simpler. I have tried to do just that:
{-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -Wall #-} module Examples.IRWidget where import qualified Graphics.UI.WX as WX import Control.Applicative import Graphics.UI.Phooey.Monad import Control.DataDriven import Control.Monad.Writer import Graphics.UI.Phooey.Imperative import Control.Compose -- IR = Intermediate Result type IRWidget a = a -> Source a -> UI (Source a) run :: IO () run = runUI basket basket :: UI (Source ()) basket = title "Shopping List" $ do a <- apples b <- bananas fruits <- title "Fruit" $ showDisplayIR 0 (liftA2 (+) a b) c <- shovels d <- spades tools <- title "Tools" $ showDisplayIR 0 (liftA2 (+) c d) title "Basket" $ showDisplay $ liftA2 (+) fruits tools apples, bananas, shovels, spades :: UI (Source Int) apples = title "apples" $ sl0 3 bananas = title "bananas" $ sl0 7 shovels = title "shovels" $ sl0 2 spades = title "spades" $ sl0 5 sl0 :: IWidget Int sl0 = islider (0,10) -- An output widget, which also returns a value -- -- However, it unfortunately do not allow recursiveness. Could be usefull for creating a -- sorted list. irWidget :: (WX.Commanding widget, WX.Widget widget) => MkWidget widget a (IRWidget a) irWidget layf mkWid attr initial mySrc = mkWidget layf $ \ win -> do wid <- mkWid win [ attr WX.:= initial ] src <- commandSource wid attr return (wid, (src <* attachSink attr wid mySrc, mempty)) -- Copied from Graphics.UI.Phooey.Monad commandSource :: WX.Commanding widget => widget -- ^ widget -> WX.Attr widget a -- ^ attribute -> IO (Source a) commandSource wid attr = fmap (dd (WX.get wid attr)) (commandNews wid) -- Attaches a Source to an WX.Attr (attribute) attachSink :: WX.Attr w a -> w -> Control.Compose.O ((,) (News IO)) IO a -> DataDriven IO () attachSink attr wid src = joinDD (sink attr wid <$> src) -- Makes a sink from an attribute sink :: WX.Attr w a -> w -> a -> IO () sink attr wid x = WX.set wid [ attr WX.:= x ] -- Better if it did not use read, but in stead read directly from the attaches source, as it would -- 1) not require that (Read a) -- 2) no risk that the value was not-readable (which make a runtime error). It could be not -- readable if the user wrote something in the textEntry or if the initial value was bad. -- -- We should properly also get rid of the initial value. It should just get it from the source. showDisplayIR :: (Read a, Show a) => a -> Source a -> UI (Source a) showDisplayIR = irWidget WX.hfill WX.textEntry (WX.mapAttr read (\_ b -> show b) WX.text)
What do you think of this approach? Is this compatible with the idea behind Phooey?
Also, how would you do self-updating widgets? For example a list that sorted itself whenever the GUI-user added a new element to the list. One should be careful not to end up with eternal recursion.
Also mutually recursive widgets could be interesting. I realise that you do some recursion in your examples, but that is not to the value of the widgets, just to there "limits" (e.g. how low/high can the slider go).
Mads 15:16, 19 August 2007 (GMT)
Hi Mads. I'm delighted to hear about your experiments with Phooey. You definitely ran into an awkward spot, and I like your solution. Below is another solution and then an explanation and a change I'm already making, about which I'd like your feedback.
You're right that the displays have to be part of the return value to work. Here's a fairly direct way to accomplish that.
basket :: UI (Source ())
basket
= title "Shopping List" $
do a <- apples
b <- bananas
let fruitsTotal = liftA2 (+) a b
phantom1 <- title "Fruit" $ showDisplay fruitsTotal
c <- shovels
d <- spades
let toolsTotal = liftA2 (+) c d
phantom2 <- title "Tools" $ showDisplay toolsTotal
-- the grand total
phantom3 <- title "Basket" $ showDisplay $ liftA2 (+) fruitsTotal toolsTotal
-- and joing all of the displays together.
return $ phantom1 `mappend` phantom2 `mappend` phantom3
The problem is that a Source ()
is an important thing, so it must not be discarded. Since Phooey is a functional UI library, the displaying does not happen as a side-effect. Instead, the UI must yield the effect to be done, which is represent as Source ()
.
By the way, I wish (>>)
had a more restricted type, namely Monad m => m () -> m a -> m a
, so that it would be an error if one failed to make bindings like phantom1
above. Then at least the programmer would know s/he had to do something with the Source ()
.
Now for the API change. I want to make it more explicit yet that displaying returns something important and what is going on. Specifically, I want to use Source (IO ())
instead of Source ()
. I hope it's then clearer that a UI yields a time-varying effect, which is executed whenever it updates, rather than somehow happening. I like this change because it says what it means: a source of effects, not a source of ()
s.
Reactions?
I'm intrigued with your question on self-updating widgets, and I'm not sure I understand it. It's easy to put up a UI with input list and sorted output list, having the sort function re-run whenever the input list is edited. I'm guessing you mean something more than that, right?
Finally, I'm very curious about your comment for recursive widgets, beyond my contrived slider-bound examples. Do you have a concrete example in mind?
Cheers, Conal 04:27, 20 August 2007 (UTC)
BTW, here's another form:
tools = liftM2 (liftA2 (+)) shovels spades
basket :: UI (Source ())
basket = title "Shopping List" $
do f <- fruit
showFruit <- title "Fruit" $ showDisplay f
t <- tools
showTools <- title "Tools" $ showDisplay t
showBasket <- title "Basket" $ showDisplay $ liftA2 (+) f t
return $
showFruit `mappend` showTools `mappend` showBasket
Conal 04:48, 20 August 2007 (UTC)
and still another variation, using something like your "intermediate result" idea:
ir :: Show a => String -> UI (Source a) -> UI (Source a, Source ())
ir str ui = do x <- ui
showx <- title str $ showDisplay x
return (x,showx)
basket = title "Shopping List" $
do (f,showFruit) <- ir "Fruit" fruit
(t,showTools) <- ir "Tools" tools
showBasket <- title "Basket" $ showDisplay $ liftA2 (+) f t
return $
showFruit `mappend` showTools `mappend` showBasket
Conal 05:01, 20 August 2007 (UTC)
I just noticed something promising about these examples. The combination of returning pairs and then using mappend
on one of them looks just like what the writer monad hides. First, swap my pairs above,
ir :: Show a => String -> UI (Source a) -> UI (Source (),Source a)
ir str ui = do x <- ui
showx <- title str $ showDisplay x
return (showx,x)
basket = title "Shopping List" $
do (showFruit,f) <- ir "Fruit" fruit
(showTools,t) <- ir "Tools" tools
showBasket <- title "Basket" $ showDisplay $ liftA2 (+) f t
return $
showFruit `mappend` showTools `mappend` showBasket
If the UI monad were to incorporate a WriterT (Source ())
, then perhaps the pairs and mappend
s could vanish, and this example could come out looking like the following. (Note the lack of Source
in the type of basket
.)
basket :: UI ()
basket = title "Shopping List" $
do f <- ir "Fruit" fruit
t <- ir "Tools" tools
title "Basket" $ showDisplay $ liftA2 (+) f t
Hi Conal,
I think the solution using WriterT (Source ())
is very promising. I find it succinct and readable. And we do not risk forgetting to tie the Source ()
's to the output.
Cheers,
Mads 18:30, 20 August 2007 (UTC)
Thanks for the feedback, Mads.
Another thought: since each source is now used just once, this version may lend itself well to an AF (applicative functor) formulation.
basket :: UI ()
basket = title "Shopping List" $
title "Basket" $ showDisplay <**>
liftA2 (+) (ir "Fruit" fruit) (ir "Tools" tools)
One can go further, defining (for all AFs f
or just for some)
instance (Applicative f, Num a) => Num a where
(+) = liftA2 (+)
fromInteger = pure . fromInteger
-- ... more methods
-- ... more classes
(I've played this game several times. It works for most functions, but not (==)
etc.)
What can we do with ir
's definition? Messing about with the new monadic version,
(m >>= \ x -> g x >> return x)
== (m >>= g `mappend` return)
So
ir str ui = ui >>= (title str . showDisplay) `mappend` return
I don't see offhand how to define an AF version of ir
without slightly breaking through the AF UI abstraction.
BTW, did you see my request on your user page?
Conal 20:02, 20 August 2007 (UTC)
Hi Conal
I can see from your examples that my intermediate result type is not nearly as necessary as I first thought.
Regarding the list, I do mean more than you suggest. Or actually less! I do not want two list widgets, I only want one. Whenever the user adds an element to the list widget, the list should sort itself.
An example may be good here. Letýs imagine that we have a text-editor and the user should be able to set the tabulator settings. E.g. if you have [5, 17, 20] then the first time you hit tabulator the cursor will jump to position five, the second time to position 17, ...
We could have some code like:
tabulatorPreferences :: UI (Source ())
tabulatorPreferences
= title "Tabulator preferences" $
mdo tabulatorList <- makeIntegerListWidget $ liftA sort tabulatorList
-- note the recursive use of tabluatorList
...
But given the current implementation, I think this will result in an eternal recursion.
Another example of recursion could be the command history in a GUI for an interactive interpreter, like GHCi. Every time the user hits the execute button, the command history should have the command added. E.g. the command history must take three inputs: itself, the command, and a button. We could have code like below. Note that I am using a button below. I do not know if this is the best way to implement buttons. I did not give it much thought, as I just made the button for this example, not as a proposal for how to make buttons.
interactiveInterpreter :: UI (Source ())
interactiveInterpreter
= title " Interactive Interpreter " $
mdo let -- When the button has been presses (and a command executed)
-- we need to append the command to the history:
commandHistoryUpdate hist cmd ButtonPressed = hist ++ [cmd]
-- When the button has not been presses we just keep the history as it is:
commandHistoryUpdate hist _ ButtonNotPressed = hist
commandHistory <- makeListWidget $ liftA3 commandHistoryUpdate commandHistory command commandButton
command <- stringWidget ýý
commandButton <- mkButton ýExecuteý $ ...
return $ commandHistory `mappend` command `mappend` commandButton
data ButtonState = ButtonPressed
| ButtonNotPressed
-- |Returns a button which can be clicked.
mkButton :: String -> ... -> UI (Source ButtonState)
mkButton ... = ...
I hope I am making myself clear :) Otherwise please point it out and I will try to improve my explanation.
BTW, I do not really like my "design" of buttons above. I think it would be better, if buttons could "transmit" arbitrary values whenever they were pressed, and not just their state.
Cheers,
Mads 11:15, 20 August 2007 (UTC)