]> code.delx.au - dotfiles/blob - .xmonad/xmonad.hs
bc4edd9308d5ef01582c3841db5960addddfde3b
[dotfiles] / .xmonad / xmonad.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 import System.IO
3 import XMonad
4 import XMonad.Actions.CycleRecentWS
5 import XMonad.Actions.PhysicalScreens
6 import XMonad.Hooks.DynamicLog
7 import XMonad.Hooks.EwmhDesktops
8 import XMonad.Hooks.ICCCMFocus
9 import XMonad.Hooks.ManageDocks
10 import XMonad.Hooks.ManageHelpers
11 import XMonad.Hooks.SetWMName
12 import XMonad.Layout.IM
13 import XMonad.Layout.LayoutHints
14 import qualified XMonad.Layout.Magnifier as Mag
15 import XMonad.Layout.Master
16 import XMonad.Layout.NoBorders
17 import XMonad.Layout.NoFrillsDecoration
18 import XMonad.Layout.PerWorkspace
19 import XMonad.Layout.Renamed
20 import XMonad.Layout.Reflect
21 import XMonad.Layout.Tabbed
22 import XMonad.Util.Run(spawnPipe)
23 import qualified Data.Map as M
24 import qualified XMonad.StackSet as W
25
26
27 myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $
28 [
29 ((modm .|. shiftMask, xK_h), spawn "xfce4-session-logout"),
30 ((modm .|. shiftMask, xK_l), spawn "xscreensaver-command --lock"),
31 ((modm .|. shiftMask, xK_r), spawn "xmonad --restart"),
32
33 ((modm, xK_n), spawn "xfce4-terminal"),
34 ((modm, xK_i), spawn "firefox"),
35 ((modm, xK_c), spawn "emacsclient --create-frame --no-wait"),
36 ((modm, xK_p), spawn "kupfer"),
37
38 ((modm .|. shiftMask, xK_c ), kill),
39 ((modm, xK_space ), sendMessage NextLayout),
40 ((modm .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf),
41 ((modm, xK_j ), windows W.focusDown),
42 ((modm, xK_k ), windows W.focusUp ),
43 ((modm, xK_m ), windows W.focusMaster ),
44 ((modm, xK_Return), windows W.swapMaster),
45 ((modm .|. shiftMask, xK_j ), windows W.swapDown ),
46 ((modm .|. shiftMask, xK_k ), windows W.swapUp ),
47 ((modm, xK_h ), sendMessage Shrink),
48 ((modm, xK_l ), sendMessage Expand),
49 ((modm, xK_t ), withFocused $ windows . W.sink),
50 ((modm , xK_comma ), sendMessage (IncMasterN 1)),
51 ((modm , xK_period), sendMessage (IncMasterN (-1))),
52 ((modm , xK_b ), sendMessage ToggleStruts),
53 ((modm , xK_z ), sendMessage Mag.Toggle),
54 ((modm , xK_a), cycleRecentWS [xK_Super_L] xK_a xK_a)
55 ]
56 ++
57
58 -- mod-{o,e,u}, Switch to physical/Xinerama screens 1, 2, or 3
59 -- mod-shift-{o,e,u}, Move client to screen 1, 2, or 3
60 [((m .|. modm, key), f sc)
61 | (key, sc) <- zip [xK_o, xK_e, xK_u] [0..]
62 , (f, m) <- [(viewScreen, 0), (sendToScreen, shiftMask)]
63 ]
64 ++
65
66 -- mod-[1..9], Switch to workspace N
67 -- mod-shift-[1..9], Move client to workspace N
68 [((m .|. modm, k), windows $ f i)
69 | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
70 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
71 ]
72
73
74 avoidMaster = W.modify' $ \c -> case c of
75 W.Stack t [] (r:rs) -> W.Stack t [r] rs
76 otherwise -> c
77
78 isSkipTaskBar = isInProperty "_NET_WM_STATE" "_NET_WM_STATE_SKIP_TASKBAR"
79
80 myManageHook =
81 manageDocks <+>
82 composeOne [
83 transience,
84 (isSkipTaskBar -?> doFloat),
85 (isDialog -?> doFloatAt 0.1 0.1),
86 (isFullscreen -?> doFullFloat),
87 (fmap Just $ doF avoidMaster)
88 ]
89
90
91 myWorkspaces = ["1", "2", "3", "4", "5", "6", "7", "8", "9"]
92
93 myPP = xmobarPP
94 {
95 ppCurrent = xmobarColor "#A01010" "" . wrap "[" "]",
96 ppTitle = xmobarColor "#10A010" ""
97 }
98
99 myLogHook hooks = do
100 mapM (\h -> dynamicLogWithPP myPP { ppOutput = hPutStrLn h }) hooks
101 takeTopFocus -- fix for Java Swing apps
102
103 myStartupHook = do
104 setWMName "LG3D" -- fix for Java Swing apps
105 spawn "xfce4-panel --restart" -- ensure it appears on top of xmobar
106
107 goldenRatio = (toRational (2/(1+sqrt(5)::Double)))
108
109 myTitleTheme = defaultTheme {
110 fontName = "xft:sans-serif:size=10",
111 decoHeight = 24
112 }
113
114 createLayout name layout =
115 renamed [Replace name] $
116 layoutHints $
117 smartBorders $
118 layout
119
120 myFullLayout = createLayout "Full" $
121 noBorders $
122 Full
123
124 myTiledLayout = createLayout "Tall" $
125 avoidStruts $
126 Mag.magnifierOff $
127 Tall nMaster ratioIncrement masterRatio
128 where
129 nMaster = 1
130 ratioIncrement = 3/100
131 masterRatio = goldenRatio
132
133 myTabbedLayout = createLayout "Tab" $
134 avoidStruts $
135 tabbed shrinkText myTitleTheme
136
137 myMasterTabbedLayout = createLayout "MTab" $
138 avoidStruts $
139 Mag.magnifierOff $
140 mastered resizeDelta masterRatio $
141 tabbed shrinkText myTitleTheme
142 where
143 resizeDelta = 3/100
144 masterRatio = goldenRatio
145
146 myGimpLayout = createLayout "Gimp" $
147 avoidStruts $
148 withIM (1/6) (Role "gimp-toolbox") $
149 reflectHoriz $
150 withIM (1/6) (Role "gimp-dock") $
151 reflectHoriz $
152 tabbed shrinkText myTitleTheme
153
154 myLayout =
155 (
156 onWorkspace "9" (myTabbedLayout ||| myFullLayout ||| myGimpLayout) $
157 (myTabbedLayout ||| myMasterTabbedLayout ||| myTiledLayout)
158 )
159
160 main = do
161 xmonadDir <- getXMonadDir
162 xmobars <- mapM (\x -> spawnPipe ("xmobar -x " ++ (show x) ++ " " ++ xmonadDir ++ "/xmobar.hs")) [1, 2]
163 xmonad $ ewmh defaultConfig {
164 manageHook = myManageHook,
165 layoutHook = myLayout,
166 workspaces = myWorkspaces,
167 logHook = myLogHook xmobars,
168 startupHook = myStartupHook,
169 keys = myKeys,
170 modMask = mod4Mask,
171 handleEventHook = handleEventHook defaultConfig <+> fullscreenEventHook,
172 focusFollowsMouse = False
173 }
174