aboutsummaryrefslogtreecommitdiff
path: root/gui/conf/xmonad.hs
blob: 71990e96a14962a89fb1b3aa5bcbc552139b3328 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
import XMonad
import XMonad.Util.EZConfig
import XMonad.StackSet

import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.InsertPosition

import XMonad.Layout.NoBorders
import XMonad.Layout.Tabbed
import XMonad.Layout.ToggleLayouts
import XMonad.Layout.MultiToggle
import XMonad.Layout.MultiToggle.Instances

import XMonad.Util.Themes
import XMonad.Util.NamedScratchpad

import XMonad.Actions.SpawnOn
import XMonad.Actions.CycleWS
import XMonad.Actions.WindowBringer
import XMonad.Actions.GroupNavigation
import XMonad.Actions.FloatKeys

import System.Exit
import Data.Maybe
import Control.Monad (when)
import qualified Data.Map as M

workspaces :: [WorkspaceId]
workspaces = map show [1 .. 9 :: Int]

customTabTheme = (theme xmonadTheme)
  { fontName      = "xft:Iosevka Medium-12"
  , decoHeight    = 20
  , activeTextColor     = "#222222"
  , activeColor         = "#909737"
  , inactiveTextColor   = "#999999"
  , inactiveColor       = "#161616"
  , activeBorderColor   = "#909737"
  , inactiveBorderColor = "#161616" }

availableLayouts = id
  . smartBorders
  . mkToggle (single NBFULL)
  $ toggleLayouts tabs tiles
  where
    tabs  = tabbed shrinkText customTabTheme
    tiles = mkToggle (single MIRROR) $ Tall 1 delta ratio
    ratio = 1/2
    delta = 3/100

windowBringerDmenuConfig = def { menuCommand  = "rofi"
                               , menuArgs     = [ "-p", "win", "-dmenu", "-i" ] }

floatRectTop    h = hideScreenBorder $ RationalRect (1/20) 0      (18/20) h
floatRectBottom h = hideScreenBorder $ RationalRect (1/20) (1-h)  (18/20) h
floatRectLeft   w = hideScreenBorder $ RationalRect 0      (1/20) w       (18/20)
floatRectRight  w = hideScreenBorder $ RationalRect (1-w)  (1/20) w       (18/20)

dropUp        = floatRectBottom $ 2/3
dropUpLarge   = floatRectBottom $ 18/20
dropDown      = floatRectTop    $ 2/3
dropDownLarge = floatRectTop    $ 18/20
sideBarLeft   = floatRectLeft   $ 1/2
sideBarRight  = floatRectRight  $ 1/2

scratchpads = [ NS "terminal" "kitty --class=scratchterm" (className =? "scratchterm")
                   (customFloating dropDown)
              , NS "browser" "firefox" (className =? "Firefox")
                   (customFloating dropDownLarge)
              , NS "documentation" "zeal" (className =? "Zeal")
                   (customFloating dropDown)
              , NS "messaging" "telegram-desktop" (className =? "TelegramDesktop")
                   (customFloating sideBarRight) ]

keybindings =
-- xmonad session control
  [ ("C-M1-<Escape>"    , io (exitWith ExitSuccess))
  , ("C-M1-<Backspace>" , spawn "xmonad --restart")
-- application launchers
  , ("M-<Space>"     , spawn "rofi -show combi")
  , ("M-<Return>"    , spawn "kitty")
  , ("M-S-<Return>"  , spawn "nvim-qt")
-- window management
  , ("M-q"           , windows $ shift "NSP")
  , ("M-S-q"         , kill)
  , ("M-j"           , windows focusDown)
  , ("M-k"           , windows focusUp)
  , ("M-S-j"         , windows swapDown)
  , ("M-S-k"         , windows swapUp)
  , ("M-h"           , sendMessage Shrink)
  , ("M-l"           , sendMessage Expand)
  , ("M-<Backspace>" , nextMatch History (return True))
-- window bringer
  , ("M-a"           , gotoMenuConfig  windowBringerDmenuConfig)
  , ("M-S-a"         , bringMenuConfig windowBringerDmenuConfig)
-- scratchpads
  , ("M-b"           , namedScratchpadAction scratchpads "browser")
  , ("M-d"           , namedScratchpadAction scratchpads "documentation")
  , ("M-m"           , namedScratchpadAction scratchpads "messaging") ] ++
-- workspace selection
  [ (p ++ [k]        , windows $ f i) | (i, k) <- zip Main.workspaces ['1' .. '9']
                                      , (p, f) <- [ ("M-"   , greedyView)
                                                  , ("M-S-" , shift) ] ] ++
-- workspace management
  [ ("M-s l"         , sendMessage ToggleLayout)
  , ("M-s m"         , sendMessage $ XMonad.Layout.MultiToggle.Toggle MIRROR)
  , ("M-s f"         , sendMessage $ XMonad.Layout.MultiToggle.Toggle NBFULL)
  , ("M-s p"         , toggleWS' ["NSP"])
  , ("M-s j"         , moveTo  Next nonEmptyWS)
  , ("M-s k"         , moveTo  Prev nonEmptyWS)
  , ("M-S-s j"       , shiftTo Next nonEmptyWS >> moveTo Next nonEmptyWS)
  , ("M-S-s k"       , shiftTo Prev nonEmptyWS >> moveTo Prev nonEmptyWS)
-- floating placement
  , ("M-w t"         , withFocused $ windows . sink)
  , ("M-w f"         , withFocused $ placeFloating $ RationalRect 0 0 1 1)
  , ("M-w j"         , withFocused $ placeFloating dropUp)
  , ("M-w S-j"       , withFocused $ placeFloating dropUpLarge)
  , ("M-w k"         , withFocused $ placeFloating dropDown)
  , ("M-w S-k"       , withFocused $ placeFloating dropDownLarge)
  , ("M-w h"         , withFocused $ placeFloating sideBarLeft)
  , ("M-w l"         , withFocused $ placeFloating sideBarRight)
-- system control
  , ("M-c <Up>"      , spawn "amixer sset Master 10%+")
  , ("M-c <Down>"    , spawn "amixer sset Master 10%-")
  , ("M-c m"         , spawn "amixer sset Master toggle") ]

customEventHook = do
  handleEventHook def
  fullscreenEventHook

customLogHook = do
  historyHook
  customizeBorderWhen (isFloat <&&> isNotFullscreen) "#aadb0f" 6

main = xmonad $ ewmh
              $ def
  { modMask             = mod4Mask -- super key as modifier
  , borderWidth         = 3
  , normalBorderColor   = "#161616"
  , focusedBorderColor  = "#909737"
  , keys                = \c -> mkKeymap c keybindings
  , startupHook         = return () >> checkKeymap def keybindings
  , handleEventHook     = customEventHook
  , layoutHook          = availableLayouts
  , manageHook          = insertPosition Below Newer <+> namedScratchpadManageHook scratchpads
  , logHook             = customLogHook }
  `additionalKeys`
  [ ((noModMask, xK_Menu) , namedScratchpadAction scratchpads "terminal") ]

nonEmptyWS = WSIs $ return (\w -> nonNSP w && nonEmpty w)
  where nonNSP (Workspace tag _ _) = tag /= "NSP"
        nonEmpty = isJust . stack

placeFloating :: RationalRect -> Window -> X ()
placeFloating rect = windows . (flip XMonad.StackSet.float $ rect)

windowSize w = do
  r <- withDisplay $ (\d -> io $ getWindowAttributes d w)
  return (fromIntegral $ wa_width r, fromIntegral $ wa_height r)

withCurrentScreen     f = withWindowSet     $ \ws -> f (current ws)
withCurrentScreenRect f = withCurrentScreen $ \s  -> f (screenRect (screenDetail s))

screenResolution = withCurrentScreenRect $ \r -> return (rect_width r, rect_height r)

isNotFullscreen :: Query Bool
isNotFullscreen = ask >>= (\w -> liftX $ do (ww, wh) <- windowSize w
                                            (sw, sh) <- screenResolution
                                            return $ not (ww == sw && wh == sh))

isFloat :: Query Bool
isFloat = ask >>= (\w -> liftX $ withWindowSet $ \ws -> return $ (M.member w (floating ws)))

customizeBorderWhen :: Query Bool -> String -> Dimension -> X ()
customizeBorderWhen q color width = withFocused $ \w -> runQuery q w >>= flip when (setWindowBorder' color width w)

setWindowBorder' :: String -> Dimension -> Window -> X ()
setWindowBorder' color