[xmonad] scratchpads broken after upgrade.

Brandon Allbery allbery.b at gmail.com
Fri Oct 21 22:36:46 UTC 2022


I haven't had a chance to look over your use of NamedScratchpads
except to verify that you seem to have `namedScratchpadManageHook`
correct (although you seem to be setting it once and then overriding
it later, and the same with `layoutHook` and `startupHook`); with the
merger of dynamic scratchpads with normal scratchpads, everything
except activation is now done in the `manageHook`, so that should be
correct.

Old-style scratchpads are no longer supported and will be removed in
the next release. Use NamedScratchpads instead. There is currently a
broken attempt at backward compatibility currently, which may be
interfering with the normal NamedScratchpad.

On Fri, Oct 21, 2022 at 4:16 PM Eric.a <e.a.gebhart at gmail.com> wrote:
>
>
> I am on Arch Linux, so there's that.  I had avoided upgrading for a couple of months.
> Until yesterday morning.
>
> I'm on ghc 9.02 and xmonad 17.1.
>
> I had to wade through numerous problems and errors, Arch as well as xmonad deprecations. Nothing to do with scratchpads.
>
> I am passing my scratchpads to all scratchpad Actions, I have a scratchToggle function to do that, which according to the doc, should continue to work even with the breaking changes to namedScratchpads.
>
> I do have multiple ways to invoke them.  I have a submap keymap, grid select, and few direct keys in the main keymap.  None of them work.
>
> None of the named scratchpads work, nor does the old unnamed scratchpad terminal.
> I've ripped out my code and replaced it with the example with no success.
> I've tested examples with xterm, uxrvt and termite.
> I am now mostly back to my original scratchpad code.  Which silently does nothing, Named or otherwise.
>
> I must be missing something very simple.
>
> Any clues would be appreciated, my haskell is a bit rusty but coming back a little at a time.
> Here's my relevant code chunks.  Also available on my github.  Itś a rather large config.
> https://github.com/EricGebhart/xmonad-setup/blob/master/.xmonad/xmonad.hs
>
> I suspect my manage hooks, but it just doesn´t make sense to me. Everything is
> a bit simpler with the new docks and ewmh stuff, I realize I could simplify it some
> more. But I hate to mess with it too much, when it all looks good and it's been this
> way for years now.
>
> Any help is much appreciated.
> Thank you,
> Eric
>
> ```haskell
>
> ----------------------------------------------------------------------------
> -- Scratch Pads ------------------------------------------------------------
>
> -- location and dimension.
>
> scratchpadSize = W.RationalRect (1/4) (1/4) (1/3) (3/7)
>
> mySPFloat = customFloating scratchpadSize
>
>             -- with a flexible location.
> -- Big BSP, Small SSP, Super small,
> --  so size is width and height. - change the fractions to get your sizes right.
> flexScratchpadSize dx dy = W.RationalRect (dx) (dy) (1/2) (5/7)
> flexSScratchpadSize dx dy = W.RationalRect (dx) (dy) (3/5) (5/8)
> flexSSScratchpadSize dx dy = W.RationalRect (dx) (dy) (1/2) (1/2)
> -- pass in a fraction to determine your x,y location. size is derived from that
> -- all based on screen size.
> flexFloatSSP dx dy = customFloating (flexSScratchpadSize dx dy)
> flexFloatSSSP dx dy = customFloating (flexSSScratchpadSize dx dy)
> flexFloatBSP dx dy = customFloating (flexScratchpadSize dx dy)
>
>
> scratchpads =
>   [ NS "conky"   spawnConky findConky manageConky
>   , NS "htop" "xterm -e htop" (title =? "htop") defaultFloating -- from the example in the doc
>   , NS "pavuControl"   spawnPavu findPavu managePavu
>   , NS "term"  (myTerminal2 ++ " -t term") (title =? "term") (flexFloatBSP (1/20) (1/20))
>   , NS "term1" (myTerminal2 ++ " -t term1") (title =? "term1") (flexFloatBSP (2/20) (2/20))
>   , NS "term2" (myTerminal2 ++ " -t term2") (title =? "term2") (flexFloatBSP (3/20) (3/20))
>   , NS "term3" (myTerminal2 ++ " -t term3") (title =? "term3") (flexFloatBSP (4/20) (4/20))
>   , NS "term4" (myTerminal2 ++ " -t term4") (title =? "term4") (flexFloatBSP (6/20) (4/20))
>   , NS "ghci"  (myTerminal2 ++ " -e ghci") (title =? "ghci") (flexFloatBSP (6/20) (1/10))
>   --, NS "sync"  (myTerminal ++ " -e sy") (title =? "sy") (flexFloatSP (1/10) (2/3))
>   , NS "top"   (myTerminal2 ++ " -e htop") (title =? "htop") (flexFloatSSP (1/4) (1/4))
>   , NS "calc"  (myTerminal2 ++ " -e bcl -t bc") (title =? "bc") (flexFloatSSSP (1/4) (1/4))
>   , NS "alsaMixer"  (myTerminal2 ++ " -e alsamixer -t alsamixer") (title =? "alsamixer") (flexFloatSSSP (1/4) (1/4))
>   ]
>   where
>     spawnConky  = "conky -c ~/.config/conky/Erics.conkyrc" -- launch Conky
>     findConky   = title =? "system_conky"   -- its window,  has a own_window_title of "system_conky"
>     manageConky = (flexFloatSSP (1/4) (1/4))
>     spawnPavu  = "pavucontrol"
>     findPavu   = title =? "pavucontrol"
>     managePavu = (flexFloatSSP (1/4) (1/4))
>
> -- Scratchpad invocation / Dismissal
> -- Warp
> bringMouse = warpToWindow (9/10) (9/10)
> scratchToggle a = namedScratchpadAction scratchpads a >> bringMouse
>
> manageScratchPad :: ManageHook
> manageScratchPad = scratchpadManageHook (W.RationalRect l t w h)
>   where
>     h = 0.6
>     w = 0.5
>     t = 1 - h
>     l = 1 - w
>
> myScratchpadManageHook =
>     manageScratchPad <+>
>     namedScratchpadManageHook scratchpads
>
> myManageHelpers = composeAll . concat $
>     [ [ className   =? c --> doFloat           | c <- classFloats]
>     , [ title       =? t --> doFloat           | t <- titleFloats]
>     , [ resource    =? r --> doFloat           | r <- resourceFloats]
>     , [ title       =? c --> doIgnore          | c <- titleIgnores]
>     , [(className =? "Firefox" <&&> resource =? "Dialog") --> doFloat]
>     ]
>   where classFloats    = ["Galculator", "Steam", "Media_Center_30", "YACReaderLibrary",
>                           "MPlayer", "Gimp", "Gajim.py", "Xmessage"]
>         titleFloats    = ["Volume Control", "alsamixer", "Onboard"]
>         resourceFloats = ["desktop_window", "Dialog", "gpicview"]
>         titleIgnores   = ["stalonetray", "xfce4-notifyd"]
>
> myManageHook = myManageHelpers <+> myScratchpadManageHook
>
> --- keymaps
> ...
>
>  -- Scratchpads
>     , ("M4-e",          toSubmap c "namedScratchpadsKeymap" namedScratchpadsKeymap) -- Scratchpad
>     , ("M4-n",          scratchpadSpawnActionTerminal  "urxvt") -- Urxvt Scratchpad
>     , ("M4-S-n",        namedScratchpadAction scratchpads  "term1") -- Term1 Scratchpad
>     , ("M4-S-e",        namedScratchpadAction scratchpads  "htop") -- htop example Scratchpad
>
> -- manage hooks / def
> myConfig = do
>   dbus <- D.connectSession
>   getWellKnownName dbus
>   return $ defaults {
>       logHook = do
>          -- dynamicLogWithPP $ (prettyPrinter dbus)
>          dynamicLogWithPP $ (myPPPolybar dbus)
>          fadeinactive
>
>       , manageHook = myManageHook
>       , layoutHook = layoutHook defaults
>       , startupHook = do
>           myStartupHook        -- >> setWMName "LG3D"
>       }
>
> -- docks :: XConfig myConfig -> XConfig myConfig
>
> ------------------------------------------------------------------------
> -- Combine it all together
> -- A structure containing your confiuration settings, overriding
> -- fields in the default config. Any you don't override, will
>
> -- use the defaults defined in xmonad/XMonad/Config.hs
> --
> -- No need to modify this.
> --
>
> -- defaultConfig
> defaults = def {
>   -- simple stuff
>    terminal           = myTerminal,
>    focusFollowsMouse  = myFocusFollowsMouse,
>    borderWidth        = myBorderWidth,
>    modMask            = myModMask,
>    workspaces         = myTopicNames,  -- MyWorkspaces
>    normalBorderColor  = myNormalBorderColor,
>    focusedBorderColor = myFocusedBorderColor,
>
>      -- key bindings
>    keys               = mainKeymap,
>    mouseBindings      = myMouseBindings,
>
>      -- hooks, layouts
>    layoutHook         = myLayout, -- smartBorders $ myLayout,
>    manageHook         = myManageHook,
>    startupHook        = myStartupHook
> } -- `additionalKeysP` myadditionalKeys
>
> main :: IO ()
> main = xmonad . ewmh . docks =<< myConfig
> ```
> _______________________________________________
> xmonad mailing list
> xmonad at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad



-- 
brandon s allbery kf8nh
allbery.b at gmail.com


More information about the xmonad mailing list