[Haskell-cafe] I'm trying to design a GUI library -- a design question
Ömer Sinan Ağacan
omeragacan at gmail.com
Mon Mar 3 09:17:30 UTC 2014
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 at 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 at 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 at 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 <daniel.trstenjak at gmail.com>:
>
>> *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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list