Difference between revisions of "Xmonad/Config archive/gray hemp's xmonad.hs"

From HaskellWiki
Jump to navigation Jump to search
Line 3: Line 3:
 
-- uses icons from dzen.geekmode.org
 
-- uses icons from dzen.geekmode.org
 
import XMonad
 
import XMonad
  +
import XMonad.Core
   
 
import XMonad.Prompt
 
import XMonad.Prompt
Line 17: Line 18:
   
 
import qualified Data.Map as M
 
import qualified Data.Map as M
  +
import Graphics.X11.Xlib
 
import XMonad.Util.Run
 
import XMonad.Util.Run
   
Line 22: Line 24:
 
myStatusBarPipe <- spawnPipe myStatusBar
 
myStatusBarPipe <- spawnPipe myStatusBar
 
spawn myTimeBar
 
spawn myTimeBar
  +
spawn myXxkbBar
 
xmonad $ myUrgencyHook $ defaultConfig {
 
xmonad $ myUrgencyHook $ defaultConfig {
 
terminal = myTerminal,
 
terminal = myTerminal,
Line 29: Line 32:
 
modMask = myModMask,
 
modMask = myModMask,
 
keys = myKeys,
 
keys = myKeys,
manageHook = manageDocks <+> manageHook defaultConfig,
+
manageHook = myManageHook <+> manageDocks <+> manageHook defaultConfig,
 
layoutHook = avoidStruts $ myLayoutHook,
 
layoutHook = avoidStruts $ myLayoutHook,
 
logHook = dynamicLogWithPP $ myDzenPP myStatusBarPipe
 
logHook = dynamicLogWithPP $ myDzenPP myStatusBarPipe
Line 39: Line 42:
   
 
-- Paths
 
-- Paths
myBitmapsPath = "/home/user/.dzen/bitmaps/"
+
myBitmapsPath = "/home/gray/.dzen/bitmaps/"
   
 
-- Colors
 
-- Colors
Line 48: Line 51:
 
myHighlightedBgColor = "#60626b"
 
myHighlightedBgColor = "#60626b"
   
myActiveBorderColor = "#d0d3e6"
+
myActiveBorderColor = "#363743"
myInactiveBorderColor = "#80828e"
+
myInactiveBorderColor = "#d0d3e6"
   
 
myLayoutColor = "#a0a3b0"
 
myLayoutColor = "#a0a3b0"
Line 69: Line 72:
 
myDzenBarGeneralOptions = " -ta l -fn '" ++ myFont ++ "' -fg '" ++ myFgColor ++ "' -bg '" ++ myBgColor ++ "'"
 
myDzenBarGeneralOptions = " -ta l -fn '" ++ myFont ++ "' -fg '" ++ myFgColor ++ "' -bg '" ++ myBgColor ++ "'"
   
myStatusBar = "dzen2 -w 1134 " ++ myDzenBarGeneralOptions
+
myStatusBar = "dzen2 -w 1117 " ++ myDzenBarGeneralOptions
myTimeBar = "conky -c ~/.conky_time | dzen2 -x 1134 " ++ myDzenBarGeneralOptions
+
myTimeBar = "conky -c ~/.conky_time | dzen2 -x 1117 -w 148" ++ myDzenBarGeneralOptions
  +
myXxkbBar = "xxkb" -- configuration in ~/.xxkbrc
   
 
-- Prefered terminal
 
-- Prefered terminal
Line 94: Line 98:
   
 
-- Add new and/or redefine key bindings
 
-- Add new and/or redefine key bindings
newKeys (XConfig {XMonad.modMask = modm}) = [
+
newKeys conf@(XConfig {XMonad.modMask = modm}) = [
 
-- Use shellPrompt instead of default dmenu
 
-- Use shellPrompt instead of default dmenu
 
((modm, xK_p), shellPrompt myXPConfig),
 
((modm, xK_p), shellPrompt myXPConfig),
 
-- Do not leave useless conky, dzen and xxkb after restart
 
-- Do not leave useless conky, dzen and xxkb after restart
((modm, xK_q), spawn "killall conky dzen2; xmonad --recompile; xmonad --restart"),
+
((modm, xK_q), spawn "killall conky dzen2 xxkb; xmonad --recompile; xmonad --restart"),
 
-- ResizableTall key bindings
 
-- ResizableTall key bindings
 
((modm, xK_a), sendMessage MirrorShrink),
 
((modm, xK_a), sendMessage MirrorShrink),
Line 104: Line 108:
 
-- Manual page prompt
 
-- Manual page prompt
 
((modm, xK_o), manPrompt myXPConfig),
 
((modm, xK_o), manPrompt myXPConfig),
((modm, xK_u), focusUrgent)
+
((modm, xK_u), focusUrgent),
  +
-- Make a screeshot
  +
((0, xK_Print), spawn "scrot -e 'mv $f ~/tmp/'"),
  +
((controlMask, xK_Print), spawn "sleep 0.2; scrot -s -e 'mv $f ~/tmp/'") -- interactive
 
]
 
]
   
Line 162: Line 169:
 
"-fn", "" ++ myFont ++ ""
 
"-fn", "" ++ myFont ++ ""
 
],
 
],
duration = seconds 7 -- with ghc-6.8* can use (7 `seconds`)
+
duration = (7 `seconds`)
 
}
 
}
  +
  +
myManageHook = composeAll [
  +
resource =? "XXkb" --> doIgnore
  +
]
 
</haskell>
 
</haskell>

Revision as of 17:40, 24 January 2010

-- dzen2 plus conky config with urgency for xmonad-0.9*
-- uses icons from dzen.geekmode.org
import XMonad
import XMonad.Core

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

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

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

import qualified Data.Map as M
import Graphics.X11.Xlib
import XMonad.Util.Run

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

-- Fonts
myFont = "xft:monospace:size=8"
mySmallFont = "xft:monospace:size=5"

-- Paths
myBitmapsPath = "/home/gray/.dzen/bitmaps/"

-- Colors
myFgColor = "#d0d3e6"
myBgColor = "#363743"

myHighlightedFgColor = "#ffffff"
myHighlightedBgColor = "#60626b"

myActiveBorderColor = "#363743"
myInactiveBorderColor = "#d0d3e6"

myLayoutColor = "#a0a3b0"

myCurrentWsFgColor = "#ffffff"
myCurrentWsBgColor = "#80828e"
myVisibleWsFgColor = "#ffffff"
myVisibleWsBgColor = "#60626b"
myHiddenWsFgColor = "#d0d3e6"
myHiddenEmptyWsFgColor = "#80828e"
myUrgentWsBgColor = "#725050"
myTitleFgColor = "#ffffff"

myUrgencyHintFgColor = "#ffffff"
myUrgencyHintBgColor = "#7e5250"


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

myStatusBar = "dzen2 -w 1117 " ++ myDzenBarGeneralOptions
myTimeBar = "conky -c ~/.conky_time | dzen2 -x 1117 -w 148" ++ myDzenBarGeneralOptions
myXxkbBar = "xxkb" -- configuration in ~/.xxkbrc

-- 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 = myFgColor,
  fgHLight = myHighlightedFgColor,
  bgHLight = myHighlightedBgColor
  }

-- 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 conf@(XConfig {XMonad.modMask = modm}) = [
  -- Use shellPrompt instead of default dmenu
  ((modm, xK_p), shellPrompt myXPConfig),
  -- Do not leave useless conky, dzen and xxkb after restart
  ((modm, xK_q), spawn "killall conky dzen2 xxkb; 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),
  -- Make a screeshot
  ((0,           xK_Print), spawn "scrot -e 'mv $f ~/tmp/'"),
  ((controlMask, xK_Print), spawn "sleep 0.2; scrot -s -e 'mv $f ~/tmp/'") -- interactive
  ]

-- 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(" ++ mySmallFont  ++ ") " ++ wsNum ++ " ^fn()^p()" ++ wsName ++ " "

-- Dzen config
myDzenPP h = defaultPP {
  ppOutput = hPutStrLn h,
  ppSep = " ",
  ppWsSep = "",
  ppCurrent = wrapFgBg myCurrentWsFgColor myCurrentWsBgColor,
  ppVisible = wrapFgBg myVisibleWsFgColor myVisibleWsBgColor,
  ppHidden = wrapFg myHiddenWsFgColor,
  ppHiddenNoWindows = wrapFg myHiddenEmptyWsFgColor,
  ppUrgent = wrapBg myUrgentWsBgColor,
  ppTitle = (\x -> " " ++ wrapFg myTitleFgColor x),
  ppLayout  = dzenColor myLayoutColor "" .
                (\x -> case x of
                    "ResizableTall" -> wrapBitmap "rob/tall.xbm"
                    "Mirror ResizableTall" -> wrapBitmap "rob/mtall.xbm"
                    "Full" -> wrapBitmap "rob/full.xbm"
                )
  }
  where
    wrapFgBg fgColor bgColor content= wrap ("^fg(" ++ fgColor ++ ")^bg(" ++ bgColor ++ ")") "^fg()^bg()" content
    wrapFg color content = wrap ("^fg(" ++ color ++ ")") "^fg()" content
    wrapBg color content = wrap ("^bg(" ++ color ++ ")") "^bg()" content
    wrapBitmap 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", "" ++ myUrgencyHintFgColor ++ "",
         "-bg", "" ++ myUrgencyHintBgColor ++ "",
         "-fn", "" ++ myFont ++ ""
         ],
      duration = (7 `seconds`)
    }

myManageHook = composeAll [
  resource  =? "XXkb" --> doIgnore
  ]