Xmonad/Config archive/gray hem's xmonad.hs

From HaskellWiki
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.
-- dzen2 plus conky config with urgency for xmonad-0.9*
-- uses icons from dzen.geekmode.org

import XMonad

import qualified Data.Map as M

import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.UrgencyHook

import XMonad.Layout
import XMonad.Layout.NoBorders
import XMonad.Layout.ResizableTile

import XMonad.Prompt
import XMonad.Prompt.Shell
import XMonad.Prompt.Man

import XMonad.Util.Run

main = do
  myStatusBarPipe <- spawnPipe myStatusBar
  spawn myTimeBar
  xmonad $ myUrgencyHook $ defaultConfig {
    terminal = myTerminal,
    normalBorderColor = myInactiveBorderColor,
    focusedBorderColor = myActiveBorderColor,
    workspaces = myWorkspaces,
    modMask = myModMask,
    keys = myKeys,
    manageHook = manageDocks <+> manageHook defaultConfig,
    layoutHook = avoidStruts myLayoutHook,
    logHook = dynamicLogWithPP $ myDzenPP myStatusBarPipe
    }

-- Parameters
myFont = "xft:monospace:size=8"
mySupFont = "xft:monospace:size=5"

myBitmapsPath = "/home/user/.dzen/bitmaps/"

myColor = "#d0d3e6"
myBgColor = "#363743"

myHighLightColor = "#ffffff"
myBgHighLightColor = "#60626b"

myActiveBorderColor = "#d0d3e6"
myInactiveBorderColor = "#80828e"

myLayoutColor = "#a0a3b0"

myCurrentWsColor = "#ffffff"
myCurrentWsBgColor = "#80828e"
myVisibleWsColor = "#d0d3e6"
myVisibleWsBgColor = "#60626b"
myHiddenWsColor = "#d0d3e6"
myHiddenWsBgColor = "#363743"
myHiddenEmptyWsColor = "#80828e"
myHiddenEmptyWsBgColor = "#363743"
myUrgentWsColor = "#ffffff"
myUrgentWsBgColor = "#8e5250"
myTitleColor = "#ffffff"
myTitleWsBgColor = "#363743"

myUrgencyHintColor = "#ffffff"
myUrgencyHintBgColor = "#8e5250"

myDzenBarGeneralOptions = " -ta l -fn '" ++ myFont ++ "' -fg '" ++ myColor ++ "' -bg '" ++ myBgColor ++ "'"

-- Bars
myStatusBar = "dzen2 -w 1134 " ++ myDzenBarGeneralOptions
myTimeBar = "conky -c ~/.conky_time | dzen2 -x 1134 " ++ myDzenBarGeneralOptions

-- Prefered terminal
myTerminal = "urxvt"

-- Rebind Mod to Windows key
myModMask = mod4Mask

-- Prompt config
myXPConfig = defaultXPConfig {
  position = Bottom,
  promptBorderWidth = 0,
  font = myFont,
  height = 15,
  bgColor = myBgColor,
  fgColor = myColor,
  fgHLight = myHighLightColor,
  bgHLight = myBgHighLightColor
  }

-- Union default and new key bindings
myKeys x  = M.union (M.fromList (newKeys x)) (keys defaultConfig x)

-- Add new and/or redefine key bindings
newKeys (XConfig {XMonad.modMask = modm}) = [
  -- Use shellPrompt instead of default dmenu
  ((modm, xK_p), shellPrompt myXPConfig),
  -- Do not leave useless conky and dzen after restart
  ((modm, xK_q), spawn "killall conky dzen2; xmonad --recompile; xmonad --restart"),
  -- ResizableTall key bindings
  ((modm, xK_a), sendMessage MirrorShrink),
  ((modm, xK_z), sendMessage MirrorExpand),
  -- Manual page prompt
  ((modm, xK_o), manPrompt myXPConfig),
  ((modm, xK_u), focusUrgent)
  ]

-- Workspaces names
myWorkspaces = [
  supWsNum "1" "dev",
  supWsNum "2" "web",
  supWsNum "3" "con",
  supWsNum "4" "msg",
  supWsNum "5" "msc",
  supWsNum "6" "tmp",
  " 7 ", " 8 ", " 9 "
  ]
  where
    supWsNum wsNum wsName = "^p(;_TOP)^fn(" ++ mySupFont  ++ ") " ++ wsNum ++ " ^fn()^p()" ++ wsName ++ " "

-- Dzen config
myDzenPP h = dzenPP {
  ppOutput = hPutStrLn h,
  ppSep = " ",
  ppWsSep = "",
  ppCurrent = wrapGeneralWp myCurrentWsColor myCurrentWsBgColor,
  ppVisible = wrapGeneralWp myVisibleWsColor myVisibleWsBgColor,
  ppHidden = wrapGeneralWp myHiddenWsColor myHiddenWsBgColor,
  ppHiddenNoWindows = wrapGeneralWp myHiddenEmptyWsColor myHiddenEmptyWsBgColor,
  ppUrgent = wrapGeneralWp myUrgentWsColor myUrgentWsBgColor . dzenStrip,
  ppTitle = \x -> ' ' : wrapGeneralWp myTitleColor myTitleWsBgColor x,
  ppLayout  = dzenColor myLayoutColor "" .
                (\x -> case x of
                    "ResizableTall" -> wrapBitmapLayout "rob/tall.xbm"
                    "Mirror ResizableTall" -> wrapBitmapLayout "rob/mtall.xbm"
                    "Full" -> wrapBitmapLayout "rob/full.xbm"
                )
  }
  where
    wrapGeneralWp wsColor wsBgColor = wrap ("^fg(" ++ wsColor ++ ")^bg(" ++ wsBgColor ++ ")") "^fg()^bg()"
    wrapBitmapLayout bitmap = "^i(" ++ myBitmapsPath ++ bitmap ++ ")"

-- Define a combination of layouts
myLayoutHook = smartBorders (tiled ||| Mirror tiled ||| Full) -- The only window w/o borders
  where
    tiled = ResizableTall nmaster delta ratio []
    nmaster = 1
    delta = 3/100
    ratio = 1/2

-- Urgency hint configuration
myUrgencyHook = withUrgencyHook dzenUrgencyHook
    {
      args = [
         "-x", "0", "-y", "785", "-h", "15", "-w", "1280",
         "-ta", "r", "-expand", "l",
         "-fg", "" ++ myUrgencyHintColor ++ "",
         "-bg", "" ++ myUrgencyHintBgColor ++ "",
         "-fn", "" ++ myFont ++ ""
         ],
      duration = seconds 6 -- with older ghc can use (6 `seconds`)
    }