Xmonad/Config archive/Xilon's xmonad.hs
xmonad.hs[edit]
-- vim :fdm=marker sw=4 sts=4 ts=4 et ai:
-- Imports {{{
import XMonad
import XMonad.Layout
import XMonad.Layout.NoBorders (noBorders)
import XMonad.Layout.PerWorkspace
import XMonad.Layout.LayoutHints
import XMonad.Layout.ThreeColumns
import XMonad.Hooks.DynamicLog (PP(..), dynamicLogWithPP, wrap, defaultPP)
import XMonad.Hooks.UrgencyHook
import XMonad.Util.Run (spawnPipe)
import qualified XMonad.StackSet as W
import qualified Data.Map as M
import System.IO (hPutStrLn)
-- }}}
-- Control Center {{{
-- Colour scheme {{{
myNormalBGColor = "#2e3436"
myFocusedBGColor = "#414141"
myNormalFGColor = "#babdb6"
myFocusedFGColor = "#73d216"
myUrgentFGColor = "#f57900"
myUrgentBGColor = myNormalBGColor
mySeperatorColor = "#2e3436"
-- }}}
-- Icon packs can be found here:
-- http://robm.selfip.net/wiki.sh/-main/DzenIconPacks
myBitmapsDir = "/home/xilon/.share/icons/dzen"
myFont = "-*-terminus-medium-*-*-*-12-*-*-*-*-*-iso8859-1"
-- }}}
-- Workspaces {{{
myWorkspaces :: [WorkspaceId]
myWorkspaces = ["general", "internet", "chat", "code"] ++ map show [5..9 :: Int]
-- }}}
-- Keybindings {{{
myKeys conf@(XConfig {modMask = modm}) = M.fromList $
[
((modm , xK_p), spawn ("exec `dmenu_path | dmenu -fn '" ++ myFont ++ "' -nb '" ++ myNormalBGColor ++ "' -nf '" ++ myNormalFGColor ++ "' -sb '" ++ myFocusedBGColor ++ "' -sf '" ++ myFocusedFGColor ++ "'`")),
((modm , xK_g), spawn ("exec gajim-remote toggle_roster_appearance"))
]
++
-- Remap switching workspaces to M-[asdfzxcv]
[((m .|. modm, k), windows $ f i)
| (i, k) <- zip (XMonad.workspaces conf) [xK_a, xK_s, xK_d, xK_f, xK_v]
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
-- }}}
statusBarCmd= "dzen2 -p -h 16 -ta l -bg '" ++ myNormalBGColor ++ "' -fg '" ++ myNormalFGColor ++ "' -w 768 -sa c -fn '" ++ myFont ++ "'"
-- Main {{{
main = do
statusBarPipe <- spawnPipe statusBarCmd
xmonad $ withUrgencyHook NoUrgencyHook $defaultConfig {
modMask = mod4Mask,
borderWidth = 1,
terminal = "urxvtc",
normalBorderColor = myNormalBGColor,
focusedBorderColor = myFocusedFGColor,
defaultGaps = [(16,0,0,0)],
manageHook = manageHook defaultConfig <+> myManageHook,
layoutHook = onWorkspace "chat" chatLayout globalLayout,
workspaces = myWorkspaces,
logHook = dynamicLogWithPP $ myPP statusBarPipe,
keys = \c -> myKeys c `M.union` keys defaultConfig c
}
where
globalLayout = layoutHints (tiled) ||| layoutHints (noBorders Full) ||| layoutHints (Mirror tiled) ||| layoutHints (Tall 1 (3/100) (1/2))
chatLayout = layoutHints (noBorders Full)
tiled = ThreeCol 1 (3/100) (1/2)
-- }}}
-- Window rules (floating, tagging, etc) {{{
myManageHook = composeAll [
className =? "Firefox-bin" --> doF(W.shift "internet"),
className =? "Gajim.py" --> doF(W.shift "chat"),
title =? "Gajim" --> doFloat,
className =? "stalonetray" --> doIgnore,
className =? "trayer" --> doIgnore
]
-- }}}
-- Dzen Pretty Printer {{{
-- Stolen from Rob [1] and modified
-- [1] http://haskell.org/haskellwiki/Xmonad/Config_archive/Robert_Manea%27s_xmonad.hs
myPP handle = defaultPP {
ppCurrent = wrap ("^fg(" ++ myFocusedFGColor ++ ")^bg(" ++ myFocusedBGColor ++ ")^p(4)") "^p(4)^fg()^bg()",
ppUrgent = wrap ("^fg(" ++ myUrgentFGColor ++ ")^bg(" ++ myUrgentBGColor ++ ")^p(4)") "^p(4)^fg()^bg()",
ppVisible = wrap ("^fg(" ++ myNormalFGColor ++ ")^bg(" ++ myNormalBGColor ++ ")^p(4)") "^p(4)^fg()^bg()",
ppSep = "^fg(" ++ mySeperatorColor ++ ")^r(3x3)^fg()",
ppLayout = (\x -> case x of
"Tall" -> " ^i(" ++ myBitmapsDir ++ "/tall.xbm) "
"Mirror Tall" -> " ^i(" ++ myBitmapsDir ++ "/mtall.xbm) "
"Full" -> " ^i(" ++ myBitmapsDir ++ "/full.xbm) "
"ThreeCol" -> " ^i(" ++ myBitmapsDir ++ "/threecol.xbm) "
"Hinted Tall" -> " ^i(" ++ myBitmapsDir ++ "/tall.xbm) "
"Hinted Mirror Tall" -> " ^i(" ++ myBitmapsDir ++ "/mtall.xbm) "
"Hinted Full" -> " ^i(" ++ myBitmapsDir ++ "/full.xbm) "
"Hinted ThreeCol" -> " ^i(" ++ myBitmapsDir ++ "/threecol.xbm) "
_ -> " " ++ x ++ " "
),
ppTitle = wrap ("^fg(" ++ myFocusedFGColor ++ ")") "^fg()" ,
ppOutput = hPutStrLn handle
}
-- }}}
.xinitrc[edit]
#!/bin/sh
#
# ~/.xinitrc
#
# Executed by startx (run your window manager from here)
#
# Start URxvt daemon so we can quickly open the other clients
urxvtd -q -o -f
[[ -x "/usr/bin/numlockx" ]] && numlockx &
[[ -x "/usr/bin/unclutter" -a -z "`pidof unclutter`" ]] && \
unclutter -idle 5 -root&
# Set Wallpaper with feh
eval `cat ~/.fehbg` &
# Set mouse cursor and background colour
xsetroot -cursor_name left_ptr -solid '#090909' &
# Launch tray and statusbar
stalonetray -i 16 --max-width 48 --icon-gravity E --geometry 48x16-0+0 -bg '#2e3436' --sticky --skip-taskbar &
~/.bin/dzen.sh | dzen2 -e 'onstart=lower' -p -ta r -fn '-*-terminus-medium-*-*-*-12-*-*-*-*-*-iso8859-1' -bg '#2e3436' -fg '#babdb6' -h 16 -w 1632 &
# Launch WM
exec xmonad
dzen2 script[edit]
#!/bin/zsh
typeset -A DISKS
###
# Config
###
DATE_FORMAT="%a %d %b, %Y"
TIME_ZONES=("Australia/Perth" "Europe/Warsaw")
DISKS=(music /media/music media /media downloads /mnt/downloads)
SEPERATOR=' ^fg(#86AA3F)^c(3)^fg() '
BAR_BG='#7DA926'
BAR_FG='#B9D56E'
BAR_HH=6
BAR_HW=40
BAR_VH=12
BAR_VW=3
BAR_ARGS="-bg $BAR_BG -fg $BAR_FG -w $BAR_HW -h $BAR_HH"
ICON_DIR="$HOME/.share/icons/dzen"
NETWORK_INTERFACE=eth0
NET_DOWN_MAX=55
NET_UP_MAX=14
MAILDIR=~/mail/GmailMain
GLOBALIVAL=1m
DATEIVAL=60
TIMEIVAL=1
DISKIVAL=1
#CPUTEMPIVAL=5
#CPUIVAL=1
#NPIVAL=3
NETIVAL=1
###
# Functions
###
_date()
{
date +${DATE_FORMAT}
}
_time()
{
local zone
print_space=0
for zone in $TIME_ZONES; do
[[ $print_space -eq 1 ]] && print -n " "
print -n "${zone:t}: $(TZ=$zone date '+%H:%M')"
print_space=1
done
}
#
# Format: label1 mountpoint1 label2 mountpoint2 ... labelN mountpointN
# Copied and modified from Rob
get_disk_usage() {
local rstr; local tstr; local i; local sep
for i in ${(k)DISKS}; do
tstr=$(print `df -h $DISKS[$i]|sed -ne 's/^.* \([0-9]*\)% .*/\1/p'` 100 | \
gdbar -h $BAR_HH -w $BAR_HW -fg $BAR_FG -bg $BAR_BG -l "${i}" -nonl | \
sed 's/[0-9]\+%//g;s/ / /g')
if [ ! -z "$rstr" ]; then
sep=${SEPERATOR}
fi
rstr="${rstr}${sep}${tstr}"
done
print -n $rstr
}
# Requires mesure
get_net_rates() {
local up; local down
up=`mesure -K -l -c 3 -t -o $NETWORK_INTERFACE`
down=`mesure -K -l -c 3 -t -i $NETWORK_INTERFACE`
echo "$down $up"
}
#cpu_temp()
#{
# print -n ${(@)$(</proc/acpi/thermal_zone/THRM/temperature)[2,3]}
#}
#
#np()
#{
# #MAXPOS="100"
# CAPTION="^i(${ICON_DIR}/musicS.xbm)"
# #POS=`mpc | sed -ne 's/^.*(\([0-9]*\)%).*$/\1/p'`
# #POSM="$POS $MAXPOS"
# print -n "$CAPTION "
# mpc | head -n1 | tr -d '\n'
# #echo "$POSM" | gdbar -h 7 -w 50 -fg $BAR_FG -bg $BAR_BG
#}
#
#cpu()
#{
# gcpubar -c 2 -bg $BAR_BG -fg $BAR_FG -w $BAR_HW -h $BAR_HH | tail -n1 | tr -d '\n'
#}
has_new_mail() {
find ${MAILDIR}/*/new -not -type d | wc -l
}
DATEI=0
TIMEI=0
DISKI=0
#NPI=0
#CPUTEMPI=0
#CPUI=0
NETI=0
date=$(_date)
times=$(_time)
disk_usage=$(get_disk_usage)
#now_playing=$(np)
#temp=$(cpu_temp)
#cpumeter=$(cpu)
net_rates=( `get_net_rates` )
while true; do
[[ $DATEI -ge $DATEIVAL ]] && date=$(_date) && DATEI=0
[[ $TIMEI -ge $TIMEIVAL ]] && times=$(_time) && TIMEI=0
[[ $DISKI -ge $DISKIVAL ]] && disk_usage=$(get_disk_usage) && DISKI=0
#[[ $NPI -ge $NPIVAL ]] && now_playing=$(np) && NPI=0
#[[ $CPUI -ge $CPUIVAL ]] && cpumeter=$(cpu) && CPUI=0
#[[ $CPUTEMPI -ge $CPUTEMPIVAL ]] && temp=$(cpu_temp) && CPUTEMPI=0
[[ $NETI -ge $NETIVAL ]] && net_rates=( `get_net_rates` ) && NETI=0
# Disk usage
echo -n "${disk_usage}${SEPERATOR}"
# Network
echo $net_rates[1] | gdbar -nonl -s v -w $BAR_VW -h $BAR_VH -min 0 \
-max $NET_DOWN_MAX -fg $BAR_FG -bg $BAR_BG
echo -n " "
echo $net_rates[2] | gdbar -nonl -s v -w $BAR_VW -h $BAR_VH -min 0 \
-max $NET_UP_MAX -fg $BAR_FG -bg $BAR_BG
echo -n "${SEPERATOR}"
# Mail notification
if [ `has_new_mail` -gt 0 ]; then
echo -n "^fg(#73d216)"
fi
echo -n "^i(${ICON_DIR}/envelope2.xbm)^fg()${SEPERATOR}"
# Time and date
echo -n "${times}${SEPERATOR}"
echo -n "${date}"
echo
DATEI=$(($DATEI+1))
TIMEI=$(($TIMEI+1))
DISKI=$(($DISKI+1))
#NPI=$(($NPI+1))
#CPUI=$(($CPUI+1))
#CPUTEMPI=$(($CPUTEMPI+1))
NETI=$(($NETI+1))
sleep $GLOBALIVAL
done