Xmonad/Config archive/Xilon's xmonad.hs

From HaskellWiki
< Xmonad‎ | Config archive
Revision as of 16:48, 25 December 2007 by Xilon (talk | contribs) (Added custom keybindings for switching workspaces)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

xmonad.hs

-- 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.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 ++ "'`"))
    ]
    ++
    -- 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 500 -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) ||| noBorders Full ||| Mirror tiled
        chatLayout = Full
        tiled = Tall 1 (3/100) (1/2)
-- }}}

-- Window rules (floating, tagging, etc) {{{
myManageHook = composeAll [
        className   =? "Firefox-bin"        --> doF(W.shift "2:internet"),
        className   =? "Gajim.py"           --> doF(W.shift "3: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) "
                ),
        ppTitle   = wrap ("^fg(" ++ myFocusedFGColor ++ ")") "^fg()" ,
        ppOutput  = hPutStrLn handle
}
-- }}}

.xinitrc

urxvtd -q -o -f
[[ -x "/usr/bin/numlockx" ]] && numlockx &
xsetroot -cursor_name left_ptr &
trayer --edge top --align right --margin 280 --widthtype pixel --width 48 --height 16 --SetDockType true --transparent true --alpha 204 &
~/.bin/dzen.sh | dzen2 -e 'onstart=lower' -p -ta r -fn '-*-terminus-medium-*-*-*-12-*-*-*-*-*-iso8859-1' -bg '#2e3436' -fg '#babdb6' -h 16 &
exec xmonad;

dzen2 script

#!/bin/zsh

###
# Config
###
DATE_FORMAT="%a %d %b, %Y"
TIME_ZONES=("Australia/Perth" "Europe/Warsaw")
SEPERATOR=' ^fg(#86AA3F)^c(3)^fg() '
BAR_BG='#7DA926'
BAR_FG='#B9D56E'
BAR_H=7
BAR_W=50
BAR_ARGS="-bg $BAR_BG -fg $BAR_FG -w $BAR_W -h $BAR_H"
ICON_DIR="$HOME/.share/icons/dzen"

GLOBALIVAL=1m
DATEIVAL=60
TIMEIVAL=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
}

DATEI=0
TIMEI=0

date=$(_date)
times=$(_time)

while true; do
    [[ $DATEI -ge $DATEIVAL ]] && date=$(_date) && DATEI=0
    [[ $TIMEI -ge $TIMEIVAL ]] && times=$(_time) && TIMEI=0

    print "${SEPERATOR}${times}${SEPERATOR}${date}"

    DATEI=$(($DATEI+1))
    TIMEI=$(($TIMEI+1))

    sleep $GLOBALIVAL
done

Preview

Xilon-config.png