[Haskell-cafe] Idea for a very simple GUI llibrary
Keith Holman
holmak at gmail.com
Sun Nov 22 22:18:12 EST 2009
You should also check out Fudgets and "Tangible Functional
Programming." Fudgets is a really old Haskell UI library concept;
Tangible FP is a recent Google talk about a UI library inspired by
Haskell types.
2009/11/22 Luke Palmer <lrpalmer at gmail.com>:
> Nice idea. I will try it if you write runGUI :-)
>
> This is an imperative style library. For more Haskellian GUI library
> ideas, see Fruit (http://www.haskell.org/fruit/) and TVs
> (http://www.haskell.org/haskellwiki/TV). They may not pass the
> "builds" constraint :-P
>
> Luke
>
> 2009/11/22 Maurício CA <mauricio.antunes at gmail.com>:
>> Hi,
>>
>> Here is a sketch for a library with these properties:
>>
>> -> Easy to test. All Haskell code can be tested in a text
>> terminal. Also, testing code that uses the library can also be
>> done without using a GUI.
>>
>> -> Extremely easy to document and use.
>>
>> -> Not even close to Gtk2hs power, but enough for small
>> applications.
>>
>> -> Could be the first GUI to build on hackage :)
>>
>> What we need is:
>>
>> -> MyState. A user suplied type for application state.
>>
>> -> WidId. A user suplied type for widget identifiers.
>>
>> -> Gui wi. A type capable of describing an interface with all of
>> its state. It's an instance of Eq.
>>
>> -> Event wi. A type for events.
>>
>> -> Prop. A type for properties than can related to a WidId.
>>
>> Running an application would be like this:
>>
>> main = runGUI
>> initState -- An initial MyState.
>> event -- :: MyState -> DiffTime -> Event WidId -> MyState
>> props -- :: WidId -> [Prop]
>> action -- :: MyState -> DiffTime -> IO (Maybe (MyState,Gui
>> WidId))
>> timeout -- :: DiffTime
>>
>> DiffTime parameters for callbacks are always the time elapsed
>> since application started.
>>
>> From initState and event, the implementation of runGUI can save a
>> state that optionally changes with time.
>>
>> From props, it can get details on what to present in widgets
>> associated with a WidId (selected state, picture to draw etc.).
>>
>> action presents a chance for using IO, and optionally change state
>> and GUI description.
>>
>> timeout is the maximum time runGUI implementation is allowed to
>> wait between calls to action.
>>
>> Examples for those types:
>>
>> newtype MyState = {
>> lastUpdate :: DiffTime,
>> builtGui :: Bool,
>> earthCoordinates :: (Double,Double),
>> map :: SVG,
>> ...
>> }
>>
>> data WidId = XCoord | YCoord | MapWindow | ReloadButton ...
>>
>> data Gui widid = TitleWindow (Gui widid)
>> | Tabs [(String,Gui widid)]
>> | PressButton String widid
>> | Selection [String] widid
>> | ...
>> deriving Eq
>> {-
>> Eq is needed by runGUI to detect if GUI has
>> changed after the last call to action.
>> -}
>>
>> data Event widid = ButtonPressed widid
>> | FileSelected String widid
>> | OptionSelected String widid
>> | ...
>>
>> data Prop widid = Active Bool
>> | Text String
>> | Draw SVG
>> | ...
>>
>> I believe this can represent most kinds of simple applications,
>> and be efficient enough for practical use.
>>
>> It's interesting that all of this can be designed, implemented and
>> tested independent of runGUI implementation. Actually, if you want
>> a pet project and want to write and design the Haskell part, I may
>> probably be able to write runGUI for you :)
>>
>> Best,
>> Maurício
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list