xmonad/xmonad

`XLookupColor` unexpectedly producing `BadValue`

geekosaur opened this issue · 26 comments

Problem Description

A user's config reproducibly uses a black pixel instead of the specified color value for normalFocusedColor. Any color value can be specified, including garbage.

The user's config produces a number of runtime errors of the form

xmonad: X11 error: BadValue (integer parameter out of range for operation), request code=91, error code=2

. I have traced this down to https://github.com/xmonad/xmonad/blob/master/src/XMonad/Operations.hs#L261

       pixel <- setPixelSolid . color_pixel . fst <$> allocNamedColor dpy (wa_colormap wa) color

where allocNamedColor (XAllocNamedColor) uses XLookupColor (X opcode 91) internally. Notably, XLookupColor is not supposed to produce BadValue according to the documentation or the protocol specification.

Steps to Reproduce

Using the attached configuration file, open a window. It is not necessary to open two windows to get one that is unfocused, as the new window will initially get normalBorderColor. (One copy of the above error will be output for each window on the visible workspace.)

Configuration File

This is not a minimal config file; I have yet to try to minimize or bisect it. I cannot reproduce it with my own config.

    -- Base
import XMonad
import System.Directory
import System.IO (hPutStrLn)
import System.Exit (exitSuccess)
import qualified XMonad.StackSet as W

    -- Actions
--import XMonad.Actions.MessageFeedback
import XMonad.Actions.CopyWindow
import XMonad.Actions.PerLayoutKeys
import XMonad.Actions.Navigation2D
import XMonad.Actions.CopyWindow (kill1)
import XMonad.Actions.CycleWS (Direction1D(..), moveTo, shiftTo, WSType(..), nextScreen, prevScreen)
import XMonad.Actions.GridSelect
import XMonad.Actions.MouseResize
import XMonad.Actions.Promote
import XMonad.Actions.RotSlaves (rotSlavesDown, rotAllDown)
import XMonad.Actions.WindowGo (runOrRaise)
import XMonad.Actions.WithAll (sinkAll, killAll)
import qualified XMonad.Actions.Search as S

    -- Data
import Data.Foldable
import Data.Ratio
import Data.Char (isSpace, toUpper)
import Data.Maybe (fromJust)
import Data.Monoid 
import Control.Monad (forM_, join)
import Data.Maybe (isJust)
import Data.Tree
import qualified Data.Map as M

    -- Hooks
import XMonad.Hooks.InsertPosition
import XMonad.Hooks.UrgencyHook
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.EwmhDesktops  -- for some fullscreen events, also for xcomposite in obs.
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers
import XMonad.Hooks.ServerMode
import XMonad.Hooks.SetWMName
import XMonad.Hooks.WorkspaceHistory

    -- Layouts
import XMonad.Layout.SubLayouts
import XMonad.Layout.Fullscreen
import XMonad.Layout.Master
import XMonad.Layout.Accordion
import XMonad.Layout.GridVariants (Grid(Grid))
import XMonad.Layout.SimplestFloat
import XMonad.Layout.Spiral
import XMonad.Layout.ResizableTile
import XMonad.Layout.Tabbed
import XMonad.Layout.ThreeColumns

    -- Layouts modifiers
import XMonad.Layout.Reflect
import XMonad.Layout.NoFrillsDecoration
import XMonad.Layout.LayoutModifier
import XMonad.Layout.LimitWindows (limitWindows, increaseLimit, decreaseLimit)
import XMonad.Layout.Magnifier
import XMonad.Layout.MultiToggle 
import XMonad.Layout.MultiToggle.Instances 
import XMonad.Layout.NoBorders
import XMonad.Layout.Renamed
import XMonad.Layout.Simplest
import XMonad.Layout.Spacing
import XMonad.Layout.SubLayouts
import XMonad.Layout.WindowArranger (windowArrange, WindowArrangerMsg(..))
import XMonad.Layout.WindowNavigation
import qualified XMonad.Layout.ToggleLayouts as T (toggleLayouts, ToggleLayout(Toggle))
import qualified XMonad.Layout.MultiToggle as MT (Toggle(..))

   -- Utilities
import XMonad.Util.NamedWindows
import XMonad.Util.Run
import XMonad.Util.Dmenu
import XMonad.Util.EZConfig (additionalKeysP)
import XMonad.Util.NamedScratchpad
import XMonad.Util.Run (runProcessWithInput, safeSpawn, spawnPipe)
import XMonad.Util.SpawnOnce

-- Prompt
import XMonad.Prompt
import XMonad.Prompt.ConfirmPrompt

-- ColorScheme
import Colors.GruvboxDark

myFont :: String
myFont = "xft:SauceCodePro Nerd Font Mono:regular:size=9:antialias=true:hinting=true"

myModMask :: KeyMask
myModMask = mod4Mask        -- Sets modkey to super/windows key

myTerminal :: String
myTerminal = "xfce4-terminal"    -- Sets default terminal

myBrowser :: String
myBrowser = "google-chrome-stable"  -- Sets qutebrowser as browser

myEmacs :: String
myEmacs = "emacsclient -c -a 'emacs' "  -- Makes emacs keybindings easier to type

myEditor :: String
myEditor = "emacsclient -c -a 'emacs' "  -- Sets emacs as editor
-- myEditor = myTerminal ++ " -e vim "    -- Sets vim as editor

myBorderWidth :: Dimension
myBorderWidth = 2           -- Sets border width for windows

myTopBarWidth :: Dimension
myTopBarWidth = 0

myPromptWidth :: Dimension
myPromptWidth = 20

myNormColor :: String       -- Border color of normal windows
myNormColor  = "#1d2021"    -- This variable is imported from Colors.THEME

myFocusColor :: String      -- Border color of focused windows
myFocusColor = color05    -- This variable is imported from Colors.THEME
-- #98971a
-- color15

myFocusFollowsMouse :: Bool
myFocusFollowsMouse = False

myClickJustFocuses :: Bool
myClickJustFocuses = False

windowCount :: X (Maybe String)
windowCount = gets $ Just . show . length . W.integrate' . W.stack . W.workspace . W.current . windowset

toggleFloat :: Window -> X ()
toggleFloat w =
  windows
    ( \s ->
        if M.member w (W.floating s)
          then W.sink w s
          else (W.float w (W.RationalRect (1 / 3) (1 / 4) (1 / 2) (1 / 2)) s)
    )

toggleCopyToAll = wsContainingCopies >>= \ws -> case ws of
                [] -> windows copyToAll
                _ -> killAllOtherCopies

forceCenterFloat :: ManageHook
forceCenterFloat = doFloatDep move
  where
    move :: W.RationalRect -> W.RationalRect
    move _ = W.RationalRect x y w h

    w, h, x, y :: Rational
    w = 1/3
    h = 1/2
    x = (1-w)/2
    y = (1-h)/2

data LibNotifyUrgencyHook = LibNotifyUrgencyHook deriving (Read, Show)

instance UrgencyHook LibNotifyUrgencyHook where
    urgencyHook LibNotifyUrgencyHook w = do
        name     <- getName w
        Just idx <- fmap (W.findTag w) $ gets windowset

        safeSpawn "notify-send" [show name, "Workspace " ++ idx]

myStartupHook :: X ()
myStartupHook = do
    spawn "~/.config/polybar/launch.sh"
    spawn "picom"
    spawnOnce "nm-applet"
    spawnOnce "feh --bg-fill ~/.config/xmonad/wallpaper-Rm.png"  -- set last saved feh wallpaper
    setWMName "LG3D"

myColorizer :: Window -> Bool -> X (String, String)
myColorizer = colorRangeFromClassName
                  (0x28,0x2c,0x34) -- lowest inactive bg
                  (0x28,0x2c,0x34) -- highest inactive bg
                  (0xc7,0x92,0xea) -- active bg
                  (0xc0,0xa7,0x9a) -- inactive fg
                  (0x28,0x2c,0x34) -- active fg

-- gridSelect menu layout
mygridConfig :: p -> GSConfig Window
mygridConfig colorizer = (buildDefaultGSConfig myColorizer)
    { gs_cellheight   = 40
    , gs_cellwidth    = 200
    , gs_cellpadding  = 6
    , gs_originFractX = 0.5
    , gs_originFractY = 0.5
    , gs_font         = myFont
    }

spawnSelected' :: [(String, String)] -> X ()
spawnSelected' lst = gridselect conf lst >>= flip whenJust spawn
    where conf = def
                   { gs_cellheight   = 40
                   , gs_cellwidth    = 200
                   , gs_cellpadding  = 6
                   , gs_originFractX = 0.5
                   , gs_originFractY = 0.5
                   , gs_font         = myFont
                   }

myAppGrid = [ ("Audacity", "audacity")
                 , ("Deadbeef", "deadbeef")
                 , ("Emacs", "emacsclient -c -a emacs")
                 , ("Firefox", "firefox")
                 , ("Geany", "geany")
                 , ("Geary", "geary")
                 , ("Gimp", "gimp")
                 , ("Kdenlive", "kdenlive")
                 , ("LibreOffice Impress", "loimpress")
                 , ("LibreOffice Writer", "lowriter")
                 , ("OBS", "obs")
                 , ("PCManFM", "pcmanfm")
                 ]

myScratchPads :: [NamedScratchpad]
myScratchPads = [ NS "terminal" spawnTerm findTerm manageTerm
                , NS "mocp" spawnMocp findMocp manageMocp
                , NS "calculator" spawnCalc findCalc manageCalc
                ]
  where
    spawnTerm  = myTerminal ++ " -t scratchpad"
    findTerm   = title =? "scratchpad"
    manageTerm = customFloating $ W.RationalRect l t w h
               where
                 h = 0.9
                 w = 0.9
                 t = 0.95 -h
                 l = 0.95 -w
    spawnMocp  = myTerminal ++ " -t mocp -e mocp"
    findMocp   = title =? "mocp"
    manageMocp = customFloating $ W.RationalRect l t w h
               where
                 h = 0.9
                 w = 0.9
                 t = 0.95 -h
                 l = 0.95 -w
    spawnCalc  = "qalculate-gtk"
    findCalc   = className =? "Qalculate-gtk"
    manageCalc = customFloating $ W.RationalRect l t w h
               where
                 h = 0.5
                 w = 0.4
                 t = 0.75 -h
                 l = 0.70 -w

--Makes setting the spacingRaw simpler to write. The spacingRaw module adds a configurable amount of space around windows.
mySpacing :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a
mySpacing i = spacingRaw False (Border i i i i) True (Border i i i i) True

-- Below is a variation of the above except no borders are applied
-- if fewer than two windows. So a single window has no gaps.
mySpacing' :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a
mySpacing' i = spacingRaw True (Border i i i i) True (Border i i i i) True

-- Defining a bunch of layouts, many that I don't use.
-- limitWindows n sets maximum number of windows displayed for layout.
-- mySpacing n sets the gap size around the windows.
tall     = renamed [Replace "Master Stack"]
           $ reflectHoriz
           $ smartBorders
           $ addTabs shrinkText myTabTheme 
           $ subLayout [] (smartBorders Simplest)
           $ limitWindows 12
           $ mySpacing 8
           $ ResizableTall 1 (3/100) (1/2) []
magnify  = renamed [Replace "magnify"]
           $ reflectHoriz
           $ smartBorders
           $ addTabs shrinkText myTabTheme
           $ subLayout [] (smartBorders Simplest)
           $ magnifier
           $ limitWindows 12
           $ mySpacing 8
           $ ResizableTall 1 (3/100) (1/2) []
grid     = renamed [Replace "Grid"]
           $ reflectHoriz
           $ smartBorders
           $ addTabs shrinkText myTabTheme
           $ subLayout [] (smartBorders Simplest)
           $ limitWindows 12
           $ mySpacing 8
           -- $ mkToggle (single MIRROR)
           $ Grid (16/10)
spirals  = renamed [Replace "spirals"]
           $ reflectHoriz
           $ smartBorders
           $ addTabs shrinkText myTabTheme
           $ subLayout [] (smartBorders Simplest)
           $ mySpacing' 8
           $ spiral (6/7)
threeColMid = renamed [Replace "Centered Master"]
           $ reflectHoriz
           $ smartBorders
           $ addTabs shrinkText myTabTheme
           $ subLayout [] (smartBorders Simplest)
           $ limitWindows 7
           $ mySpacing' 8
           $ ThreeColMid 1 (1/20) (1/2)
threeCol = renamed [Replace "threeCol"]
           $ reflectHoriz
           $ smartBorders
           $ addTabs shrinkText myTabTheme
           $ subLayout [] (smartBorders Simplest)
           $ limitWindows 7
           $ mySpacing' 8
           $ ThreeCol 1 (3/100) (1/2)
threeRow = renamed [Replace "threeRow"]
           $ reflectHoriz
           $ smartBorders
           $ addTabs shrinkText myTabTheme
           $ subLayout [] (smartBorders Simplest)
           $ limitWindows 7
           -- Mirror takes a layout and rotates it by 90 degrees.
           -- So we are applying Mirror to the ThreeCol layout.
           $ Mirror
           $ ThreeCol 1 (3/100) (1/2)
tabs     = renamed [Replace "tabs"]
           -- I cannot add spacing to this layout because it will
           -- add spacing between window and tabs which looks bad.
           $ tabbed shrinkText myTabTheme
tallAccordion  = renamed [Replace "tallAccordion"]
           $ reflectHoriz
           $ Accordion
wideAccordion  = renamed [Replace "wideAccordion"]
           $ reflectHoriz
           $ Mirror Accordion

-- setting colors for tabs layout and tabs sublayout.
myTabTheme = def { fontName            = myFont
                 , activeColor         = color04
                 , inactiveColor       = color01
                 , activeBorderColor   = color04
                 , inactiveBorderColor = color01
                 , activeTextColor     = color01
                 , inactiveTextColor   = color16
                 }

myTopBarTheme = def { fontName              = myFont
                    , inactiveBorderColor   = color05
                    , inactiveColor         = color05
                    , inactiveTextColor     = color05
                    , activeBorderColor     = color04
                    , activeColor           = color04
                    , activeTextColor       = color04
                    , urgentBorderColor     = color02
                    , urgentTextColor       = color02
                    , decoHeight            = myTopBarWidth
                    }

myPromptTheme = def { font                  = myFont
                    , bgColor               = color01
                    , fgColor               = color16
                    , fgHLight              = color16
                    , bgHLight              = color04
                    , borderColor           = color01
                    , promptBorderWidth     = 0
                    , height                = myPromptWidth
                    , position              = Top
                    }

warmPromptTheme = myPromptTheme { bgColor               = color03
                                , fgColor               = color16
                                , position              = Top
                                }

hotPromptTheme = myPromptTheme  { bgColor               = color02
                                , fgColor               = color16
                                , position              = Top
                                }

-- The layout hook
myLayoutHook = avoidStruts
               $ mouseResize
               $ windowArrange
               $ mkToggle (single REFLECTX)
               $ mkToggle (single FULL) myDefaultLayout
             where
             myDefaultLayout =       tall
                                 ||| grid
                                 ||| threeCol
                                 ||| threeColMid
                                 ||| Main.magnify
                                 ||| noBorders tabs
                                 ||| spirals
                                 ||| threeRow
                                 ||| tallAccordion
                                 ||| wideAccordion

myWorkspaces = ["1", "2", "3", "4", "5", "6", "7", "8", "9"]

myManageHook :: ManageHook
myManageHook =
        insertPosition Below Newer
    <+> fullscreenManageHook
    <+> composeAll
     -- 'doFloat' forces a window to float.  Useful for dialog boxes and such.
     -- using 'doShift ( myWorkspaces !! 7)' sends program to workspace 8!
     -- I'm doing it this way because otherwise I would have to write out the full
     -- name of my workspaces and the names would be very long if using clickable workspaces.
     [ className =? "confirm"         --> doFloat
     , className =? "file_progress"   --> doFloat
     , className =? "dialog"          --> doFloat
     , className =? "download"        --> doFloat
     , className =? "error"           --> doFloat
     , className =? "Gimp"            --> doFloat
     , className =? "notification"    --> doFloat
     , className =? "pinentry-gtk-2"  --> doFloat
     , className =? "splash"          --> doFloat
     , className =? "toolbar"         --> doFloat
     , className =? "Yad"             --> doCenterFloat
     , className =? "zoom"            --> doFullFloat
     , isFullscreen                   --> doFullFloat
     ] <+> namedScratchpadManageHook myScratchPads

myNav2DConf = def
    { defaultTiledNavigation    = centerNavigation
    , floatNavigation           = centerNavigation
    , screenNavigation          = lineNavigation
    , layoutNavigation          = [("Full", centerNavigation), ("ReflectX Full", centerNavigation)]
    , unmappedWindowRect        = [("Full", singleWindowRect), ("ReflectX Full", singleWindowRect)]
    }

-- START_KEYS
myKeys :: [(String, X ())]
myKeys =
    -- KB_GROUP Xmonad
        [ ("M-C-q", confirmPrompt hotPromptTheme "kill all windows in this workspace?" $ killAll)
        , ("M-S-r", spawn "xmonad --recompile && xmonad --restart") -- Restarts xmonad
        , ("M-S-e", confirmPrompt hotPromptTheme "Quit Xmonad?" $ io exitSuccess)  -- Quits xmonad
        , ("M-c", toggleCopyToAll)

    -- KB_GROUP Get Help
        , ("M-S-/", spawn "~/.xmonad/xmonad_keys.sh") -- Get list of keybindings
        , ("M-/", spawn "dtos-help")                  -- DTOS help/tutorial videos

    -- KB_GROUP Run Prompt
        , ("M-S-<Return>", spawn "dm-run") -- Dmenu

    -- KB_GROUP Other Dmenu Prompts
    -- In Xmonad and many tiling window managers, M-p is the default keybinding to
    -- launch dmenu_run, so I've decided to use M-p plus KEY for these dmenu scripts.
        , ("M-p h", spawn "dm-hub")           -- allows access to all dmscripts
        , ("M-p a", spawn "dm-sounds")        -- choose an ambient background
        , ("M-p b", spawn "dm-setbg")         -- set a background
        , ("M-p c", spawn "dtos-colorscheme") -- choose a colorscheme
        , ("M-p C", spawn "dm-colpick")       -- pick color from our scheme
        , ("M-p e", spawn "dm-confedit")      -- edit config files
        , ("M-p i", spawn "dm-maim")          -- screenshots (images)
        , ("M-p k", spawn "dm-kill")          -- kill processes
        , ("M-p m", spawn "dm-man")           -- manpages
        , ("M-p n", spawn "dm-note")          -- store one-line notes and copy them
        , ("M-p o", spawn "dm-bookman")       -- qutebrowser bookmarks/history
        , ("M-p p", spawn "passmenu -p \"Pass: \"") -- passmenu
        , ("M-p q", spawn "dm-logout")        -- logout menu
        , ("M-p r", spawn "dm-radio")         -- online radio
        , ("M-p s", spawn "dm-websearch")     -- search various search engines
        , ("M-p t", spawn "dm-translate")     -- translate text (Google Translate)

    -- KB_GROUP Useful programs to have a keybinding for launch
        , ("M-<Return>", spawn (myTerminal))
        , ("M-b", spawn (myBrowser))
        , ("M-d", spawn "dmenu_run")
        --, ("M-M1-h", spawn (myTerminal ++ " -e htop"))

    -- KB_GROUP Kill windows
        , ("M-q", kill1)  -- Kill the currently focused client
        , ("M-S-q", killAll) -- Kill all windows of focused client on current ws

    -- KB_GROUP Workspaces
        , ("M-.", nextScreen)  -- Switch focus to next monitor
        , ("M-,", prevScreen)  -- Switch focus to prev monitor
        , ("M-S-<KP_Add>", shiftTo Next nonNSP >> moveTo Next nonNSP)       -- Shifts focused window to next ws
        , ("M-S-<KP_Subtract>", shiftTo Prev nonNSP >> moveTo Prev nonNSP)  -- Shifts focused window to prev ws

    -- KB_GROUP Floating windows
        --, ("M-t", withFocused $ windows . W.sink)  -- Push floating window back to tile
        , ("M-t", sinkAll)                       -- Push ALL floating windows to tile
        , ("M-f", sendMessage $ XMonad.Layout.MultiToggle.Toggle FULL)
        , ("M-x", sendMessage $ XMonad.Layout.MultiToggle.Toggle REFLECTX)
        , ("M-y", withFocused toggleFloat)
        --, ("M-d", sendMessage (MT.Toggle NBFULL) >> sendMessage ToggleStruts) -- Toggles noborder/full

    -- KB_GROUP Increase/decrease spacing (gaps)
        --, ("C-M1-j", decWindowSpacing 4)         -- Decrease window spacing
        --, ("C-M1-k", incWindowSpacing 4)         -- Increase window spacing
        --, ("C-M1-h", decScreenSpacing 4)         -- Decrease screen spacing
        --, ("C-M1-l", incScreenSpacing 4)         -- Increase screen spacing

    -- KB_GROUP Grid Select (CTR-g followed by a key)
        , ("C-g g", spawnSelected' myAppGrid)                 -- grid select favorite apps
        , ("C-g t", goToSelected $ mygridConfig myColorizer)  -- goto selected window
        , ("C-g b", bringSelected $ mygridConfig myColorizer) -- bring selected window

    -- KB_GROUP Windows navigation
     -- , ("M-h", sendMessage $ Go L)     -- Move focus to the right window
     -- , ("M-l", sendMessage $ Go R)     -- Move focus to the right window
     -- , ("M-l", bindByLayout [("Master Stack", windows W.focusDown), ("", sendMessage $ Go R)])    -- Move focus to the left window
        , ("M-m", windows W.focusDown)    -- Quick fix for monocle layout
        , ("M-S-m", windows W.focusUp)    -- Quick fix for monocle layout
        , ("M-j", sendMessage $ Go D)     -- Move focus to the below window
        , ("M-k", sendMessage $ Go U)     -- Move focus to the above window
        , ("M-h", bindByLayout [("Full", windows W.focusDown), ("ReflectX Full", windows W.focusUp), ("", sendMessage $ Go L)])
        , ("M-l", bindByLayout [("Full", windows W.focusUp), ("ReflectX Full", windows W.focusDown), ("", sendMessage $ Go R)])
        , ("M-S-j", sendMessage $ Swap D) -- Swap focused window with below window
        , ("M-S-k", sendMessage $ Swap U) -- Swap focused window with above window
       -- , ("M-S-h", sendMessage $ Swap L) -- Swap focused window with below window
        , ("M-S-h", traverse_ sendMessage [Go R, Swap L, Go L]) -- Swap focused window with above window
        , ("M-S-l", traverse_ sendMessage [Go R, Swap L, Go R]) -- Swap focused window with above window
       -- , ("M-<Backspace>", promote)      -- Moves focused window to master, others maintain order
       --, ("M-S-<Tab>", rotSlavesDown)    -- Rotate all windows except master and keep focus in place
       --, ("M-<Backspace>", traverse_ sendMessage [Go R, Swap L, Go R]) -- Swap focused window with above window
        , ("M-<Backspace>", rotSlavesDown)    -- Rotate all windows except master and keep focus in place
        , ("M-S-<Backspace>", rotAllDown)       -- Rotate all the windows in the current stack

    -- KB_GROUP Layouts
        , ("M-<Space>", sendMessage NextLayout)           -- Switch to next layout
        , ("M1-<Space>", spawn "rofi -modi drun -show drun -config ~/.config/rofi/rofidmenu.rasi")           -- Switch to next layout
        --, ("M-d", sendMessage (MT.Toggle NBFULL) >> sendMessage ToggleStruts) -- Toggles noborder/full

    -- KB_GROUP Increase/decrease windows in the master pane or the stack
        , ("M-S-<Up>", sendMessage (IncMasterN 1))      -- Increase # of clients master pane
        , ("M-S-<Down>", sendMessage (IncMasterN (-1))) -- Decrease # of clients master pane
        , ("M-C-<Up>", increaseLimit)                   -- Increase # of windows
        , ("M-C-<Down>", decreaseLimit)                 -- Decrease # of windows

    -- KB_GROUP Window resizing
--        , ("M-h", sendMessage Shrink)                   -- Shrink horiz window width
 --       , ("M-l", sendMessage Expand)                   -- Expand horiz window width
        --, ("M-M1-j", sendMessage MirrorShrink)          -- Shrink vert window width
        --, ("M-M1-k", sendMessage MirrorExpand)          -- Expand vert window width

    -- KB_GROUP Sublayouts
    -- This is used to push windows to tabbed sublayouts, or pull them out of it.
        , ("M-C-h", sendMessage $ pullGroup L)
        , ("M-C-l", sendMessage $ pullGroup R)
        , ("M-C-k", sendMessage $ pullGroup U)
        , ("M-C-j", sendMessage $ pullGroup D)
        , ("M-C-m", withFocused (sendMessage . MergeAll))
        , ("M-C-u", withFocused (sendMessage . UnMerge))
        --, ("M-C-/", withFocused (sendMessage . UnMergeAll))
        , ("M-M1-l", bindByLayout [("tabs", windows W.focusDown), ("", onGroup W.focusDown')]) -- Switch focus to prev tab
        , ("M-M1-h", bindByLayout [("tabs", windows W.focusUp), ("", onGroup W.focusUp')])  -- Switch focus to next tab

    -- KB_GROUP Scratchpads
    -- Toggle show/hide these programs.  They run on a hidden workspace.
    -- When you toggle them to show, it brings them to your current workspace.
    -- Toggle them to hide and it sends them back to hidden workspace (NSP).
        , ("M-s t", namedScratchpadAction myScratchPads "terminal")
        , ("M-s m", namedScratchpadAction myScratchPads "mocp")
        , ("M-s c", namedScratchpadAction myScratchPads "calculator")

    -- KB_GROUP Controls for mocp music player (SUPER-u followed by a key)
        , ("M-u p", spawn "mocp --play")
        , ("M-u l", spawn "mocp --next")
        , ("M-u h", spawn "mocp --previous")
        , ("M-u <Space>", spawn "mocp --toggle-pause")

    -- KB_GROUP Emacs (SUPER-e followed by a key)
        , ("M-e e", spawn (myEmacs ++ ("--eval '(dashboard-refresh-buffer)'")))   -- emacs dashboard
        , ("M-e b", spawn (myEmacs ++ ("--eval '(ibuffer)'")))   -- list buffers
        , ("M-e d", spawn (myEmacs ++ ("--eval '(dired nil)'"))) -- dired
        , ("M-e i", spawn (myEmacs ++ ("--eval '(erc)'")))       -- erc irc client
        , ("M-e n", spawn (myEmacs ++ ("--eval '(elfeed)'")))    -- elfeed rss
        , ("M-e s", spawn (myEmacs ++ ("--eval '(eshell)'")))    -- eshell
        , ("M-e t", spawn (myEmacs ++ ("--eval '(mastodon)'")))  -- mastodon.el
        , ("M-e v", spawn (myEmacs ++ ("--eval '(+vterm/here nil)'"))) -- vterm if on Doom Emacs
        , ("M-e w", spawn (myEmacs ++ ("--eval '(doom/window-maximize-buffer(eww \"distro.tube\"))'"))) -- eww browser if on Doom Emacs
        , ("M-e a", spawn (myEmacs ++ ("--eval '(emms)' --eval '(emms-play-directory-tree \"~/Music/\")'")))

    -- KB_GROUP Multimedia Keys
        , ("<XF86AudioPlay>", spawn "playerctl play-pause")
        , ("<XF86AudioPrev>", spawn "playerctl previous")
        , ("<XF86AudioNext>", spawn "playerctl next")
        , ("<XF86AudioMute>", spawn "amixer set Master toggle")
        , ("<XF86AudioLowerVolume>", spawn "amixer set Master 5%- unmute")
        , ("<XF86AudioRaiseVolume>", spawn "amixer set Master 5%+ unmute")
        , ("<XF86HomePage>", spawn "qutebrowser https://www.youtube.com/c/DistroTube")
        , ("<XF86Search>", spawn "dm-websearch")
        , ("<XF86Mail>", runOrRaise "thunderbird" (resource =? "thunderbird"))
        , ("<XF86Calculator>", runOrRaise "qalculate-gtk" (resource =? "qalculate-gtk"))
        , ("<XF86Eject>", spawn "toggleeject")
        , ("<Print>", spawn "dm-maim")
        ]
    -- The following lines are needed for named scratchpads.
          where nonNSP          = WSIs (return (\ws -> W.tag ws /= "NSP"))
                nonEmptyNonNSP  = WSIs (return (\ws -> isJust (W.stack ws) && W.tag ws /= "NSP"))
-- END_KEYS
myHandleEventHook = XMonad.Layout.Fullscreen.fullscreenEventHook

main :: IO ()
main = do
    forM_ [".xmonad-layout-log"] $ \file -> safeSpawn "mkfifo" ["/tmp/" ++ file]
    -- the xmonad, ya know...what the WM is named after!
    xmonad $ fullscreenSupport $ withUrgencyHook LibNotifyUrgencyHook $ withNavigation2DConfig myNav2DConf $ docks $ ewmh def
        { manageHook         = myManageHook
        , handleEventHook    = myHandleEventHook
        , modMask            = myModMask
        , terminal           = myTerminal
        , focusFollowsMouse  = myFocusFollowsMouse
        , clickJustFocuses   = myClickJustFocuses
        , startupHook        = myStartupHook
        , layoutHook         = configurableNavigation noNavigateBorders $ withBorder myBorderWidth myLayoutHook
        , workspaces         = myWorkspaces
        , borderWidth        = myBorderWidth
        , normalBorderColor  = myNormColor
        , focusedBorderColor = myFocusColor
        , logHook = eventLogHookForPolyBar
        } `additionalKeysP` myKeys

eventLogHookForPolyBar :: X ()
eventLogHookForPolyBar = do
   winset <- gets windowset
   let layout = description . W.layout . W.workspace . W.current $ winset

   io $ appendFile "/tmp/.xmonad-layout-log" (layout ++ "\n")

Imported file:

module Colors.GruvboxDark where

import XMonad

colorScheme = "gruvbox-dark"

colorBack = "#282828"
colorFore = "#ebdbb2"

color01 = "#282828"
color02 = "#cc241d"
color03 = "#98971a"
color04 = "#d79921"
color05 = "#458588"
color06 = "#b16286"
color07 = "#689d6a"
color08 = "#a89984"
color09 = "#928374"
color10 = "#fb4934"
color11 = "#b8bb26"
color12 = "#fabd2f"
color13 = "#83a598"
color14 = "#d3869b"
color15 = "#8ec07c"
color16 = "#ebdbb2"

colorTrayer :: String
colorTrayer = "--tint 0x282828"

Checklist

  • I've read CONTRIBUTING.md

  • I tested my configuration

    • With xmonad version 0.17.0.9 (commit 3009304 if using git)
    • With xmonad-contrib version 0.17.0.9 (commit 0e106cc if using git)

I copied the whole configuration file in, as the user has a history of changing things or even switching configs without warning anyone in the middle of debugging.

I think this is likely a contrib issue.

Minimal reproducer:

import XMonad
import XMonad.Layout.WindowNavigation

main :: IO ()
main = xmonad $ def
  { layoutHook = windowNavigation $ Tall 1 (1/100) (1/2)
  }

I tracked it down to two spots (because one would be too boring I guess).

The first is the call to averagePixels, more precisely the first call to queryColors there. The second one comes from sc, more precisely the call to pixelToString. Indeed, if I remove both of these and set a default colour then everything is fine. According to the manual, queryColors can produce a BadValue.

Haven't investigated further.

queryColors can but it's request 92. The X error indicates request 91, lookupColor. (The error can't pin it to a specific event unless you're logging the entire event stream so you can identify it by sequence number, but it can pin it to a specific request type.)

It turns out that if I locally revert bb448cc and 202e239 then borders behave properly. This pretty well pins it down to setWindowBorderWithFallback. (Simply reverting those commits is not a viable fix, since they fix our handling of window colormaps and opacity.)

Also, setWindowBorderWithFallback is used directly by WindowNavigation, so it turns out we're both right.

Per #398 it appears that the problem actually appears after dbe9c4f.

Okay, that one is just the merge commit for the one I cited earlier, so we're still left with the original diagnosis. Now to figure out why….

Speaking strictly by the protocol, there are two problems with the way setPixelSolid is implemented:

  1. You can't directly manipulate a color value like that on visuals other than TrueColor and DirectColor. This should only matter when running xmonad under VNC or similar.
  2. The modified color is not, strictly speaking, allocated for the window; only the unmodified color is. This will matter for visuals other than DirectColor, and may matter for DirectColor.

If I wanted to be really pedantic, the RGB masks should be retrieved from the visual and masked out of 0xffffffff to set the opacity. In practice, I think we can be reasonably certain this will never come up.

Also, if you're wondering what I meant by "visual", see https://tronche.com/gui/x/xlib/window/visual-types.html. This controls, among other things, how colormaps and color allocation work.

Reviewing our colormap (non)support, I'm slightly surprised nobody ever reported colormap issues under VNC, because we pretty much make no attempt to support PseudoColor and in particular have no support for WM_COLORMAP_WINDOW. In any case, while we perhaps accidentally worked before that commit, we would have lost it afterward (unless VNC now supports DirectColor, which would surprise me as it'd slow the protocol down considerably).

So what's the best course of action here? Revert dbe9c4f until we figure out what to do here? We certainly don't want to include it in 0.17.1, imo

I know what to do, I just don't want to do it since it'll like triple the size of the code and it's in a relatively hot path. And may require corresponding changes to contrib, which means more testing. If we';re putting out 0.17.1 soonish than the revert probably makes sense.

I've done this now: e5a258f

Cc.: @Thiago4532

You also need to revert a corresponding change in xmonad-contrib (part of which is why WindowNavigation blacks out).

I don't think so? I don't remember a corresponding contrib pr for this one (and can't find it now either)

Someone made a patch that uses the function you removed in a couple of places; I ran into it when I reverted it locally.

I know what to do, I just don't want to do it since it'll like triple the size of the code and it's in a relatively hot path.

dbe9c4f fixes an issue that I was having whenever I floated my browser window so I'd be keen to understand what the fix would look like and help testing it (when the time comes). :-)

The function was not exported, was it? Either way, grepping the contrib repo doesn't seem to return any matches

Hey, sorry about that :(
I am the author of the PR that was reverted. If I manage to fix this problem, does anyone know if I have to create a new PR? Or it's possible to modify the reverted one?

@Thiago4532 You'll definitely need to open a new PR. I believe @geekosaur already spent some time figuring out what the problem is so you may want to coordinate with him on the fix (unless you already know all that needs to be done from his comments above :-)) — IRC/Matrix is where we usually talk.

I should clarify that I only outlined the protocol violations above. This may not fix the problem, but it's the first step to trying to do so since proper diagnosis is much harder when we're breaking the rules (and even more so when the result half-works).

Um.

[03 14:56:41] <geekosaur> I will be surprised if just making it allocate colormap cells correctly fixes it, but it still is a prerequisite
[03 14:59:02] * geekosaur does wonder how alpha even works, since XColor doesn't have a field for it
[03 14:59:28] <geekosaur> which may mean what the code was doing was acceptable because it's the only way to do it…

And, as it turns out, that was prescient: doing the allocation properly ignores the alpha entirely, because an XColor only knows RGB values, not alpha, even though it has a Pixel value that supports it. So you have to do it the "wrong" way (with a side effect that supporting alpha locks you into DirectColor)

Sadly, that still leaves the original problem, and diagnosis will now be harder. In the meantime, we get to decide whether the WindowNavigation border bug or transparent borders is the worse problem to live with.

Actually, it turns out to have been simple, although I'm still testing. WindowNavigation does a number of operations on Pixel values which have alpha. So far, pixelToString has been found to always return #000000 if the Pixel has alpha, and I am currently testing to see if averagePixels does something similarly buggy.

And the answer is that it does, and the borders work and the BadValue errors go away with the alphas masked out.