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