[xmonad] XMobar covered by display-1 main window

Zev Weiss zev at bewilderbeest.net
Thu Apr 5 16:28:28 UTC 2018


On Thu, Apr 05, 2018 at 10:39:20AM CDT, Peter Fitzgibbons wrote:
>HI Folks,
>I have 2 displays in portrait-mode, both 1200x1920.
>ghc 7.6.3
>xmonad 0.11
>xmobar 0.25
>
>I've been reading several-years-old and even recent google results on this
>issue.
>https://mail.haskell.org/pipermail/xmonad/2017-June/015266.html
>
>xmobar --dock made the dock display on main (in display 1), though the
>window is still full-screen, not giving space for the bar.
>
>Could any of you please describe to me how to:
>1) instruct main window to give space for the bar?
>(other workspaces work fine, only ws2(display-1) does this.
>2) display xmobar in both displays? (extra credit for separate bar contents
>-- not necessary)
>
>
>Your help is most kindly appreciated!
>-- 
>Peter Fitzgibbons
>(224) 307-9689

The lack-of-space problem I'm afraid I don't know much about, but 
regarding point number 2, I have something like that set up in my xmonad 
config roughly as follows -- I *think* this snippet contains all the 
relevant parts, though I may have missed something (and parts of it are 
likely not relevant to you)...I'm also not the most experienced 
Haskeller in the world, so there may be better/more-direct ways of 
achieving this, but: 

--- 8< ---

barKey :: XConfig t -> (KeyMask, KeySym)
barKey XConfig { modMask = modm } = (modm, xK_b)

wsWinTitle :: (LayoutClass layout a) => S.Workspace String (layout a) Window -> X String
wsWinTitle ws = case S.stack ws of
                  Nothing -> return "-"
                  Just stk -> fmap show $ getName $ S.focus stk

wsFormat t ws = unwords [S.tag ws, wrap "[" "]:" $ description $ S.layout ws, t]

getScreenDesc :: ScreenId -> X (Maybe String)
getScreenDesc sid = do
                      screens  <- (\w -> (S.current w):(S.visible w)) <$> gets windowset
                      let wsSids = [(ws, s) | S.Screen ws s _ <- screens]
                      wts <- mapM (\(ws, _) -> wsWinTitle ws) wsSids
                      let wtSids = zip wts wsSids
                      return $ listToMaybe [wsFormat wt ws | (wt, (ws, s)) <- wtSids, s == sid]

mkPP :: ScreenId -> PP
mkPP s = def { ppCurrent = no,
               ppVisible = no,
               ppHidden = no,
               ppTitle = no,
               ppSep = "",
               ppLayout = no,
               ppExtras = [getScreenDesc s] }
         where no = const ""

mkExtraPP :: ScreenId -> Handle -> PP
mkExtraPP s h = (mkPP s) { ppOutput = hPutStrLn h }

mkStatusBar scr = let barcmd = xbar scr
                  in statusBar barcmd (mkPP scr) barKey

xbar :: ScreenId -> String
xbar sid = let s = show (toInteger sid) in "xmobar -x " ++ s ++ " $HOME/.dotfiles/xmobarrc-" ++ s

numScreens = 3
mainScreen:extraScreens = take numScreens [0..]

main = do
         barpipes <- mapM spawnPipe (xbar <$> extraScreens)
         let screenbars = zip extraScreens barpipes
         let lhs = dynamicLogWithPP . uncurry mkExtraPP <$> screenbars
         let lh = foldl (>>) def lhs
         mkStatusBar mainScreen (ewmh zConf { logHook = lh }) >>= xmonad

--- >8 ---

Each xmobar instance uses its own separate config at 
~/.dotfiles/xmobbarrc-$NUMBER, each of which contains a StdinReader to 
display what xmonad sends it, plus whatever else is configured for that 
screen.

Zev



More information about the xmonad mailing list