{-# OPTIONS_GHC -fno-warn-missing-signatures -fno-warn-orphans #-}
{-# LANGUAGE TypeFamilies #-}
module XMonad.Config (defaultConfig, Default(..)) where
import XMonad.Core as XMonad hiding
(workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
,handleEventHook,clickJustFocuses,rootMask,clientMask)
import qualified XMonad.Core as XMonad
(workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
,handleEventHook,clickJustFocuses,rootMask,clientMask)
import XMonad.Layout
import XMonad.Operations
import XMonad.ManageHook
import qualified XMonad.StackSet as W
import Data.Bits ((.|.))
import Data.Default
import Data.Monoid
import qualified Data.Map as M
import System.Exit
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
workspaces :: [WorkspaceId]
workspaces = map show [1 .. 9 :: Int]
defaultModMask :: KeyMask
defaultModMask = mod1Mask
borderWidth :: Dimension
borderWidth = 1
normalBorderColor, focusedBorderColor :: String
normalBorderColor = "gray"
focusedBorderColor = "red"
manageHook :: ManageHook
manageHook = composeAll
[ className =? "MPlayer" --> doFloat
, className =? "mplayer2" --> doFloat ]
logHook :: X ()
logHook = return ()
handleEventHook :: Event -> X All
handleEventHook _ = return (All True)
startupHook :: X ()
startupHook = return ()
layout = tiled ||| Mirror tiled ||| Full
where
tiled = Tall nmaster delta ratio
nmaster = 1
ratio = 1/2
delta = 3/100
clientMask :: EventMask
clientMask = structureNotifyMask .|. enterWindowMask .|. propertyChangeMask
rootMask :: EventMask
rootMask = substructureRedirectMask .|. substructureNotifyMask
.|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask
.|. buttonPressMask
terminal :: String
terminal = "xterm"
focusFollowsMouse :: Bool
focusFollowsMouse = True
clickJustFocuses :: Bool
clickJustFocuses = True
keys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
[ ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
, ((modMask, xK_p ), spawn "dmenu_run")
, ((modMask .|. shiftMask, xK_p ), spawn "gmrun")
, ((modMask .|. shiftMask, xK_c ), kill)
, ((modMask, xK_space ), sendMessage NextLayout)
, ((modMask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf)
, ((modMask, xK_n ), refresh)
, ((modMask, xK_Tab ), windows W.focusDown)
, ((modMask .|. shiftMask, xK_Tab ), windows W.focusUp )
, ((modMask, xK_j ), windows W.focusDown)
, ((modMask, xK_k ), windows W.focusUp )
, ((modMask, xK_m ), windows W.focusMaster )
, ((modMask, xK_Return), windows W.swapMaster)
, ((modMask .|. shiftMask, xK_j ), windows W.swapDown )
, ((modMask .|. shiftMask, xK_k ), windows W.swapUp )
, ((modMask, xK_h ), sendMessage Shrink)
, ((modMask, xK_l ), sendMessage Expand)
, ((modMask, xK_t ), withFocused $ windows . W.sink)
, ((modMask , xK_comma ), sendMessage (IncMasterN 1))
, ((modMask , xK_period), sendMessage (IncMasterN (-1)))
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
, ((modMask , xK_q ), spawn "if type xmonad; then xmonad --recompile && xmonad --restart; else xmessage xmonad not in \\$PATH: \"$PATH\"; fi")
, ((modMask .|. shiftMask, xK_slash ), helpCommand)
, ((modMask , xK_question), helpCommand)
]
++
[((m .|. modMask, k), windows $ f i)
| (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
++
[((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
where
helpCommand :: X ()
helpCommand = spawn ("echo " ++ show help ++ " | xmessage -file -")
mouseBindings :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ())
mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList
[ ((modMask, button1), \w -> focus w >> mouseMoveWindow w
>> windows W.shiftMaster)
, ((modMask, button2), windows . (W.shiftMaster .) . W.focusWindow)
, ((modMask, button3), \w -> focus w >> mouseResizeWindow w
>> windows W.shiftMaster)
]
instance (a ~ Choose Tall (Choose (Mirror Tall) Full)) => Default (XConfig a) where
def = XConfig
{ XMonad.borderWidth = borderWidth
, XMonad.workspaces = workspaces
, XMonad.layoutHook = layout
, XMonad.terminal = terminal
, XMonad.normalBorderColor = normalBorderColor
, XMonad.focusedBorderColor = focusedBorderColor
, XMonad.modMask = defaultModMask
, XMonad.keys = keys
, XMonad.logHook = logHook
, XMonad.startupHook = startupHook
, XMonad.mouseBindings = mouseBindings
, XMonad.manageHook = manageHook
, XMonad.handleEventHook = handleEventHook
, XMonad.focusFollowsMouse = focusFollowsMouse
, XMonad.clickJustFocuses = clickJustFocuses
, XMonad.clientMask = clientMask
, XMonad.rootMask = rootMask
, XMonad.handleExtraArgs = \ xs theConf -> case xs of
[] -> return theConf
_ -> fail ("unrecognized flags:" ++ show xs)
}
{-# DEPRECATED defaultConfig "Use def (from Data.Default, and re-exported by XMonad and XMonad.Config) instead." #-}
defaultConfig :: XConfig (Choose Tall (Choose (Mirror Tall) Full))
defaultConfig = def
help :: String
help = unlines ["The default modifier key is 'alt'. Default keybindings:",
"",
"-- launching and killing programs",
"mod-Shift-Enter Launch xterminal",
"mod-p Launch dmenu",
"mod-Shift-p Launch gmrun",
"mod-Shift-c Close/kill the focused window",
"mod-Space Rotate through the available layout algorithms",
"mod-Shift-Space Reset the layouts on the current workSpace to default",
"mod-n Resize/refresh viewed windows to the correct size",
"",
"-- move focus up or down the window stack",
"mod-Tab Move focus to the next window",
"mod-Shift-Tab Move focus to the previous window",
"mod-j Move focus to the next window",
"mod-k Move focus to the previous window",
"mod-m Move focus to the master window",
"",
"-- modifying the window order",
"mod-Return Swap the focused window and the master window",
"mod-Shift-j Swap the focused window with the next window",
"mod-Shift-k Swap the focused window with the previous window",
"",
"-- resizing the master/slave ratio",
"mod-h Shrink the master area",
"mod-l Expand the master area",
"",
"-- floating layer support",
"mod-t Push window back into tiling; unfloat and re-tile it",
"",
"-- increase or decrease number of windows in the master area",
"mod-comma (mod-,) Increment the number of windows in the master area",
"mod-period (mod-.) Deincrement the number of windows in the master area",
"",
"-- quit, or restart",
"mod-Shift-q Quit xmonad",
"mod-q Restart xmonad",
"",
"-- Workspaces & screens",
"mod-[1..9] Switch to workSpace N",
"mod-Shift-[1..9] Move client to workspace N",
"mod-{w,e,r} Switch to physical/Xinerama screens 1, 2, or 3",
"mod-Shift-{w,e,r} Move client to screen 1, 2, or 3",
"",
"-- Mouse bindings: default actions bound to mouse events",
"mod-button1 Set the window to floating mode and move by dragging",
"mod-button2 Raise the window to the top of the stack",
"mod-button3 Set the window to floating mode and resize by dragging"]