1{-# OPTIONS_GHC -fno-warn-missing-signatures -fno-warn-orphans #-}
2{-# LANGUAGE TypeFamilies #-}
3-----------------------------------------------------------------------------
4-- |
5-- Module      :  XMonad.Config
6-- Copyright   :  (c) Spencer Janssen 2007
7-- License     :  BSD3-style (see LICENSE)
8--
9-- Maintainer  :  dons@galois.com
10-- Stability   :  stable
11-- Portability :  portable
12--
13-- This module specifies the default configuration values for xmonad.
14--
15-- DO NOT MODIFY THIS FILE!  It won't work.  You may configure xmonad
16-- by providing your own @~\/.xmonad\/xmonad.hs@ that overrides
17-- specific fields in the default config, 'def'.  For a starting point, you can
18-- copy the @xmonad.hs@ found in the @man@ directory, or look at
19-- examples on the xmonad wiki.
20--
21------------------------------------------------------------------------
22
23module XMonad.Config (defaultConfig, Default(..)) where
24
25--
26-- Useful imports
27--
28import XMonad.Core as XMonad hiding
29    (workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
30    ,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
31    ,handleEventHook,clickJustFocuses,rootMask,clientMask)
32import qualified XMonad.Core as XMonad
33    (workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
34    ,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
35    ,handleEventHook,clickJustFocuses,rootMask,clientMask)
36
37import XMonad.Layout
38import XMonad.Operations
39import XMonad.ManageHook
40import qualified XMonad.StackSet as W
41import Data.Bits ((.|.))
42import Data.Default.Class
43import Data.Monoid
44import qualified Data.Map as M
45import System.Exit
46import Graphics.X11.Xlib
47import Graphics.X11.Xlib.Extras
48
49-- | The default number of workspaces (virtual screens) and their names.
50-- By default we use numeric strings, but any string may be used as a
51-- workspace name. The number of workspaces is determined by the length
52-- of this list.
53--
54-- A tagging example:
55--
56-- > workspaces = ["web", "irc", "code" ] ++ map show [4..9]
57--
58workspaces :: [WorkspaceId]
59workspaces = map show [1 .. 9 :: Int]
60
61-- | modMask lets you specify which modkey you want to use. The default
62-- is mod1Mask ("left alt").  You may also consider using mod3Mask
63-- ("right alt"), which does not conflict with emacs keybindings. The
64-- "windows key" is usually mod4Mask.
65--
66defaultModMask :: KeyMask
67defaultModMask = mod1Mask
68
69-- | Width of the window border in pixels.
70--
71borderWidth :: Dimension
72borderWidth = 1
73
74-- | Border colors for unfocused and focused windows, respectively.
75--
76normalBorderColor, focusedBorderColor :: String
77normalBorderColor  = "gray" -- "#dddddd"
78focusedBorderColor = "red"  -- "#ff0000" don't use hex, not <24 bit safe
79
80------------------------------------------------------------------------
81-- Window rules
82
83-- | Execute arbitrary actions and WindowSet manipulations when managing
84-- a new window. You can use this to, for example, always float a
85-- particular program, or have a client always appear on a particular
86-- workspace.
87--
88-- To find the property name associated with a program, use
89--  xprop | grep WM_CLASS
90-- and click on the client you're interested in.
91--
92manageHook :: ManageHook
93manageHook = composeAll
94                [ className =? "MPlayer"        --> doFloat
95                , className =? "mplayer2"       --> doFloat ]
96
97------------------------------------------------------------------------
98-- Logging
99
100-- | Perform an arbitrary action on each internal state change or X event.
101-- Examples include:
102--
103--      * do nothing
104--
105--      * log the state to stdout
106--
107-- See the 'DynamicLog' extension for examples.
108--
109logHook :: X ()
110logHook = return ()
111
112------------------------------------------------------------------------
113-- Event handling
114
115-- | Defines a custom handler function for X Events. The function should
116-- return (All True) if the default handler is to be run afterwards.
117-- To combine event hooks, use mappend or mconcat from Data.Monoid.
118handleEventHook :: Event -> X All
119handleEventHook _ = return (All True)
120
121-- | Perform an arbitrary action at xmonad startup.
122startupHook :: X ()
123startupHook = return ()
124
125------------------------------------------------------------------------
126-- Extensible layouts
127--
128-- You can specify and transform your layouts by modifying these values.
129-- If you change layout bindings be sure to use 'mod-shift-space' after
130-- restarting (with 'mod-q') to reset your layout state to the new
131-- defaults, as xmonad preserves your old layout settings by default.
132--
133
134-- | The available layouts.  Note that each layout is separated by |||, which
135-- denotes layout choice.
136layout = tiled ||| Mirror tiled ||| Full
137  where
138     -- default tiling algorithm partitions the screen into two panes
139     tiled   = Tall nmaster delta ratio
140
141     -- The default number of windows in the master pane
142     nmaster = 1
143
144     -- Default proportion of screen occupied by master pane
145     ratio   = 1/2
146
147     -- Percent of screen to increment by when resizing panes
148     delta   = 3/100
149
150------------------------------------------------------------------------
151-- Event Masks:
152
153-- | The client events that xmonad is interested in
154clientMask :: EventMask
155clientMask = structureNotifyMask .|. enterWindowMask .|. propertyChangeMask
156
157-- | The root events that xmonad is interested in
158rootMask :: EventMask
159rootMask =  substructureRedirectMask .|. substructureNotifyMask
160        .|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask
161        .|. buttonPressMask
162
163------------------------------------------------------------------------
164-- Key bindings:
165
166-- | The preferred terminal program, which is used in a binding below and by
167-- certain contrib modules.
168terminal :: String
169terminal = "xterm"
170
171-- | Whether focus follows the mouse pointer.
172focusFollowsMouse :: Bool
173focusFollowsMouse = True
174
175-- | Whether a mouse click select the focus or is just passed to the window
176clickJustFocuses :: Bool
177clickJustFocuses = True
178
179
180-- | The xmonad key bindings. Add, modify or remove key bindings here.
181--
182-- (The comment formatting character is used when generating the manpage)
183--
184keys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
185keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
186    -- launching and killing programs
187    [ ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf) -- %! Launch terminal
188    , ((modMask,               xK_p     ), spawn "dmenu_run") -- %! Launch dmenu
189    , ((modMask .|. shiftMask, xK_p     ), spawn "gmrun") -- %! Launch gmrun
190    , ((modMask .|. shiftMask, xK_c     ), kill) -- %! Close the focused window
191
192    , ((modMask,               xK_space ), sendMessage NextLayout) -- %! Rotate through the available layout algorithms
193    , ((modMask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf) -- %!  Reset the layouts on the current workspace to default
194
195    , ((modMask,               xK_n     ), refresh) -- %! Resize viewed windows to the correct size
196
197    -- move focus up or down the window stack
198    , ((modMask,               xK_Tab   ), windows W.focusDown) -- %! Move focus to the next window
199    , ((modMask .|. shiftMask, xK_Tab   ), windows W.focusUp  ) -- %! Move focus to the previous window
200    , ((modMask,               xK_j     ), windows W.focusDown) -- %! Move focus to the next window
201    , ((modMask,               xK_k     ), windows W.focusUp  ) -- %! Move focus to the previous window
202    , ((modMask,               xK_m     ), windows W.focusMaster  ) -- %! Move focus to the master window
203
204    -- modifying the window order
205    , ((modMask,               xK_Return), windows W.swapMaster) -- %! Swap the focused window and the master window
206    , ((modMask .|. shiftMask, xK_j     ), windows W.swapDown  ) -- %! Swap the focused window with the next window
207    , ((modMask .|. shiftMask, xK_k     ), windows W.swapUp    ) -- %! Swap the focused window with the previous window
208
209    -- resizing the master/slave ratio
210    , ((modMask,               xK_h     ), sendMessage Shrink) -- %! Shrink the master area
211    , ((modMask,               xK_l     ), sendMessage Expand) -- %! Expand the master area
212
213    -- floating layer support
214    , ((modMask,               xK_t     ), withFocused $ windows . W.sink) -- %! Push window back into tiling
215
216    -- increase or decrease number of windows in the master area
217    , ((modMask              , xK_comma ), sendMessage (IncMasterN 1)) -- %! Increment the number of windows in the master area
218    , ((modMask              , xK_period), sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area
219
220    -- quit, or restart
221    , ((modMask .|. shiftMask, xK_q     ), io (exitWith ExitSuccess)) -- %! Quit xmonad
222    , ((modMask              , xK_q     ), spawn "if type xmonad; then xmonad --recompile && xmonad --restart; else xmessage xmonad not in \\$PATH: \"$PATH\"; fi") -- %! Restart xmonad
223
224    , ((modMask .|. shiftMask, xK_slash ), helpCommand) -- %! Run xmessage with a summary of the default keybindings (useful for beginners)
225    -- repeat the binding for non-American layout keyboards
226    , ((modMask              , xK_question), helpCommand) -- %! Run xmessage with a summary of the default keybindings (useful for beginners)
227    ]
228    ++
229    -- mod-[1..9] %! Switch to workspace N
230    -- mod-shift-[1..9] %! Move client to workspace N
231    [((m .|. modMask, k), windows $ f i)
232        | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
233        , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
234    ++
235    -- mod-{w,e,r} %! Switch to physical/Xinerama screens 1, 2, or 3
236    -- mod-shift-{w,e,r} %! Move client to screen 1, 2, or 3
237    [((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
238        | (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
239        , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
240  where
241    helpCommand :: X ()
242    helpCommand = xmessage help
243
244-- | Mouse bindings: default actions bound to mouse events
245mouseBindings :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ())
246mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList
247    -- mod-button1 %! Set the window to floating mode and move by dragging
248    [ ((modMask, button1), \w -> focus w >> mouseMoveWindow w
249                                          >> windows W.shiftMaster)
250    -- mod-button2 %! Raise the window to the top of the stack
251    , ((modMask, button2), windows . (W.shiftMaster .) . W.focusWindow)
252    -- mod-button3 %! Set the window to floating mode and resize by dragging
253    , ((modMask, button3), \w -> focus w >> mouseResizeWindow w
254                                         >> windows W.shiftMaster)
255    -- you may also bind events to the mouse scroll wheel (button4 and button5)
256    ]
257
258instance (a ~ Choose Tall (Choose (Mirror Tall) Full)) => Default (XConfig a) where
259  def = XConfig
260    { XMonad.borderWidth        = borderWidth
261    , XMonad.workspaces         = workspaces
262    , XMonad.layoutHook         = layout
263    , XMonad.terminal           = terminal
264    , XMonad.normalBorderColor  = normalBorderColor
265    , XMonad.focusedBorderColor = focusedBorderColor
266    , XMonad.modMask            = defaultModMask
267    , XMonad.keys               = keys
268    , XMonad.logHook            = logHook
269    , XMonad.startupHook        = startupHook
270    , XMonad.mouseBindings      = mouseBindings
271    , XMonad.manageHook         = manageHook
272    , XMonad.handleEventHook    = handleEventHook
273    , XMonad.focusFollowsMouse  = focusFollowsMouse
274    , XMonad.clickJustFocuses       = clickJustFocuses
275    , XMonad.clientMask         = clientMask
276    , XMonad.rootMask           = rootMask
277    , XMonad.handleExtraArgs = \ xs theConf -> case xs of
278                [] -> return theConf
279                _ -> fail ("unrecognized flags:" ++ show xs)
280    , XMonad.extensibleConf     = M.empty
281    }
282
283-- | The default set of configuration values itself
284{-# DEPRECATED defaultConfig "Use def (from Data.Default, and re-exported by XMonad and XMonad.Config) instead." #-}
285defaultConfig :: XConfig (Choose Tall (Choose (Mirror Tall) Full))
286defaultConfig = def
287
288-- | Finally, a copy of the default bindings in simple textual tabular format.
289help :: String
290help = unlines ["The default modifier key is 'alt'. Default keybindings:",
291    "",
292    "-- launching and killing programs",
293    "mod-Shift-Enter  Launch xterminal",
294    "mod-p            Launch dmenu",
295    "mod-Shift-p      Launch gmrun",
296    "mod-Shift-c      Close/kill the focused window",
297    "mod-Space        Rotate through the available layout algorithms",
298    "mod-Shift-Space  Reset the layouts on the current workSpace to default",
299    "mod-n            Resize/refresh viewed windows to the correct size",
300    "mod-Shift-/      Show this help message with the default keybindings",
301    "",
302    "-- move focus up or down the window stack",
303    "mod-Tab        Move focus to the next window",
304    "mod-Shift-Tab  Move focus to the previous window",
305    "mod-j          Move focus to the next window",
306    "mod-k          Move focus to the previous window",
307    "mod-m          Move focus to the master window",
308    "",
309    "-- modifying the window order",
310    "mod-Return   Swap the focused window and the master window",
311    "mod-Shift-j  Swap the focused window with the next window",
312    "mod-Shift-k  Swap the focused window with the previous window",
313    "",
314    "-- resizing the master/slave ratio",
315    "mod-h  Shrink the master area",
316    "mod-l  Expand the master area",
317    "",
318    "-- floating layer support",
319    "mod-t  Push window back into tiling; unfloat and re-tile it",
320    "",
321    "-- increase or decrease number of windows in the master area",
322    "mod-comma  (mod-,)   Increment the number of windows in the master area",
323    "mod-period (mod-.)   Deincrement the number of windows in the master area",
324    "",
325    "-- quit, or restart",
326    "mod-Shift-q  Quit xmonad",
327    "mod-q        Restart xmonad",
328    "",
329    "-- Workspaces & screens",
330    "mod-[1..9]         Switch to workSpace N",
331    "mod-Shift-[1..9]   Move client to workspace N",
332    "mod-{w,e,r}        Switch to physical/Xinerama screens 1, 2, or 3",
333    "mod-Shift-{w,e,r}  Move client to screen 1, 2, or 3",
334    "",
335    "-- Mouse bindings: default actions bound to mouse events",
336    "mod-button1  Set the window to floating mode and move by dragging",
337    "mod-button2  Raise the window to the top of the stack",
338    "mod-button3  Set the window to floating mode and resize by dragging"]
339