I'm trying to design a GUI library -- a design question

Hi all, I'm designing a ncurses based GUI library. I'm calling smallest GUI elements "widgets". A widget can have internal state of any type. Let's call this type `s`. I want to be able to have something like this:
data Widget s = Widget { handleKey :: Key -> s -> s , draw :: Int -> Int -> Int -> Int -> IO () , getFocus :: s -> s , loseFocus :: s -> s -- more methods may be added in the future }
I also want to be able to have container types like this:
data Container = Container [Widget s]
but obviously this does not work because widgets may have different types of states. So problem I'm trying to solve here is that I should somehow abstract internal state used in a Widget but still be able to keep track of that state so that I can pass it to methods in sequential invocations of that methods. Also, once I have a container like this, updating widget states would become a problem. I'd have to somehow keep all those states like:
data Container = Container [Widget] [WidgetState]
or
data Container = Container [(Widget, WidgetState)]
and then manually pass state to widgets when calling methods, and update the list using return values of methods. In a sense I'm like trying to emulate something like closures with mutable closed-over data in impure languages. I think one way to have a similar effect is to use closures with closed-over IORefs. Then I could modify that state but then I'd need to have methods with types `IO ()`. I want to have more "precise" types. i.e. IO is a lot more general than what I'd like to have as my widget methods. (side effect of a widget should be limited with changes in it's internal state) Sorry for badly organized post, I'm a bit tired right now and I hope my points are clear. I'm trying to figure out Haskell way of doing something like this, without going into IO world. Ideas/suggestions would be appreciated. Thanks, --- Ömer Sinan Ağacan http://osa1.net

Hi Ömer,
In a sense I'm like trying to emulate something like closures with mutable closed-over data in impure languages.
One way is to keep the specific data completely out of the Widget and use a closure to hold the data: data Widget = Widget { handleKey :: Key -> Widget , draw :: Int -> Int -> Int -> Int -> IO () , getFocus :: Widget , loseFocus :: Widget } someWidget :: SomeWidgetData -> Widget someWidget dat = Widget { handleKey = \key -> case key of 'A' -> someWidget $ dat { ... } ; ... , draw = \x y w h -> ... , getFocus = someWidget $ dat { focus = True } , loseFocus = someWidget $ dat { focus = False } } Greetings, Daniel

Hi Daniel,
This won't work. Let's say there has been two keypresses and I called
handleKey two times. First time it updates the `dat` and returns it
but how can I pass that updated `dat` object to the same function in
second invocation?
---
Ömer Sinan Ağacan
http://osa1.net
2014-03-02 23:38 GMT+02:00 Daniel Trstenjak
Hi Ömer,
In a sense I'm like trying to emulate something like closures with mutable closed-over data in impure languages.
One way is to keep the specific data completely out of the Widget and use a closure to hold the data:
data Widget = Widget { handleKey :: Key -> Widget , draw :: Int -> Int -> Int -> Int -> IO () , getFocus :: Widget , loseFocus :: Widget }
someWidget :: SomeWidgetData -> Widget someWidget dat = Widget { handleKey = \key -> case key of 'A' -> someWidget $ dat { ... } ; ... , draw = \x y w h -> ... , getFocus = someWidget $ dat { focus = True } , loseFocus = someWidget $ dat { focus = False } }
Greetings, Daniel _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Ömer, On Mon, Mar 03, 2014 at 09:50:19AM +0200, Ömer Sinan Ağacan wrote:
This won't work. Let's say there has been two keypresses and I called handleKey two times. First time it updates the `dat` and returns it but how can I pass that updated `dat` object to the same function in second invocation?
If you call 'handleKey', then it returns a new Widget with a new 'handleKey' function having a closure over the modified 'dat'. data Counter = Counter { increase :: Counter , draw :: IO () } someCounter :: Int -> Counter someCounter count = Counter { increase = someCounter $ count + 1 , draw = print count } *Main> let c = someCounter 0 *Main> draw c 0 *Main> let c' = increase someCounter *Main> draw c' 1 Greetings, Daniel

*Main> let c = someCounter 0 *Main> draw c 0 *Main> let c' = increase someCounter *Main> draw c' 1
Sorry, the example should have been: *Main> let c = someCounter 0 *Main> draw c 0 *Main> let c' = increase c *Main> draw c' 1 Greetings, Daniel

Ops, sorry. I misunderstand your code. Now that looks like solving my problem of updating widgets, and maybe I can use Data.Map.Map to keep widgets and update them when methods are called. Now this works but that explicit state updating and passing is not ideal for me. I know I can always hide that kind of things behind a state monad:
data Program = Program { ... , widgets :: (Map Int Widget, Int) , ... }
handleKey' :: Key -> State Program () handleKey' key = do programState@Program{(widgets, focusIdx)=widgets} <- get let widget = fromJust $ lookup focusIdx widgets widget' = handlekey widget key
put programState{widgets=(M.insert focusIdx widget', focusIdx)}
and I can even create a typeclass like `HasWidgets` which provides required methods for updating widget states and that would be even more flexible:
{-# LANGUAGE PackageImports, MultiParamTypeClasses, FlexibleInstance #-}
import "mtl" Control.Monad.State import qualified Data.Map as M import Data.Maybe
type Key = Int type Widget = Int -- placeholder type FocusIdx = Int
data Program = Program { widgets :: (M.Map Int Int, Int) }
class HasWidgets s where getWidgets :: s -> (M.Map Int Widget, FocusIdx) updateWidgets :: (M.Map Int Widget, FocusIdx) -> s -> s
class (MonadState s m, HasWidgets s) => Widgets s m where handleKey_ :: Key -> m ()
instance HasWidgets Program where getWidgets = widgets updateWidgets w p = p{widgets=w}
instance Monad m => Widgets Program (StateT Program m) where handleKey_ key = do programState@Program{widgets=(widgets, focusIdx)} <- get let w = fromJust $ M.lookup focusIdx widgets w' = undefined -- just call handleKey method of widget `w` put programState{widgets=(M.insert focusIdx w' widgets, focusIdx)}
test :: State Program () test = do programState@Program{widgets=(widgets, focusIdx)} <- get return ()
... but is there a better way to do this? Maybe by using Lens(I'm not
sure if something like that makes sense -- this just came to my mind
because all I do here is to do nested record updates, which as far as
I know where Lens shines) ?
---
Ömer Sinan Ağacan
http://osa1.net
2014-03-03 10:10 GMT+02:00 Daniel Trstenjak
*Main> let c = someCounter 0 *Main> draw c 0 *Main> let c' = increase someCounter *Main> draw c' 1
Sorry, the example should have been:
*Main> let c = someCounter 0 *Main> draw c 0 *Main> let c' = increase c *Main> draw c' 1
Greetings, Daniel _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Again, sorry, just pasted wrong code, correct version should be:
{-# LANGUAGE PackageImports, MultiParamTypeClasses, FlexibleInstances, FlexibleContexts #-}
import "mtl" Control.Monad.State import "mtl" Control.Monad.Identity import qualified Data.Map as M import Data.Maybe
type Key = Int type Widget = Int -- placeholder type FocusIdx = Int
data Program = Program { widgets :: (M.Map Int Int, Int) }
class HasWidgets s where getWidgets :: s -> (M.Map Int Widget, FocusIdx) updateWidgets :: (M.Map Int Widget, FocusIdx) -> s -> s
instance HasWidgets Program where getWidgets p = widgets p updateWidgets w p = p{widgets=w}
handleKey :: (MonadState s m, HasWidgets s) => Key -> m () handleKey key = do p <- get let (widgets, focusIdx) = getWidgets p w = fromJust $ M.lookup focusIdx widgets w' = undefined -- just update the widget put $ updateWidgets (M.insert focusIdx w' widgets, focusIdx) p
test :: StateT Program Identity () test = do handleKey undefined return ()
---
Ömer Sinan Ağacan
http://osa1.net
2014-03-03 11:17 GMT+02:00 Ömer Sinan Ağacan
Ops, sorry. I misunderstand your code. Now that looks like solving my problem of updating widgets, and maybe I can use Data.Map.Map to keep widgets and update them when methods are called.
Now this works but that explicit state updating and passing is not ideal for me. I know I can always hide that kind of things behind a state monad:
data Program = Program { ... , widgets :: (Map Int Widget, Int) , ... }
handleKey' :: Key -> State Program () handleKey' key = do programState@Program{(widgets, focusIdx)=widgets} <- get let widget = fromJust $ lookup focusIdx widgets widget' = handlekey widget key
put programState{widgets=(M.insert focusIdx widget', focusIdx)}
and I can even create a typeclass like `HasWidgets` which provides required methods for updating widget states and that would be even more flexible:
{-# LANGUAGE PackageImports, MultiParamTypeClasses, FlexibleInstance #-}
import "mtl" Control.Monad.State import qualified Data.Map as M import Data.Maybe
type Key = Int type Widget = Int -- placeholder type FocusIdx = Int
data Program = Program { widgets :: (M.Map Int Int, Int) }
class HasWidgets s where getWidgets :: s -> (M.Map Int Widget, FocusIdx) updateWidgets :: (M.Map Int Widget, FocusIdx) -> s -> s
class (MonadState s m, HasWidgets s) => Widgets s m where handleKey_ :: Key -> m ()
instance HasWidgets Program where getWidgets = widgets updateWidgets w p = p{widgets=w}
instance Monad m => Widgets Program (StateT Program m) where handleKey_ key = do programState@Program{widgets=(widgets, focusIdx)} <- get let w = fromJust $ M.lookup focusIdx widgets w' = undefined -- just call handleKey method of widget `w` put programState{widgets=(M.insert focusIdx w' widgets, focusIdx)}
test :: State Program () test = do programState@Program{widgets=(widgets, focusIdx)} <- get return ()
... but is there a better way to do this? Maybe by using Lens(I'm not sure if something like that makes sense -- this just came to my mind because all I do here is to do nested record updates, which as far as I know where Lens shines) ?
--- Ömer Sinan Ağacan http://osa1.net
2014-03-03 10:10 GMT+02:00 Daniel Trstenjak
: *Main> let c = someCounter 0 *Main> draw c 0 *Main> let c' = increase someCounter *Main> draw c' 1
Sorry, the example should have been:
*Main> let c = someCounter 0 *Main> draw c 0 *Main> let c' = increase c *Main> draw c' 1
Greetings, Daniel _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Ömer, I don't think that you need the 'HasWidgets' class, it really doesn't give you a lot. Something like a function 'withFocused' would be a lot more useful: withFocused :: (Widget -> Widget) -> State Program () Greetings, Daniel

I think HasWidgets is useful because when focus is moved to another
widget, I somehow need to find the widget that just got the focus in
collection of widgets.. So I need to somehow search in widget map.
I need a typeclass because I may have different types of widget
containers and I want to be able to update them uniformly.
---
Ömer Sinan Ağacan
http://osa1.net
2014-03-03 12:14 GMT+02:00 Daniel Trstenjak
Hi Ömer,
I don't think that you need the 'HasWidgets' class, it really doesn't give you a lot. Something like a function 'withFocused' would be a lot more useful:
withFocused :: (Widget -> Widget) -> State Program ()
Greetings, Daniel _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Ömer,
I don't think that you need the 'HasWidgets' class, it really doesn't give you a lot. Something like a function 'withFocused' would be a lot more useful:
withFocused :: (Widget -> Widget) -> State Program ()
Greetings, Daniel _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
This looks like a use case for a lens to me.
focused :: Lens' Program Widget over focused :: (Widget -> Widget) -> Program -> Program
(focused %=) :: MonadState Program m => (Widget -> Widget) -> m () zoom focused :: (MonadState Widget m, MonadState Program n) => m a -> n a

Hi Ömer
A bit tangential, but you might find looking at Wolfram Kahl and his
co-author's "Editor combinators" helpful:
http://www.cas.mcmaster.ca/~kahl/Publications/TR/2000-01/
As you are using records to encapsulate functional "objects", your
code strongly reminded me of editor combinators.
Best wishes
Stephen
On 2 March 2014 19:54, Ömer Sinan Ağacan
Hi all,
I'm designing a ncurses based GUI library.
I'm calling smallest GUI elements "widgets".
A widget can have internal state of any type. Let's call this type `s`. I want to be able to have something like this:
data Widget s = Widget { handleKey :: Key -> s -> s , draw :: Int -> Int -> Int -> Int -> IO () , getFocus :: s -> s , loseFocus :: s -> s -- more methods may be added in the future }
I also want to be able to have container types like this:
data Container = Container [Widget s]
but obviously this does not work because widgets may have different types of states.
So problem I'm trying to solve here is that I should somehow abstract internal state used in a Widget but still be able to keep track of that state so that I can pass it to methods in sequential invocations of that methods.
Also, once I have a container like this, updating widget states would become a problem. I'd have to somehow keep all those states like:
data Container = Container [Widget] [WidgetState]
or
data Container = Container [(Widget, WidgetState)]
and then manually pass state to widgets when calling methods, and update the list using return values of methods.
In a sense I'm like trying to emulate something like closures with mutable closed-over data in impure languages.
I think one way to have a similar effect is to use closures with closed-over IORefs. Then I could modify that state but then I'd need to have methods with types `IO ()`. I want to have more "precise" types. i.e. IO is a lot more general than what I'd like to have as my widget methods. (side effect of a widget should be limited with changes in it's internal state)
Sorry for badly organized post, I'm a bit tired right now and I hope my points are clear. I'm trying to figure out Haskell way of doing something like this, without going into IO world. Ideas/suggestions would be appreciated.
Thanks,
--- Ömer Sinan Ağacan http://osa1.net _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Daniel Trstenjak
-
Niklas Haas
-
Stephen Tetley
-
Ömer Sinan Ağacan