1 {-# LANGUAGE NamedFieldPuns #-}
 
   2 {-# OPTIONS_GHC -Wall #-}
 
   3 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
 
   5 import qualified Data.Char as Char
 
   6 import Data.List as List
 
   9 import qualified Data.Map as Map
 
  10 import Control.Arrow (first)
 
  12 -- import XMonad.Actions.DwmPromote
 
  13 -- import XMonad.Actions.Warp
 
  14 -- import XMonad.Layout.Maximize
 
  15 -- import XMonad.Layout.Monitor
 
  16 -- import XMonad.Layout.ResizableTile
 
  17 -- import XMonad.Layout.TabBarDecoration
 
  18 -- import XMonad.Util.EZConfig
 
  19 -- import XMonad.Util.EZConfig(additionalKeys)
 
  20 -- import XMonad.Util.WorkspaceCompare
 
  21 import XMonad hiding ((|||))
 
  22 import XMonad.Actions.CopyWindow
 
  23 import XMonad.Actions.CycleWS
 
  24 import XMonad.Actions.SwapWorkspaces
 
  25 import XMonad.Actions.UpdatePointer
 
  26 import XMonad.Config.Azerty
 
  27 import XMonad.Hooks.DynamicLog
 
  28 import XMonad.Hooks.EwmhDesktops
 
  29 import XMonad.Hooks.ManageDocks
 
  30 import XMonad.Hooks.ManageHelpers
 
  31 import XMonad.Hooks.Rescreen
 
  32 import XMonad.Hooks.SetWMName
 
  33 import XMonad.Hooks.StatusBar
 
  34 import XMonad.Hooks.UrgencyHook
 
  35 import XMonad.Layout.Fullscreen
 
  36 import XMonad.Layout.Grid
 
  37 import XMonad.Layout.LayoutCombinators
 
  38 import XMonad.Layout.Magnifier
 
  39 import XMonad.Layout.MultiToggle
 
  40 import XMonad.Layout.MultiToggle.Instances
 
  41 import XMonad.Layout.NoBorders
 
  42 import XMonad.Layout.ResizableTile
 
  43 import XMonad.Layout.Spiral
 
  44 import XMonad.Layout.Tabbed
 
  45 import XMonad.Layout.ThreeColumns
 
  47 import XMonad.Prompt.FuzzyMatch
 
  48 import XMonad.Prompt.Pass
 
  49 import XMonad.Prompt.Window
 
  50 --import XMonad.Operations (unGrab) -- TODO: needs xmonad 0.18
 
  51 import XMonad.Util.SpawnOnce
 
  52 import qualified XMonad.StackSet as W
 
  55   withUrgencyHook NoUrgencyHook $
 
  56   -- dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] } $
 
  57   --addAfterRescreenHook myAfterRescreenHook $
 
  58   addRandrChangeHook (spawnExec "autorandr --change") $
 
  59   dynamicSBs barSpawner $
 
  61   setEwmhActivateHook doAskUrgent $
 
  66   , focusFollowsMouse = True
 
  67   , focusedBorderColor = "#00b10b"
 
  68   , handleEventHook = handleEventHook def
 
  69   , keys = \conf@XConfig{XMonad.modMask} ->
 
  71       let xK_XF86Backward = 0x1008ff26
 
  72           xK_XF86Forward = 0x1008ff27 in
 
  75         ((modMask, xK_Return), spawnExec $ XMonad.terminal conf)
 
  77       , ((modMask, xK_Menu), spawnCommand)
 
  78       , ((modMask, xK_space), spawnCommand)
 
  79       -- Browse the filesystem
 
  80       , ((modMask, xK_BackSpace), spawnExec "systemd-run --user --unit=app-org.rofi.caja@$RANDOM -p CollectMode=inactive-or-failed caja")
 
  83       , ((0, xK_Pause), {-unGrab >>-} spawnExec "loginctl lock-session \"$XDG_SESSION_ID\"")
 
  84       , ((modMask, xK_Delete), {-unGrab >>-} spawnExec "loginctl lock-session \"$XDG_SESSION_ID\"")
 
  86       -- Take a full screenshot
 
  87       , ((0, xK_Print), spawn "mkdir -p ~/Images/screenshots && scrot --quality 42 ~/Images/screenshots/'%Y-%m-%d_%H-%M-%S.png' && caja ~/Images/screenshots")
 
  88       -- Take a selective screenshot
 
  89       , ((modMask, xK_Print), spawn "select-screenshot")
 
  92       , ((0, 0x1008FF12), spawnExec "pactl -- set-sink-mute @DEFAULT_SINK@ toggle") -- XF88AudioMute
 
  93       , ((0, 0x1008FF11), spawnExec "pactl -- set-sink-volume @DEFAULT_SINK@ -5%") -- XF86AudioLowerVolume
 
  94       , ((0, 0x1008FF13), spawnExec "pactl -- set-sink-volume @DEFAULT_SINK@ +5%") -- XF86AudioRaiseVolume
 
  96       -- , ((0, 0x1008FF16), spawnExec "")
 
  98       -- , ((0, 0x1008FF14), spawnExec "")
 
 100       -- , ((0, 0x1008FF17), spawnExec "")
 
 102       -- , ((0, 0x1008FF2C), spawnExec "eject -T")
 
 104       -- Close focused window.
 
 105       , ((modMask, xK_Escape), kill)
 
 108       , ((modMask, xK_c), spawnExec "clipster --select --primary")
 
 110       -- Temporarily maximize a window
 
 111       , ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle FULL)
 
 112       -- , ((modMask, xK_f), withFocused (sendMessage . maximizeRestore))
 
 114       -- Cycle through the available layout algorithms
 
 115       , ((modMask, 0x13bd),        sendMessage NextLayout) -- oe (²)
 
 116       , ((modMask, xK_ampersand),  sendMessage $ JumpToLayout "ResizableTall") -- & (1)
 
 117       , ((modMask, xK_eacute),     sendMessage $ JumpToLayout "Mirror ResizableTall") -- é (2)
 
 118       , ((modMask, xK_quotedbl),   sendMessage $ JumpToLayout "Tabbed Simplest") -- ' (3)
 
 119       , ((modMask, xK_apostrophe), sendMessage $ JumpToLayout "Magnifier Grid") -- " (4)
 
 120       , ((modMask, xK_parenleft),  sendMessage $ JumpToLayout "Spiral") -- ( (5)
 
 121       , ((modMask, xK_minus),      sendMessage $ JumpToLayout "Full") -- - (6)
 
 122       , ((modMask, xK_egrave),     sendMessage $ JumpToLayout "ThreeCol") -- è (7)
 
 124       -- Reset the layouts on the current workspace to default
 
 125       -- , ((modMask .|. shiftMask, xK_space), setLayout $ XMonad.layoutHook conf)
 
 127       -- Resize viewed windows to the correct size.
 
 128       , ((modMask, xK_n), refresh)
 
 130       -- Move focus between windows
 
 131       , ((modMask, xK_Tab), windows W.focusDown)
 
 132       , ((modMask .|. shiftMask, xK_Tab), windows W.focusUp)
 
 133       , ((modMask, xK_i), windows W.focusUp)
 
 134       , ((modMask, xK_k), windows W.focusDown)
 
 136       -- Move focus to the master window
 
 137       , ((modMask, xK_m), windows W.focusMaster)
 
 138       -- Swap the focused window and the master window
 
 139       , ((modMask, xK_ugrave), windows W.swapMaster)
 
 141       -- Swap the focused window with the next window.
 
 142       --, ((modMask, xK_o), windows W.swapDown >> windows W.focusMaster)
 
 143       -- Swap the focused window with the previous window.
 
 144       , ((modMask, xK_m), windows W.swapUp >> windows W.focusMaster)
 
 146       -- Push window back into tiling.
 
 147       , ((modMask, xK_t), withFocused $ windows . W.sink)
 
 149       -- Change the number of windows in the master area
 
 150       , ((modMask, xK_Up), sendMessage $ IncMasterN 1)
 
 151       , ((modMask, xK_Down), sendMessage $ IncMasterN (-1))
 
 153       -- Toggle the status bar gap.
 
 154       , ((modMask, xK_b), sendMessage ToggleStruts)
 
 157       , ((modMask .|. shiftMask, xK_End), io exitSuccess)
 
 159       , ((modMask, xK_End), restart "xmonad" True)
 
 161       , ((modMask, xK_p), passPrompt promptConfig)
 
 162       , ((modMask .|. controlMask, xK_p), passGeneratePrompt promptConfig)
 
 163       , ((modMask .|. controlMask  .|. shiftMask, xK_p), passRemovePrompt promptConfig)
 
 164       , ((modMask, xK_Tab), windowMultiPrompt promptConfig [(Goto, allWindows), (Goto, wsWindows)])
 
 166       -- Workspace management
 
 167       -- XF86Back: Switch to previous workspace
 
 168       , ((0, xK_XF86Backward), prevWS)
 
 169       , ((modMask, xK_j), prevWS)
 
 170       , ((modMask, xK_Page_Up), prevWS)
 
 171       -- Switch to next workspace
 
 172       , ((0, xK_XF86Forward), nextWS)
 
 173       , ((modMask, xK_l), nextWS)
 
 174       , ((modMask, xK_Page_Down), nextWS)
 
 175       -- XF86Back: Move the current client to the previous workspace and go there
 
 176       , ((modMask, xK_XF86Backward), shiftToPrev >> prevWS)
 
 177       , ((modMask .|. shiftMask, xK_j), shiftToPrev >> prevWS)
 
 178       -- Move the current client to the next workspace and go there
 
 179       , ((modMask, xK_XF86Forward), shiftToNext >> nextWS)
 
 180       , ((modMask .|. shiftMask, xK_l), shiftToNext >> nextWS)
 
 181       -- Switch to previous workspace
 
 182       -- Switch to next workspace
 
 184       -- Move the current client to the previous workspace
 
 185       , ((0 .|. shiftMask   , xK_XF86Backward), shiftToPrev          )
 
 186       -- Move the current client to the next workspace
 
 187       , ((0 .|. shiftMask   , xK_XF86Forward), shiftToNext          )
 
 190       -- Toggle copying window on all workspaces (sticky window)
 
 191       , ((modMask, xK_s), do
 
 192           copies <- wsContainingCopies -- NOTE: consider only hidden workspaces
 
 194            [] -> windows copyToAll
 
 195            _  -> killAllOtherCopies
 
 198       -- Resize the master area
 
 199       , ((modMask, xK_Left), sendMessage Shrink)
 
 200       , ((modMask, xK_Right), sendMessage Expand)
 
 201       -- Resize windows in ResizableTall mode
 
 202       , ((modMask .|. shiftMask, xK_Left), sendMessage MirrorShrink)
 
 203       , ((modMask .|. shiftMask, xK_Right), sendMessage MirrorExpand)
 
 206       -- mod-[F1..F9], Switch to workspace N
 
 207       -- mod-shift-[F1..F9], Move client to workspace N
 
 208       [ ((m .|. modMask, k), windows $ f i)
 
 209       | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
 
 210                   zip (workspaces conf) [xK_1 ..]
 
 211       , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
 
 213       {- NOTE: with Xinerama
 
 214       [((m .|. modMask, k), windows $ onCurrentScreen f i)
 
 215        | (i, k) <- zip (workspaces' conf) [xK_F1 ..]
 
 216        , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] ]
 
 219       -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
 
 220       -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
 
 221       [ ((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
 
 222       | (key, sc) <- zip [xK_w, xK_e, xK_r] [0 ..]
 
 223       , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
 
 226       -- mod-shift-[F1..F9], Swap workspace with workspace N
 
 227       -- mod-shift-[1..9], Swap workspace with workspace N
 
 228       [ ((modMask .|. controlMask, k), windows $ swapWithCurrent i)
 
 229       | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
 
 230                   zip (workspaces conf) [xK_1 ..]
 
 232       {- NOTE: with Xinerama
 
 233       [((modMask .|. controlMask, k), windows $ onCurrentScreen swapWithCurrent i)
 
 234        | (i, k) <- zip (workspaces' conf) [xK_F1 ..] ]
 
 236       , layoutHook         = smartBorders $
 
 237                              mkToggle (NOBORDERS ?? FULL ?? EOT) $ -- enable temporarily maximizing a window
 
 238                              avoidStruts $ -- prevents windows from overlapping dock windows
 
 239                              let tall = ResizableTall 1 (1%200) (8%13) [] in
 
 240                              tabbed shrinkText tabConfig
 
 243                              ||| magnifiercz (13%10) Grid
 
 245                              ||| noBorders (fullscreenFull Full)
 
 246                              ||| ThreeColMid 1 (1%200) (1%2)
 
 247                              -- ||| Tall 1 (3/100) (1/2)
 
 248       , manageHook         = composeAll
 
 249                              -- [ , isFullscreen --> (doF W.focusDown <+> doFullFloat)
 
 250                              [ isFullscreen --> doFullFloat
 
 252                              , manageDocks -- NOTE: do not tile dock windows
 
 253                              , resource  =? "desktop_window" --> doIgnore
 
 254                              , className =? "Gimp" --> doFloat
 
 255                              , resource  =? "gpicview" --> doSink
 
 256                              , className =? "mpv" --> doFloat
 
 257                              , className =? "ultrastardx" --> doSink
 
 258                              --, className =? "MPlayer" --> doShift "3:media" -- <+> doFloat
 
 259                              --, className =? "vlc" --> doShift "3:media"
 
 260                              , className =? "trayer" --> doIgnore
 
 263   , mouseBindings = \XConfig{XMonad.modMask} ->
 
 266       -- mod-button1, Set the window to floating mode and move by dragging
 
 267         ((modMask, button1), \w -> focus w >> mouseMoveWindow w)
 
 269       -- mod-button2, Raise the window to the top of the stack
 
 270       , ((modMask, button2), \w -> focus w >> windows W.swapMaster)
 
 272       -- mod-button3, Set the window to floating mode and resize by dragging
 
 273       , ((modMask, button3), \w -> focus w >> mouseResizeWindow w)
 
 275       , ((modMask, button4), \_ -> windows W.focusUp)
 
 276       , ((modMask, button5), \_ -> windows W.focusDown)
 
 278       -- Cycle through workspaces
 
 279       , ((controlMask .|. modMask, button5), nextNonEmptyWS)
 
 280       , ((controlMask .|. modMask, button4), prevNonEmptyWS)
 
 282   , normalBorderColor = "#7C7C7C"
 
 283   , startupHook = setWMName "XMonad"
 
 284       <+> spawnExec "wmname XMonad"
 
 285       <+> spawnExec "xrdb -all .Xresources"
 
 286       <+> spawn "sleep 1 && xmodmap .Xmodmap"
 
 287       <+> spawnExec "xset r rate 250 25"
 
 288       <+> spawnExec "xset b off"
 
 289       <+> spawnExec "xhost local:root"
 
 290       <+> spawnExec "setxkbmap -option keypad:pointerkeys"
 
 291       -- Useful for programs launched by rofi
 
 292       <+> spawnExec (unwords [ "systemctl --user import-environment"
 
 293                              , "DBUS_SESSION_BUS_ADDRESS"
 
 294                              , "GDK_PIXBUF_MODULE_FILE"
 
 295                              , "GIO_EXTRA_MODULES"
 
 303                              , "LD_LIBRARY_PATH" -- For sane and pipewire
 
 305                              , "NIX_PROFILES" -- fcitx5 does not work without it…
 
 306                              , "PASSWORD_STORE_DIR"
 
 308                              , "QTWEBKIT_PLUGIN_PATH"
 
 316       -- <+> spawnOnce "exec arbtt-capture -r 60"
 
 317       -- <+> spawnOnce "exec parcellite"
 
 318       -- <+> spawnOnce "exec xautolock"
 
 319       -- <+> spawnOnce "exec redshift-gtk -l -45.7800:1.9700 -t 6500:3700"
 
 320       <+> spawnOnce "exec nm-applet"
 
 321   , terminal = "urxvtc"
 
 322   , workspaces = {- withScreens nScreens $ -}
 
 323                  {-["1:work","2:web","3:media"] ++-}
 
 324                  map show [1::Int .. 9]
 
 325   , logHook = updatePointer (0.5, 0.5) (0, 0)
 
 326     -- >> updatePointer (Relative 0.5 0.5)
 
 330      { activeBorderColor   = "#7C7C7C"
 
 331      , activeColor         = "#000000"
 
 332      , activeTextColor     = "#00FF00"
 
 333      , inactiveBorderColor = "#7C7C7C"
 
 334      , inactiveColor       = "#000000"
 
 335      , inactiveTextColor   = "#EEEEEE"
 
 336      , fontName            = "Hack 7"
 
 339 spawnCommand = spawnExec "rofi -show run -no-disable-history -run-command \"bash -c 'systemd-run --user --unit=app-org.rofi.\\$(systemd-escape \\\"{cmd}\\\")@\\$RANDOM -p CollectMode=inactive-or-failed {cmd}'\""
 
 341 barSpawner :: ScreenId -> X StatusBarConfig
 
 342 barSpawner 0 = pure $ topXmobar <> traySB
 
 343 --barSpawner 1 = pure $ xmobar1
 
 344 barSpawner _ = pure $ topXmobar -- nothing on the rest of the screens
 
 346 -- Display properties of the root window:
 
 347 -- xprop -display $DISPLAY -root
 
 348 topXmobar = statusBarPropTo "_XMONAD_XMOBAR0" "xmobar -x 0 ~/.config/xmonad/xmobar0.hs" (pure topPP)
 
 352       { ppCurrent = xmobarColor "black" "#CCCCCC"
 
 353       , ppHidden  = xmobarColor "#CCCCCC" "black"
 
 354       , ppHiddenNoWindows = xmobarColor "#606060" "black"
 
 355       , ppLayout  = \s -> xmobarColor "black" "#606060" $
 
 357                        "ResizableTall"        -> " | "
 
 358                        "Mirror ResizableTall" -> " - "
 
 359                        "Tabbed Simplest"      -> " + "
 
 360                        "Magnifier Grid"       -> " ~ "
 
 366       , ppTitle   = xmobarColor "white" "black" . shorten 50
 
 367       , ppUrgent  = xmobarColor "yellow" "black"
 
 371 traySB :: StatusBarConfig
 
 378         , "--distancefrom top,right"
 
 382         , "--monitor primary"
 
 385         , "--transparent true"
 
 386         , "--widthtype request"
 
 392 nextNonEmptyWS _ = moveTo Next (WSIs ((not .) <$> isWindowSpaceVisible))
 
 393 prevNonEmptyWS _ = moveTo Prev (WSIs ((not .) <$> isWindowSpaceVisible))
 
 395 isWindowSpaceVisible :: X (WindowSpace -> Bool)
 
 396 isWindowSpaceVisible = do
 
 397   vs <- gets (map (W.tag . W.workspace) . W.visible . windowset)
 
 398   return (\w -> W.tag w `elem` vs)
 
 400 spawnExec s = spawn $ List.unwords $ [ "exec" ] <> systemdCat <> [ s ]
 
 401 systemdCat = [ "systemd-cat" , "--priority=info", "--stderr-priority=warning", "--level-prefix=false" , "--" ]
 
 403 promptConfig :: XPConfig
 
 405   { font                = "xft:monospace-"<>show fontSize
 
 409   , fgHLight            = "#000000"
 
 410   , borderColor         = "darkgreen"
 
 411   , promptBorderWidth   = 1
 
 412   , promptKeymap        = promptKeyMap
 
 413   , position            = CenteredAt { xpCenterY = 0.3, xpWidth = 0.5 }
 
 414   , height              = fontSize + 11
 
 418   , autoComplete        = Nothing -- Just 500000 -- nanoseconds
 
 419   , showCompletionOnTab = False
 
 420   , completionKey       = (0, xK_Down)
 
 421   , prevCompletionKey   = (0, xK_Up)
 
 422   , searchPredicate     = fuzzyMatch -- isPrefixOf
 
 424   , defaultPrompter     = const ""
 
 425   , alwaysHighlight     = True
 
 426   , maxComplRows        = Just 10
 
 427   , maxComplColumns     = Just 1
 
 428   , changeModeKey       = xK_twosuperior
 
 433 promptKeyMap :: Map.Map (KeyMask,KeySym) (XP ())
 
 434 promptKeyMap = Map.fromList $
 
 435      List.map (first $ (,) controlMask) -- control + <key>
 
 436        [ (xK_z, killBefore)               -- kill line backwards
 
 437        , (xK_k, killAfter)                -- kill line forwards
 
 438        , (xK_u, killBefore)               -- kill line backwards
 
 439        , (xK_a, startOfLine)              -- move to the beginning of the line
 
 440        , (xK_e, endOfLine)                -- move to the end of the line
 
 441        , (xK_m, deleteString Next)        -- delete a character foward
 
 442        , (xK_b, moveCursor Prev)          -- move cursor forward
 
 443        , (xK_f, moveCursor Next)          -- move cursor backward
 
 444        , (xK_BackSpace, killWord Prev)    -- kill the previous word
 
 445        , (xK_y, pasteString)              -- paste a string
 
 446        , (xK_g, quit)                     -- quit out of prompt
 
 447        , (xK_bracketleft, quit)
 
 450      List.map (first $ (,) altMask)     -- meta key + <key>
 
 451        [ (xK_BackSpace, killWord Prev)    -- kill the prev word
 
 452        , (xK_f, moveWord Next)            -- move a word forward
 
 453        , (xK_b, moveWord Prev)            -- move a word backward
 
 454        , (xK_d, killWord Next)            -- kill the next word
 
 455        , (xK_n, moveHistory W.focusUp')   -- move up through history
 
 456        , (xK_p, moveHistory W.focusDown') -- move down through history
 
 459      List.map (first $ (,) 0) -- <key>
 
 460        [ (xK_Return, setSuccess True >> setDone True)
 
 461        , (xK_KP_Enter, setSuccess True >> setDone True)
 
 462        , (xK_BackSpace, deleteString Prev)
 
 463        , (xK_Delete, deleteString Next)
 
 464        , (xK_Left, moveCursor Prev)
 
 465        , (xK_Right, moveCursor Next)
 
 466        , (xK_Home, startOfLine)
 
 467        , (xK_End, endOfLine)
 
 468        , (xK_Down, moveHistory W.focusUp')
 
 469        , (xK_Up, moveHistory W.focusDown')