Xmonad/Config archive/Gwern's xmonad.hs
< Xmonad | Config archive
Jump to navigation
Jump to search
import Data.List (isInfixOf)
import Data.Map as M (fromList,union, Map())
import XMonad
import XMonad.Actions.Search (google, scholar, wikipedia, selectSearch, promptSearch)
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
import XMonad.Config.Mate (mateConfig)
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
import XMonad.Hooks.UrgencyHook (withUrgencyHook, FocusHook(..))
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Prompt (greenXPConfig, XPConfig(font))
import XMonad.Prompt.Shell (shellPrompt, prompt, safePrompt)
import XMonad.StackSet as W (focusUp, focusDown, shift, sink, view)
import XMonad.Util.Run (unsafeSpawn, runInTerm, safeSpawnProg)
import XMonad.Util.XSelection (safePromptSelection)
import XMonad.Hooks.SetWMName
main :: IO ()
main = spawn "killall unclutter;unclutter" >> xmonad myConfig
where myConfig = withUrgencyHook FocusHook $ mateConfig {
keys = \c -> myKeys c `M.union` keys def c
, layoutHook = avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
, logHook = ewmhDesktopsLogHook
, manageHook = myManageHook
, modMask = mod4Mask
, normalBorderColor = "grey"
, focusedBorderColor = "red"
, borderWidth = 2
, terminal = "urxvt"
, startupHook = setWMName "LD3D"
, XMonad.workspaces = ["web", "irc", "code", "background"] }
where tiled = Tall 1 0.03 0.5
{- Important things to note: We specifically don't use 'managehook
defaultConfig, since I don't like floating mplayer and I don't use the other
specified applications. Otherwise, we have manageDocks there to allow use of
mate-panel; Firefox/Emacs/Irssi go to their designated workspaces. -}
myManageHook :: ManageHook
myManageHook = composeAll [ moveC "Iceweasel" "web",
moveC "Firefox" "web",
moveC "Gimp" "irc",
moveC "emacs" "code",
moveC "Mnemosyne" "code",
moveC "Liferea" "code",
className =? "mate-panel" --> doIgnore,
className =? "defcon.bin.x86" --> unfloat,
className =? "Mnemosyne" --> unfloat,
-- className =? "Zenity" --> unfloat,
title =? "Brain Workshop 4.8.6" --> unfloat,
title ~? "Irssi" --> doShift "irc"]
<+> manageDocks
where moveC c w = className =? c --> doShift w
-- moveT t w = title =? t --> doShift w
unfloat = ask >>= doF . W.sink
-- helper function for doing a simple string match on window titles
(~?) :: (Eq a, Functor f) => f [a] -> [a] -> f Bool
q ~? x = fmap (x `isInfixOf`) q
myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ())
myKeys XConfig {modMask = m, terminal = term} = M.fromList $ [ -- rebind standard keys
((m .|. shiftMask,xK_p), shellPrompt greenXPConfig')
, ((m, xK_k), kill)
, ((m, xK_n), windows W.focusDown)
, ((m, xK_p), windows W.focusUp)
, ((m, xK_z), withFocused $ windows . W.sink) -- unfloat
-- Custom bindings and commands
, ((m, xK_b), safePrompt "firefox" greenXPConfig')
, ((m .|. shiftMask,xK_b), safePromptSelection "firefox")
, ((m, xK_c), safeSpawnProg term)
, ((m .|. shiftMask,xK_c), prompt (term ++ " -e") greenXPConfig')
, ((m, xK_e), raiseEditor)
, ((m .|. shiftMask,xK_e), prompt "emacs" greenXPConfig')
, ((m, xK_g), promptSearch greenXPConfig' google)
, ((m .|. shiftMask,xK_g), selectSearch google)
, ((m, xK_t), promptSearch greenXPConfig' wikipedia)
, ((m .|. shiftMask,xK_t), selectSearch wikipedia)
, ((m, xK_y), promptSearch greenXPConfig' scholar)
, ((m .|. shiftMask,xK_y), selectSearch scholar)
, ((m, xK_Print), unsafeSpawn "import -quality 90 -descend png:$HOME/xwd-$(date +%s)$$.png")
, ((m, xK_i), raiseMaybe (runInTerm "-title Irssi" "sh -c 'screen -A -r irssi'") (title ~? "Irssi"))
, ((m .|. shiftMask,xK_i), spawn "TMP=$(mktemp --suffix='.txt'); xclip -o|tr '\n' ' '|sed -e 's/- //' -e 's/^ *//' -e 's/ *$//' -e 's/[[:blank:]]\\+/ /g' > $TMP && screen -S 'irssi' -X readbuf $TMP && screen -S 'irssi' -X paste .;rm $TMP")
, ((m, xK_m), runOrRaise "mnemosyne" (className =? "Mnemosyne"))
, ((m, xK_r), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -A -r rtorrent'") (title =? "rtorrent"))
, ((m .|. shiftMask,xK_r), spawn "/home/gwern/bin/bin/rotate-screen.sh")
, ((m, xK_f), raiseBrowser)
, ((m, xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/$(date +%Y)/log.txt")
, ((m .|. shiftMask,xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/$(date +%Y)/log-media.txt")]
++ [((m .|. m', key), screenWorkspace sc >>= flip whenJust (windows . f))
| (key, sc) <- zip [xK_s, xK_a] [0..]
, (f, m') <- [(W.view, 0), (W.shift, shiftMask)]]
where greenXPConfig' = greenXPConfig { font = "xft:Bitstream Vera Sans Mono:pixelsize=18" }