[Haskell-cafe] Automatic liftIO or how to write this shorter?

Alexander V Vershilov alexander.vershilov at gmail.com
Sun May 10 15:57:26 UTC 2015


Hello, Gleb.

On 10 May 2015 at 17:41, Gleb Popov <6yearold at gmail.com> wrote:
>
>
> On Sat, May 9, 2015 at 12:54 AM, Alexander V Vershilov
> <alexander.vershilov at gmail.com> wrote:
>>
>> Hi, Gleb.
>>
>> Assuming that you already in IO, and don't want to use lift or liftIO
>> to lift actions into another stack level, you can choose one of the
>> following:
>>
>> 1. Create a module with lifted operations for all operations in the
>> framework. Then by the cost of some boilerplate code you'll have
>> a framework that could be used in any MonadBaseControl.
>
>
> I'd go this way for bindings library itself, but i'm wonder why bindings to
> other toolkits use plain IO.

Quite possiblly this will be good solution here. I can't speak for all
developers,
but I can imagine following reasons:

a. laziness, c2hs or hsc2hs provides a way to create bindings in IO,
so you have those for free and in many cases you are not interested
in generalization.

b. bindings author wants to keep 2 layers anyway, one for bindings itself
in IO and another - safe highlevel wrapper with a number of utility functions,
that make bindings easy to use in functional way. Then generalization is not
required

c. developer think that using monad-control is too scary to use (not
applicable to
generalization to MonadIO)

d. bindings have incorrect MonadBaseControl instance (very rare situation,
that could happen if you use forkIO and your state depends on the process
where you are running action, or compicated resource handling).
(not applicable to generalization to MonadIO)

Indeed there can be other reasons

>
>>
>> 2. Another way is to introduce concurrent primitives that will allow
>> you to 'log' events. Here is an incomplete sketch:
>>
>> data ConfigUI = CUI { setText :: Text -> IO (),  setAnotherText ::
>> Text -> IO () }
>>
>> defCUI = ...
>>
>> newtype LogRef a = LV (IORef (Endo a))
>>
>> newLog  :: IO (LogRef a)
>> newLog = LV <$> newIORef id
>>
>> writeLog :: LogRef a -> (a -> a) -> IO ()
>> writeLog (LV r) f = modifyIORef r (\x -> x <> Endo f)
>>
>> applyLog :: LogRef a -> a -> IO a
>> applyLog (LV r) f = ($) <$> fmap appEndo (readIORef r)  <*>  pure f
>>
>> withLog ::  a -> (LogRef a -> IO b) -> IO (a,b)
>> withLog f v = newLog >>= \l -> f l >>= liftM2 (,) (applyLog lg v)
>>
>> configureConfigUI = do
>>      (cui, a) <- withLog defCUI $ \lg -> do
>>                         ....
>>                         writeLog (\x -> x{setText = entrySet e})
>
>
> This is, basically, a reimplementation of Writer monad functionality using
> mutable variables in IO. I've also come up with this, but was hoping to
> somehow reuse existing Writer monad.

Yes it is, except the fact that you can reimplement stack of writers using
single IO layer. But it gives you an ability to implement configuration in
a composable way without changing bindings, or writing wrappers, so I had
to mention this path.

>>
>> There is a big window for solutions that are using mutable references
>> to log events in IO monad. Each with it's own pros and cons.
>>
>> Hope it helps
>>
>> --
>> Alexander
>>
>> On 8 May 2015 at 14:20, Gleb Popov <6yearold at gmail.com> wrote:
>> > Hello haskell-cafe@
>> >
>> > I'm writing a GUI app in Haskell and bindings to the widget toolkit i'm
>> > using in parallel. These bindings are very simple and all its functions
>> > have
>> > return type (IO something).
>> >
>> > So far so good, i wrote the following code to create an config window:
>> >
>> > createConfigUI root = do
>> >     box <- Box.add root
>> >
>> >     -- first field
>> >     addToPackEnd box =<< do
>> >         f <- Fr.add box
>> >         setPartText f Nothing "E-mail"
>> >         setPartContent f Nothing =<< do
>> >             box <- Box.add box
>> >
>> >             addToPackEnd box =<< do
>> >                 e <- Ent.add box
>> >                 Ent.singleLineSet e True
>> >                 -- Here
>> >                 onEvent "changed,user" e $ do
>> >                      reactOnUserInput e
>> >                 objectShow e
>> >                 return e
>> >
>> >             objectShow box
>> >             return box
>> >
>> >         objectShow f
>> >         return f
>> >
>> >     -- next field
>> >     addToPackEnd box =<< do
>> >         ...
>> >
>> > Initially, i was quite satisfied with flipped bind use for creating UI
>> > elements and arranging them. Nested do scopes allow copypasting code
>> > without
>> > renaming variables and also provide some visual representation on widget
>> > hierarchy.
>> >
>> > But at some point i need to return some stuff from some inner do block
>> > into
>> > outmost. For example, at the line with comment "Here" i defined
>> >
>> > let setText t = entrySet e t
>> >
>> > and wanted to return it from whole createConfigUI action. Moreover,
>> > createConfigUI have much more fields, for each of them i want to do the
>> > same.
>> >
>> > My initial thought was to wrap everything with runWriter and just call
>> >
>> > tell setText
>> >
>> > wherever i want to gather all setter functions into a list, but i can't
>> > do
>> > this because i would need to put liftIO before every IO action all over
>> > the
>> > place.
>> >
>> > If only there was i way to turn an (IO a) into (MonadIO m => m a), it
>> > would
>> > be easy.
>> >
>> > Another solution is to make my bindings return (MonadIO m => m a). This
>> > would be equal effort of plugging liftIO's everywhere, but at least it
>> > would
>> > be hidden from user of bindings. I'd gone this way, but looked at gtk
>> > bindings first and found that (IO a) is used there.
>> >
>> > So, my questions are:
>> >
>> > 1. What would you recommend in my situation? Is it possible yield values
>> > from inner do blocks into outer without much hassle?
>> > 2. If there is nothing wrong with switching bindings from (IO a) to
>> > MonadIO
>> > typeclass, why not to do this for gtk, wxWidgets and nearly every FFI
>> > binding?
>> >
>> > Thanks in advance.
>> >
>> > _______________________________________________
>> > Haskell-Cafe mailing list
>> > Haskell-Cafe at haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> >
>>
>>
>>
>> --
>> Alexander
>
>



-- 
Alexander


More information about the Haskell-Cafe mailing list