Xmonad again, oh fuck yes.

This commit is contained in:
Josh Sherman 2012-05-20 17:12:09 -04:00
parent 1c399b8d9d
commit 311629e01f
7 changed files with 671 additions and 0 deletions

4
xmonad/.gitignore vendored Normal file
View file

@ -0,0 +1,4 @@
xmonad-x86_64-linux
xmonad.errors
xmonad.hi
xmonad.o

10
xmonad/bin/dmenu Executable file
View file

@ -0,0 +1,10 @@
#!/bin/sh
# Script to launch dmenu with colors matching IR_Black theme
# Author: Vic Fryzel
# http://github.com/vicfryzel/xmonad-config
# eval `exec /usr/bin/dmenu_run -fn '9x15' \
# -nb '#000000' -nf '#FFFFFF' -sb '#333333' -sf '#CEFFAC' -p '>' -i`
eval `exec /usr/bin/dmenu_run -fn 'xft:Ubuntu Mono-11' \
-nb '#000000' -nf '#FFFFFF' -sb '#333333' -sf '#CEFFAC' -p '>' -i`

7
xmonad/bin/fixscreens Executable file
View file

@ -0,0 +1,7 @@
#!/bin/sh
# Fix screens after, for example, a fullscreen game shut off one monitor.
# Author: Vic Fryzel
# http://github.com/vicfryzel/xmonad-config
xrandr -s 0

22
xmonad/bin/startup Executable file
View file

@ -0,0 +1,22 @@
#!/bin/sh
#xcompmgr &
# gsettings set org.gnome.desktop.background picture-uri "" &
#
# #empathy &
# tomboy &
# shutter --min_at_startup &
# #dropbox start -i
# #killall naturalscrolling
#
# #gnome-terminal &
# #chromium-browser &
# #gnome-do &
#
# #gnome-settings-daemon &
# #gnome-sound-applet
# #nm-applet &
# #gnome-power-manager &
#
# ~/.xmonad/bin/tray &

208
xmonad/xmonad.hs Normal file
View file

@ -0,0 +1,208 @@
{-# LANGUAGE OverloadedStrings #-}
import System.IO
import System.Exit
import XMonad
import XMonad.Config.Gnome
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers
-- import XMonad.Hooks.SetWMName
-- import XMonad.Layout.NoBorders
-- import XMonad.Layout.Spacing
-- import XMonad.Layout.Grid
-- import XMonad.Layout.Spiral
-- import XMonad.Layout.Tabbed
-- import XMonad.Layout.PerWorkspace
-- import XMonad.Layout.Named
import XMonad.Util.Run(spawnPipe)
-- import XMonad.Util.EZConfig(additionalKeys)
import qualified XMonad.StackSet as W
import qualified Data.Map as M
import qualified DBus.Client.Simple as D
import qualified Codec.Binary.UTF8.String as UTF8
-- mod#Mask
-- 1 = Left Alt (Conflicts with Gnome3 Panel)
-- 2 = ???
-- 3 = Right Alt
-- 4 = "Windows"
myModMask = mod1Mask
myWorkspaces = ["1","2","3","4"] ++ map show [5..9]
-- xprop | grep WM_CLASS
myManageHook :: [ManageHook]
myManageHook =
[ resource =? "chromium-browser" --> doShift "2"
, resource =? "desktop_window" --> doIgnore
, className =? "Firefox" --> doShift "2"
, className =? "Empathy" --> doShift "2"
, className =? "Galculator" --> doCenterFloat
, className =? "Gimp" --> doFloat
, className =? "Google-chrome" --> doShift "2"
, resource =? "gpicview" --> doFloat
, resource =? "kdesktop" --> doIgnore
, className =? "MPlayer" --> doFloat
, resource =? "nm-connection-editor" --> doFloat
, className =? "Rhythmbox" --> doShift "4"
, className =? "Banshee" --> doShift "4"
, className =? "Agave" --> doCenterFloat
, className =? "Gmail - Inbox" --> doShift "3"]
myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
-- Start a terminal. Terminal to start is specified by myTerminal variable.
[ ((modMask .|. shiftMask, xK_Return),
spawn $ XMonad.terminal conf)
, ((modMask, xK_p),
spawn "~/.xmonad/bin/dmenu")
-- Close focused window.
, ((modMask .|. shiftMask, xK_c),
kill)
-- Cycle through the available layout algorithms.
, ((modMask, xK_space),
sendMessage NextLayout)
-- Reset the layouts on the current workspace to default.
, ((modMask .|. shiftMask, xK_space),
setLayout $ XMonad.layoutHook conf)
-- Resize viewed windows to the correct size.
, ((modMask, xK_n),
refresh)
-- Move focus to the next window.
, ((modMask, xK_Tab),
windows W.focusDown)
-- Move focus to the next window.
, ((modMask, xK_j),
windows W.focusDown)
-- Move focus to the previous window.
, ((modMask, xK_k),
windows W.focusUp )
-- Move focus to the master window.
, ((modMask, xK_m),
windows W.focusMaster )
-- Swap the focused window and the master window.
, ((modMask, xK_Return),
windows W.swapMaster)
-- Swap the focused window with the next window.
, ((modMask .|. shiftMask, xK_j),
windows W.swapDown )
-- Swap the focused window with the previous window.
, ((modMask .|. shiftMask, xK_k),
windows W.swapUp )
-- Shrink the master area.
, ((modMask, xK_h),
sendMessage Shrink)
-- Expand the master area.
, ((modMask, xK_l),
sendMessage Expand)
-- Push window back into tiling.
, ((modMask, xK_t),
withFocused $ windows . W.sink)
-- Increment the number of windows in the master area.
, ((modMask, xK_comma),
sendMessage (IncMasterN 1))
-- Decrement the number of windows in the master area.
, ((modMask, xK_period),
sendMessage (IncMasterN (-1)))
-- Toggle the status bar gap.
-- TODO: update this binding with avoidStruts, ((modMask, xK_b),
-- Quit xmonad.
--, ((modMask .|. shiftMask, xK_q),
-- spawn "gnome-session-quit --logout --no-prompt")
--promptio (exitWith ExitSuccess))
-- Quit xmonad
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
-- Restart xmonad.
, ((modMask, xK_q),
restart "xmonad" True)
]
++
-- mod-[1..9], Switch to workspace N
-- mod-shift-[1..9], Move client to workspace N
[((m .|. modMask, k), windows $ f i)
| (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
++
-- 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
[((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)]]
main :: IO ()
main = do
dbus <- D.connectSession
getWellKnownName dbus
xmonad $ gnomeConfig
{ logHook = dynamicLogWithPP (prettyPrinter dbus)
, modMask = myModMask
, keys = myKeys
, workspaces = myWorkspaces
, manageHook = manageHook gnomeConfig <+> composeAll myManageHook
}
prettyPrinter :: D.Client -> PP
prettyPrinter dbus = defaultPP
{ ppOutput = dbusOutput dbus
, ppTitle = pangoSanitize
, ppCurrent = pangoColor "green" . wrap "[" "]" . pangoSanitize
, ppVisible = pangoColor "yellow" . wrap "(" ")" . pangoSanitize
, ppHidden = const ""
, ppUrgent = pangoColor "red"
, ppLayout = const ""
, ppSep = " "
}
getWellKnownName :: D.Client -> IO ()
getWellKnownName dbus = do
D.requestName dbus (D.busName_ "org.xmonad.Log")
[D.AllowReplacement, D.ReplaceExisting, D.DoNotQueue]
return ()
dbusOutput :: D.Client -> String -> IO ()
dbusOutput dbus str = D.emit dbus
"/org/xmonad/Log"
"org.xmonad.Log"
"Update"
[D.toVariant ("<b>" ++ (UTF8.decodeString str) ++ "</b>")]
pangoColor :: String -> String -> String
pangoColor fg = wrap left right
where
left = "<span foreground=\"" ++ fg ++ "\">"
right = "</span>"
pangoSanitize :: String -> String
pangoSanitize = foldr sanitize ""
where
sanitize '>' xs = "&gt;" ++ xs
sanitize '<' xs = "&lt;" ++ xs
sanitize '\"' xs = "&quot;" ++ xs
sanitize '&' xs = "&amp;" ++ xs
sanitize x xs = x:xs

364
xmonad/xmonad.josh Normal file
View file

@ -0,0 +1,364 @@
import System.IO
import System.Exit
import XMonad
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers
import XMonad.Hooks.SetWMName
import XMonad.Config.Gnome
import XMonad.Layout.NoBorders
import XMonad.Layout.Spacing
import XMonad.Layout.Grid
import XMonad.Layout.Spiral
import XMonad.Layout.Tabbed
import XMonad.Layout.PerWorkspace
import XMonad.Layout.Named
import XMonad.Util.Run(spawnPipe)
import XMonad.Util.EZConfig(additionalKeys)
import qualified XMonad.StackSet as W
import qualified Data.Map as M
import qualified DBus.Client.Simple as D
import qualified Codec.Binary.UTF8.String as UTF8
myTerminal = "/usr/bin/gnome-terminal"
myWorkspaces = ["1","2","3","4"] ++ map show [5..9]
-- xprop | grep WM_CLASS
myManageHook = composeAll
[ resource =? "chromium-browser" --> doShift "2"
, resource =? "desktop_window" --> doIgnore
, className =? "Firefox" --> doShift "2"
, className =? "Empathy" --> doShift "2"
, className =? "Galculator" --> doCenterFloat
, className =? "Gimp" --> doFloat
, className =? "Google-chrome" --> doShift "2"
, resource =? "gpicview" --> doFloat
, resource =? "kdesktop" --> doIgnore
, className =? "MPlayer" --> doFloat
, resource =? "nm-connection-editor" --> doFloat
, className =? "Rhythmbox" --> doShift "4"
, className =? "Banshee" --> doShift "4"
, className =? "Agave" --> doCenterFloat
, className =? "Gmail - Inbox" --> doShift "3"]
nmaster = 1
ratio = 1/2
delta = 3/100
tiled = spacing 2 $ Tall nmaster delta ratio
grid = spacing 2 $ Grid
web = spacing 2 $ Tall 1 (3/100) (80/100)
full = noBorders $ Full
myLayout = avoidStruts (onWorkspace "2" (named "Web" web) (named "Tiled" tiled) ||| named "Grid" grid) ||| named "Full" full
{-
myLayout = avoidStruts (
Tall 1 (3/100) (1/2) |||
Mirror (Tall 1 (3/100) (1/2)) |||
tabbed shrinkText tabConfig |||
Full |||
spiral (6/7))
-}
{-
myLayout = avoidStruts (
Tall 1 (3/100) (1/2) |||
Mirror (Tall 1 (3/100) (1/2)) |||
tabbed shrinkText tabConfig |||
Full |||
spiral (6/7))
-}
------------------------------------------------------------------------
-- Colors and borders
-- Currently based on the ir_black theme.
--
myNormalBorderColor = "#7c7c7c"
-- myFocusedBorderColor = "#ffb6b0"
myFocusedBorderColor = "#CD0000"
-- Colors for text and backgrounds of each tab when in "Tabbed" layout.
tabConfig = defaultTheme {
activeBorderColor = "#7C7C7C",
activeTextColor = "#CEFFAC",
activeColor = "#000000",
inactiveBorderColor = "#7C7C7C",
inactiveTextColor = "#EEEEEE",
inactiveColor = "#000000"
}
myBorderWidth = 1
-- mod#Mask
-- 1 = Left Alt (Conflicts with Gnome3 Panel)
-- 2 = ???
-- 3 = Right Alt
-- 4 = "Windows"
myModMask = mod4Mask
myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
-- Custom key bindings
-- Start a terminal. Terminal to start is specified by myTerminal variable.
[ ((modMask .|. shiftMask, xK_Return),
spawn $ XMonad.terminal conf)
-- Lock the screen using xscreensaver.
, ((modMask .|. controlMask, xK_l),
-- spawn "slock")
spawn "xscreensaver-command -lock")
-- Launch dmenu via yeganesh.
-- Use this to launch programs without a key binding.
, ((modMask, xK_p),
spawn "~/.xmonad/bin/dmenu")
-- Take a screenshot in select mode.
-- After pressing this key binding, click a window, or draw a rectangle with
-- the mouse.
, ((modMask .|. shiftMask, xK_p),
spawn "~/.xmonad/bin/select-screenshot")
-- Take full screenshot in multi-head mode.
-- That is, take a screenshot of everything you see.
, ((modMask .|. controlMask .|. shiftMask, xK_p),
spawn "~/.xmonad/bin/screenshot")
-- Mute volume.
, ((0, 0x1008FF12),
spawn "amixer -q set Front toggle")
-- Decrease volume.
, ((0, 0x1008FF11),
spawn "amixer -q set Front 10%-")
-- Increase volume.
, ((0, 0x1008FF13),
spawn "amixer -q set Front 10%+")
-- Audio previous.
, ((0, 0x1008FF16),
spawn "")
-- Play/pause.
, ((0, 0x1008FF14),
spawn "")
-- Audio next.
, ((0, 0x1008FF17),
spawn "")
-- Eject CD tray.
, ((0, 0x1008FF2C),
spawn "eject -T")
-- "Standard" xmonad key bindings
-- Close focused window.
, ((modMask .|. shiftMask, xK_c),
kill)
-- Cycle through the available layout algorithms.
, ((modMask, xK_space),
sendMessage NextLayout)
-- Reset the layouts on the current workspace to default.
, ((modMask .|. shiftMask, xK_space),
setLayout $ XMonad.layoutHook conf)
-- Resize viewed windows to the correct size.
, ((modMask, xK_n),
refresh)
-- Move focus to the next window.
, ((modMask, xK_Tab),
windows W.focusDown)
-- Move focus to the next window.
, ((modMask, xK_j),
windows W.focusDown)
-- Move focus to the previous window.
, ((modMask, xK_k),
windows W.focusUp )
-- Move focus to the master window.
, ((modMask, xK_m),
windows W.focusMaster )
-- Swap the focused window and the master window.
, ((modMask, xK_Return),
windows W.swapMaster)
-- Swap the focused window with the next window.
, ((modMask .|. shiftMask, xK_j),
windows W.swapDown )
-- Swap the focused window with the previous window.
, ((modMask .|. shiftMask, xK_k),
windows W.swapUp )
-- Shrink the master area.
, ((modMask, xK_h),
sendMessage Shrink)
-- Expand the master area.
, ((modMask, xK_l),
sendMessage Expand)
-- Push window back into tiling.
, ((modMask, xK_t),
withFocused $ windows . W.sink)
-- Increment the number of windows in the master area.
, ((modMask, xK_comma),
sendMessage (IncMasterN 1))
-- Decrement the number of windows in the master area.
, ((modMask, xK_period),
sendMessage (IncMasterN (-1)))
-- Toggle the status bar gap.
-- TODO: update this binding with avoidStruts, ((modMask, xK_b),
-- Quit xmonad.
--, ((modMask .|. shiftMask, xK_q),
-- spawn "gnome-session-quit --logout --no-prompt")
--promptio (exitWith ExitSuccess))
-- Quit xmonad
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
-- Restart xmonad.
, ((modMask, xK_q),
restart "xmonad" True)
]
++
-- mod-[1..9], Switch to workspace N
-- mod-shift-[1..9], Move client to workspace N
[((m .|. modMask, k), windows $ f i)
| (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
++
-- 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
[((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)]]
------------------------------------------------------------------------
-- Mouse bindings
--
-- Focus rules
-- True if your focus should follow your mouse cursor.
myFocusFollowsMouse :: Bool
myFocusFollowsMouse = True
myMouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
[
-- mod-button1, Set the window to floating mode and move by dragging
((modMask, button1),
(\w -> focus w >> mouseMoveWindow w))
-- mod-button2, Raise the window to the top of the stack
, ((modMask, button2),
(\w -> focus w >> windows W.swapMaster))
-- mod-button3, Set the window to floating mode and resize by dragging
, ((modMask, button3),
(\w -> focus w >> mouseResizeWindow w))
-- you may also bind events to the mouse scroll wheel (button4 and button5)
]
myStartupHook = return ()
main :: IO ()
main = do
dbus <- D.connectSession
getWellKnownName dbus
spawnPipe "~/.xmonad/bin/startup"
-- xmonad $ defaults {
xmonad $ gnomeConfig {
logHook = dynamicLogWithPP (prettyPrinter dbus)
-- manageHook = manageDocks <+> myManageHook
-- , startupHook = setWMName "LG3D"
}
prettyPrinter :: D.Client -> PP
prettyPrinter dbus = defaultPP
{ ppOutput = dbusOutput dbus
, ppTitle = pangoSanitize
, ppCurrent = pangoColor "green" . wrap "[" "]" . pangoSanitize
, ppVisible = pangoColor "yellow" . wrap "(" ")" . pangoSanitize
, ppHidden = const ""
, ppUrgent = pangoColor "red"
, ppLayout = const ""
, ppSep = " "
}
getWellKnownName :: D.Client -> IO ()
getWellKnownName dbus = do
D.requestName dbus (D.busName_ "org.xmonad.Log")
[D.AllowReplacement, D.ReplaceExisting, D.DoNotQueue]
return ()
dbusOutput :: D.Client -> String -> IO ()
dbusOutput dbus str = D.emit dbus
"/org/xmonad/Log"
"org.xmonad.Log"
"Update"
[D.toVariant ("<b>" ++ (UTF8.decodeString str) ++ "</b>")]
pangoColor :: String -> String -> String
pangoColor fg = wrap left right
where
left = "<span foreground=\"" ++ fg ++ "\">"
right = "</span>"
pangoSanitize :: String -> String
pangoSanitize = foldr sanitize ""
where
sanitize '>' xs = "&gt;" ++ xs
sanitize '<' xs = "&lt;" ++ xs
sanitize '\"' xs = "&quot;" ++ xs
sanitize '&' xs = "&amp;" ++ xs
sanitize x xs = x:xs
------------------------------------------------------------------------
-- Combine it all together
-- A structure containing your configuration settings, overriding
-- fields in the default config. Any you don't override, will
-- use the defaults defined in xmonad/XMonad/Config.hs
--
-- No need to modify this.
--
defaults = defaultConfig {
-- simple stuff
terminal = myTerminal,
focusFollowsMouse = myFocusFollowsMouse,
borderWidth = myBorderWidth,
modMask = myModMask,
workspaces = myWorkspaces,
normalBorderColor = myNormalBorderColor,
focusedBorderColor = myFocusedBorderColor,
-- key bindings
keys = myKeys,
mouseBindings = myMouseBindings,
-- hooks, layouts
layoutHook = smartBorders $ myLayout,
manageHook = myManageHook,
startupHook = myStartupHook
}

56
xmonad/xmonad.working Normal file
View file

@ -0,0 +1,56 @@
{-# LANGUAGE OverloadedStrings #-}
import XMonad
import XMonad.Config.Gnome
import XMonad.Hooks.DynamicLog
import qualified DBus.Client.Simple as D
import qualified Codec.Binary.UTF8.String as UTF8
main :: IO ()
main = do
dbus <- D.connectSession
getWellKnownName dbus
xmonad $ gnomeConfig
{ logHook = dynamicLogWithPP (prettyPrinter dbus)
}
prettyPrinter :: D.Client -> PP
prettyPrinter dbus = defaultPP
{ ppOutput = dbusOutput dbus
, ppTitle = pangoSanitize
, ppCurrent = pangoColor "green" . wrap "[" "]" . pangoSanitize
, ppVisible = pangoColor "yellow" . wrap "(" ")" . pangoSanitize
, ppHidden = const ""
, ppUrgent = pangoColor "red"
, ppLayout = const ""
, ppSep = " "
}
getWellKnownName :: D.Client -> IO ()
getWellKnownName dbus = do
D.requestName dbus (D.busName_ "org.xmonad.Log")
[D.AllowReplacement, D.ReplaceExisting, D.DoNotQueue]
return ()
dbusOutput :: D.Client -> String -> IO ()
dbusOutput dbus str = D.emit dbus
"/org/xmonad/Log"
"org.xmonad.Log"
"Update"
[D.toVariant ("<b>" ++ (UTF8.decodeString str) ++ "</b>")]
pangoColor :: String -> String -> String
pangoColor fg = wrap left right
where
left = "<span foreground=\"" ++ fg ++ "\">"
right = "</span>"
pangoSanitize :: String -> String
pangoSanitize = foldr sanitize ""
where
sanitize '>' xs = "&gt;" ++ xs
sanitize '<' xs = "&lt;" ++ xs
sanitize '\"' xs = "&quot;" ++ xs
sanitize '&' xs = "&amp;" ++ xs
sanitize x xs = x:xs