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

From HaskellWiki
Jump to navigation Jump to search
m (removed pointless elements from mXPConfig)
(color theme, layout, keybindings changed)
Line 11: Line 11:
 
--
 
--
 
-- customization for the xmonad window manager
 
-- customization for the xmonad window manager
-- Last Modified: 2008 Nov 04 Tue - 07:53:00
 
 
-----------------------------------------------------------------------
 
-----------------------------------------------------------------------
 
-- Imports {{{
 
-- Imports {{{
Line 31: Line 30:
 
import XMonad.Actions.UpdatePointer
 
import XMonad.Actions.UpdatePointer
 
import qualified XMonad.Actions.Search as S
 
import qualified XMonad.Actions.Search as S
  +
import qualified XMonad.Actions.GridSelect
 
-- Util
 
-- Util
 
import XMonad.Util.Run (safeSpawn, unsafeSpawn, runInTerm, spawnPipe)
 
import XMonad.Util.Run (safeSpawn, unsafeSpawn, runInTerm, spawnPipe)
Line 36: Line 36:
 
import XMonad.Util.XSelection (safePromptSelection)
 
import XMonad.Util.XSelection (safePromptSelection)
 
import XMonad.Util.EZConfig hiding (additionalMouseBindings, removeMouseBindings)
 
import XMonad.Util.EZConfig hiding (additionalMouseBindings, removeMouseBindings)
  +
import Xmonad.Util.WorkspaceCompare (getSortByIndex)
 
-- Layouts
 
-- Layouts
 
import XMonad.Layout.NoBorders (smartBorders)
 
import XMonad.Layout.NoBorders (smartBorders)
 
import XMonad.Layout.ResizableTile (ResizableTall(..))
 
import XMonad.Layout.ResizableTile (ResizableTall(..))
  +
import XMonad.Layout.Grid (Grid(..))
  +
import XMonad.Layout.Magnifier (magnifiercz)
  +
import XMonad.Layout.PerWorkspace (onWorkspace)
  +
import XMonad.Layout.IM
  +
import XMonad.Layout.Reflect (reflectHoriz)
  +
 
import System.IO (hPutStrLn)
 
import System.IO (hPutStrLn)
 
import Data.Char (isSpace)
 
import Data.Char (isSpace)
Line 57: Line 64:
 
, normalBorderColor = colorNormalBorder
 
, normalBorderColor = colorNormalBorder
 
, focusedBorderColor = colorFocusedBorder
 
, focusedBorderColor = colorFocusedBorder
, layoutHook = mLayout
+
, layoutHook = avoidStruts $
  +
smartBorders (
  +
onWorkspace "term" grids $
  +
onWorkspace "web" mostlyTall $
  +
onWorkspace "art" gimp $
  +
standardLayouts)
 
, manageHook = mManageHook
 
, manageHook = mManageHook
 
, logHook = (dynamicLogWithPP $ mPP dzpipe) >> updatePointer (Relative 0.95 0.95)
 
, logHook = (dynamicLogWithPP $ mPP dzpipe) >> updatePointer (Relative 0.95 0.95)
Line 68: Line 80:
 
, ((0 ,0x1008ff12 ), unsafeSpawn "amixer -q set Master toggle") -- XF86Audio Mute
 
, ((0 ,0x1008ff12 ), unsafeSpawn "amixer -q set Master toggle") -- XF86Audio Mute
 
, ((0 ,0x1008ff13 ), unsafeSpawn "amixer -q set Master 2dB+" ) -- XF86AudioRaiseVolume
 
, ((0 ,0x1008ff13 ), unsafeSpawn "amixer -q set Master 2dB+" ) -- XF86AudioRaiseVolume
, ((0 ,xK_Print ), unsafeSpawn "scrot '%Y-%m-%d-%H%M_$wx$h.png' -e 'mv $f ~/screenshots/'") -- Print Screen
+
, ((0 ,xK_Print ), unsafeSpawn "scrot '%Y-%m-%d-%H%M_$wx$h.png' -e 'mv $f ~/screenshots/'") -- Print Screen
 
]
 
]
 
-- }}}
 
-- }}}
Line 77: Line 89:
   
 
-- Theme {{{
 
-- Theme {{{
  +
-- Color names are easier to remember
 
colorNormalBorder, colorFocusedBorder, colorNormalBG, colorNormalFG, colorFocusBG, colorFocusFG, colorFocusBO, colorUrgentBG, colorUrgentFG :: [Char]
 
colorNormalBorder, colorFocusedBorder, colorNormalBG, colorNormalFG, colorFocusBG, colorFocusFG, colorFocusBO, colorUrgentBG, colorUrgentFG :: [Char]
 
colorNormalBorder = "#1c2636"
 
colorNormalBorder = "#1c2636"
Line 87: Line 100:
 
colorUrgentBG = "#ff00cc"
 
colorUrgentBG = "#ff00cc"
 
colorUrgentFG = "#00ff99"
 
colorUrgentFG = "#00ff99"
  +
colorNormalBorder, colorFocusedBorder :: [Char]
  +
colorNormalBorder = "#1c2636"
  +
colorFocusedBorder = "#2797d8"
 
barFont, barXFont, statusBarCmd, notesFile, mTerm :: [Char]
 
barFont, barXFont, statusBarCmd, notesFile, mTerm :: [Char]
 
barFont = "terminus"
 
barFont = "terminus"
Line 92: Line 108:
 
--}}}
 
--}}}
 
statusBarCmd = "dzen2" ++
 
statusBarCmd = "dzen2" ++
" -bg '" ++ colorNormalBG ++ "'" ++
+
" -bg '" ++ colorDarkGray ++ "'" ++
" -fg '" ++ colorNormalFG ++ "'" ++
+
" -fg '" ++ colorBlue ++ "'" ++
 
" -sa c" ++
 
" -sa c" ++
 
" -fn '" ++ barXFont ++ "'" ++
 
" -fn '" ++ barXFont ++ "'" ++
Line 104: Line 120:
 
enro40 = S.searchEngine "enro40" "http://dictionare.com/phpdic/enro40.php?field0="
 
enro40 = S.searchEngine "enro40" "http://dictionare.com/phpdic/enro40.php?field0="
 
roen40 = S.searchEngine "roen40" "http://dictionare.com/phpdic/roen40.php?field0="
 
roen40 = S.searchEngine "roen40" "http://dictionare.com/phpdic/roen40.php?field0="
  +
hayoo = S.searchEngine "hayoo" "http://holumbus.fh-wedel.de/hayoo/hayoo.html?query="
   
 
-- Pretty printer {{{
 
-- Pretty printer {{{
 
-- dynamiclog pretty printer for dzen
 
-- dynamiclog pretty printer for dzen
 
mPP h = defaultPP
 
mPP h = defaultPP
{ ppCurrent = wrap ("^fg(" ++ colorFocusFG ++ ")^bg(" ++ colorFocusBG ++ ")^p(2)") "^p(2)^fg()^bg()"
+
{ ppCurrent = wrap ("^fg(" ++ colorOrange ++ ")^bg(" ++ colorDarkGray ++ ")^p(2)") "^p(2)^fg()^bg()"
, ppVisible = wrap ("^fg(" ++ colorNormalFG ++ ")^bg(" ++ colorNormalBG ++ ")^p(2)") "^p(2)^fg()^bg()"
+
, ppVisible = wrap ("^fg(" ++ colorBlue ++ ")^bg(" ++ colorDarkGray ++ ")^p(2)") "^p(2)^fg()^bg()"
 
, ppSep = " ^fg(grey60)^r(1x8)^fg() "
 
, ppSep = " ^fg(grey60)^r(1x8)^fg() "
, ppLayout = dzenColor colorNormalFG "" . (\x -> case x of
+
, ppLayout = dzenColor colorWhite "" . (\x -> case x of
 
"Mirror Tall" -> "^i(/home/webframp/.xmonad/dzen/mtall.xbm)"
 
"Mirror Tall" -> "^i(/home/webframp/.xmonad/dzen/mtall.xbm)"
 
"ResizableTall" -> "^i(/home/webframp/.xmonad/dzen/tall.xbm)"
 
"ResizableTall" -> "^i(/home/webframp/.xmonad/dzen/tall.xbm)"
Line 117: Line 134:
 
_ -> " " ++ x ++ " "
 
_ -> " " ++ x ++ " "
 
)
 
)
, ppUrgent = dzenColor colorNormalBG colorUrgentBG . wrap "[" "]"
+
, ppUrgent = dzenColor colorDarkGray colorYellow . wrap "[" "]"
, ppTitle = dzenColor colorFocusFG "" . wrap "<" ">"
+
, ppTitle = dzenColor colorWhite "" . wrap "<" ">"
 
, ppOutput = hPutStrLn h
 
, ppOutput = hPutStrLn h
 
}
 
}
Line 127: Line 144:
 
mXPConfig =
 
mXPConfig =
 
defaultXPConfig { font = barFont
 
defaultXPConfig { font = barFont
, bgColor = colorFocusBG
+
, bgColor = colorDarkGray
, fgColor = colorNormalFG
+
, fgColor = colorGreen
, bgHLight = colorNormalBG
+
, bgHLight = colorGreen
, fgHLight = colorFocusFG
+
, fgHLight = colorDarkGray
 
, promptBorderWidth = 0
 
, promptBorderWidth = 0
 
, height = 14
 
, height = 14
  +
, historyFilter = deleteConsecutive
 
}
 
}
   
Line 143: Line 161:
   
 
-- Layout Hook{{{
 
-- Layout Hook{{{
  +
standardLayouts = Mirror tiled |||
mLayout = avoidStruts $ smartBorders(
 
Mirror tiled |||
+
defaultTall |||
ResizableTall 1 (3/100) (1/2) [] |||
+
Full
Full)
+
where
 
tiled = Tall nmaster delta ratio
where
 
  +
defaultTall = ResizableTall 1 (3/100) (1/2) []
tiled = Tall nmaster delta ratio
 
nmaster = 1
+
nmaster = 1
ratio = toRational (2/(1+sqrt(5)::Double)) -- golden, thx Octoploid
+
ratio = toRational (2/(1+sqrt(5)::Double)) -- golden, thx Octoploid
delta = 0.03
+
delta = 0.03
  +
  +
grids = magnifiercz 1.2 (GridRatio (4/3)) |||
  +
GridRatio (4/3)
  +
  +
mostlyTall = ResizableTall 1 (3/100) (1/2) [] ||| Full
  +
  +
gimp = reflectHoriz $
  +
withIM (11/64) (Role "gimp-toolbox") $
  +
ResizableTall 2 (1/118) (11/20) [5/4,5/4,5/4]
 
--}}}
 
--}}}
 
-- Window rules aka Manage Hook {{{
 
-- Window rules aka Manage Hook {{{
Line 166: Line 193:
 
, title =? "irssi" --> doShift "irc"
 
, title =? "irssi" --> doShift "irc"
 
, title =? "Save a Bookmark" --> doFloat
 
, title =? "Save a Bookmark" --> doFloat
, title =? "Add-ons" --> doFloat
 
 
, className =? "Mitter" --> doShift "irc"
 
, className =? "Mitter" --> doShift "irc"
 
, className =? "Evolution" --> doShift "mail"
 
, className =? "Evolution" --> doShift "mail"
Line 172: Line 198:
 
, className =? "VirtualBox" --> doShift "win"
 
, className =? "VirtualBox" --> doShift "win"
 
, className =? "Tsclient" --> doShift "win"
 
, className =? "Tsclient" --> doShift "win"
 
, className =? "Gimp" --> doShift "art"
  +
, isFullscreen --> doFullFloat
  +
, isDialog --> doCenterFloat
 
] ])
 
] ])
 
<+> manageDocks -- make some space
 
<+> manageDocks -- make some space
 
where floats = ["Mplayer","Tsclient","VirtualBox","Gtklp","smc"]
<+> composeOne [ isFullscreen -?> doFullFloat ]
 
where floats = ["Mplayer","Gimp","Gimp-2.6","Tsclient","VirtualBox","Gtklp","smc"]
 
 
webs = ["Navigator","Gran Paradiso","Firefox", "Midori", "Minefield"]
 
webs = ["Navigator","Gran Paradiso","Firefox", "Midori", "Minefield"]
 
games = ["roguestar-gl","neverputt","neverball","wesnoth"]
 
games = ["roguestar-gl","neverputt","neverball","wesnoth"]
 
 
-- }}}
 
-- }}}
 
lacKeys :: [([Char], X ())]
 
lacKeys :: [([Char], X ())]
 
lacKeys =
 
lacKeys =
[ ("M-p" , runOrRaisePrompt largeXPConfig { bgHLight = colorFocusFG, fgHLight = colorNormalBG })
+
[ ("M-p" , runOrRaisePrompt largeXPConfig )
  +
, ("M-S-p" , spawn "exe=`dmenu_path | dmenu -b` \"exec $exe\"") -- backup launcher incase prompt causes lockups
 
, ("M-g" , runOrRaise "firefox-nightly" (className =? "Minefield"))
 
, ("M-g" , runOrRaise "firefox-nightly" (className =? "Minefield"))
 
, ("M-S-g" , safePromptSelection "firefox-nightly")
 
, ("M-S-g" , safePromptSelection "firefox-nightly")
, ("M-w w" , workspacePrompt largeXPConfig (windows . W.view))
+
, ("M-w" , goToSelected defaultGSConfig)
, ("M-w g" , windowPromptGoto largeXPConfig)
+
, ("M-C-n" , appendFilePrompt largeXPConfig { bgColor = colorOrange, fgColor = colorDarkGray } notesFile)
, ("M-S-w w" , workspacePrompt largeXPConfig (windows . W.shift))
+
, ("M-S-z" , safeSpawn "mocp" "-G") -- play/pause
, ("M-S-w g" , windowPromptBring largeXPConfig)
+
, ("M-S-," , safeSpawn "mocp" "-r") -- rev
, ("M-C-n" , appendFilePrompt largeXPConfig { bgColor = colorFocusFG, fgColor = colorFocusBG } notesFile)
+
, ("M-S-." , safeSpawn "mocp" "-f") -- fwd
, ("M-S-z" , safeSpawn "mocp" "-G") -- play/pause
 
, ("M-S-," , safeSpawn "mocp" "-r") -- rev
 
, ("M-S-." , safeSpawn "mocp" "-f") -- fwd
 
 
, ("M-<Esc>" , focusUrgent)
 
, ("M-<Esc>" , focusUrgent)
 
, ("M-`" , scratchpadSpawnAction defaultConfig { terminal = mTerm }) -- scratchpad
 
, ("M-`" , scratchpadSpawnAction defaultConfig { terminal = mTerm }) -- scratchpad
, ("M-S-x" , unsafeSpawn "slock") -- screen lock
+
, ("M-S-l" , unsafeSpawn "slock") -- screen lock
, ("M-i" , raiseMaybe (runInTerm "-title irssi" "sh -c 'screen -D -R -S irc irssi'") (title =? "irssi"))
+
, ("M-i" , raiseMaybe (runInTerm "-title irssi" "sh -c 'screen -D -R -S irc irssi'") (title =? "irssi"))
, ("M-m" , raiseMaybe (runInTerm "-title mutt" "sh -c 'screen -D -R -S mail mutt'") (title =? "mutt"))
+
, ("M-S-i" , raiseMaybe (runInTerm "-title irssi" "sh -c 'ssh -t webframp@astrotrain screen -D -R -S irc irssi'") (title =? "irssi"))
, ("M-S-m", runOrRaise "evolution" (className =? "Evolution"))
+
, ("M-m" , raiseMaybe (runInTerm "-title mutt" "sh -c 'screen -D -R -S mail mutt'") (title =? "mutt"))
, ("M-e" , safeSpawn "pcmanfm" "--no-desktop")
+
, ("M-S-m" , runOrRaise "thunderbird3" (className =? "Shredder")) -- work email
, ("M-b" , sendMessage ToggleStruts)
+
, ("M-e" , safeSpawn "pcmanfm" "--no-desktop")
, ("M-s" , moveTo Next NonEmptyWS)
+
, ("M-S-e" , unsafeSpawn "dolphin")
, ("M-d" , moveTo Prev NonEmptyWS)
+
, ("M-b" , sendMessage ToggleStruts)
  +
-- focus NonEmpty wss except scratchpad
, ("M-C-s", nextWS)
 
  +
, ("M-s", windows . W.greedyView =<< findWorkspace getSortByIndexNoSP Next NonEmptyWS 1)
, ("M-C-d", prevWS)
 
  +
, ("M-d", windows . W.greedyView =<< findWorkspace getSortByIndexNoSP Prev NonEmptyWS 1)
, ("M-S-s", shiftToNext)
 
  +
-- move window to NonEmpty wss except scratchpad
, ("M-S-d", shiftToPrev)
 
  +
, ("M-S-s", windows . W.shift =<< findWorkspace getSortByIndexNoSP Next NonEmptyWS 1)
  +
, ("M-S-d", windows . W.shift =<< findWorkspace getSortByIndexNoSP Prev NonEmptyWS 1)
  +
-- move window to and focus NonEmpty wss except scratchpad
 
, ("M-C-s", shiftAndView Next)
 
, ("M-C-d", shiftAndView Prev)
 
, ("M-f" , nextScreen)
 
, ("M-f" , nextScreen)
 
, ("M-a" , prevScreen)
 
, ("M-a" , prevScreen)
Line 212: Line 242:
 
, ("M-S-a", shiftPrevScreen)
 
, ("M-S-a", shiftPrevScreen)
 
, ("M-z" , toggleWS)
 
, ("M-z" , toggleWS)
]
+
]
 
++
 
++
 
-- Search methods
 
-- Search methods
Line 219: Line 249:
 
++
 
++
 
[("M-C-c " ++ k, S.selectSearch f) | (k,f) <- searchList ]
 
[("M-C-c " ++ k, S.selectSearch f) | (k,f) <- searchList ]
  +
where -- | non-empty workspaces less scratchpad
  +
shiftAndView dir = findWorkspace getSortByIndexNoSP dir NonEmptyWS 1
  +
>>= \t -> (windows . W.shift $ t) >> (windows . W.greedyView $ t)
  +
getSortByIndexNoSP =
  +
fmap (.scratchpadFilterOutWorkspace) getSortByIndex
   
 
searchList :: [([Char], S.SearchEngine)]
 
searchList :: [([Char], S.SearchEngine)]
 
searchList = [ ("g", S.google)
 
searchList = [ ("g", S.google)
, ("h", S.hoogle)
+
, ("h", hayoo)
  +
, ("i", S.isohunt)
 
, ("w", S.wikipedia)
 
, ("w", S.wikipedia)
 
, ("d", S.dictionary)
 
, ("d", S.dictionary)

Revision as of 20:02, 6 April 2009

-----------------------------------------------------------------------
--
-- Module      :  xmonad.hs
-- Copyright   :  (c) Sean Escriva 2008
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  sean.escriva@gmail.com
-- Stability   :  unstable
-- Portability :  not portable, 
--
-- customization for the xmonad window manager
-----------------------------------------------------------------------
-- Imports {{{
import XMonad
-- Hooks
import XMonad.Hooks.DynamicLog hiding (xmobar, xmobarPP, xmobarColor, sjanssenPP, byorgeyPP)
import XMonad.Hooks.UrgencyHook (withUrgencyHook, NoUrgencyHook(..), focusUrgent)
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks, ToggleStruts(..))
import XMonad.Hooks.ManageHelpers
-- Prompt
import XMonad.Prompt
import XMonad.Prompt.RunOrRaise (runOrRaisePrompt)
import XMonad.Prompt.Window (windowPromptGoto, windowPromptBring)
import XMonad.Prompt.Workspace (workspacePrompt)
import XMonad.Prompt.AppendFile (appendFilePrompt)
-- Actions 
import XMonad.Actions.CycleWS --(nextWS, prevWS, shiftToNext, shiftToPrev, nextScreen, prevScreen, shiftNextScreen, shiftPrevScreen, toggleWS)
import XMonad.Actions.WindowGo (title, raiseMaybe, runOrRaise, (=?))
import XMonad.Actions.UpdatePointer
import qualified XMonad.Actions.Search as S
import qualified XMonad.Actions.GridSelect
-- Util
import XMonad.Util.Run (safeSpawn, unsafeSpawn, runInTerm, spawnPipe)
import XMonad.Util.Scratchpad (scratchpadSpawnAction, scratchpadManageHook) --, scratchpadFilterOutWorkspace)
import XMonad.Util.XSelection (safePromptSelection)
import XMonad.Util.EZConfig hiding (additionalMouseBindings, removeMouseBindings)
import Xmonad.Util.WorkspaceCompare (getSortByIndex)
-- Layouts 
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Layout.ResizableTile (ResizableTall(..))
import XMonad.Layout.Grid (Grid(..))
import XMonad.Layout.Magnifier (magnifiercz)
import XMonad.Layout.PerWorkspace (onWorkspace)
import XMonad.Layout.IM
import XMonad.Layout.Reflect (reflectHoriz)

import System.IO (hPutStrLn)
import Data.Char (isSpace)
import qualified XMonad.StackSet as W
--}}}

-- Main {{{
main :: IO ()
main = do
    dzpipe <- spawnPipe statusBarCmd
    xmonad $ withUrgencyHook NoUrgencyHook $ defaultConfig 
        { terminal              = mTerm
        , focusFollowsMouse     = False
        , borderWidth           = 1
        , modMask               = mod4Mask -- win key
        , numlockMask           = mod2Mask
        , workspaces            = ["mail","web","code","irc","term","read","game","art","win"]
        , normalBorderColor     = colorNormalBorder
        , focusedBorderColor    = colorFocusedBorder
        , layoutHook            = avoidStruts $
                                  smartBorders (
                                               onWorkspace "term" grids $
                                               onWorkspace "web"  mostlyTall $
                                               onWorkspace "art"  gimp $
                                               standardLayouts)
        , manageHook            = mManageHook
        , logHook               = (dynamicLogWithPP $ mPP dzpipe) >> updatePointer (Relative 0.95 0.95)
        , startupHook           = return () >> checkKeymap defaultConfig lacKeys
        }
        `additionalKeysP` lacKeys
        `additionalKeys`
        -- Mediakeys on the Latitude D830 
        [ ((0 			,0x1008ff11 ), unsafeSpawn "amixer -q set Master 2dB-" 	) -- XF86AudioLowerVolume
        , ((0 			,0x1008ff12 ), unsafeSpawn "amixer -q set Master toggle") -- XF86Audio Mute
        , ((0 			,0x1008ff13 ), unsafeSpawn "amixer -q set Master 2dB+" 	) -- XF86AudioRaiseVolume
        , ((0           ,xK_Print   ), unsafeSpawn "scrot '%Y-%m-%d-%H%M_$wx$h.png' -e 'mv $f ~/screenshots/'") -- Print Screen
        ]
-- }}}

-- Config {{{
-- single options here
-- }}}

-- Theme {{{
-- Color names are easier to remember
colorNormalBorder, colorFocusedBorder, colorNormalBG, colorNormalFG, colorFocusBG, colorFocusFG, colorFocusBO, colorUrgentBG, colorUrgentFG :: [Char]
colorNormalBorder    = "#1c2636"
colorFocusedBorder   = "#99ff99"
colorNormalBG        = "#1e1e27"
colorNormalFG        = "#cfbfad"
colorFocusFG         = "#33ccff"
colorFocusBG         = "#1C2636"
colorFocusBO         = "#99ffcc"
colorUrgentBG        = "#ff00cc"
colorUrgentFG        = "#00ff99"
colorNormalBorder, colorFocusedBorder :: [Char]
colorNormalBorder    = "#1c2636"
colorFocusedBorder   = "#2797d8"
barFont, barXFont, statusBarCmd, notesFile, mTerm :: [Char]
barFont  = "terminus"
barXFont = "-*-terminus-*-*-*-*-14-*-*-*-*-*-*-*"
--}}}
statusBarCmd = "dzen2" ++ 
               " -bg '" ++ colorDarkGray ++ "'" ++
               " -fg '" ++ colorBlue ++ "'" ++
               " -sa c" ++
               " -fn '" ++ barXFont ++ "'" ++
               " -ta l -expand r -e ''"
notesFile = "/home/webframp/TODO"
mTerm     = "urxvt"

-- Custom Searches
enro40, roen40 :: S.SearchEngine
enro40 = S.searchEngine "enro40" "http://dictionare.com/phpdic/enro40.php?field0="
roen40 = S.searchEngine "roen40" "http://dictionare.com/phpdic/roen40.php?field0=" 
hayoo = S.searchEngine "hayoo" "http://holumbus.fh-wedel.de/hayoo/hayoo.html?query="

-- Pretty printer {{{
-- dynamiclog pretty printer for dzen
mPP h = defaultPP 
        { ppCurrent = wrap ("^fg(" ++ colorOrange ++ ")^bg(" ++ colorDarkGray ++ ")^p(2)") "^p(2)^fg()^bg()"
        , ppVisible = wrap ("^fg(" ++ colorBlue ++ ")^bg(" ++ colorDarkGray ++ ")^p(2)") "^p(2)^fg()^bg()"
        , ppSep     = " ^fg(grey60)^r(1x8)^fg() "
        , ppLayout  = dzenColor colorWhite "" . (\x -> case x of
                                                            "Mirror Tall"       -> "^i(/home/webframp/.xmonad/dzen/mtall.xbm)"
                                                            "ResizableTall"     -> "^i(/home/webframp/.xmonad/dzen/tall.xbm)"
                                                            "Full"              -> "^i(/home/webframp/.xmonad/dzen/full.xbm)"
                                                            _                   -> " " ++ x ++ " "
                                                   )
        , ppUrgent  = dzenColor colorDarkGray colorYellow . wrap "[" "]"
        , ppTitle   = dzenColor colorWhite "" . wrap "<" ">" 
        , ppOutput  = hPutStrLn h
        }
--}}}

-- Prompt Config {{{
mXPConfig :: XPConfig
mXPConfig = 
    defaultXPConfig { font                  = barFont
                    , bgColor               = colorDarkGray
                    , fgColor               = colorGreen
                    , bgHLight              = colorGreen
                    , fgHLight              = colorDarkGray
                    , promptBorderWidth     = 0
                    , height                = 14
                    , historyFilter         = deleteConsecutive
                    }

largeXPConfig :: XPConfig
largeXPConfig = mXPConfig 
                { font = "-*-terminus-*-*-*-*-16-*-*-*-*-*-*-*"
                , height = 16 
                }
-- }}}

-- Layout Hook{{{
standardLayouts = Mirror tiled  |||
                  defaultTall   |||
                  Full
                where
                  tiled       = Tall nmaster delta ratio
                  defaultTall = ResizableTall 1 (3/100) (1/2) []
                  nmaster     = 1
                  ratio       = toRational (2/(1+sqrt(5)::Double)) -- golden, thx Octoploid
                  delta       = 0.03

grids = magnifiercz 1.2 (GridRatio (4/3))  |||
        GridRatio (4/3)

mostlyTall = ResizableTall 1 (3/100) (1/2) [] ||| Full

gimp       = reflectHoriz $ 
             withIM (11/64) (Role "gimp-toolbox") $ 
             ResizableTall 2 (1/118) (11/20) [5/4,5/4,5/4]
--}}} 
-- Window rules aka Manage Hook {{{ 
mManageHook :: ManageHook
mManageHook = scratchpadManageHook (W.RationalRect 0.25 0.375 0.5 0.35) <+> 
               (composeAll . concat $
    [ [ className =? c --> doFloat       | c <- floats ],
      [ className =? w --> doShift "web"  | w <- webs]   ,
      [ className =? g --> doShift "game" | g <- games]  ,
      [ resource  =? "desktop_window"  --> doIgnore
      , className =? "Epdfview"        --> doShift "read"
      , className =? "Okular"          --> doShift "read"
      , title     =? "mutt"            --> doShift "mail"
      , title     =? "irssi"           --> doShift "irc"
      , title     =? "Save a Bookmark" --> doFloat
      , className =? "Mitter"          --> doShift "irc"
      , className =? "Evolution"       --> doShift "mail"
      , className =? "Shredder"        --> doShift "mail"
      , className =? "VirtualBox"      --> doShift "win"
      , className =? "Tsclient"        --> doShift "win"
      , className =? "Gimp"            --> doShift "art"
      , isFullscreen                   --> doFullFloat
      , isDialog                       --> doCenterFloat
      ] ])
        <+> manageDocks -- make some space
            where floats = ["Mplayer","Tsclient","VirtualBox","Gtklp","smc"]
                  webs   = ["Navigator","Gran Paradiso","Firefox", "Midori", "Minefield"]
                  games  = ["roguestar-gl","neverputt","neverball","wesnoth"]
-- }}}
lacKeys :: [([Char], X ())]
lacKeys =
    [ ("M-p"        , runOrRaisePrompt largeXPConfig )
    , ("M-S-p"      , spawn "exe=`dmenu_path | dmenu -b` \"exec $exe\"") -- backup launcher incase prompt causes lockups
    , ("M-g"        , runOrRaise "firefox-nightly" (className =? "Minefield"))
    , ("M-S-g"      , safePromptSelection "firefox-nightly")
    , ("M-w"        , goToSelected defaultGSConfig)
    , ("M-C-n"      , appendFilePrompt largeXPConfig { bgColor = colorOrange, fgColor = colorDarkGray } notesFile)
    , ("M-S-z"      , safeSpawn "mocp" "-G")  -- play/pause
    , ("M-S-,"      , safeSpawn "mocp" "-r")  -- rev
    , ("M-S-."      , safeSpawn "mocp" "-f")  -- fwd
    , ("M-<Esc>"    , focusUrgent)
    , ("M-`"        , scratchpadSpawnAction defaultConfig { terminal = mTerm })  -- scratchpad
    , ("M-S-l"      , unsafeSpawn "slock")    -- screen lock
    , ("M-i"    , raiseMaybe (runInTerm "-title irssi" "sh -c 'screen -D -R -S irc irssi'") (title =? "irssi"))
    , ("M-S-i"  , raiseMaybe (runInTerm "-title irssi" "sh -c 'ssh -t webframp@astrotrain screen -D -R -S irc irssi'") (title =? "irssi"))
    , ("M-m"    , raiseMaybe (runInTerm "-title mutt" "sh -c 'screen -D -R -S mail mutt'") (title =? "mutt"))
    , ("M-S-m"  , runOrRaise "thunderbird3" (className =? "Shredder")) -- work email
    , ("M-e"    , safeSpawn "pcmanfm" "--no-desktop")
    , ("M-S-e"  , unsafeSpawn "dolphin")
    , ("M-b"    , sendMessage ToggleStruts)
    -- focus NonEmpty wss except scratchpad
    , ("M-s", windows . W.greedyView =<< findWorkspace getSortByIndexNoSP Next NonEmptyWS 1)
    , ("M-d", windows . W.greedyView =<< findWorkspace getSortByIndexNoSP Prev NonEmptyWS 1)
    -- move window to NonEmpty wss except scratchpad
    , ("M-S-s", windows . W.shift =<< findWorkspace getSortByIndexNoSP Next NonEmptyWS 1)
    , ("M-S-d", windows . W.shift =<< findWorkspace getSortByIndexNoSP Prev NonEmptyWS 1)
    -- move window to and focus NonEmpty wss except scratchpad
    , ("M-C-s", shiftAndView Next)
    , ("M-C-d", shiftAndView Prev)
    , ("M-f"  , nextScreen)
    , ("M-a"  , prevScreen)
    , ("M-S-f", shiftNextScreen)
    , ("M-S-a", shiftPrevScreen)
    , ("M-z"  , toggleWS)
    ]
    ++ 
    -- Search methods
    -- mapped to mod-c for 'a căuta'
    [("M-c " ++ k, S.promptSearch largeXPConfig f) | (k,f) <- searchList ]
    ++
    [("M-C-c " ++ k, S.selectSearch f) | (k,f) <- searchList ]
    where -- | non-empty workspaces less scratchpad
        shiftAndView dir = findWorkspace getSortByIndexNoSP dir NonEmptyWS 1
                >>= \t -> (windows . W.shift $ t) >> (windows . W.greedyView $ t)
        getSortByIndexNoSP =
                fmap (.scratchpadFilterOutWorkspace) getSortByIndex

searchList :: [([Char], S.SearchEngine)]
searchList = [ ("g", S.google)
             , ("h", hayoo)
             , ("i", S.isohunt)
             , ("w", S.wikipedia)
             , ("d", S.dictionary)
             , ("t", S.thesaurus)
             , ("a", S.amazon)
             , ("y", S.youtube)
             , ("e", enro40)
             , ("r", roen40)
             ]
-- vim:foldmethod=marker sw=4 sts=4 ts=4 tw=0 et ai nowrap