[xmonad] erratic panel unhide in xmonad + xfce

Brandon Allbery allbery.b at gmail.com
Wed Nov 29 21:37:53 UTC 2017


For several years now, xfce4-panel has required ManageDocks' docksEventHook
to function properly.

Also note that, from xmonad 0.12 on, you need more than manageDocks and
avoidStruts in *all* cases: you need both docksEventHook and (as of 0.13)
docksStartupHook as well. Starting in 0.13 we recommend using the new
"docks" combinator instead of the individual hooks. (You would compose it
with the "ewmh" combinator in your config. Speaking of which... why do you
explicitly use ewmhDesktopsLogHook and ewmhDesktopsEventHook? "ewmh"
already adds them. (Fullscreen is not added automatically, because you
might choose to use XMonad.Layout.Fullscreen's fullscreen event hook
instead which provides more control by communicating with its layout hook
instead of just making the window a full screen float.)

On Wed, Nov 29, 2017 at 5:03 AM, Tom Hirschowitz <
tom.hirschowitz at univ-smb.fr> wrote:

>
> Dear all,
>
> I'm using xfce4 with xmonad and panel autohide. The problem is that,
> depending on which windows are present, the panel sometimes does not
> unhide. In my experience, it only unhides to cover windows that were
> spawned after it. E.g., if it doesn't unhide over a given window and I
> restart it, then it does unhide fine.
>
> Snippets of my xmonad.hs are included below.
>
> Does anyone have an idea how to sort this out?
>
> Thanks,
> Tom
>
> conf = ewmh xfceConfig
>         { manageHook        = pbManageHook <+> myManageHook
>                                            <+> manageDocks
>                                            <+> manageHook xfceConfig
>         , layoutHook        = myLayoutHook
>         , handleEventHook   = ewmhDesktopsEventHook <+> fullscreenEventHook
>         , borderWidth       = 4
>         , focusedBorderColor= "#80c0ff"
>         , normalBorderColor = "#13294e"
>         , workspaces        = map show [1 .. 9 :: Int]
>         , modMask           = mod4Mask
>         , keys              = myKeys
>         , terminal          = "xfce4-terminal"
>          }
>
> -- Main --
> main :: IO ()
> main =
>     xmonad $ conf
>         { startupHook       = startupHook conf
>                             >> setWMName "LG3D" -- Java app focus fix
>         , logHook           =  ewmhDesktopsLogHook
>          }
>
> -- Layouts --
> myLayoutHook = desktopLayoutModifiers $ avoidStruts $ Full
>
> [...]
>
> -- ManageHook --
> pbManageHook :: ManageHook
> pbManageHook = composeAll $ concat
>     [ [ manageDocks ]
>     , [ manageHook defaultConfig ]
>     , [ isDialog --> doCenterFloat ]
>     , [ isFullscreen --> doFullFloat ]
>     , [ fmap not isDialog --> doF avoidMaster ]
>     ]
>
> [...]
>
> -- Helpers --
> -- avoidMaster:  Avoid the master window, but otherwise manage new windows
> normally
> avoidMaster :: W.StackSet i l a s sd -> W.StackSet i l a s sd
> avoidMaster = W.modify' $ \c -> case c of
>     W.Stack t [] (r:rs) -> W.Stack t [r] rs
>     otherwise           -> c
> _______________________________________________
> xmonad mailing list
> xmonad at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad
>



-- 
brandon s allbery kf8nh                               sine nomine associates
allbery.b at gmail.com                                  ballbery at sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad        http://sinenomine.net
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/xmonad/attachments/20171129/30417c2c/attachment.html>


More information about the xmonad mailing list