Xmonad/Config archive/And1's xmonad.hs

From HaskellWiki
< Xmonad‎ | Config archive
Revision as of 13:35, 2 August 2008 by And1 (talk | contribs)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
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/xmonad.hs
-- validate syntax: $ ghci ~/.xmonad/xmonad.hs
------------------------------------------------------------------------

import XMonad hiding (Tall)
import XMonad.Actions.CycleWS
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.UrgencyHook
import XMonad.Layout.HintedTile
import XMonad.Layout.LayoutHints
import XMonad.Layout.PerWorkspace
import XMonad.ManageHook
import XMonad.Prompt
import XMonad.Prompt.Shell
import XMonad.Util.Run
import System.Exit
import System.IO

import qualified Data.Map as M
import qualified System.IO.UTF8
import qualified XMonad.Actions.FlexibleResize as Flex
import qualified XMonad.StackSet as W

main = do
    din <- spawnPipe myStatusBar
    din2 <- spawnPipe myTopBar
    din3 <- spawnPipe myBottomBar
    xmonad $ myUrgencyHook $ defaultConfig

       { normalBorderColor = "#222222"
       , focusedBorderColor = "#2277aa"
       , terminal = "urxvt"
       , layoutHook = myLayout
       , manageHook = myManageHook <+> manageDocks
       , workspaces = ["1:irc", "2:www", "3:music"] ++ map show [4..9]
       , numlockMask = mod2Mask
       , modMask = mod1Mask
       , keys = myKeys
       , mouseBindings = myMouseBindings
       , borderWidth = 1
       , logHook = dynamicLogWithPP $ myLogHook din
       , focusFollowsMouse = True
       }

-- Statusbar options:
myStatusBar = "dzen2 -x '0' -y '0' -h '16' -w '1020' -ta 'l' -bg '#222222' -fg '#aaaaaa' -fn '-xos4-terminus-medium-r-normal-*-14-*-*-*-c-*-iso10646-1'"
myTopBar = "conky -c .conkytoprc | dzen2 -x '1020' -y '0' -h '16' -w '580' -ta 'r' -bg '#222222' -fg '#555555' -fn '-xos4-terminus-medium-r-normal-*-14-*-*-*-c-*-iso10646-1'"
myBottomBar = "conky -c .conkybottomrc | dzen2 -x '0' -y '1184' -h '16' -w '1600' -ta 'l' -bg '#222222' -fg '#555555' -fn '-xos4-terminus-medium-r-normal-*-14-*-*-*-c-*-iso10646-1'"

-- Urgency hint options:
myUrgencyHook = withUrgencyHook dzenUrgencyHook
    { args = ["-x", "0", "-y", "1168", "-h", "16", "-w", "1600", "-ta", "r", "-expand", "l", "-bg", "#222222", "-fg", "#0077cc", "-fn", "-xos4-terminus-medium-r-normal-*-14-*-*-*-c-*-iso10646-1"] }

-- Layout options:
myLayout = avoidStruts $ layoutHints $ onWorkspace "1:irc" (hintedTile Wide) $ onWorkspaces ["2:www","3:music","4"] (Full) $ (hintedTile Tall ||| hintedTile Wide ||| Full)
    where
    hintedTile = HintedTile nmaster delta ratio TopLeft
    nmaster = 1
    ratio = toRational (2/(1+sqrt(5)::Double))
    delta = 3/100

-- XPConfig options:
myXPConfig = defaultXPConfig
    { font = "-xos4-terminus-medium-r-normal-*-14-*-*-*-c-*-iso10646-1"
    , bgColor = "#222222"
    , fgColor = "#ffffff"
    , fgHLight = "#ffffff"
    , bgHLight = "#0066ff"
    , borderColor = "#ffffff"
    , promptBorderWidth = 1
    , position = Bottom
    , height = 16
    , historySize = 100
    }

-- Key bindings:
myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
    [ ((mod4Mask, xK_q), spawn "urxvt -g 120x40+20+30 -e ssh and1@donnergurgler.net")
    , ((mod4Mask, xK_e), spawn "iceweasel")
    , ((mod4Mask, xK_r), spawn "urxvt -g 120x40+20+30")
    , ((mod4Mask, xK_t), spawn "icedove")
    , ((mod4Mask, xK_o), spawn "openoffice")
    , ((mod4Mask, xK_p), shellPrompt myXPConfig)
    , ((mod4Mask, xK_l), spawn "slock")
    , ((mod4Mask, xK_x), spawn "schroot -p gmpc")
    , ((mod4Mask, xK_n), spawn "nicotine")
    , ((modMask .|. controlMask, xK_Home), spawn "mpc toggle") -- play/pause song
    , ((modMask .|. controlMask, xK_End), spawn "mpc stop") -- stop playback
    , ((modMask .|. controlMask, xK_Prior), spawn "mpc prev") -- previous song
    , ((modMask .|. controlMask, xK_Next), spawn "mpc next") -- next song
    , ((modMask, xK_Print), spawn "scrot desk_%Y-%m-%d.png -d 1") -- take a screenshot
    , ((modMask .|. controlMask, xK_x), kill) -- close focused window
    , ((modMask, xK_f), sendMessage NextLayout) -- rotate through the available layout algorithms
    , ((modMask .|. shiftMask, xK_f), setLayout $ XMonad.layoutHook conf) -- reset the layouts on the current workspace to default
    , ((modMask, xK_n), refresh) -- resize viewed windows to the correct size
    , ((modMask, xK_Tab), windows W.focusDown) -- move focus to the next window
    , ((modMask, xK_Down), windows W.focusDown) -- move focus to the next window
    , ((modMask .|. shiftMask, xK_Tab), windows W.focusUp) -- move focus to the next window
    , ((modMask, xK_Up), windows W.focusUp) -- move focus to the previous window
    , ((modMask, xK_Return), windows W.focusMaster) -- move focus to the master window
    , ((modMask, xK_m), windows W.swapMaster) -- swap the focused window and the master window
    , ((modMask .|. controlMask, xK_Down), windows W.swapDown) -- swap the focused window with the next window
    , ((modMask .|. controlMask, xK_Up), windows W.swapUp)  -- swap the focused window with the previous window
    , ((modMask .|. shiftMask, xK_Left), sendMessage Shrink) -- shrink the master area
    , ((modMask .|. shiftMask, xK_Right), sendMessage Expand) -- expand the master area
    , ((modMask .|. controlMask, xK_d), withFocused $ windows . W.sink) -- push window back into tiling
    , ((modMask .|. controlMask, xK_Left), sendMessage (IncMasterN 1)) -- increment the number of windows in the master area
    , ((modMask .|. controlMask, xK_Right), sendMessage (IncMasterN (-1))) -- deincrement the number of windows in the master area
    , ((modMask .|. controlMask, xK_q), io (exitWith ExitSuccess)) -- quit xmonad
    , ((modMask .|. controlMask, xK_r), spawn "killall conky dzen2" >> restart "xmonad" True) -- restart xmonad
    ]
    ++
    [ ((m .|. modMask, k), windows $ f i)
    | (i, k) <- zip (XMonad.workspaces conf) [xK_F1 .. xK_F9] -- mod-[F1..F9], Switch to workspace N
    , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] -- mod-shift-[F1..F9], Move client to workspace N
    ]
    ++
    [ ((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
    | (key, sc) <- zip [xK_F10, xK_F11, xK_F12] [0..] -- mod-{F10,F11,F12}, Switch to physical/Xinerama screens 1, 2, or 3
    , (f, m) <- [(W.view, 0), (W.shift, shiftMask)] -- mod-shift-{F10,F11,F12}, Move client to screen 1, 2, or 3
    ]

-- Mouse bindings:
myMouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
    [ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w)) -- Set the window to floating mode and move by dragging
    , ((modMask, button2), (\w -> focus w >> windows W.swapMaster)) -- Raise the window to the top of the stack
    , ((modMask, button3), (\w -> focus w >> Flex.mouseResizeWindow w)) -- Set the window to floating mode and resize by dragging
    , ((modMask, button4), (\_ -> prevWS)) -- Switch to previous workspace
    , ((modMask, button5), (\_ -> nextWS)) -- Switch to next workspace
    ]

-- Window rules:
myManageHook = composeAll . concat $
    [ [className =? c --> doFloat | c <- myFloats]
    , [title =? t --> doFloat | t <- myOtherFloats]
    , [resource =? r --> doFloat | r <- myIgnores]
    , [className =? "Firefox-bin" --> doF (W.shift "2:www")]
    , [className =? "Gmpc" --> doF (W.shift "3:music")]
    , [className =? "Nicotine" --> doF (W.shift "4")]
    ]
    where
    myFloats = ["ekiga", "Gimp", "gimp", "MPlayer", "Nitrogen", "Transmission-gtk", "Xmessage", "xmms"]
    myOtherFloats = ["Downloads", "Iceweasel Preferences", "Save As...", "Compose: (no subject)", "Icedove Preferences", "Tag and File Name scan", "Preferences...", "Confirm...", "gmpc - Configuration", "gmpc - song info", "Save Playlist", "GQview Preferences", "Inkscape Preferences (Shift+Ctrl+P)", "Select file to open", "Select file to save to", "Warning", "Closing Project - K3b", "Open Files - K3b", "Options - K3b", "Close Nicotine-Plus?", "Nicotine Settings", "OpenOffice.org 2.0", "Open", "Options - OpenOffice.org - User Data", "File Properties", "Preference", "Plugins:", "Preferences"]
    myIgnores = []

-- dynamicLog pretty printer for dzen:
myLogHook h = defaultPP
    { ppCurrent = wrap "^bg(#444444)^p(2)^fg(#00aaff)^i(/home/and1/.dzen/plus.xbm)^fg(#ffffff)" "^p(2)^fg()^bg()" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppVisible = wrap "^bg(#444444)^fg(#aaaaaa)^p(2)" "^p(2)^fg()^bg()"
    , ppHidden = wrap "^fg(#ffffff)^p(2)^i(/home/and1/.dzen/plus.xbm)^fg()" "^p(2)^fg()" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppHiddenNoWindows = id . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppSep = " ^fg(#555555)::^fg() "
    , ppWsSep = " "
    , ppLayout = dzenColor "#ffffff" "" .
        (\x -> case x of
        "Hinted Tall" -> "tall"
        "Hinted Wide" -> "mirror"
        "Hinted Full" -> "full"
    --    "Hinted Tall" -> "^i(/home/and1/.dzen/layout-tall.xbm)"
    --    "Hinted Wide" -> "^i(/home/and1/.dzen/layout-mtall.xbm)"
    --    "Hinted Full" -> "^i(/home/and1/.dzen/layout-full.xbm)"
        )
    , ppTitle = dzenColor "#ffffff" "" . wrap "< " " >"
    , ppOutput = System.IO.UTF8.hPutStrLn h
    }