[xmonad] Catching exceptions from getWindowAttributes

Daniel Wagner dmwit at dmwit.com
Wed Jun 22 19:55:38 UTC 2016


The simplest thing will be to wrap just the call to `getWindowAttributes`,
if that's the one you expect to fail. It is not conveniently possible to
wrap `X` actions; so instead, something like

    withDisplay $ \d -> do
      ws <- gets windowset
      ewa <- io $ try (getWindowAttributes d w)
      case ewa of
          Left e -> io (putStrLn "HELP! do something!")
          Right wa -> do
              let bw = (fromIntegral . wa_border_width) wa
              {- ... etc. -}

~d

On Sun, Jun 12, 2016 at 10:24 AM, Adam Sjøgren <asjo at koldfront.dk> wrote:

> I am trying to modify xmonad to handle exceptions thrown in
> getWindowAttributes.
>
> Since I am still copy/paste-coding, I need some help.
>
> Take a function like this, which I have seen crashes in (especially when
> using Gimp):
>
>   floatLocation :: Window -> X (ScreenId, W.RationalRect)
>   floatLocation w = withDisplay $ \d -> do
>       ws <- gets windowset
>       wa <- io $ getWindowAttributes d w
>       let bw = (fromIntegral . wa_border_width) wa
>       sc <- fromMaybe (W.current ws) <$> pointScreen (fi $ wa_x wa) (fi $
> wa_y wa)
>
>       let sr = screenRect . W.screenDetail $ sc
>           rr = W.RationalRect ((fi (wa_x wa) - fi (rect_x sr)) % fi
> (rect_width sr))
>                               ((fi (wa_y wa) - fi (rect_y sr)) % fi
> (rect_height sr))
>                               (fi (wa_width  wa + bw*2) % fi (rect_width
> sr))
>                               (fi (wa_height wa + bw*2) % fi (rect_height
> sr))
>
>       return (W.screen sc, rr)
>     where fi x = fromIntegral x
>
> I somehow need to wrap the code from getWindowAttributes and on, in
> something that "does the right thing" if gWA throws an exception.
>
> In other places, I have done something like this:
>
>   sendConfigureEvent :: Display -> XEventPtr -> Window -> Event -> IO ()
>   sendConfigureEvent dpy ev w e = C.handle (\(C.SomeException _) ->
> putStrLn "sendConfigureEvent failed") $ do
>                    wa <- io $ getWindowAttributes dpy w
>                    setEventType ev configureNotify
>                    setConfigureEvent ev w w
>                        (wa_x wa) (wa_y wa) (wa_width wa)
>                        (wa_height wa) (ev_border_width e) none
> (wa_override_redirect wa)
>                    sendEvent dpy w False 0 ev
>
> which works, but in floatLocation the type is X and not IO, and ...
> well, what's a boy to do?
>
>
>   Best regards,
>
>     Adam
>
> --
>  "It's part of our policy not to be taken seriously"          Adam Sjøgren
>                                                          asjo at koldfront.dk
>
> _______________________________________________
> xmonad mailing list
> xmonad at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/xmonad/attachments/20160622/7971bfd9/attachment.html>


More information about the xmonad mailing list