aboutsummaryrefslogtreecommitdiff
path: root/XMonad/xmonad.hs
blob: 2be29b07f2aec3f87f6c375d26c964d26fb760e8 (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
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
import XMonad
import qualified XMonad.StackSet as W

-- actions
import XMonad.Actions.CycleWS (moveTo, shiftTo, WSType(..), nextScreen, prevScreen)
import XMonad.Actions.CopyWindow
import XMonad.Actions.CycleWS
import XMonad.Actions.GridSelect
import XMonad.Actions.SwapWorkspaces
import XMonad.Actions.WindowBringer
import XMonad.Actions.MouseResize

-- layouts modifiers
import XMonad.Layout.Spacing
import XMonad.Layout.LayoutModifier
import XMonad.Layout.WindowNavigation as WN

-- Layouts
import XMonad.Layout.AvoidFloats
import XMonad.Layout.BinarySpacePartition as BSP
import XMonad.Layout.CenteredMaster
import XMonad.Layout.Grid
import XMonad.Layout.ThreeColumns
import XMonad.Layout.TwoPane
import XMonad.Layout.Spiral
import XMonad.Layout.ResizableTile
import XMonad.Layout.Tabbed

-- hooks
import XMonad.Hooks.SetWMName
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.DynamicLog
-- import XMonad.Hooks.FadeInactive

-- utilities
import XMonad.Util.SpawnOnce
import XMonad.Util.EZConfig (additionalKeys)
import XMonad.Util.Cursor
import XMonad.Util.Paste
import XMonad.Util.Run

myStartupHook :: X ()
myStartupHook = do
          spawnOnce "/home/zt/.xmonad/baraction | lemonbar -g 1366x21+0+0  -B '#171520' -F '#ffffff' -f 'Source Han Sans JP:size=10' -n 'XMobar'"
	  spawnOnce "/home/zt/.config/scripts/weather"
          spawnOnce "nitrogen --restore &"
          spawnOnce "picom &"
          spawnOnce "deadd-notification-center &"
          -- spawnOnce "firefox &"
          spawnOnce "sxhkd &"
          spawnOnce "weather"
          spawnOnce "betterlockscreen -l -t 'Welcome, Vidhu Kant!'"
          spawnOnce "sleep 3; trayer --align center --edge top --width 20 --height 21 --expand true --distance 90 --distancefrom right --tint 0x171520 --transparent true --alpha 0 --iconspacing 8"
	  setWMName "Oppai"
          setDefaultCursor xC_left_ptr


-- bar actions


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


-- defaults

-- myFont :: String
-- myFont = "Roboto"

myModMask :: KeyMask
myModMask = mod4Mask 

myTerminal :: String
myTerminal = "st"

myDmenu :: String
myDmenu = "run_dmenu"

myBrowser :: String
myBrowser = "firefox"

-- myEditor :: String
-- myEditor = "vim"

-- wm variables

nBorder = "#000000" -- "#3804f4" -- "#bf00ff"
fBorder = "#6e02fc"

myBorderWidth = 1

sGap = 0 -- screen gap
wGap = 1 -- window gap

myExtraWorkspaces = [(xK_0, "  十  ")] -- ,(xK_minus, "tmp"),(xK_equal, "swap")]
myWorkspaces = ["  一  ","  二  ","  三  ","  四  ","  五  ","  六  ","  七  ","  八  ", "  九  "] ++ (map snd myExtraWorkspaces)


-- keybindings
myKeys = [
         ((mod4Mask, xK_Return), spawn (myTerminal ++ " -e fish"))
         , ((mod1Mask, xK_p), spawn "/home/zt/.config/scripts/run_dmenu")
         , ((mod1Mask, xK_w), kill1)
         , ((mod1Mask .|. shiftMask, xK_k), kill1)
         , ((mod1Mask, xK_o), withFocused $ windows . W.sink) -- unfloat windows

         -- view prev/next workspaces
         , ((mod1Mask, xK_h), prevWS)
         , ((mod1Mask, xK_l), nextWS)

         -- move to prev/next workspaces
         , ((mod1Mask .|. shiftMask, xK_h), shiftToPrev >> prevWS)
         , ((mod1Mask .|. shiftMask, xK_l), shiftToNext >> nextWS)

         -- modify gaps on runtime
         , ((mod1Mask, xK_equal), incWindowSpacing 1)
         , ((mod1Mask, xK_minus), decWindowSpacing 1)
         , ((mod1Mask .|. shiftMask, xK_equal), incScreenSpacing 1)  
         , ((mod1Mask .|. shiftMask, xK_minus), decScreenSpacing 1) 
         
         , ((mod4Mask .|. shiftMask, xK_Return), windows W.swapMaster) -- Swap the focused window and the master window

         -- these keybindings are for WindowNavigation
         -- and they conflict with BSP layout

         -- directional navigation of windows
         , ((mod4Mask,                 xK_l), sendMessage $ Go R)
         , ((mod4Mask,                 xK_h), sendMessage $ Go L)
         , ((mod4Mask,                 xK_k), sendMessage $ Go U)
         , ((mod4Mask,                 xK_j), sendMessage $ Go D)

         -- swap windows
         , ((mod4Mask .|. shiftMask, xK_l), sendMessage $ WN.Swap R)
         , ((mod4Mask .|. shiftMask, xK_h), sendMessage $ WN.Swap L)
         , ((mod4Mask .|. shiftMask, xK_k), sendMessage $ WN.Swap U)
         , ((mod4Mask .|. shiftMask, xK_j), sendMessage $ WN.Swap D)
         
         -- cycle through windows 
         , ((mod1Mask, xK_j), windows W.focusDown)
         , ((mod1Mask, xK_k), windows W.focusUp)

         -- grid select
         , ((mod1Mask, xK_n), goToSelected defaultGSConfig)
      
         -- windowbringer
         , ((mod1Mask, xK_b), bringMenu)
         , ((mod1Mask, xK_g), gotoMenu)

         -- paste x selection
         , ((0, xK_Insert), pasteSelection)

         -- toggle bars
         , ((mod1Mask, xK_backslash), sendMessage ToggleStruts) -- toggle both bars
         , ((mod1Mask, xK_bracketleft), sendMessage $ ToggleStrut D) -- toggle bottom bar
         , ((mod1Mask, xK_bracketright), sendMessage $ ToggleStrut U) -- toggle top bar

         -- BSP layout keybindings
         -- resize
         , ((mod4Mask .|. mod1Mask,                  xK_l  ), sendMessage $ ExpandTowards R)
         , ((mod4Mask .|. mod1Mask,                  xK_h  ), sendMessage $ ExpandTowards L)
         , ((mod4Mask .|. mod1Mask,                  xK_j  ), sendMessage $ ExpandTowards D)
         , ((mod4Mask .|. mod1Mask,                  xK_k  ), sendMessage $ ExpandTowards U)
         , ((mod4Mask .|. mod1Mask .|. shiftMask ,   xK_l  ), sendMessage $ ShrinkFrom R)
         , ((mod4Mask .|. mod1Mask .|. shiftMask ,   xK_h  ), sendMessage $ ShrinkFrom L)
         , ((mod4Mask .|. mod1Mask .|. shiftMask ,   xK_j  ), sendMessage $ ShrinkFrom D)
         , ((mod4Mask .|. mod1Mask .|. shiftMask ,   xK_k  ), sendMessage $ ShrinkFrom U)
         -- other
         , ((mod1Mask,                              xK_r     ), sendMessage Rotate)
         , ((mod1Mask,                              xK_s     ), sendMessage BSP.Swap)
--          , ((mod4Mask .|. shiftMask .|. controlMask , xK_j     ), sendMessage $ SplitShift Prev)
--          , ((mod4Mask .|. shiftMask .|. controlMask , xK_k     ), sendMessage $ SplitShift Next)

 

         ] ++ [ -- for extra workspace(s)
         ((myModMask, key), (windows $ W.greedyView ws))
         | (key,ws) <- myExtraWorkspaces
         ] ++ [ -- also for extra workspaces
         ((myModMask .|. shiftMask, key), (windows $ W.shift ws))
         | (key,ws) <- myExtraWorkspaces
         ] ++ [ -- to swap workspaces
         ((mod4Mask .|. controlMask, k), windows $ swapWithCurrent i)
         | (i, k) <- zip myWorkspaces [xK_1 ..]
         ]



-- layouts
myGap = spacingRaw False (Border sGap sGap sGap sGap) True (Border wGap wGap wGap wGap) True
 
myLayouts = avoidStruts $ mouseResize $ windowNavigation $ myGap $ emptyBSP ||| ThreeColMid 1 (3/100) (1/2) ||| Grid ||| TwoPane (3/100) (1/2) ||| ThreeCol 1 (3/100) (1/2) ||| ThreeCol 2 (3/100) (1/2) ||| topRightMaster emptyBSP

myLayoutHook = myLayouts


myLemonbarPP = def {ppCurrent = wrap "%{F#6c71c4}%{B#d33682}%{F-}" "%{F#d33682}%{B-}%{F-}" 
                   , ppWsSep = "  "
		   , ppHidden = wrap "%{B#268bd2}" "%{B-}"
                   , ppHiddenNoWindows = wrap "%{F#02fc45}" "%{F-}"
                   , ppTitle = wrap "  %{B#6c71c4}%{F#f0f0f0}  " "  %{B-}" . shorten 75
                   , ppUrgent = wrap "%{B#9cfc02}    " "    %{B-}%{F-}"
                   , ppLayout = wrap "%{r}%{B#99B1D5}%{F#232627} " " %{B-} "
		   , ppSep =  " "
		   , ppExtras  = [windowCount]
                   , ppOrder  = \(ws:l:t:ex) -> [ws]++[t]++[l]++["%{B#50FA7B}%{F#232627}  WIN:"]++ex++["%{B-}%{F-} "]
                   }

main = do
  notXMobar <- spawnPipe "lemonbar -b  -g 1366x21+0+0  -B '#171520' -F '#ffffff' -f 'Source Han Sans JP:size=10' -o -3 -f 'RobotoMono Nerd Font:style=Regular:size=15' -f -n 'notXMobar' -o 0"
  xmonad $ docks def
    {
  terminal           = myTerminal,
  focusFollowsMouse  = True,
  borderWidth        = myBorderWidth,
  modMask            = myModMask,
  workspaces         = myWorkspaces,
  normalBorderColor  = nBorder,
  focusedBorderColor = fBorder,
  -- mouseBindings      = myMouseBindings,
  layoutHook         = myLayoutHook,
  -- manageHook         = myManageHook,
  -- handleEventHook    = myEventHook,
  logHook            = dynamicLogWithPP myLemonbarPP { ppOutput = \x -> hPutStrLn notXMobar x},
  startupHook        = myStartupHook
} `additionalKeys` myKeys