[~] $NB_

[?] CODE / KEYBOARDS / TERMINAL / NIXOS


[M] [POSTS] [HOWTO] [WHOAMI] [PODCASTS] [KEYBOARDS]


~~ NV-XMONAD ~~

** MODAL XMONAD CONFIG **

[COD] | [20250918] | [0x17]




NV-XMONAD

As already announced in XMONAD, I’ve now expanded my XMonad configuration so that it works modally, just like Vim itself. I took a few minutes (or more like days) and rebuilt XMonad so that it has this functionality and also outputs the whole thing neatly to the XMobar.

MODALITY

In case no one has noticed, I’m a Vim user and have been for quite some time now. Anyone who works with Vim regularly quickly realizes that Vim keybindings become second nature, and you find yourself typing more and more often, for example, using Vim keybindings in other tools. Admit it, you’ve also tried closing gedit with :wq. Another thing you get used to is Vim’s modality. It’s a blessing and a curse, because I’d argue the biggest hurdle to getting started with Vim is the different modes. This brings us to modality. On the one hand, this provides different input modes, and on the other hand, the keys are mapped depending on the mode and have different functions.

Now, by default, XMonad is used in such a way that there is one layer (mode would probably be incorrect here, as it is the only one used) on which the user operates. Here, a different layer is simulated at most through combinations with MOD + CTRL / SHIFT. The problem that arises here is that a third finger comes into play to operate the TilingWM. I personally find combinations with three fingers rather tiring and simply painful in the long run. The sheer number of possible key combinations in modal and default mode should be almost identical. What has changed, however, is the operation of the WindowManager with two-finger combos. On the one hand, the mode is activated with a two-finger combination, and in the selected mode another two-finger combination is used to trigger the respective function. At first glance, it is noticeable that four keys instead of the original three have to be pressed for each individual action that is to be carried out. The advantage here, however, is that instead of three keys with three fingers, you only play two keys twice with two fingers, and this is much smoother than a three-finger combo. It sounds incredibly theoretical at first, but you’ll notice it in no time.

Now, of course, the question arises as to which modes actually make sense in a TilingWM. In my initial considerations, I came to the conclusion that NORMAL, RESIZE, MOVE, LAYOUT, SESSION, and LAUNCH would make sense. Whether this will remain so in the long run remains to be seen, but these modes are quite useful for a start. There is one small “drawback.” I had configured my workflow to the point where I no longer needed a status bar like xmobar. However, in the beginning, it is quite helpful to see the current mode somewhere. So the xmobar is making a big comeback in my configuration. But more on that later. What is not included in modal control is switching between workspaces. Workspaces can be accessed across all modes with MOD + 1, MOD + 2, and so on.

MODES

MODES

Of course, the individual modes are also assigned special tasks and house their own specific keybindings. I use NORMAL mode as the default mode (like Vim). [NORMAL]: Since NORMAL mode is the default, it serves as the basis for everything, i.e., if we are in another mode, we can always return to NORMAL mode with the combination MOD + SPACE. For the most part, NORMAL mode is similar to XMonad’s default mode. Here, you can spawn a terminal with MOD + ENTER, or kill the currently focused window with MOD + d. You can also open the standard browser with MOD + f.

[ RESIZE ]: RESIZE also does what you’d expect. It resizes the windows while retaining the tiling. MOD + h/j/k/l resizes them in the desired direction.

[ MOVE ]: MOVE does what it’s supposed to: it moves windows. MOD + h/j/k/l always moves windows 10px in the desired direction. Windows can also be moved to another workspace. This works with MOD + SHIFT + 1…9. This moves the window in focus to the selected workspace.

[ LAYOUT ]: The LAYOUT mode takes care of the arrangement of the windows. MOD + n jumps to the next available layout and cycles through the layouts until you end up back at the default layout. MOD + f changes the layout to a floating layout, i.e. with freely positionable windows. MOD + l switches to fullscreen mode and stretches the current window to the full screen size. MOD + o and MOD + b switch to a mirrored and a borderless layout. The two bindings MOD + d and MOD + u are currently used to switch to the default layout or to integrate floating windows back into the tiling concept.

[ SESSION ]: SESSION mode controls everything that is user- or session-related (as the name suggests). The keybindings MOD + h (restart XMonad), MOD + k (end XMonad), and MOD + l (lock session) are defined here. NOTE! If XMonad (as described in the last post) is configured via nixpkgs, the two keybindings restart XMonad and exit XMonad may not work. Separate parameters must be set in the nix configuration so that it can be restarted or ended from within nix-config.

[ LAUNCH ]: LAUNCH is primarily used to spawn frequently used tools directly without having to go through Rofi or the terminal. For example, MOD + t opens a terminal, MOD + f opens the browser, MOD + v opens an NVIM instance, MOD + d opens Rofi to launch other tools, and MOD + o opens Obsidian to organize all that stuff.

Now, the integration wasn’t entirely easy. I find Haskell incredibly exciting, but Haskell doesn’t really make things easy. Somehow, though, it worked.

INTEGRATION IN XMONAD

To get the modes working in XMonad, we start by defining the different modes:

1    data Mode = Normal | ResizeMode | MoveMode | LayoutMode | SessionMode | LaunchMode deriving (Eq, Show)

This tells XMonad that it can be in any of these modes and provides the appropriate keybindings for each mode. To ensure that XMonad remembers which mode is currently active, we use IORef Mode:

1    main = do
2        modeRef <- newIORef Normal
3            ...

Here, the mode is stored in IORef. IORef is a container in the IO monad that allows the current mode to be read and changed. The default is Normal. Next, we need to ensure that XMonad recognizes and correctly processes mode changes via key combinations. Mode switching is done using myKeys:

1    switchMode :: IORef Mode -> Mode -> X ()
2    switchMode modeRef newMode = do
3        liftIO $ writeIORef modeRef newMode
4        refresh

With switchMode, we write the new mode in IORef. refresh causes XMonad to refresh the screen. To make the mode change work via keybinding, we define the mode keys as a comprehensive cluster of keybindings:

1    ((mod4Mask, xK_space), switchMode modeRef Normal)
2    ((mod4Mask, xK_r), switchMode modeRef ResizeMode)
3    ((mod4Mask, xK_m), switchMode modeRef MoveMode)
4    ((mod4Mask, xK_y), switchMode modeRef LayoutMode)
5    ((mod4Mask, xK_s), switchMode modeRef SessionMode)
6    ((mod4Mask, xK_a), switchMode modeRef LaunchMode)

This way, when we use the combination MOD + r, modeRef is set to ResizeMode. Then refresh is executed from the switchMode function so that XMonad applies the change directly. This allows for a direct mode change. Initially, I had the problem that the mode change was only recognized when the subsequent key combination was triggered. With the helper function, the change becomes active immediately after the change.

The next step is to map the keys, or rather their corresponding functions, to the available modes. The previous keybinding mapping looked like this (this remains the way to go for a non-modal operation):

1    normalKeys modeRef =
2        [ ((mod4Mask, xK_h), withMode Normal modeRef $ windows W.focusUp)
3        , ((mod4Mask, xK_l), withMode Normal modeRef $ windows W.focusDown)
4        ]
5
6    resizeKeys modeRef =
7        [ ((mod4Mask, xK_h), withMode ResizeMode modeRef $ sendMessage Shrink)
8        , ((mod4Mask, xK_l), withMode ResizeMode modeRef $ sendMessage Expand)
9        ]

Unfortunately, XMonad always caused problems here, overwriting the bindings with the last defined mode. Thus, mode-specific bindings weren’t possible. Fortunately, XMonad can be tweaked to the point where, instead of assigning modes to keybindings, we do the opposite: assigning keybindings to the modes. We make this possible by building a cluster of context-sensitive keybindings:

 1    dynamicKeys :: IORef Mode -> [((KeyMask, KeySym), X ())]
 2    dynamicKeys modeRef = 
 3        [ ((mod4Mask, xK_h), modeDispatch modeRef
 4            [ (Normal, windows W.focusUp)
 5            , (ResizeMode, sendMessage Shrink)
 6            , (MoveMode, sendMessage (MoveLeft 10))
 7            , (SessionMode, spawn "xmonad --restart")
 8            ])
 9        --- more keybindings
10    ]

The helper function modeDispatcher checks the current mode and then executes the corresponding action. In this case, we assign the keybinding MOD + h to check the current mode and then execute the corresponding action. This “overwrites” the keys and provides the functions for each mode. For example, MOD + h can move the window focus in NORMAL mode, narrow the current window in RESIZE mode, and move the window to the left in MOVE mode.

Of course, we also want to pass all this to xmobar. Passing the mode to the xmobar is done using modeLogger:

 1    modeLogger :: IORef Mode -> X (Maybe String)
 2    modeLogger modeRef = do
 3        mode <- liftIO $ readIORef modeRef
 4        let icon txt = "<fn=1>" ++ txt ++ "</fn>"
 5        let formatMode bg fg name = wrapColor bg fg (icon " \xE61F " ++ name)
 6        return $ Just $ case mode of
 7            Normal      -> formatMode "#50FA7B" "282A36" "NORMAL"
 8            ResizeMode  -> formatMode "#FFB86C" "282A36" "RESIZE"
 9            MoveMode    -> formatMode "#8B39FD" "282A36" "MOVE"
10            LayoutMode  -> formatMode "#FF79C6" "282A36" "LAYOUT"
11            SessionMode -> formatMode "#BD93F9" "282A36" "SESSION"
12            LaunchMode  -> formatMode "#F1FA8C" "282A36" "LAUNCH"

Here, the current mode is displayed in color and with an icon. NORMAL mode appears in green, RESIZE in orange, and everything looks just like the Dracula theme. We’ll also integrate modeLogger into myXmobarPP:

1    myXmobarPP xmproc modeRef = def {
2        ppExtras = [modeLogger moderef, windowCountLogger, timeAndKernelLogger]
3    )

This allows us to perfectly operate XMonad with modes.

Keybindings

This allows us to pass the strings to xmobar in addition to the workspaces, layout, and title and display them there. All that’s missing now is our .xmobarrc.

INTEGRATION IN XMOBAR

The integration in xmobar, however, is much simpler. We’ll integrate a function into xmobar that is usually used by default: StdinReader:

    , Run StdinReader 

StdinReader waits until any process sends a message to the default input stream (stdin). In the xmobarrc, StdinReader is responsible for receiving dynamic information from XMonad, specifically workspaces and window titles. Since we’ve already completely styled the mode display in the XMonad config, we don’t need any additional color definitions here in the xmobar; we can use StdinReader directly. The entire .xmobarrc is provided below.

COMPLETE CONFIG

This should make the modal configuration of XMonad and its integration into xmobar work perfectly. If you want to test it yourself, you can find the config files on GITHUB and, for the sake of completeness, here is the complete XMONAD.HS (integrated into NixOS):

  1{ ... }:
  2
  3{
  4  services.xserver = {
  5    windowManager.xmonad = {
  6      enable = true;
  7      enableContribAndExtras = true;
  8      
  9      config = ''
 10         ------------------------------------------------------------------------
 11        ---IMPORTS
 12        ------------------------------------------------------------------------
 13        -- Base
 14        import XMonad
 15        import XMonad.Config.Desktop (desktopConfig)
 16        import Data.Monoid
 17        import Data.Maybe (isJust)
 18        import System.IO
 19        import System.Exit (exitSuccess)
 20        import System.Process (readProcess)
 21        import qualified XMonad.StackSet as W
 22
 23        -- Utilities
 24        import XMonad.Util.EZConfig (additionalKeysP, additionalMouseBindings)
 25        import XMonad.Util.NamedScratchpad
 26        import XMonad.Util.Run (safeSpawn, unsafeSpawn, runInTerm, spawnPipe, runProcessWithInput)
 27        import XMonad.Util.SpawnOnce
 28        
 29        -- Hooks
 30        import XMonad.Hooks.DynamicLog (dynamicLogWithPP, ppCurrent, ppVisible, ppTitle, ppOrder, ppSep, ppLayout, ppExtras, ppOutput, wrap, pad, xmobarPP, xmobarColor, shorten, PP(..))
 31        import XMonad.Hooks.ManageDocks
 32        import XMonad.Hooks.ManageHelpers (isFullscreen, isDialog,  doFullFloat, doCenterFloat)
 33        import XMonad.Hooks.SetWMName
 34        import XMonad.Hooks.EwmhDesktops
 35        
 36        -- Actions
 37        import XMonad.Actions.Minimize (minimizeWindow)
 38        import XMonad.Actions.Promote
 39        import XMonad.Actions.CopyWindow (kill1)
 40        import XMonad.Actions.WindowGo (runOrRaise, raiseMaybe)
 41        import XMonad.Actions.WithAll (sinkAll, killAll)
 42        import XMonad.Actions.CycleWS (moveTo, shiftTo, WSType(..), nextScreen, prevScreen, shiftNextScreen, shiftPrevScreen)
 43        import XMonad.Actions.GridSelect
 44        import XMonad.Actions.DynamicWorkspaces (addWorkspacePrompt, removeEmptyWorkspace)
 45        import XMonad.Actions.MouseResize
 46        
 47        -- Layouts modifiers
 48        import XMonad.Layout.PerWorkspace (onWorkspace)
 49        import XMonad.Layout.Renamed (renamed, Rename(CutWordsLeft, Replace))
 50        import XMonad.Layout.Spacing (spacing)
 51        import XMonad.Layout.NoBorders
 52        import XMonad.Layout.LimitWindows (limitWindows, increaseLimit, decreaseLimit)
 53        import XMonad.Layout.WindowArranger 
 54        import XMonad.Layout.Reflect (reflectVert, reflectHoriz, REFLECTX(..), REFLECTY(..))
 55        import XMonad.Layout.MultiToggle (mkToggle, single, EOT(EOT), Toggle(..), (??))
 56        import XMonad.Layout.MultiToggle.Instances (StdTransformers(NBFULL, MIRROR, NOBORDERS))
 57        import qualified XMonad.Layout.ToggleLayouts as T (toggleLayouts, ToggleLayout(Toggle))
 58        
 59        -- Layouts
 60        import XMonad.Layout.NoFrillsDecoration
 61        import XMonad.Layout.SimplestFloat
 62        import XMonad.Layout.OneBig
 63        import XMonad.Layout.ThreeColumns
 64        import XMonad.Layout.ResizableTile
 65        import XMonad.Layout.ZoomRow (zoomRow, zoomIn, zoomOut, zoomReset, ZoomMessage(ZoomFullToggle))
 66        
 67        -- Prompts
 68        import XMonad.Prompt
 69
 70        -- Modal imports
 71        import qualified Data.Map as M
 72        import qualified DBus as D 
 73        import qualified DBus.Client as D
 74        import Data.IORef (IORef, newIORef, readIORef, writeIORef)
 75        import XMonad.Actions.MessageFeedback
 76        import Control.Monad (when)
 77        import XMonad (liftIO)
 78        import Data.Time (getZonedTime, formatTime, defaultTimeLocale)
 79        import Data.Time.Clock (getCurrentTime)
 80        import XMonad.StackSet as W
 81
 82------------------------------------------------------------------------
 83        ---CONFIG
 84        ------------------------------------------------------------------------
 85        data Mode = Normal | ResizeMode | MoveMode | LayoutMode | SessionMode | LaunchMode deriving (Eq, Show)
 86
 87        myFont          = "xft:Berkeley Mono Nerd Font:style=Regular:pixelsize=11"
 88        myModMask       = mod4Mask
 89        myTerminal      = "alacritty"
 90        myTextEditor    = "nvim"
 91        myBorderWidth   = 2
 92
 93        initialClient :: Mode
 94        initialClient = Normal
 95
 96        main :: IO ()
 97        main = do
 98            modeRef <- newIORef Normal
 99            dbus <- D.connectSession
100            xmproc <- spawnPipe "xmobar"
101            dbusRef <- newIORef dbus
102            xmonad $ docks def 
103                  { terminal           = myTerminal
104                  , modMask            = myModMask
105                  , startupHook        = myStartupHook
106                  , XMonad.workspaces  = myWorkspaces
107                  , borderWidth        = myBorderWidth
108                  , normalBorderColor  = "#44475A"
109                  , focusedBorderColor = "#50FA7b"
110                  , keys               = \c -> myKeys modeRef c
111                  , layoutHook         = myLayoutHook
112                  , manageHook         = manageDocks <+> manageHook def
113                  , logHook            = dynamicLogWithPP (myXmobarPP xmproc modeRef)
114                                          { ppOutput = hPutStrLn xmproc
115                                          , ppTitle = xmobarColor "#BD93F9" "" . shorten 50
116                                          , ppExtras = [modeLogger modeRef]
117                                          }
118                                        >> updateModeLog modeRef dbusRef
119                  }
120
121        ------------------------------------------------------------------------
122        ---AUTOSTART
123        ------------------------------------------------------------------------
124        myStartupHook = do
125                  spawnOnce "nitrogen --restore &"
126
127        ------------------------------------------------------------------------
128        --- SET KEYS 
129        --- TO FIND KEY IDENTIFIERS: XEV
130        ------------------------------------------------------------------------
131        myKeys :: IORef Mode -> XConfig l -> M.Map (KeyMask, KeySym) (X ())
132        myKeys modeRef conf = M.fromList $
133            [ ((mod4Mask, xK_space), switchMode modeRef Normal)
134            , ((mod4Mask, xK_r),     switchMode modeRef ResizeMode)
135            , ((mod4Mask, xK_m),     switchMode modeRef MoveMode)
136            , ((mod4Mask, xK_y),     switchMode modeRef LayoutMode)
137            , ((mod4Mask, xK_s),     switchMode modeRef SessionMode)
138            , ((mod4Mask, xK_a),     switchMode modeRef LaunchMode)
139
140            , ((mod4Mask, xK_1),     windows $ W.view "0") 
141            , ((mod4Mask, xK_2),     windows $ W.view "1") 
142            , ((mod4Mask, xK_3),     windows $ W.view "2") 
143            , ((mod4Mask, xK_4),     windows $ W.view "3") 
144            , ((mod4Mask, xK_5),     windows $ W.view "4") 
145            , ((mod4Mask, xK_6),     windows $ W.view "5") 
146            , ((mod4Mask, xK_7),     windows $ W.view "6") 
147            , ((mod4Mask, xK_8),     windows $ W.view "7") 
148            , ((mod4Mask, xK_9),     windows $ W.view "8") 
149            ]
150            ++ dynamicKeys modeRef
151        
152        switchMode :: IORef Mode -> Mode -> X ()
153        switchMode modeRef newMode = do
154            liftIO $ writeIORef modeRef newMode
155            refresh
156
157        modeDispatch :: IORef Mode -> [(Mode, X ())] -> X ()
158        modeDispatch modeRef actions = do
159            current <- liftIO $ readIORef modeRef
160            case lookup current actions of
161                Just action -> action
162                Nothing     -> return ()
163
164        ------------------------------------------------------------------------
165        --- DEFINE MODE KEY MAPS 
166        ------------------------------------------------------------------------
167        dynamicKeys :: IORef Mode -> [((KeyMask, KeySym), X ())]
168        dynamicKeys modeRef = 
169            [ ((mod4Mask, xK_h), modeDispatch modeRef
170                [ (Normal, windows W.focusUp)
171                , (ResizeMode, sendMessage Shrink)
172                , (MoveMode, sendMessage (MoveLeft 10))
173                -- , (LayoutMode, COMMAND)
174                , (SessionMode, spawn "xmonad --restart")
175                -- , (LaunchMode, COMMAND)
176                ])
177            
178            , ((mod4Mask, xK_j), modeDispatch modeRef
179                [ (Normal, windows W.focusMaster)
180                , (ResizeMode, sendMessage MirrorShrink)
181                , (MoveMode, sendMessage (MoveDown 10))
182                -- , (LayoutMode,  COMMAND)
183                -- , (SessionMode, COMMAND)
184                -- , (LaunchMode,  COMMAND)
185                ])
186            
187            , ((mod4Mask, xK_k), modeDispatch modeRef
188                [ -- (Normal,     COMMAND)
189                  (ResizeMode, sendMessage MirrorExpand)
190                , (MoveMode, sendMessage (MoveUp 10))
191                -- , (LayoutMode, COMMAND)
192                , (SessionMode, io exitSuccess)
193                -- , (LaunchMode, COMMAND)
194                ])
195            
196            , ((mod4Mask, xK_l), modeDispatch modeRef
197                [ (Normal, windows W.focusDown)
198                , (ResizeMode, sendMessage Expand)
199                , (MoveMode, sendMessage (MoveRight 10))
200                , (LayoutMode, sendMessage ZoomFullToggle)
201                , (SessionMode, spawn "loginctl lock-session")
202                -- , (LaunchMode, COMMAND)
203                ])
204            
205            , ((mod4Mask, xK_Return), modeDispatch modeRef
206                [ (Normal, spawn myTerminal)
207                -- , (ResizeMode,  COMMAND)
208                -- , (MoveMode,    COMMAND)
209                -- , (LayoutMode,  COMMAND)
210                -- , (SessionMode, COMMAND)
211                -- , (LaunchMode,  COMMAND)
212                ])
213
214            , ((mod4Mask, xK_d), modeDispatch modeRef
215                [ (Normal, kill1)
216                -- , (ResizeMode,  COMMAND)
217                -- , (MoveMode,    COMMAND)
218                , (LayoutMode, setLayout (Layout (Tall 1 (3/100) (1/2))))
219                -- , (SessionMode, COMMAND)
220                , (LaunchMode, spawn "rofi -show run")
221                ])
222
223            , ((mod4Mask, xK_f), modeDispatch modeRef
224                [ (Normal, spawn "librewolf")
225                -- , (ResizeMode,  COMMAND)
226                -- , (MoveMode,    COMMAND)
227                , (LayoutMode, sendMessage (T.Toggle "float"))
228                -- , (SessionMode, COMMAND)
229                , (LaunchMode, spawn "librewolf")
230                ])
231
232            , ((mod4Mask, xK_n), modeDispatch modeRef
233                [-- (Normal,       COMMAND)
234                --, (ResizeMode,   COMMAND)
235                --, (MoveMode,     COMMAND)
236                  (LayoutMode, sendMessage (MoveRight 10))
237                -- , (SessionMode, COMMAND)
238                -- , (LaunchMode,  COMMAND)
239                ])
240
241            , ((mod4Mask, xK_o), modeDispatch modeRef
242                [ -- (Normal, COMMAND)
243                -- , (ResizeMode,  COMMAND)
244                -- , (MoveMode,    COMMAND)
245                  (LayoutMode, sendMessage $ Toggle MIRROR)
246                -- , (SessionMode, COMMAND)
247                , (LaunchMode, spawn "obsidian")
248                ])
249
250            , ((mod4Mask, xK_b), modeDispatch modeRef
251                [ -- (Normal, COMMAND)
252                -- , (ResizeMode,  COMMAND)
253                -- , (MoveMode,    COMMAND)
254                  (LayoutMode, sendMessage $ Toggle NOBORDERS)
255                -- , (SessionMode, COMMAND)
256                -- , (LaunchMode,  COMMAND)
257                ])
258
259            , ((mod4Mask, xK_u), modeDispatch modeRef
260                [ -- (Normal, COMMAND)
261                -- , (ResizeMode,  COMMAND)
262                -- , (MoveMode,    COMMAND)
263                -- , (LayoutMode,  COMMAND)
264                -- , (SessionMode, COMMAND)
265                -- , (LaunchMode,  COMMAND)
266                ])
267
268            , ((mod4Mask, xK_t), modeDispatch modeRef
269                [ -- (Normal, COMMAND)
270                -- , (ResizeMode,  COMMAND)
271                -- , (MoveMode,    COMMAND)
272                -- , (LayoutMode,  COMMAND)
273                -- , (SessionMode, COMMAND)
274                 (LaunchMode, spawn myTerminal)
275                ])
276
277            , ((mod4Mask, xK_v), modeDispatch modeRef
278                [ -- (Normal, COMMAND)
279                -- , (ResizeMode,  COMMAND)
280                -- , (MoveMode,    COMMAND)
281                -- , (LayoutMode,  COMMAND)
282                -- , (SessionMode, COMMAND)
283                 (LaunchMode, spawn "nvim")
284                ])
285            ]
286        
287        withMode :: Mode -> IORef Mode -> X () -> X ()
288        withMode expected modeRef action = do
289            mode <- liftIO $ readIORef modeRef
290            when (mode == expected) $ do
291               liftIO $ writeIORef modeRef expected
292               action
293    
294        ------------------------------------------------------------------------
295        ---WORKSPACES
296        ------------------------------------------------------------------------
297        xmobarEscape :: String -> String
298        xmobarEscape = concatMap doubleLts
299          where
300                doubleLts '<' = "<<"
301                doubleLts x   = [x]
302        
303        myWorkspaces :: [String]
304        myWorkspaces = ["0", "1", "2", "3", "4", "5", "6", "7", "8"]
305
306        myManageHook :: Query (Data.Monoid.Endo WindowSet)
307        myManageHook = composeAll
308            [
309                className =? "Firefox"     --> doShift "<action=xdotool key super+1>www</action>"
310              , title =? "Vivaldi"         --> doShift "<action=xdotool key super+1>www</action>"
311              , title =? "irssi"           --> doShift "<action=xdotool key super+9>irc</action>"
312              , (className =? "Firefox" <&&> resource =? "Dialog") --> doFloat  -- Float Firefox Dialog
313            ] 
314
315        ------------------------------------------------------------------------
316        --- XMOBAR
317        ------------------------------------------------------------------------
318        myXmobarPP :: Handle -> IORef Mode -> PP
319        myXmobarPP xmproc modeRef = def {
320            ppCurrent            = xmobarColor "#50FA7b" "" . wrap " [" "] ",
321            ppVisible            = const "",
322            ppHidden             = const "",
323            ppHiddenNoWindows    = const "",
324            ppTitle              = xmobarColor "#f8f8f2" "" . shorten 60,
325            ppSep                = " ",
326            ppLayout             = xmobarColor "#ff79c6" "",
327            ppOrder              = \(ws:l:t:extras) -> extras ++ [ws, t],
328            ppExtras = [modeLogger modeRef, windowCountLogger, timeAndKernelLogger]
329
330            }
331
332        timeAndKernelLogger :: X (Maybe String)
333        timeAndKernelLogger = liftIO $ do
334           time <- getCurrentTime
335           let timeString = formatTime defaultTimeLocale "%Y-%m-%d %H:%M:%S" time
336           kernel <- readProcess "uname" ["-r"] ""
337           return $ Just $ xmobarColor "#6272A4" "" (kernel ++ " | " ++ timeString)
338        
339        dynamicLogTimeAndKernel :: IO String
340        dynamicLogTimeAndKernel = do
341          time <- dynamicLogTime
342          kernel <- kernelInfo
343          return (kernel ++ " | " ++ time)
344              
345        dynamicLogTime :: IO String
346        dynamicLogTime = do
347          time <- getCurrentTime
348          let timeString = formatTime defaultTimeLocale "%Y-%m-%d %H:%M:%S" time
349          return timeString
350
351        kernelInfo :: IO String
352        kernelInfo = do
353          kernel <- readProcess "uname" ["-r"] ""
354          return kernel
355          
356        modeLogger :: IORef Mode -> X (Maybe String)
357        modeLogger modeRef = do
358                mode <- liftIO $ readIORef modeRef
359                let icon txt = "<fn=1>" ++ txt ++ "</fn>"
360                let formatMode bg fg name = wrapColor bg fg (icon " \xE61F " ++ name) 
361                let fmt bg fg txt = "<fc=" ++ fg ++ "," ++ bg ++ "> " ++ txt ++ " </fc>"
362                return $ Just $ case mode of
363                       Normal       -> formatMode "#50FA7B" "#282A36" ( "NORMAL " )
364                       ResizeMode   -> formatMode "#FFB86C" "#282A36" ( "RESIZE " )
365                       MoveMode     -> formatMode "#8B39FD" "#282A36" ( "MOVE " )
366                       LayoutMode   -> formatMode "#FF79C6" "#282A36" ( "LAYOUT " )
367                       SessionMode  -> formatMode "#BD93F9" "#282A36" ( "SESSION " )
368                       LaunchMode   -> formatMode "#F1FA8C" "#282A36" ( "LAUNCH " )
369
370        windowCountLogger :: X (Maybe String)
371        windowCountLogger = withWindowSet $ \ws -> do
372          let count = length (W.index ws)
373          return $ Just $ xmobarColor "#ff79c6" "" (show count)
374          
375        updateModeLog :: IORef Mode -> IORef D.Client -> X ()
376        updateModeLog modeRef dbusRef = do
377            mode <- liftIO $ readIORef modeRef
378            dbus <- liftIO $ readIORef dbusRef
379            let modeText = case mode of
380                    Normal             -> " NORMAL "
381                    ResizeMode     -> " RESIZE "
382                    MoveMode       -> " MOVE "
383                    LayoutMode     -> " LAYOUT "
384                    SessionMode   -> " SESSION "
385                    LaunchMode    -> " LAUNCH "
386
387            let modeFile = "/tmp/xmonad_mode.txt"
388            liftIO $ do
389                handle <- openFile modeFile WriteMode
390                hPutStrLn handle modeText
391                hClose handle
392
393            io $ D.emit dbus (D.signal objectPath interfaceName memberName)
394               { D.signalBody = [D.toVariant (modeText)] }
395            where
396              objectPath = D.objectPath_ "/org/xmonad/Log"
397              interfaceName = D.interfaceName_ "org.xmonad.Log"
398              memberName = D.memberName_ "Update"
399            
400        wrapColor :: String -> String -> String -> String
401        wrapColor bg fg txt = "<box type=Full width=2 mb=0 color=" ++ bg ++ "><fc=" ++ fg ++ "," ++ bg ++ ">" ++ txt ++ "</fc></box>"
402        
403        ------------------------------------------------------------------------
404        --- LAYOUTS
405        ------------------------------------------------------------------------
406        
407        myLayoutHook = avoidStruts $ mouseResize $ windowArrange $ T.toggleLayouts floats $
408                       mkToggle (NBFULL ?? NOBORDERS ?? EOT) $ myDefaultLayout
409        myDefaultLayout =
410              tall 
411          ||| threeCol 
412          ||| threeRow 
413          ||| oneBig 
414          ||| noBorders monocle 
415          ||| space 
416          ||| floats
417
418
419        tall       = renamed [Replace "T"]     $ limitWindows 12 $ spacing 6 $ ResizableTall 1 (3/100) (1/2) [] 
420        threeCol   = renamed [Replace "3C"]    $ limitWindows 3  $ ThreeCol 1 (3/100) (1/2)
421        threeRow   = renamed [Replace "3R"]    $ limitWindows 3  $ Mirror $ mkToggle (single MIRROR) zoomRow
422        oneBig     = renamed [Replace "1B"]    $ limitWindows 6  $ Mirror $ mkToggle (single MIRROR) $ mkToggle (single REFLECTX) $ mkToggle (single REFLECTY) $ OneBig (5/9) (8/12)
423        monocle    = renamed [Replace "M"]     $ limitWindows 20 $ Full
424        space      = renamed [Replace "S"]     $ limitWindows 4  $ spacing 12 $ Mirror $ mkToggle (single MIRROR) $ mkToggle (single REFLECTX) $ mkToggle (single REFLECTY) $ OneBig (2/3) (2/3)
425        floats     = renamed [Replace "F"]     $ limitWindows 20 $ simplestFloat
426
427        myTitleTheme :: Theme
428        myTitleTheme = def {
429                fontName                = "xft:Berkeley Mono Nerd Font:style=Regular:pixelsize=11"
430                , inactiveBorderColor   = "#44475A"
431                , inactiveColor         = "#44475A"
432                , inactiveTextColor     = "#BD93F9"
433                , activeBorderColor     = "#44475A"
434                , activeColor           = "#44475A"
435                , activeTextColor       = "#50FA7B"
436                , urgentBorderColor     = "#FF4242"
437                , urgentTextColor       = "#262626"
438                , urgentColor           = "#FF4242"
439                , decoHeight            = 12
440        }
441      '';
442      enableConfiguredRecompile = true;
443    };
444  };
445
446
447}

and of course the corresponding .XMOBARRC:

 1Config { font    = "Berkeley Mono Nerd Font 9"
 2       , additionalFonts = [ "xft:BerkeleyMono Nerd Font:pixelsize=9" ]
 3       , textOffset = 0
 4       , bgColor = "#44475A"
 5       , fgColor = "#F8F8F2"
 6       , position = Top
 7       , lowerOnStart = True
 8       , hideOnStart = False
 9       , allDesktops = True
10       , persistent = True
11       , iconRoot = "/home/pho/.xmonad/xpm/"
12       , commands = [ Run Date "%H:%M:%S" "date" 10
13                    , Run Com "uname" ["-r"] "kernel" 36000
14                    , Run StdinReader
15                    ]
16       , sepChar = "%"
17       , alignSep = "}{"
18       , template = "%StdinReader% }{ <fc=#FF79C6>%kernel%</fc> <fc=#50FA7B>::</fc> <fc=#F1FA8C>%date%</fc>"
19       }

CONCLUSION

At first, XMonad’s modal controls feel like extra effort. The significant change that results from modal controls is the elimination of three-finger combinations. Additionally, there are more combinations that can be used with two fingers. This means you have to use two fingers each time you change modes, and two-finger combinations again for other functions. However, you can optimize your workflow by adapting your actions to the mode. For example, spawning as many terminals as you need in normal mode and resizing them to the size you need in resize mode so you can then work with them. My workflow has been quite the opposite so far. Windows are spawned, used, closed, opened, resized, used, and closed. Many of these actions are three-finger combinations and, over time, take their toll on your hands and fingers. The keybindings I’m currently using certainly still need to be optimized, but for now, they work, and XMonad behaves like Vim. I created most of the modal configuration for XMonad on my ThinkPad with the default QWERTY keyboard, so a configuration for something like KYB3RKEYS would look completely different. Anyone using other layouts and wanting to provide the appropriate XMonad config for them is welcome to do so; I’ll include it in the repo. All in all, this is a solid foundation from which you can continue to tweak the settings to further refine and improve the user experience.

Happy Hacking!


[~] BACK