X-Git-Url: https://ruderich.org/simon/gitweb/?p=config%2Fdotfiles.git;a=blobdiff_plain;f=x11%2Fxmonad%2Fxmonad.hs;fp=x11%2Fxmonad%2Fxmonad.hs;h=bdee75d1a9d31e8498a52386890b47e5796c07a0;hp=0000000000000000000000000000000000000000;hb=d11857eb2b9693235ed3531144a6b0a4d5cb1740;hpb=e0a76c26f9164e070166fcc62e1c287cc1033eef diff --git a/x11/xmonad/xmonad.hs b/x11/xmonad/xmonad.hs new file mode 100644 index 0000000..bdee75d --- /dev/null +++ b/x11/xmonad/xmonad.hs @@ -0,0 +1,196 @@ +-- xmonad configuration file. + +-- Copyright (C) 2011-2015 Simon Ruderich +-- +-- This file is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This file is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this file. If not, see . + + +import XMonad hiding ( (|||) ) +import XMonad.Actions.CycleWS (toggleWS) +import XMonad.Hooks.ManageHelpers ((-?>), composeOne) +import XMonad.Hooks.SetWMName (setWMName) +import XMonad.Layout.LayoutCombinators ((|||), JumpToLayout(..)) +import XMonad.Layout.Named (named) +import XMonad.Layout.NoBorders (smartBorders) +import XMonad.Layout.TwoPane (TwoPane(..)) +import XMonad.Util.EZConfig (additionalKeys) +import qualified XMonad.StackSet as W + + +-- Prevent new windows from spawning in the master pane. Taken from +-- http://haskell.org/haskellwiki/Xmonad/Frequently_asked_questions on +-- 2009-06-30. Thanks. Modified to not steal focus from the master pane when a +-- new window is created, thanks to vav in #xmonad on Freenode (2010-04-15 +-- 21:59 CEST). +avoidMaster :: W.StackSet i l a s sd -> W.StackSet i l a s sd +avoidMaster = W.modify' $ \c -> case c of + W.Stack t [] (r:rs) -> W.Stack r [] (t:rs) + _ -> c + +-- Create my custom layout. +-- +-- Only use horizontal (Mirror tiled) and fullscreen layouts, but allow +-- switching to other layouts with bindings. +-- +-- The master pane is at the top of the screen. To make sure new windows don't +-- spawn in the master pane avoidMaster (see below) is used. Borders are only +-- drawn when the screen has more then one window (smartBorders). +-- +-- Thanks to jrick in #xmonad on Freenode (2009-06-29 22:19 CEST) for telling +-- me how to remove the vertical tiled layout. +-- +-- JumpToLayout (from LayoutCombinators) is used to jump to specific layouts, +-- thanks to aavogt in #xmonad on Freenode (2011-06-12 22:13 CEST). +-- +-- named is used to name layouts which allows switching to a specific layout +-- (see below), thanks to vav in #xmonad on Freenode (2011-06-12 22:28 CEST). +-- +-- The limit layout displays only one window in the lower pane, thanks to to +-- Qantourisc (2010-06-12 15:15 CEST) for the hint to use TwoPane. +-- +-- onWorkspace is used for a special layout for Gimp, thanks to Nathan Howell +-- (http://nathanhowell.net/2009/03/08/xmonad-and-the-gimp/) for this layout +-- (read on 2011-06-19). +myLayoutHook = + named "Default" (smartBorders $ Mirror tiled) + ||| named "Full" (smartBorders Full) + ||| named "Vertical" (smartBorders tiled) + ||| named "Limit" (smartBorders $ Mirror $ TwoPane delta ratio) + where + -- Default tiling algorithm partitions the screen into two panes. + tiled = Tall nmaster delta ratio + -- The default number of windows in the master pane. + nmaster = 1 + -- Percent of screen to increment by when resizing panes. + delta = 3/100 + -- Default proportion of screen occupied by master pane. + ratio = 1/2 + +-- Don't spawn new windows in the master pane (which is at the top of the +-- screen). Thanks to dschoepe, aavogt and especially vav in #xmonad on +-- Freenode (2009-06-30 02:10f CEST). +-- +-- Also some applications are spawned on specific workspaces. Thanks to +-- dschoepe and ivanm in #xmonad on Freenode (2009-07-12 14:50 CEST). +myManageHook :: ManageHook +myManageHook = composeOne + -- Browser on "2". + [ className =? "Iceweasel" -?> doF (W.shift "2") + -- Miscellaneous on "3". + , className =? "Wireshark" -?> doF (W.shift "3") + , title =? "OpenOffice.org" -?> doF (W.shift "3") -- splash screen + , className =? "OpenOffice.org 2.4" -?> doF (W.shift "3") + , className =? "Vncviewer" -?> doF (W.shift "3") + -- Wine on "4". + , className =? "Wine" -?> doF (W.shift "4") + -- Gimp on "5". + , className =? "Gimp" -?> doF (W.shift "5") + + -- Don't spawn new windows in the master pane. + , return True -?> doF avoidMaster + -- Prevent windows which get moved to other workspaces from removing the + -- focus of the currently selected window. Thanks to vav in #xmonad on + -- Freenode (2010-04-15 21:04 CEST). + , return True -?> doF W.focusDown + ] + +-- Switch to next layout, but skip all layouts not in layouts argument. This +-- allows switching to some layouts with mappings but excluding them from +-- meta-space (which gets mapped to this function). Thanks to aavogt in +-- #xmonad on Freenode for this function (2011-06-13 12:45 CEST) and +-- rootzlevel in #xmonad on Freenode for fixes (2011-06-13 15:20 CEST), +-- modified to take list of layouts to switch to, not layouts to exclude. +nextLayoutIncluding :: [String] -> X () +nextLayoutIncluding layouts = do + cws <- gets (W.workspace . W.current . windowset) + sendMessageWithNoRefresh NextLayout cws + nextLayoutIncluding' layouts 1000 -- nobody has more than 1000 layouts + +nextLayoutIncluding' :: [String] -> Int -> X () +nextLayoutIncluding' layouts iterations = do + cws <- gets (W.workspace . W.current . windowset) + -- iterations prevents an endless loop if no valid layout can be found. + if not ((description $ W.layout cws) `elem` layouts) && iterations > 0 + -- Skip over excluded layouts. + then do + sendMessageWithNoRefresh NextLayout cws + nextLayoutIncluding' layouts (iterations - 1) + -- Found allowed layout, show it. + else refresh + +-- Use additional workspaces. Access with meta 1,2,..,9,0 for the first ten, +-- meta f1,f2,..,f10 for the second ten workspaces (see mappings below). +myWorkspaces :: [String] +myWorkspaces = map show [1 .. 20 :: Int] + +-- Use Windows (= Super) key as main key as it doesn't conflict with any other +-- key bindings. +myModMask :: KeyMask +myModMask = mod4Mask + +myKeys :: [((KeyMask, KeySym), X ())] +myKeys = [ + -- Switch to next layout, but only use the listed layouts. + ((myModMask, xK_space), nextLayoutIncluding ["Default", "Full"]) + -- Switch to vertical tiled layout. + , ((myModMask, xK_v), sendMessage $ JumpToLayout "Vertical") + -- Switch to limit layout which displays only one window in the lower + -- pane. + , ((myModMask, xK_b), sendMessage $ JumpToLayout "Limit") + + -- Switch to last active workspace, thanks to moljac024 in #xmonad on + -- Freenode (2010-12-18 14:45 CET). + , ((myModMask, xK_b), toggleWS) + + -- Lock the screen. + , ((myModMask, xK_z), spawn "$HOME/.xlockscreen lock") + ] + ++ + -- When using multiple screens, switching to another workspace causes + -- xmonad to pull the workspace to the current screen if it was also + -- displayed on another one. This is confusing for me so the following + -- code changes it to just switch to the screen where the workspace is + -- already displayed. + -- + -- Thanks to the xmonad FAQ, read on 2010-06-16 13:42 CEST + -- (http://www.haskell.org/haskellwiki/Xmonad/Frequently_asked_questions). + -- Thanks to MrElendig in #xmonad on Freenode (2010-06-17 17:16 CEST) how + -- to use the default xmonad workspaces. Thanks to geekosaur and OODavo in + -- #xmonad on Freenode (2012-12-23 01:14 CET) how to use more workspaces. + [((m .|. myModMask, k), windows $ f i) + | (i, k) <- zip myWorkspaces ([xK_1 .. xK_9] ++ [xK_0] -- 1..9,0 + ++ [xK_F1 .. xK_F10]) -- f1..f10 + , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]] + +main :: IO () +main = xmonad $ defaultConfig + -- Change main key. + { modMask = myModMask + -- Inactive borders are black - invisible on my black screen. + , normalBorderColor = "#000000" + -- Active borders are dark red. + , focusedBorderColor = "#990000" + -- Use my layout and manage hooks (see above). + , layoutHook = myLayoutHook + , manageHook = myManageHook + -- Use unicode rxvt as my terminal. + , terminal = "urxvt" + -- Necessary for Java so it recognizes xmonad as tiling window manager. + , startupHook = setWMName "LG3D" + -- Use more workspaces than the default. + , workspaces = myWorkspaces + } + `additionalKeys` myKeys + +-- vim: nospell