Xmonad/Config archive/Gwern's xmonad.hs: Difference between revisions
< Xmonad | Config archive
(update my config; greenXPConfig now in darcs, and finish up xcompmgr support) |
(gnome-panel autohide!) |
||
Line 13: | Line 13: | ||
import XMonad.Hooks.UrgencyHook (withUrgencyHook, FocusHook(..)) | import XMonad.Hooks.UrgencyHook (withUrgencyHook, FocusHook(..)) | ||
import XMonad.Layout (Full(..), Mirror(..), Tall(..), (|||)) | import XMonad.Layout (Full(..), Mirror(..), Tall(..), (|||)) | ||
import XMonad.Layout.Monitor (addMonitor, Property(ClassName)) | |||
import XMonad.Layout.NoBorders (smartBorders) | import XMonad.Layout.NoBorders (smartBorders) | ||
import XMonad.Main (xmonad) | import XMonad.Main (xmonad) | ||
Line 26: | Line 27: | ||
where myConfig = withUrgencyHook FocusHook $ gnomeConfig { focusedBorderColor = "red" | where myConfig = withUrgencyHook FocusHook $ gnomeConfig { focusedBorderColor = "red" | ||
, keys = \c -> myKeys c `M.union` keys defaultConfig c | , keys = \c -> myKeys c `M.union` keys defaultConfig c | ||
, layoutHook = avoidStruts $ smartBorders (Full ||| Mirror tiled ||| tiled ) | , layoutHook = hideGnome $ avoidStruts $ smartBorders $ (Full ||| Mirror tiled ||| tiled ) | ||
, logHook = ewmhDesktopsLogHook >> fadeInactiveLogHook 0xdddddddd | , logHook = ewmhDesktopsLogHook >> fadeInactiveLogHook 0xdddddddd | ||
, manageHook = myManageHook | , manageHook = myManageHook | ||
Line 35: | Line 36: | ||
where tiled :: Tall a | where tiled :: Tall a | ||
tiled = Tall 1 0.03 0.5 | tiled = Tall 1 0.03 0.5 | ||
hideGnome = addMonitor (ClassName "gnome-panel") (Rectangle 0 0 0 0) | |||
{- Important things to note: We specifically don't use 'managehook | {- Important things to note: We specifically don't use 'managehook | ||
Line 45: | Line 47: | ||
moveToT "irssi" "irc", | moveToT "irssi" "irc", | ||
className =? "defcon.bin.x86" --> unfloat, | className =? "defcon.bin.x86" --> unfloat, | ||
className =? "Darwinia" --> unfloat ] | className =? "Darwinia" --> unfloat, | ||
className =? "gnome-panel" --> doIgnore ] | |||
<+> manageDocks | <+> manageDocks | ||
where moveToC c w = className =? c --> doF (W.shift w) | where moveToC c w = className =? c --> doF (W.shift w) | ||
Line 52: | Line 55: | ||
myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ()) | myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ()) | ||
myKeys conf@(XConfig {modMask = m}) = M.fromList [ -- rebind standard | myKeys conf@(XConfig {modMask = m}) = M.fromList [ -- rebind standard keys | ||
((m .|. shiftMask,xK_p), shellPrompt greenXPConfig) | ((m .|. shiftMask,xK_p), shellPrompt greenXPConfig) | ||
, ((m, xK_k), kill) | , ((m, xK_k), kill) | ||
Line 58: | Line 61: | ||
, ((m, xK_p), windows W.focusUp) | , ((m, xK_p), windows W.focusUp) | ||
, ((m, xK_z), withFocused $ windows . W.sink) -- unfloat | , ((m, xK_z), withFocused $ windows . W.sink) -- unfloat | ||
-- | -- Custom bindings and commands | ||
, ((m, xK_s), goToSelected defaultGSConfig) | , ((m, xK_s), goToSelected defaultGSConfig) | ||
, ((m, xK_a), runOrRaise "amarok" (className =? "amarokapp")) | , ((m, xK_a), runOrRaise "amarok" (className =? "amarokapp")) |
Revision as of 00:30, 25 December 2008
import Data.Bits (Bits((.|.)))
import Data.Map as M (fromList, union, Map())
import XMonad
import XMonad.Actions.GridSelect (defaultGSConfig, goToSelected)
import XMonad.Actions.Search (google, isohunt, wayback, wikipedia, selectSearch, promptSearch)
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
import XMonad.Config (defaultConfig)
import XMonad.Config.Gnome (gnomeConfig)
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
import XMonad.Hooks.FadeInactive (fadeInactiveLogHook)
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
import XMonad.Hooks.UrgencyHook (withUrgencyHook, FocusHook(..))
import XMonad.Layout (Full(..), Mirror(..), Tall(..), (|||))
import XMonad.Layout.Monitor (addMonitor, Property(ClassName))
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Main (xmonad)
import XMonad.Operations (kill, windows, withFocused)
import XMonad.Prompt (greenXPConfig)
import XMonad.Prompt.Shell (shellPrompt, prompt, safePrompt)
import XMonad.StackSet as W (focusUp, focusDown, shift, sink)
import XMonad.Util.Run (unsafeSpawn, runInTerm)
import XMonad.Util.XSelection (safePromptSelection)
main :: IO ()
main = spawn "xcompmgr" >> xmonad myConfig
where myConfig = withUrgencyHook FocusHook $ gnomeConfig { focusedBorderColor = "red"
, keys = \c -> myKeys c `M.union` keys defaultConfig c
, layoutHook = hideGnome $ avoidStruts $ smartBorders $ (Full ||| Mirror tiled ||| tiled )
, logHook = ewmhDesktopsLogHook >> fadeInactiveLogHook 0xdddddddd
, manageHook = myManageHook
, modMask = mod4Mask
, normalBorderColor = "grey"
, terminal = "gnome-terminal"
, XMonad.workspaces = ["web", "irc", "code", "5"] }
where tiled :: Tall a
tiled = Tall 1 0.03 0.5
hideGnome = addMonitor (ClassName "gnome-panel") (Rectangle 0 0 0 0)
{- 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
gnome-panel; Firefox/Emacs/Irssi go to their designated workspaces. -}
myManageHook :: ManageHook
myManageHook = composeAll [ moveToC "Emacs" "code",
moveToC "Firefox" "web",
moveToT "irssi" "irc",
className =? "defcon.bin.x86" --> unfloat,
className =? "Darwinia" --> unfloat,
className =? "gnome-panel" --> doIgnore ]
<+> manageDocks
where moveToC c w = className =? c --> doF (W.shift w)
moveToT t w = title =? t --> doF (W.shift w)
unfloat = ask >>= doF . W.sink
myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ())
myKeys conf@(XConfig {modMask = m}) = 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_s), goToSelected defaultGSConfig)
, ((m, xK_a), runOrRaise "amarok" (className =? "amarokapp"))
, ((m, xK_b), safePrompt "firefox" greenXPConfig)
, ((m .|. shiftMask,xK_b), safePromptSelection "firefox")
, ((m, xK_c), unsafeSpawn term)
, ((m .|. shiftMask,xK_c), prompt (term ++ " -e") greenXPConfig)
, ((m .|. shiftMask,xK_d), raiseMaybe (runInTerm "--title=elinks" "elinks") (title =? "elinks"))
, ((m, xK_e), raiseEditor)
, ((m .|. shiftMask,xK_e), prompt "emacsclient -a 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_u), promptSearch greenXPConfig isohunt)
, ((m .|. shiftMask,xK_u), selectSearch isohunt)
, ((m, xK_y), promptSearch greenXPConfig wayback)
, ((m .|. shiftMask,xK_y), selectSearch wayback)
, ((m, xK_Print), unsafeSpawn "import -quality 90 -window root png:$HOME/xwd-$(date +%s)$$.png")
, ((m, xK_i), raiseMaybe (runInTerm "--title=irssi" "\"sh -c 'screen -r irssi'\"") (title =? "irssi"))
-- We ask for zsh specifically so ~/.zshenv gets picked up and my
-- expanded $PATH gets used; otherwise Mutt can't find needed scripts.
, ((m, xK_m), raiseMaybe (runInTerm "--title=mutt" "\"zsh -c 'mutt'\"") (title =? "mutt"))
, ((m .|. shiftMask,xK_m), runOrRaise "mnemosyne" (className =? "Mnemosyne"))
, ((m, xK_r), raiseMaybe (runInTerm "--title='rtorrent'" "\"sh -c 'screen -r rtorrent'\"") (title =? "rtorrent"))
, ((m, xK_d), raiseBrowser) ]
where term :: String
term = XMonad.terminal conf