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

From HaskellWiki
Jump to navigation Jump to search
(3 intermediate revisions by the same user not shown)
Line 4: Line 4:
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
 
-- ~/.xmonad/xmonad.hs --
 
-- ~/.xmonad/xmonad.hs --
-- validate syntax: xmonad --recompile --
+
-- Author: Nnoell <nnoell3[at]gmail.com> --
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
   
-- Misc
+
-- Language
{-# LANGUAGE DeriveDataTypeable, NoMonomorphismRestriction, TypeSynonymInstances, MultiParamTypeClasses #-}
+
{-# LANGUAGE DeriveDataTypeable, NoMonomorphismRestriction, TypeSynonymInstances, MultiParamTypeClasses, ImplicitParams, PatternGuards #-}
   
 
-- Imported libraries
 
-- Imported libraries
Line 22: Line 22:
 
import XMonad.Layout.Reflect
 
import XMonad.Layout.Reflect
 
import XMonad.Layout.MosaicAlt
 
import XMonad.Layout.MosaicAlt
  +
import XMonad.Layout.NoFrillsDecoration
  +
import XMonad.Layout.SimplestFloat
 
import XMonad.Layout.NoBorders (noBorders,smartBorders,withBorder)
 
import XMonad.Layout.NoBorders (noBorders,smartBorders,withBorder)
 
import XMonad.Layout.ResizableTile
 
import XMonad.Layout.ResizableTile
Line 28: Line 30:
 
import XMonad.Layout.PerWorkspace (onWorkspace)
 
import XMonad.Layout.PerWorkspace (onWorkspace)
 
import XMonad.Layout.Minimize
 
import XMonad.Layout.Minimize
  +
import XMonad.Layout.Maximize
  +
import XMonad.Layout.WindowNavigation
 
import XMonad.StackSet (RationalRect (..), currentTag)
 
import XMonad.StackSet (RationalRect (..), currentTag)
  +
import XMonad.Util.Loggers
 
import XMonad.Hooks.DynamicLog
 
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks (avoidStruts,avoidStrutsOn,manageDocks)
+
import XMonad.Hooks.DynamicHooks
import XMonad.Hooks.ManageHelpers
+
import XMonad.Hooks.ManageDocks
 
import XMonad.Hooks.UrgencyHook
 
import XMonad.Hooks.UrgencyHook
 
import XMonad.Hooks.EwmhDesktops
 
import XMonad.Hooks.EwmhDesktops
 
import XMonad.Hooks.SetWMName
 
import XMonad.Hooks.SetWMName
  +
import XMonad.Hooks.ManageHelpers
 
import XMonad.Prompt
 
import XMonad.Prompt
 
import XMonad.Prompt.Shell
 
import XMonad.Prompt.Shell
 
import XMonad.Prompt.XMonad
 
import XMonad.Prompt.XMonad
  +
import XMonad.Prompt.Man
  +
import XMonad.Util.Timer
 
import XMonad.Util.Cursor
 
import XMonad.Util.Cursor
  +
import XMonad.Util.EZConfig
 
import XMonad.Util.Run (spawnPipe)
 
import XMonad.Util.Run (spawnPipe)
import XMonad.Util.Scratchpad (scratchpadManageHook, scratchpadSpawnActionCustom)
+
import XMonad.Util.Scratchpad
 
import XMonad.Util.NamedScratchpad
 
import XMonad.Util.NamedScratchpad
import XMonad.Actions.CycleWS (nextWS, prevWS, toggleWS, toggleOrView)
+
import XMonad.Actions.CycleWS
 
import XMonad.Actions.GridSelect
 
import XMonad.Actions.GridSelect
import XMonad.Actions.FloatKeys
+
import XMonad.Actions.MouseResize
  +
import Data.IORef
 
import Data.Monoid
 
import Data.Monoid
 
import Data.List
 
import Data.List
Line 50: Line 60:
 
import System.Exit
 
import System.Exit
 
import System.IO (Handle, hPutStrLn)
 
import System.IO (Handle, hPutStrLn)
  +
import System.IO
 
import qualified XMonad.StackSet as W
 
import qualified XMonad.StackSet as W
 
import qualified Data.Map as M
 
import qualified Data.Map as M
 
import qualified XMonad.Actions.FlexibleResize as Flex
 
import qualified XMonad.Actions.FlexibleResize as Flex
  +
import qualified XMonad.Util.ExtensibleState as XS
  +
   
 
-- Main
 
-- Main
 
main :: IO ()
 
main :: IO ()
 
main = do
 
main = do
  +
topLeftBar <- spawnPipe myTopLeftBar
  +
topRightBar <- spawnPipe myTopRightBar
 
workspaceBar <- spawnPipe myWorkspaceBar
 
workspaceBar <- spawnPipe myWorkspaceBar
bottomStatusBar <- spawnPipe myBottomStatusBar
+
bottomBar <- spawnPipe $ myBinPath ++ "bottomBar.sh"
topStatusBar <- spawnPipe myTopStatusBar
+
focusFollow <- newIORef True; let ?focusFollow = focusFollow
 
xmonad $ myUrgencyHook $ defaultConfig
 
xmonad $ myUrgencyHook $ defaultConfig
 
{ terminal = "urxvtc"
 
{ terminal = "urxvtc"
 
, modMask = mod4Mask
 
, modMask = mod4Mask
, focusFollowsMouse = True
+
, focusFollowsMouse = False
 
, borderWidth = 1
 
, borderWidth = 1
 
, normalBorderColor = myNormalBorderColor
 
, normalBorderColor = myNormalBorderColor
Line 69: Line 84:
 
, layoutHook = myLayoutHook
 
, layoutHook = myLayoutHook
 
, workspaces = myWorkspaces
 
, workspaces = myWorkspaces
, manageHook = manageDocks <+> myManageHook
+
, manageHook = myManageHook <+> manageScratchPad <+> manageDocks <+> dynamicMasterHook
, logHook = (myLogHook workspaceBar) <+> ewmhDesktopsLogHook >> setWMName "LG3D" --ewmh needed so that chromium gain focus
+
, logHook = myLogHook workspaceBar <+> myLogHook2 topLeftBar <+> myLogHook3 topRightBar <+> ewmhDesktopsLogHook >> setWMName "LG3D"
  +
, handleEventHook = myHandleEventHook
, handleEventHook = fullscreenEventHook --needed for chromium full screen
 
 
, keys = myKeys
 
, keys = myKeys
 
, mouseBindings = myMouseBindings
 
, mouseBindings = myMouseBindings
, startupHook = setDefaultCursor xC_left_ptr >> setWMName "LG3D"
+
, startupHook = (startTimer 1 >>= XS.put . TID) <+> setDefaultCursor xC_left_ptr >> setWMName "LG3D"
 
}
 
}
  +
`additionalKeysP`
  +
[ ("<XF86TouchpadToggle>", spawn $ myBinPath ++ "touchpadtoggle.sh") --because xF86XK_TouchpadToggle doesnt exist
  +
, ("M-v", io $ modifyIORef ?focusFollow not) --Toggle focus follow moouse
  +
]
   
   
Line 82: Line 101:
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
   
-- Colors and fonts
+
-- Colors, fonts and paths
myFont = "-xos4-terminus-medium-r-normal-*-12-120-72-72-c-60-*-*"
 
 
dzenFont = "-*-montecarlo-medium-r-normal-*-11-*-*-*-*-*-*-*"
 
dzenFont = "-*-montecarlo-medium-r-normal-*-11-*-*-*-*-*-*-*"
 
colorBlack = "#020202" --Background (Dzen_BG)
 
colorBlack = "#020202" --Background (Dzen_BG)
 
colorBlackAlt = "#1c1c1c" --Black Xdefaults
 
colorBlackAlt = "#1c1c1c" --Black Xdefaults
 
colorGray = "#444444" --Gray (Dzen_FG2)
 
colorGray = "#444444" --Gray (Dzen_FG2)
colorGrayAlt = "#161616" --Gray dark
+
colorGrayAlt = "#101010" --Gray dark
 
colorWhite = "#a9a6af" --Foreground (Shell_FG)
 
colorWhite = "#a9a6af" --Foreground (Shell_FG)
 
colorWhiteAlt = "#9d9d9d" --White dark (Dzen_FG)
 
colorWhiteAlt = "#9d9d9d" --White dark (Dzen_FG)
 
colorMagenta = "#8e82a2"
 
colorMagenta = "#8e82a2"
colorBlue = "#3475aa"
+
colorBlue = "#44aacc"
colorRed = "#d74b73"
+
colorBlueAlt = "#3955c4"
colorGreen = "#99cc66"
+
colorRed = "#e0105f"
  +
colorGreen = "#66ff66"
myArrow = "^fg(" ++ colorWhiteAlt ++ ")>^fg(" ++ colorBlue ++ ")>^fg(" ++ colorGray ++ ")>"
 
  +
colorGreenAlt = "#558965"
 
myNormalBorderColor = colorBlackAlt
 
myNormalBorderColor = colorBlackAlt
 
myFocusedBorderColor = colorGray
 
myFocusedBorderColor = colorGray
  +
myIconPath = "/home/nnoell/.icons/xbm_icons/subtle/"
  +
myBinPath = "/home/nnoell/bin/"
  +
xRes = 1366
  +
yRes = 768
  +
panelHeight = 16
  +
panelBoxHeight = 12
   
-- Tab theme
+
-- Title theme
myTabTheme :: Theme
+
myTitleTheme :: Theme
myTabTheme = defaultTheme
+
myTitleTheme = defaultTheme
{ fontName = myFont
+
{ fontName = dzenFont
 
, inactiveBorderColor = colorBlackAlt
 
, inactiveBorderColor = colorBlackAlt
 
, inactiveColor = colorBlack
 
, inactiveColor = colorBlack
Line 117: Line 142:
 
myXPConfig :: XPConfig
 
myXPConfig :: XPConfig
 
myXPConfig = defaultXPConfig
 
myXPConfig = defaultXPConfig
{ font = myFont
+
{ font = dzenFont
 
, bgColor = colorBlack
 
, bgColor = colorBlack
 
, fgColor = colorWhite
 
, fgColor = colorWhite
 
, bgHLight = colorBlue
 
, bgHLight = colorBlue
, fgHLight = colorWhite
+
, fgHLight = colorBlack
 
, borderColor = colorGrayAlt
 
, borderColor = colorGrayAlt
 
, promptBorderWidth = 1
 
, promptBorderWidth = 1
Line 135: Line 160:
 
myColorizer = colorRangeFromClassName
 
myColorizer = colorRangeFromClassName
 
(0x00,0x00,0x00) -- lowest inactive bg
 
(0x00,0x00,0x00) -- lowest inactive bg
(0x60,0xA0,0xC0) -- highest inactive bg
+
(0x1C,0x1C,0x1C) -- highest inactive bg
(0x34,0x75,0xAA) -- active bg
+
(0x44,0xAA,0xCC) -- active bg
 
(0xBB,0xBB,0xBB) -- inactive fg
 
(0xBB,0xBB,0xBB) -- inactive fg
 
(0x00,0x00,0x00) -- active fg
 
(0x00,0x00,0x00) -- active fg
Line 146: Line 171:
 
, gs_cellwidth = 200
 
, gs_cellwidth = 200
 
, gs_cellpadding = 10
 
, gs_cellpadding = 10
, gs_font = myFont
+
, gs_font = dzenFont
 
}
 
}
   
 
-- Workspaces
 
-- Workspaces
 
myWorkspaces :: [WorkspaceId]
 
myWorkspaces :: [WorkspaceId]
myWorkspaces = ["TERM", "WEBS", "CODE", "GRFX", "CHAT", "GAME", "VIDS", "OTHR"]
+
myWorkspaces = ["1", "2", "3", "4", "5", "6", "7", "8", "9", "0"]
   
   
Line 158: Line 183:
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
   
  +
-- Layouts (name must be diferent of Minimize, Maximize and Mirror)
-- Layouts
 
myTile = named "T" $ smartBorders $ ResizableTall 1 0.03 0.5 []
+
myTile = named "ResizableTall" $ smartBorders $ ResizableTall 1 0.03 0.5 []
myMirr = named "MT" $ smartBorders $ Mirror myTile
+
myMirr = named "MirrResizableTall" $ smartBorders $ Mirror myTile
myMosA = named "M" $ smartBorders $ MosaicAlt M.empty
+
myMosA = named "MosaicAlt" $ smartBorders $ MosaicAlt M.empty
myObig = named "O" $ smartBorders $ OneBig 0.75 0.65
+
myObig = named "OneBig" $ smartBorders $ OneBig 0.75 0.65
myTabs = named "TS" $ smartBorders $ tabbed shrinkText myTabTheme
+
myTabs = named "Simple Tabbed" $ smartBorders $ tabbed shrinkText myTitleTheme
myFull = named "TS" $ smartBorders $ tabbedAlways shrinkText myTabTheme
+
myFull = named "Full Tabbed" $ smartBorders $ tabbedAlways shrinkText myTitleTheme
myTabM = named "TM" $ smartBorders $ mastered 0.01 0.4 $ tabbed shrinkText myTabTheme
+
myTabM = named "Master Tabbed" $ smartBorders $ mastered 0.01 0.4 $ tabbed shrinkText myTitleTheme
  +
myFlat = named "Simple Float" $ mouseResize $ noFrillsDeco shrinkText myTitleTheme simplestFloat
myGimp = named "G" $ withIM (0.15) (Role "gimp-toolbox") $ reflectHoriz $ withIM (0.20) (Role "gimp-dock") myMosA
 
myChat = named "C" $ withIM (0.20) (Title "Buddy List") $ Mirror $ ResizableTall 1 0.03 0.5 []
+
myGimp = named "Gimp MosaicAlt" $ withIM (0.15) (Role "gimp-toolbox") $ reflectHoriz $ withIM (0.20) (Role "gimp-dock") myMosA
  +
myChat = named "Pidgin MosaicAlt" $ withIM (0.20) (Title "Buddy List") $ Mirror $ ResizableTall 1 0.03 0.5 []
   
-- Transformers (Ctrl+f)
+
-- Tabbed transformer (W+f)
 
data TABBED = TABBED deriving (Read, Show, Eq, Typeable)
 
data TABBED = TABBED deriving (Read, Show, Eq, Typeable)
 
instance Transformer TABBED Window where
 
instance Transformer TABBED Window where
 
transform TABBED x k = k myFull (\_ -> x)
 
transform TABBED x k = k myFull (\_ -> x)
  +
  +
-- Floated transformer (W+ctl+f)
  +
data FLOATED = FLOATED deriving (Read, Show, Eq, Typeable)
  +
instance Transformer FLOATED Window where
  +
transform FLOATED x k = k myFlat (\_ -> x)
   
 
-- Layout hook
 
-- Layout hook
myLayoutHook = id
+
myLayoutHook = gaps [(U,16), (D,16), (L,0), (R,0)]
$ gaps [(U,16), (D,16), (L,0), (R,0)]
 
 
$ avoidStruts
 
$ avoidStruts
  +
$ windowNavigation
 
$ minimize
 
$ minimize
  +
$ maximize
 
$ mkToggle (single TABBED)
 
$ mkToggle (single TABBED)
  +
$ mkToggle (single FLOATED)
 
$ mkToggle (single MIRROR)
 
$ mkToggle (single MIRROR)
 
$ mkToggle (single REFLECTX)
 
$ mkToggle (single REFLECTX)
Line 190: Line 223:
 
where
 
where
 
allLayouts = myTile ||| myObig ||| myMirr ||| myMosA ||| myTabM
 
allLayouts = myTile ||| myObig ||| myMirr ||| myMosA ||| myTabM
webLayouts = myTabs ||| myTabM
+
webLayouts = myTabs ||| myMirr ||| myTabM
 
codeLayouts = myTabM ||| myTile
 
codeLayouts = myTabM ||| myTile
 
gimpLayouts = myGimp
 
gimpLayouts = myGimp
 
chatLayouts = myChat
 
chatLayouts = myChat
  +
  +
  +
--------------------------------------------------------------------------------------------
  +
-- HANDLE EVENT HOOK CONFIG --
  +
--------------------------------------------------------------------------------------------
  +
  +
-- wrapper for the Timer id, so it can be stored as custom mutable state
  +
data TidState = TID TimerId deriving Typeable
  +
  +
instance ExtensionClass TidState where
  +
initialValue = TID 0
  +
  +
-- Handle event hook
  +
myHandleEventHook :: (?focusFollow::IORef Bool) => Event -> X All
  +
myHandleEventHook = fullscreenEventHook <+> docksEventHook <+> toggleFocus <+> clockEventHook
  +
where
  +
toggleFocus e = case e of --thanks to Vgot
  +
CrossingEvent {ev_window=w, ev_event_type=t}
  +
| t == enterNotify, ev_mode e == notifyNormal -> do
  +
whenX (io $ readIORef ?focusFollow) (focus w)
  +
return $ All True
  +
_ -> return $ All True
  +
clockEventHook e = do --thanks to DarthFennec
  +
(TID t) <- XS.get --get the recent Timer id
  +
handleTimer t e $ do --run the following if e matches the id
  +
startTimer 1 >>= XS.put . TID --restart the timer, store the new id
  +
ask >>= logHook.config --get the loghook and run it
  +
return Nothing --return required type
  +
return $ All True --return required type
   
   
Line 200: Line 262:
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
   
-- Scratchpad (Alt+º)
+
-- Scratchpad (W+º)
 
manageScratchPad :: ManageHook
 
manageScratchPad :: ManageHook
 
manageScratchPad = scratchpadManageHook (W.RationalRect (0) (1/50) (1) (3/4))
 
manageScratchPad = scratchpadManageHook (W.RationalRect (0) (1/50) (1) (3/4))
Line 207: Line 269:
 
-- Manage hook
 
-- Manage hook
 
myManageHook :: ManageHook
 
myManageHook :: ManageHook
myManageHook = (composeAll . concat $
+
myManageHook = composeAll . concat $
 
[ [resource =? r --> doIgnore | r <- myIgnores] --ignore desktop
 
[ [resource =? r --> doIgnore | r <- myIgnores] --ignore desktop
 
, [className =? c --> doShift (myWorkspaces !! 1) | c <- myWebS ] --move myWebS windows to workspace 1 by classname
 
, [className =? c --> doShift (myWorkspaces !! 1) | c <- myWebS ] --move myWebS windows to workspace 1 by classname
  +
, [className =? c --> doShift (myWorkspaces !! 2) | c <- myCodeS ] --move myCodeS windows to workspace 2 by classname
 
, [className =? c --> doShift (myWorkspaces !! 4) | c <- myChatS ] --move myChatS windows to workspace 4 by classname
 
, [className =? c --> doShift (myWorkspaces !! 4) | c <- myChatS ] --move myChatS windows to workspace 4 by classname
 
, [className =? c --> doShift (myWorkspaces !! 3) | c <- myGfxS ] --move myGfxS windows to workspace 4 by classname
 
, [className =? c --> doShift (myWorkspaces !! 3) | c <- myGfxS ] --move myGfxS windows to workspace 4 by classname
, [className =? c --> doShiftAndGo (myWorkspaces !! 5) | c <- myGameS ] --move myGameS windows to workspace 5 by classname and shift
+
, [className =? c --> doShiftAndGo (myWorkspaces !! 5) | c <- myAlt1S ] --move myGameS windows to workspace 5 by classname and shift
, [className =? c --> doShiftAndGo (myWorkspaces !! 7) | c <- myOtherS ] --move myOtherS windows to workspace 5 by classname and shift
+
, [className =? c --> doShift (myWorkspaces !! 7) | c <- myAlt3S ] --move myOtherS windows to workspace 5 by classname and shift
 
, [className =? c --> doCenterFloat | c <- myFloatCC] --float center geometry by classname
 
, [className =? c --> doCenterFloat | c <- myFloatCC] --float center geometry by classname
 
, [name =? n --> doCenterFloat | n <- myFloatCN] --float center geometry by name
 
, [name =? n --> doCenterFloat | n <- myFloatCN] --float center geometry by name
Line 219: Line 282:
 
, [className =? c --> doF W.focusDown | c <- myFocusDC] --dont focus on launching by classname
 
, [className =? c --> doF W.focusDown | c <- myFocusDC] --dont focus on launching by classname
 
, [isFullscreen --> doFullFloat]
 
, [isFullscreen --> doFullFloat]
  +
]
]) <+> manageScratchPad
 
 
where
 
where
 
doShiftAndGo ws = doF (W.greedyView ws) <+> doShift ws
 
doShiftAndGo ws = doF (W.greedyView ws) <+> doShift ws
Line 225: Line 288:
 
name = stringProperty "WM_NAME"
 
name = stringProperty "WM_NAME"
 
myIgnores = ["desktop","desktop_window"]
 
myIgnores = ["desktop","desktop_window"]
myWebS = ["Chromium","Firefox"]
+
myWebS = ["Chromium","Firefox", "Opera"]
myGfxS = ["gimp-2.6", "Gimp-2.6", "Gimp", "gimp", "GIMP"]
+
myCodeS = ["NetBeans IDE 7.2"]
  +
myGfxS = ["Gimp", "gimp", "GIMP"]
 
myChatS = ["Pidgin", "Xchat"]
 
myChatS = ["Pidgin", "Xchat"]
myGameS = ["zsnes", "jpcsp-MainGUI", "Desmume"]
+
myAlt1S = ["zsnes"]
myOtherS = ["Amule", "Transmission-gtk"]
+
myAlt3S = ["Amule", "Transmission-gtk"]
myFloatCC = ["MPlayer", "File-roller", "zsnes", "Gcalctool", "Exo-helper-1", "Gksu", "PSX", "Galculator", "Nvidia-settings", "XFontSel", "XCalc", "XClock", "Desmume", "Ossxmix", "Xvidcap", "Main", "Wicd-client.py", "com-mathworks-util-PostVMInit"]
+
myFloatCC = ["MPlayer", "File-roller", "zsnes", "Gcalctool", "Exo-helper-1", "Gksu", "PSX", "Galculator", "Nvidia-settings", "XFontSel"
  +
, "XCalc", "XClock", "Desmume", "Ossxmix", "Xvidcap", "Main", "Wicd-client.py", "com-mathworks-util-PostVMInit", "MATLAB"]
myFloatCN = ["ePSXe - Enhanced PSX emulator", "Seleccione Archivo", "Config Video", "Testing plugin", "Config Sound", "Config Cdrom", "Config Bios", "Config Netplay", "Config Memcards", "About ePSXe", "Config Controller", "Config Gamepads", "Select one or more files to open", "Add media", "Choose a file", "Open Image", "File Operation Progress", "Firefox Preferences", "Preferences", "Search Engines", "Set up sync", "Passwords and Exceptions", "Autofill Options", "Rename File", "Copying files", "Moving files", "File Properties", "Replace", ""]
 
  +
myFloatCN = ["ePSXe - Enhanced PSX emulator", "Seleccione Archivo", "Config Video", "Testing plugin", "Config Sound", "Config Cdrom", "Config Bios"
  +
, "Config Netplay", "Config Memcards", "About ePSXe", "Config Controller", "Config Gamepads", "Select one or more files to open"
  +
, "Add media", "Choose a file", "Open Image", "File Operation Progress", "Firefox Preferences", "Preferences", "Search Engines"
  +
, "Set up sync", "Passwords and Exceptions", "Autofill Options", "Rename File", "Copying files", "Moving files", "File Properties", "Replace", ""]
 
myFloatSN = ["Event Tester"]
 
myFloatSN = ["Event Tester"]
 
myFocusDC = ["Event Tester", "Notify-osd"]
 
myFocusDC = ["Event Tester", "Notify-osd"]
Line 242: Line 310:
 
-- UrgencyHook
 
-- UrgencyHook
 
myUrgencyHook = withUrgencyHook dzenUrgencyHook
 
myUrgencyHook = withUrgencyHook dzenUrgencyHook
{ args = ["-fn", dzenFont, "-bg", colorBlack, "-fg", colorGreen] }
+
{ args = ["-fn", dzenFont, "-bg", colorBlack, "-fg", colorGreen, "-h", show panelHeight] }
   
  +
-- WorkspaceBar
-- StatusBars
 
  +
myWorkspaceBar = "dzen2 -x 0 -y 752 -h 16 -w 380 -ta 'l' -fg '" ++ colorWhiteAlt ++ "' -bg '" ++ colorBlack ++ "' -fn '" ++ dzenFont ++ "' -p -e 'onstart=lower'"
myWorkspaceBar, myBottomStatusBar, myTopStatusBar :: String
 
myWorkspaceBar = "dzen2 -x '0' -y '784' -h '16' -w '870' -ta 'l' -fg '" ++ colorWhiteAlt ++ "' -bg '" ++ colorBlack ++ "' -fn '" ++ dzenFont ++ "' -p -e ''"
 
myBottomStatusBar = "/home/nnoell/bin/bottomstatusbar.sh"
 
myTopStatusBar = "/home/nnoell/bin/topstatusbar.sh"
 
 
-- myWorkspaceBar config
 
 
myLogHook :: Handle -> X ()
 
myLogHook :: Handle -> X ()
 
myLogHook h = dynamicLogWithPP $ defaultPP
 
myLogHook h = dynamicLogWithPP $ defaultPP
 
{ ppOutput = hPutStrLn h
 
{ ppOutput = hPutStrLn h
, ppSort = fmap (namedScratchpadFilterOutWorkspace.) (ppSort defaultPP) -- hide "NSP" from workspace list
+
, ppSort = fmap (namedScratchpadFilterOutWorkspace .) (ppSort defaultPP) --hide "NSP" from workspace list
, ppOrder = orderText
+
, ppOrder = \(ws:l:_:x) -> [ws,l]
, ppExtras = []
+
, ppSep = " "
, ppSep = "^fg(" ++ colorGray ++ ")|"
 
 
, ppWsSep = ""
 
, ppWsSep = ""
, ppCurrent = dzenColor colorBlue colorBlack . pad
+
, ppCurrent = wrapTextBox colorBlack colorBlue colorBlack
, ppUrgent = dzenColor colorGreen colorBlack . pad . wrapClickWorkSpace . (\a -> (a,a))
+
, ppUrgent = wrapTextBox colorBlack colorGreen colorBlack . wrapClickWorkspace
, ppVisible = dzenColor colorGray colorBlack . pad . wrapClickWorkSpace . (\a -> (a,a))
+
, ppVisible = wrapTextBox colorBlack colorGrayAlt colorBlack . wrapClickWorkspace
  +
, ppHiddenNoWindows = wrapTextBox colorBlack colorGrayAlt colorBlack . wrapClickWorkspace
, ppHidden = dzenColor colorWhiteAlt colorBlack . pad . wrapClickWorkSpace . (\a -> (a,a))
 
  +
, ppHidden = wrapTextBox colorWhiteAlt colorGrayAlt colorBlack . wrapClickWorkspace
, ppHiddenNoWindows = dzenColor colorGray colorBlack . pad . wrapClickWorkSpace . (\a -> (a,a))
 
, ppLayout = dzenColor colorBlue colorBlack . pad . wrapClickLayout . layoutText
+
, ppLayout = \l -> (wrapClickLayout (wrapTextBox colorBlue colorGrayAlt colorBlack "LAYOUT")) ++ (wrapTextBox colorGray colorGrayAlt colorBlack $ layoutText $ removeWord $ removeWord l)
, ppTitle = dzenColor colorWhiteAlt colorBlack . pad . wrapClickTitle . titleText . dzenEscape
 
 
}
 
}
 
where
 
where
  +
removeWord = tail . dropWhile (/= ' ')
--display config
 
  +
layoutText xs
orderText (ws:l:t:_) = [ws,l,t]
 
  +
| isPrefixOf "Mirror" xs = layoutText $ removeWord xs ++ " [M]"
titleText [] = "Desktop" ++ myArrow
 
  +
| isPrefixOf "ReflectY" xs = layoutText $ removeWord xs ++ " [Y]"
titleText x = (shorten 82 x) ++ " " ++ myArrow
 
  +
| isPrefixOf "ReflectX" xs = layoutText $ removeWord xs ++ " [X]"
layoutText "Minimize T" = "ReTall"
 
  +
| isPrefixOf "Float" xs = "^fg(" ++ colorRed ++ ")" ++ xs
layoutText "Minimize O" = "OneBig"
 
  +
| isPrefixOf "Full" xs = "^fg(" ++ colorGreen ++ ")" ++ xs
layoutText "Minimize TS" = "Tabbed"
 
  +
| otherwise = "^fg(" ++ colorWhiteAlt ++ ")" ++ xs
layoutText "Minimize TM" = "Master"
 
  +
layoutText "Minimize M" = "Mosaic"
 
  +
-- TopLeftBar
layoutText "Minimize MT" = "Mirror"
 
  +
myTopLeftBar = "dzen2 -x 0 -y 0 -h 16 -w 1050 -ta 'l' -fg '" ++ colorWhiteAlt ++ "' -bg '" ++ colorBlack ++ "' -fn '" ++ dzenFont ++ "' -p -e 'onstart=lower'"
layoutText "Minimize G" = "Mosaic"
 
  +
myLogHook2 :: Handle -> X ()
layoutText "Minimize C" = "Mirror"
 
  +
myLogHook2 h = dynamicLogWithPP $ defaultPP
layoutText "Minimize ReflectX T" = "^fg(" ++ colorGreen ++ ")ReTall X^fg()"
 
  +
{ ppOutput = hPutStrLn h
layoutText "Minimize ReflectX O" = "^fg(" ++ colorGreen ++ ")OneBig X^fg()"
 
  +
, ppOrder = \(_:_:_:x) -> x
layoutText "Minimize ReflectX TS" = "^fg(" ++ colorGreen ++ ")Tabbed X^fg()"
 
  +
, ppSep = " "
layoutText "Minimize ReflectX TM" = "^fg(" ++ colorGreen ++ ")Master X^fg()"
 
  +
, ppExtras = [ wrapL (wrapClickGrid $ wrapTextBox colorBlue colorGrayAlt colorBlack "WORKSPACE") "" $ wrapLoggerBox colorWhiteAlt colorGrayAlt colorBlack $ onLogger namedWorkspaces logCurrent
layoutText "Minimize ReflectX M" = "^fg(" ++ colorGreen ++ ")Mosaic X^fg()"
 
  +
, wrapL (wrapClickTitle $ wrapTextBox colorBlack colorWhiteAlt colorBlack "FOCUS") "" $ wrapLoggerBox colorWhiteAlt colorGrayAlt colorBlack $ shortenL 144 logTitle
layoutText "Minimize ReflectX MT" = "^fg(" ++ colorGreen ++ ")Mirror X^fg()"
 
  +
]
layoutText "Minimize ReflectX G" = "^fg(" ++ colorGreen ++ ")Mosaic X^fg()"
 
  +
}
layoutText "Minimize ReflectX C" = "^fg(" ++ colorGreen ++ ")Mirror X^fg()"
 
  +
where
layoutText "Minimize ReflectY T" = "^fg(" ++ colorGreen ++ ")ReTall Y^fg()"
 
  +
namedWorkspaces w
layoutText "Minimize ReflectY O" = "^fg(" ++ colorGreen ++ ")OneBig Y^fg()"
 
layoutText "Minimize ReflectY TS" = "^fg(" ++ colorGreen ++ ")Tabbed Y^fg()"
+
| w == "1" = "^fg(" ++ colorGreen ++ ")1^fg(" ++ colorGray ++ ")|^fg()Terminal"
layoutText "Minimize ReflectY TM" = "^fg(" ++ colorGreen ++ ")Master Y^fg()"
+
| w == "2" = "^fg(" ++ colorGreen ++ ")2^fg(" ++ colorGray ++ ")|^fg()Network"
layoutText "Minimize ReflectY M" = "^fg(" ++ colorGreen ++ ")Mosaic Y^fg()"
+
| w == "3" = "^fg(" ++ colorGreen ++ ")3^fg(" ++ colorGray ++ ")|^fg()Development"
layoutText "Minimize ReflectY MT" = "^fg(" ++ colorGreen ++ ")Mirror Y^fg()"
+
| w == "4" = "^fg(" ++ colorGreen ++ ")4^fg(" ++ colorGray ++ ")|^fg()Graphics"
layoutText "Minimize ReflectY G" = "^fg(" ++ colorGreen ++ ")Mosaic Y^fg()"
+
| w == "5" = "^fg(" ++ colorGreen ++ ")5^fg(" ++ colorGray ++ ")|^fg()Chatting"
layoutText "Minimize ReflectY C" = "^fg(" ++ colorGreen ++ ")Mirror Y^fg()"
+
| w == "6" = "^fg(" ++ colorGreen ++ ")6^fg(" ++ colorGray ++ ")|^fg()Alternative"
layoutText "Minimize ReflectX ReflectY T" = "^fg(" ++ colorGreen ++ ")ReTall XY^fg()"
+
| w == "7" = "^fg(" ++ colorGreen ++ ")7^fg(" ++ colorGray ++ ")|^fg()Alternative"
layoutText "Minimize ReflectX ReflectY O" = "^fg(" ++ colorGreen ++ ")OneBig XY^fg()"
+
| w == "8" = "^fg(" ++ colorGreen ++ ")8^fg(" ++ colorGray ++ ")|^fg()Alternative"
layoutText "Minimize ReflectX ReflectY TS" = "^fg(" ++ colorGreen ++ ")Tabbed XY^fg()"
+
| w == "9" = "^fg(" ++ colorGreen ++ ")9^fg(" ++ colorGray ++ ")|^fg()Alternative"
layoutText "Minimize ReflectX ReflectY TM" = "^fg(" ++ colorGreen ++ ")Master XY^fg()"
+
| w == "0" = "^fg(" ++ colorGreen ++ ")0^fg(" ++ colorGray ++ ")|^fg()Alternative"
layoutText "Minimize ReflectX ReflectY M" = "^fg(" ++ colorGreen ++ ")Mosaic XY^fg()"
+
| otherwise = "^fg(" ++ colorRed ++ ")x^fg(" ++ colorGray ++ ")|^fg()" ++ w
  +
layoutText "Minimize ReflectX ReflectY MT" = "^fg(" ++ colorGreen ++ ")Mirror XY^fg()"
 
  +
-- TopRightBar
layoutText "Minimize ReflectX ReflectY G" = "^fg(" ++ colorGreen ++ ")Mosaic XY^fg()"
 
  +
myTopRightBar = "dzen2 -x 1050 -y 0 -h 16 -w 366 -ta 'r' -fg '" ++ colorWhiteAlt ++ "' -bg '" ++ colorBlack ++ "' -fn '" ++ dzenFont ++ "' -p -e 'onstart=lower'"
layoutText "Minimize ReflectX ReflectY C" = "^fg(" ++ colorGreen ++ ")Mirror XY^fg()"
 
  +
myLogHook3 :: Handle -> X ()
layoutText x = "^fg(" ++ colorGreen ++ ")" ++ x ++ "^fg()"
 
  +
myLogHook3 h = dynamicLogWithPP $ defaultPP
--clickable config
 
  +
{ ppOutput = hPutStrLn h
wrapClickLayout content = "^ca(1,xdotool key super+space)" ++ content ++ "^ca()" --clickable layout
 
  +
, ppOrder = \(_:_:_:x) -> x
wrapClickTitle content = "^ca(1,xdotool key super+j)" ++ content ++ "^ca()" --clickable title
 
  +
, ppSep = " "
wrapClickWorkSpace (idx,str) = "^ca(1," ++ xdo "w;" ++ xdo index ++ ")" ++ "^ca(3," ++ xdo "e;" ++ xdo index ++ ")" ++ str ++ "^ca()^ca()" --clickable workspaces
 
  +
, ppExtras = [ date $ (wrapTextBox colorBlack colorWhiteAlt colorBlack "%A") ++ (wrapTextBox colorWhiteAlt colorGrayAlt colorBlack $ "%Y^fg(" ++ colorGray ++ ").^fg()%m^fg(" ++ colorGray ++ ").^fg()^fg(" ++ colorBlue ++ ")%d^fg() ^fg(" ++ colorGray ++ ")-^fg() %H^fg(" ++ colorGray ++"):^fg()%M^fg(" ++ colorGray ++ "):^fg()^fg(" ++ colorGreen ++ ")%S^fg()")
where
 
  +
, return $ return $ wrapClickCalendar $ wrapTextBox colorBlue colorGrayAlt colorBlack "CALENDAR"
wsIdxToString Nothing = "1"
 
  +
]
wsIdxToString (Just n) = show (n+1)
 
  +
}
index = wsIdxToString (elemIndex idx myWorkspaces)
 
  +
xdo key = "xdotool key super+" ++ key
 
  +
-- Wrap Clickable Area
  +
wrapClickGrid x = "^ca(1,/usr/bin/xdotool key super+g)" ++ x ++ "^ca()"
  +
wrapClickCalendar x = "^ca(1," ++ myBinPath ++ "dzencal.sh)" ++ x ++ "^ca()"
  +
wrapClickLayout x = "^ca(1,/usr/bin/xdotool key super+space)^ca(3,/usr/bin/xdotool key super+shift+space)" ++ x ++ "^ca()^ca()"
  +
wrapClickTitle x = "^ca(1,/usr/bin/xdotool key super+m)^ca(2,/usr/bin/xdotool key super+c)^ca(3,/usr/bin/xdotool key super+shift+m)" ++ x ++ "^ca()^ca()^ca()"
  +
wrapClickWorkspace ws = "^ca(1," ++ xdo "w;" ++ xdo index ++ ")" ++ "^ca(3," ++ xdo "w;" ++ xdo index ++ ")" ++ ws ++ "^ca()^ca()"
  +
where
  +
wsIdxToString Nothing = "1"
  +
wsIdxToString (Just n) = show $ mod (n+1) $ length myWorkspaces
  +
index = wsIdxToString (elemIndex ws myWorkspaces)
  +
xdo key = "/usr/bin/xdotool key super+" ++ key
  +
  +
-- Wrap Box
  +
wrapTextBox :: String -> String -> String -> String -> String
  +
wrapTextBox fg bg1 bg2 t = "^fg(" ++ bg1 ++ ")^i(" ++ myIconPath ++ "boxleft.xbm)^ib(1)^r(" ++ show xRes ++ "x" ++ show panelBoxHeight ++ ")^p(-" ++ show xRes ++ ")^fg(" ++ fg ++ ")" ++ t ++ "^fg(" ++ bg1 ++ ")^i(" ++ myIconPath ++ "boxright.xbm)^fg(" ++ bg2 ++ ")^r(" ++ show xRes ++ "x" ++ show panelBoxHeight ++ ")^p(-" ++ show xRes ++ ")^fg()^ib(0)"
  +
  +
wrapLoggerBox :: String -> String -> String -> Logger -> Logger
  +
wrapLoggerBox fg bg1 bg2 l = do
  +
log <- l
  +
let text = do
  +
logStr <- log
  +
return $ wrapTextBox fg bg1 bg2 logStr
  +
return text
   
   
Line 323: Line 407:
 
myKeys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
 
myKeys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
 
myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
 
myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
  +
--Xmonad bindings
[ ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf) --Launch a terminal
 
, ((mod1Mask, xK_F2), shellPrompt myXPConfig) --Launch Xmonad shell prompt
+
[((modMask .|. shiftMask, xK_q), io (exitWith ExitSuccess)) --Quit xmonad
, ((modMask, xK_F2), xmonadPrompt myXPConfig) --Launch Xmonad prompt
+
, ((modMask, xK_q), restart "xmonad" True) --Restart xmonad
, ((modMask, xK_g), goToSelected $ myGSConfig myColorizer) --Launch GridSelect
+
, ((mod1Mask, xK_F2), shellPrompt myXPConfig) --Launch Xmonad shell prompt
, ((modMask, xK_masculine), scratchPad) --Scratchpad
+
, ((modMask, xK_F2), xmonadPrompt myXPConfig) --Launch Xmonad prompt
, ((modMask, xK_o), spawn "gksu halt") --Power off
+
, ((mod1Mask, xK_F3), manPrompt myXPConfig) --Launch man prompt
, ((modMask .|. shiftMask, xK_o), spawn "gksu reboot") --Reboot
+
, ((modMask, xK_g), goToSelected $ myGSConfig myColorizer) --Launch GridSelect
, ((mod1Mask, xK_F3), spawn "chromium") --Launch chromium
+
, ((modMask, xK_masculine), scratchPad) --Scratchpad
, ((modMask, xK_c), kill) --Close focused window
+
, ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf) --Launch default terminal
  +
--Window management bindings
  +
, ((modMask, xK_c), kill) --Close focused window
 
, ((mod1Mask, xK_F4), kill)
 
, ((mod1Mask, xK_F4), kill)
, ((modMask, xK_space), sendMessage NextLayout) --Rotate through the available layout algorithms
+
, ((modMask, xK_n), refresh) --Resize viewed windows to the correct size
, ((modMask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf) --Reset the layouts on the current workspace to default
+
, ((modMask, xK_Tab), windows W.focusDown) --Move focus to the next window
, ((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_j), windows W.focusDown)
 
, ((modMask, xK_j), windows W.focusDown)
 
, ((mod1Mask, xK_Tab), windows W.focusDown)
 
, ((mod1Mask, xK_Tab), windows W.focusDown)
, ((modMask, xK_k), windows W.focusUp) --Move focus to the previous window
+
, ((modMask, xK_k), windows W.focusUp) --Move focus to the previous window
, ((modMask, xK_a), windows W.focusMaster) --Move focus to the master window
+
, ((modMask, xK_a), windows W.focusMaster) --Move focus to the master window
, ((modMask .|. shiftMask, xK_a), windows W.swapMaster) --Swap the focused window and the master window
+
, ((modMask .|. shiftMask, xK_a), windows W.swapMaster) --Swap the focused window and the master window
, ((modMask .|. shiftMask, xK_j), windows W.swapDown ) --Swap the focused window with the next window
+
, ((modMask .|. shiftMask, xK_j), windows W.swapDown) --Swap the focused window with the next window
, ((modMask .|. shiftMask, xK_k), windows W.swapUp ) --Swap the focused window with the previous window
+
, ((modMask .|. shiftMask, xK_k), windows W.swapUp) --Swap the focused window with the previous window
, ((modMask, xK_h), sendMessage Shrink) --Shrink the master area
+
, ((modMask, xK_h), sendMessage Shrink) --Shrink the master area
 
, ((modMask .|. shiftMask, xK_Left), sendMessage Shrink)
 
, ((modMask .|. shiftMask, xK_Left), sendMessage Shrink)
, ((modMask, xK_l), sendMessage Expand) --Expand the master area
+
, ((modMask, xK_l), sendMessage Expand) --Expand the master area
 
, ((modMask .|. shiftMask, xK_Right), sendMessage Expand)
 
, ((modMask .|. shiftMask, xK_Right), sendMessage Expand)
, ((modMask .|. shiftMask, xK_h), sendMessage MirrorShrink) --MirrorShrink the master area
+
, ((modMask .|. shiftMask, xK_h), sendMessage MirrorShrink) --MirrorShrink the master area
 
, ((modMask .|. shiftMask, xK_Down), sendMessage MirrorShrink)
 
, ((modMask .|. shiftMask, xK_Down), sendMessage MirrorShrink)
, ((modMask .|. shiftMask, xK_l), sendMessage MirrorExpand) --MirrorExpand the master area
+
, ((modMask .|. shiftMask, xK_l), sendMessage MirrorExpand) --MirrorExpand the master area
 
, ((modMask .|. shiftMask, xK_Up), sendMessage MirrorExpand)
 
, ((modMask .|. shiftMask, xK_Up), sendMessage MirrorExpand)
, ((modMask .|. controlMask, xK_Left), withFocused (keysResizeWindow (-30,0) (0,0))) --Shrink floated window horizontally by 50 pixels
+
, ((modMask, xK_t), withFocused $ windows . W.sink) --Push window back into tiling
  +
, ((modMask .|. shiftMask, xK_t), rectFloatFocused) --Push window into float
, ((modMask .|. controlMask, xK_Right), withFocused (keysResizeWindow (30,0) (0,0))) --Expand floated window horizontally by 50 pixels
 
, ((modMask .|. controlMask, xK_Up), withFocused (keysResizeWindow (0,-30) (0,0))) --Shrink floated window verticaly by 50 pixels
+
, ((modMask, xK_m), withFocused minimizeWindow) --Minimize window
, ((modMask .|. controlMask, xK_Down), withFocused (keysResizeWindow (0,30) (0,0))) --Expand floated window verticaly by 50 pixels
+
, ((modMask, xK_b), withFocused (sendMessage . maximizeRestore)) --Maximize window
, ((modMask, xK_t), withFocused $ windows . W.sink) --Push window back into tiling
+
, ((modMask .|. shiftMask, xK_m), sendMessage RestoreNextMinimizedWin) --Restore window
, ((modMask .|. shiftMask, xK_t), rectFloatFocused) --Push window into float
+
, ((modMask .|. shiftMask, xK_f), fullFloatFocused) --Push window into full screen
, ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle TABBED) --Push layout into tabbed
+
, ((modMask, xK_comma), sendMessage (IncMasterN 1)) --Increment the number of windows in the master area
, ((modMask .|. shiftMask, xK_z), sendMessage $ Toggle MIRROR) --Push layout into mirror
+
, ((modMask, xK_period), sendMessage (IncMasterN (-1))) --Deincrement the number of windows in the master area
, ((modMask .|. shiftMask, xK_x), sendMessage $ XMonad.Layout.MultiToggle.Toggle REFLECTX) --Reflect layout by X
+
, ((modMask, xK_Right), sendMessage $ Go R) --Change focus to right
, ((modMask .|. shiftMask, xK_y), sendMessage $ XMonad.Layout.MultiToggle.Toggle REFLECTY) --Reflect layout by Y
+
, ((modMask, xK_Left ), sendMessage $ Go L) --Change focus to left
, ((modMask, xK_m), withFocused minimizeWindow) --Minimize window
+
, ((modMask, xK_Up ), sendMessage $ Go U) --Change focus to up
, ((modMask .|. shiftMask, xK_m), sendMessage RestoreNextMinimizedWin) --Restore window
+
, ((modMask, xK_Down ), sendMessage $ Go D) --Change focus to down
, ((modMask .|. shiftMask, xK_f), fullFloatFocused) --Push window into full screen
+
, ((modMask .|. controlMask, xK_Right), sendMessage $ Swap R) --Swap focused window to right
, ((modMask, xK_comma), sendMessage (IncMasterN 1)) --Increment the number of windows in the master area
+
, ((modMask .|. controlMask, xK_Left ), sendMessage $ Swap L) --Swap focused window to left
, ((modMask, xK_period), sendMessage (IncMasterN (-1))) --Deincrement the number of windows in the master area
+
, ((modMask .|. controlMask, xK_Up ), sendMessage $ Swap U) --Swap focused window to up
, ((modMask , xK_d), spawn "killall dzen2") --Kill dzen2 and trayer
+
, ((modMask .|. controlMask, xK_Down ), sendMessage $ Swap D) --Swap focused window to down
  +
--Layout management bindings
, ((modMask , xK_s), spawn "xscreensaver-command -lock") --Lock screen
 
, ((modMask .|. shiftMask, xK_q), io (exitWith ExitSuccess)) --Quit xmonad
+
, ((modMask, xK_space), sendMessage NextLayout) --Rotate through the available layout algorithms
, ((modMask, xK_q), restart "xmonad" True) --Restart xmonad
+
, ((modMask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf) --Reset the layout on the current workspace to default
, ((modMask, xK_comma), toggleWS) --Toggle to the workspace displayed previously
+
, ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle TABBED) --Push layout into tabbed
  +
, ((modMask .|. controlMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle FLOATED) --Push layout into float
, ((mod1Mask, xK_masculine), toggleOrView (myWorkspaces !! 0)) --if ws != 0 then move to workspace 0, else move to latest ws I was
 
, ((mod1Mask .|. controlMask, xK_Left), prevWS) --Move to previous Workspace
+
, ((modMask .|. shiftMask, xK_z), sendMessage $ Toggle MIRROR) --Push layout into mirror
  +
, ((modMask .|. shiftMask, xK_x), sendMessage $ XMonad.Layout.MultiToggle.Toggle REFLECTX) --Reflect layout by X
, ((modMask, xK_Left), prevWS)
 
  +
, ((modMask .|. shiftMask, xK_y), sendMessage $ XMonad.Layout.MultiToggle.Toggle REFLECTY) --Reflect layout by Y
, ((modMask, xK_Right), nextWS) --Move to next Workspace
 
  +
--Gaps management bindings
, ((mod1Mask .|. controlMask, xK_Right), nextWS)
 
, ((0, xF86XK_AudioMute), spawn "sh /home/nnoell/bin/voldzen.sh t -d") --Mute/unmute volume
+
, ((modMask .|. controlMask, xK_t), sendMessage $ ToggleGaps) --toogle all gaps
  +
, ((modMask .|. controlMask, xK_u), sendMessage $ ToggleGap U) --toogle the top gap
, ((0, xF86XK_AudioRaiseVolume), spawn "sh /home/nnoell/bin/voldzen.sh + -d") --Raise volume
 
  +
, ((modMask .|. controlMask, xK_d), sendMessage $ ToggleGap D) --toogle the bottom gap
, ((0, xF86XK_AudioLowerVolume), spawn "sh /home/nnoell/bin/voldzen.sh - -d") --Lower volume
 
  +
--Scripts management bindings
, ((0, xF86XK_AudioNext), spawn "ncmpcpp next") --next song
 
  +
, ((modMask , xK_x), spawn "/usr/bin/xcalib -invert -alter") --Invert colors in X
, ((0, xF86XK_AudioPrev), spawn "ncmpcpp prev") --prev song
 
, ((0, xF86XK_AudioPlay), spawn "ncmpcpp toggle") --toggle song
+
, ((modMask , xK_d), spawn "/usr/bin/killall dzen2") --Kill dzen2
, ((0, xF86XK_AudioStop), spawn "ncmpcpp stop") --stop song
+
, ((0, xF86XK_AudioMute), spawn $ myBinPath ++ "voldzen.sh t -d") --Mute/unmute volume
, ((0, xF86XK_MonBrightnessUp), spawn "sh /home/nnoell/bin/bridzen.sh") --Raise brightness
+
, ((0, xF86XK_AudioRaiseVolume), spawn $ myBinPath ++ "voldzen.sh + -d") --Raise volume
  +
, ((mod1Mask, xK_Up), spawn $ myBinPath ++ "voldzen.sh + -d")
, ((0, xF86XK_MonBrightnessDown), spawn "sh /home/nnoell/bin/bridzen.sh") --Lower brightness
 
, ((0, xF86XK_ScreenSaver), spawn "xscreensaver-command -lock") --Lock screen
+
, ((0, xF86XK_AudioLowerVolume), spawn $ myBinPath ++ "voldzen.sh - -d") --Lower volume
  +
, ((mod1Mask, xK_Down), spawn $ myBinPath ++ "voldzen.sh - -d")
, ((0, xK_Print), spawn "scrot '%Y-%m-%d_$wx$h.png'") --Take a screenshot
 
  +
, ((0, xF86XK_AudioNext), spawn "/usr/bin/ncmpcpp next") --Next song
  +
, ((mod1Mask, xK_Right), spawn "/usr/bin/ncmpcpp next")
  +
, ((0, xF86XK_AudioPrev), spawn "/usr/bin/ncmpcpp prev") --Prev song
  +
, ((mod1Mask, xK_Left), spawn "/usr/bin/ncmpcpp prev")
  +
, ((0, xF86XK_AudioPlay), spawn "/usr/bin/ncmpcpp toggle") --Toggle song
  +
, ((mod1Mask .|. controlMask, xK_Down), spawn "/usr/bin/ncmpcpp toggle")
  +
, ((0, xF86XK_AudioStop), spawn "/usr/bin/ncmpcpp stop") --Stop song
  +
, ((mod1Mask .|. controlMask, xK_Up), spawn "ncmpcpp stop")
  +
, ((0, xF86XK_MonBrightnessUp), spawn $ myBinPath ++ "bridzen.sh") --Raise brightness
  +
, ((0, xF86XK_MonBrightnessDown), spawn $ myBinPath ++ "bridzen.sh") --Lower brightness
  +
, ((0, xF86XK_ScreenSaver), spawn $ myBinPath ++ "turnoffscreen.sh") --Lock screen
  +
, ((0, xK_Print), spawn "/usr/bin/scrot '%Y-%m-%d_$wx$h.png'") --Take a screenshot
  +
, ((modMask , xK_s), spawn $ myBinPath ++ "turnoffscreen.sh") --Turn off screen
  +
--Workspaces management bindings
  +
, ((mod1Mask, xK_comma), toggleWS) --Toggle to the workspace displayed previously
  +
, ((mod1Mask, xK_masculine), toggleOrView (myWorkspaces !! 0)) --If ws != 0 then move to workspace 0, else move to latest ws I was
  +
, ((mod1Mask .|. controlMask, xK_Left), prevWS) --Move to previous Workspace
  +
, ((mod1Mask .|. controlMask, xK_Right), nextWS) --Move to next Workspace
  +
, ((modMask .|. shiftMask, xK_n), shiftToNext) --Send client to next workspace
  +
, ((modMask .|. shiftMask, xK_p), shiftToPrev) --Send client to previous workspace
 
]
 
]
 
++
 
++
[((m .|. modMask, k), windows $ f i) --Switch to n workspaces and send client to n workspaces
+
[((m .|. modMask, k), windows $ f i) --Switch to n workspaces and send client to n workspaces
| (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
+
| (i, k) <- zip (XMonad.workspaces conf) ([xK_1 .. xK_9] ++ [xK_0])
 
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
 
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
 
++
 
++
[((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f)) --Switch to n screens and send client to n screens
+
[((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f)) --Switch to n screens and send client to n screens
 
| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
 
| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
 
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
 
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
Line 404: Line 508:
 
myMouseBindings :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ())
 
myMouseBindings :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ())
 
myMouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
 
myMouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w >> windows W.shiftMaster)) -- set the window to floating mode and move by dragging
+
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w >> windows W.shiftMaster)) --Set the window to floating mode and move by dragging
, ((modMask, button2), (\w -> focus w >> windows W.shiftMaster)) -- raise the window to the top of the stack
+
, ((modMask, button2), (\w -> focus w >> windows W.shiftMaster)) --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, 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, button4), (\_ -> prevWS)) --Switch to previous workspace
, ((modMask, button5), (\_ -> nextWS)) -- switch to next workspace
+
, ((modMask, button5), (\_ -> nextWS)) --Switch to next workspace
  +
, (((modMask .|. shiftMask), button4), (\_ -> shiftToPrev)) --Send client to previous workspace
  +
, (((modMask .|. shiftMask), button5), (\_ -> shiftToNext)) --Send client to next workspace
 
]
 
]
 
</haskell>
 
</haskell>

Revision as of 19:45, 9 March 2013

xmonad.hs

--------------------------------------------------------------------------------------------
-- ~/.xmonad/xmonad.hs                                                                    --
-- Author: Nnoell <nnoell3[at]gmail.com>                                                  --
--------------------------------------------------------------------------------------------

-- Language
{-# LANGUAGE DeriveDataTypeable, NoMonomorphismRestriction, TypeSynonymInstances, MultiParamTypeClasses,  ImplicitParams, PatternGuards #-}

-- Imported libraries
import XMonad
import XMonad.Core
import XMonad.Layout
import XMonad.Layout.IM
import XMonad.Layout.Gaps
import XMonad.Layout.Named
import XMonad.Layout.Tabbed
import XMonad.Layout.OneBig
import XMonad.Layout.Master
import XMonad.Layout.Reflect
import XMonad.Layout.MosaicAlt
import XMonad.Layout.NoFrillsDecoration
import XMonad.Layout.SimplestFloat
import XMonad.Layout.NoBorders (noBorders,smartBorders,withBorder)
import XMonad.Layout.ResizableTile
import XMonad.Layout.MultiToggle
import XMonad.Layout.MultiToggle.Instances
import XMonad.Layout.PerWorkspace (onWorkspace)
import XMonad.Layout.Minimize
import XMonad.Layout.Maximize
import XMonad.Layout.WindowNavigation
import XMonad.StackSet (RationalRect (..), currentTag)
import XMonad.Util.Loggers
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.DynamicHooks
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.UrgencyHook
import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.SetWMName
import XMonad.Hooks.ManageHelpers
import XMonad.Prompt
import XMonad.Prompt.Shell
import XMonad.Prompt.XMonad
import XMonad.Prompt.Man
import XMonad.Util.Timer
import XMonad.Util.Cursor
import XMonad.Util.EZConfig
import XMonad.Util.Run (spawnPipe)
import XMonad.Util.Scratchpad
import XMonad.Util.NamedScratchpad
import XMonad.Actions.CycleWS
import XMonad.Actions.GridSelect
import XMonad.Actions.MouseResize
import Data.IORef
import Data.Monoid
import Data.List
import Graphics.X11.ExtraTypes.XF86
import System.Exit
import System.IO (Handle, hPutStrLn)
import System.IO
import qualified XMonad.StackSet as W
import qualified Data.Map as M
import qualified XMonad.Actions.FlexibleResize as Flex
import qualified XMonad.Util.ExtensibleState as XS


-- Main
main :: IO ()
main = do
	topLeftBar              <- spawnPipe myTopLeftBar
	topRightBar             <- spawnPipe myTopRightBar
	workspaceBar            <- spawnPipe myWorkspaceBar
	bottomBar               <- spawnPipe $ myBinPath ++ "bottomBar.sh"
	focusFollow             <- newIORef True; let ?focusFollow = focusFollow
	xmonad $ myUrgencyHook $ defaultConfig
		{ terminal           = "urxvtc"
		, modMask            = mod4Mask
		, focusFollowsMouse  = False
		, borderWidth        = 1
		, normalBorderColor  = myNormalBorderColor
		, focusedBorderColor = myFocusedBorderColor
		, layoutHook         = myLayoutHook
		, workspaces         = myWorkspaces
		, manageHook         = myManageHook <+> manageScratchPad <+> manageDocks <+> dynamicMasterHook
		, logHook            = myLogHook workspaceBar <+> myLogHook2 topLeftBar <+> myLogHook3 topRightBar <+> ewmhDesktopsLogHook >> setWMName "LG3D"
		, handleEventHook    = myHandleEventHook
		, keys               = myKeys
		, mouseBindings      = myMouseBindings
		, startupHook        = (startTimer 1 >>= XS.put . TID) <+> setDefaultCursor xC_left_ptr >> setWMName "LG3D"
		}
		`additionalKeysP`
		[ ("<XF86TouchpadToggle>", spawn $ myBinPath ++ "touchpadtoggle.sh") --because xF86XK_TouchpadToggle doesnt exist
		, ("M-v", io $ modifyIORef ?focusFollow not)                         --Toggle focus follow moouse
		]


--------------------------------------------------------------------------------------------
-- APPEARANCE CONFIG                                                                      --
--------------------------------------------------------------------------------------------

-- Colors, fonts and paths
dzenFont             = "-*-montecarlo-medium-r-normal-*-11-*-*-*-*-*-*-*"
colorBlack           = "#020202" --Background (Dzen_BG)
colorBlackAlt        = "#1c1c1c" --Black Xdefaults
colorGray            = "#444444" --Gray       (Dzen_FG2)
colorGrayAlt         = "#101010" --Gray dark
colorWhite           = "#a9a6af" --Foreground (Shell_FG)
colorWhiteAlt        = "#9d9d9d" --White dark (Dzen_FG)
colorMagenta         = "#8e82a2"
colorBlue            = "#44aacc"
colorBlueAlt         = "#3955c4"
colorRed             = "#e0105f"
colorGreen           = "#66ff66"
colorGreenAlt        = "#558965"
myNormalBorderColor  = colorBlackAlt
myFocusedBorderColor = colorGray
myIconPath           = "/home/nnoell/.icons/xbm_icons/subtle/"
myBinPath            = "/home/nnoell/bin/"
xRes                 = 1366
yRes                 = 768
panelHeight          = 16
panelBoxHeight       = 12

-- Title theme
myTitleTheme :: Theme
myTitleTheme = defaultTheme
	{ fontName            = dzenFont
	, inactiveBorderColor = colorBlackAlt
	, inactiveColor       = colorBlack
	, inactiveTextColor   = colorGray
	, activeBorderColor   = colorGray
	, activeColor         = colorBlackAlt
	, activeTextColor     = colorWhiteAlt
	, urgentBorderColor   = colorGray
	, urgentTextColor     = colorGreen
	, decoHeight          = 14
	}

-- Prompt theme
myXPConfig :: XPConfig
myXPConfig = defaultXPConfig
	{ font                = dzenFont
	, bgColor             = colorBlack
	, fgColor             = colorWhite
	, bgHLight            = colorBlue
	, fgHLight            = colorBlack
	, borderColor         = colorGrayAlt
	, promptBorderWidth   = 1
	, height              = 16
	, position            = Top
	, historySize         = 100
	, historyFilter       = deleteConsecutive
	, autoComplete        = Nothing
	}

-- GridSelect color scheme
myColorizer :: Window -> Bool -> X (String, String)
myColorizer = colorRangeFromClassName
	(0x00,0x00,0x00) -- lowest inactive bg
	(0x1C,0x1C,0x1C) -- highest inactive bg
	(0x44,0xAA,0xCC) -- active bg
	(0xBB,0xBB,0xBB) -- inactive fg
	(0x00,0x00,0x00) -- active fg

-- GridSelect theme
myGSConfig :: t -> GSConfig Window
myGSConfig colorizer = (buildDefaultGSConfig myColorizer)
	{ gs_cellheight  = 50
	, gs_cellwidth   = 200
	, gs_cellpadding = 10
	, gs_font        = dzenFont
	}

-- Workspaces
myWorkspaces :: [WorkspaceId]
myWorkspaces = ["1", "2", "3", "4", "5", "6", "7", "8", "9", "0"]


--------------------------------------------------------------------------------------------
-- LAYOUT CONFIG                                                                          --
--------------------------------------------------------------------------------------------

-- Layouts (name must be diferent of Minimize, Maximize and Mirror)
myTile = named "ResizableTall"     $ smartBorders $ ResizableTall 1 0.03 0.5 []
myMirr = named "MirrResizableTall" $ smartBorders $ Mirror myTile
myMosA = named "MosaicAlt"         $ smartBorders $ MosaicAlt M.empty
myObig = named "OneBig"            $ smartBorders $ OneBig 0.75 0.65
myTabs = named "Simple Tabbed"     $ smartBorders $ tabbed shrinkText myTitleTheme
myFull = named "Full Tabbed"       $ smartBorders $ tabbedAlways shrinkText myTitleTheme
myTabM = named "Master Tabbed"     $ smartBorders $ mastered 0.01 0.4 $ tabbed shrinkText myTitleTheme
myFlat = named "Simple Float"      $ mouseResize  $ noFrillsDeco shrinkText myTitleTheme simplestFloat
myGimp = named "Gimp MosaicAlt"    $ withIM (0.15) (Role "gimp-toolbox") $ reflectHoriz $ withIM (0.20) (Role "gimp-dock") myMosA
myChat = named "Pidgin MosaicAlt"  $ withIM (0.20) (Title "Buddy List") $ Mirror $ ResizableTall 1 0.03 0.5 []

-- Tabbed transformer (W+f)
data TABBED = TABBED deriving (Read, Show, Eq, Typeable)
instance Transformer TABBED Window where
	transform TABBED x k = k myFull (\_ -> x)

-- Floated transformer (W+ctl+f)
data FLOATED = FLOATED deriving (Read, Show, Eq, Typeable)
instance Transformer FLOATED Window where
	transform FLOATED x k = k myFlat (\_ -> x)

-- Layout hook
myLayoutHook = gaps [(U,16), (D,16), (L,0), (R,0)]
	$ avoidStruts
	$ windowNavigation
	$ minimize
	$ maximize
	$ mkToggle (single TABBED)
	$ mkToggle (single FLOATED)
	$ mkToggle (single MIRROR)
	$ mkToggle (single REFLECTX)
	$ mkToggle (single REFLECTY)
	$ onWorkspace (myWorkspaces !! 1) webLayouts  --Workspace 1 layouts
	$ onWorkspace (myWorkspaces !! 2) codeLayouts --Workspace 2 layouts
	$ onWorkspace (myWorkspaces !! 3) gimpLayouts --Workspace 3 layouts
	$ onWorkspace (myWorkspaces !! 4) chatLayouts --Workspace 4 layouts
	$ allLayouts
	where
		allLayouts  = myTile ||| myObig ||| myMirr ||| myMosA ||| myTabM
		webLayouts  = myTabs ||| myMirr ||| myTabM
		codeLayouts = myTabM ||| myTile
		gimpLayouts = myGimp
		chatLayouts = myChat


--------------------------------------------------------------------------------------------
-- HANDLE EVENT HOOK CONFIG                                                               --
--------------------------------------------------------------------------------------------

-- wrapper for the Timer id, so it can be stored as custom mutable state
data TidState = TID TimerId deriving Typeable

instance ExtensionClass TidState where
  initialValue = TID 0

-- Handle event hook
myHandleEventHook :: (?focusFollow::IORef Bool) => Event -> X All
myHandleEventHook = fullscreenEventHook <+> docksEventHook <+> toggleFocus <+> clockEventHook
	where
		toggleFocus e = case e of --thanks to Vgot
			CrossingEvent {ev_window=w, ev_event_type=t}
				| t == enterNotify, ev_mode e == notifyNormal -> do
					whenX (io $ readIORef ?focusFollow) (focus w)
					return $ All True
			_ -> return $ All True
		clockEventHook e = do                   --thanks to DarthFennec
			(TID t) <- XS.get                   --get the recent Timer id
			handleTimer t e $ do                --run the following if e matches the id
			    startTimer 1 >>= XS.put . TID   --restart the timer, store the new id
			    ask >>= logHook.config          --get the loghook and run it
			    return Nothing                  --return required type
			return $ All True                   --return required type


--------------------------------------------------------------------------------------------
-- MANAGE HOOK CONFIG                                                                     --
--------------------------------------------------------------------------------------------

-- Scratchpad (W+º)
manageScratchPad :: ManageHook
manageScratchPad = scratchpadManageHook (W.RationalRect (0) (1/50) (1) (3/4))
scratchPad = scratchpadSpawnActionCustom "urxvtc -name scratchpad"

-- Manage hook
myManageHook :: ManageHook
myManageHook = composeAll . concat $
	[ [resource     =? r     --> doIgnore                             | r <- myIgnores] --ignore desktop
	, [className    =? c     --> doShift (myWorkspaces !! 1)          | c <- myWebS   ] --move myWebS windows to workspace 1 by classname
	, [className    =? c     --> doShift (myWorkspaces !! 2)          | c <- myCodeS  ] --move myCodeS windows to workspace 2 by classname
	, [className    =? c     --> doShift (myWorkspaces !! 4)          | c <- myChatS  ] --move myChatS windows to workspace 4 by classname
	, [className    =? c     --> doShift (myWorkspaces !! 3)          | c <- myGfxS   ] --move myGfxS windows to workspace 4 by classname
	, [className    =? c     --> doShiftAndGo (myWorkspaces !! 5)     | c <- myAlt1S  ] --move myGameS windows to workspace 5 by classname and shift
	, [className    =? c     --> doShift (myWorkspaces !! 7)          | c <- myAlt3S  ] --move myOtherS windows to workspace 5 by classname and shift
	, [className    =? c     --> doCenterFloat                        | c <- myFloatCC] --float center geometry by classname
	, [name         =? n     --> doCenterFloat                        | n <- myFloatCN] --float center geometry by name
	, [name         =? n     --> doSideFloat NW                       | n <- myFloatSN] --float side NW geometry by name
	, [className    =? c     --> doF W.focusDown                      | c <- myFocusDC] --dont focus on launching by classname
	, [isFullscreen          --> doFullFloat]
	]
	where
		doShiftAndGo ws = doF (W.greedyView ws) <+> doShift ws
		role            = stringProperty "WM_WINDOW_ROLE"
		name            = stringProperty "WM_NAME"
		myIgnores       = ["desktop","desktop_window"]
		myWebS          = ["Chromium","Firefox", "Opera"]
		myCodeS         = ["NetBeans IDE 7.2"]
		myGfxS          = ["Gimp", "gimp", "GIMP"]
		myChatS         = ["Pidgin", "Xchat"]
		myAlt1S         = ["zsnes"]
		myAlt3S         = ["Amule", "Transmission-gtk"]
		myFloatCC       = ["MPlayer", "File-roller", "zsnes", "Gcalctool", "Exo-helper-1", "Gksu", "PSX", "Galculator", "Nvidia-settings", "XFontSel"
						  , "XCalc", "XClock", "Desmume", "Ossxmix", "Xvidcap", "Main", "Wicd-client.py", "com-mathworks-util-PostVMInit", "MATLAB"]
		myFloatCN       = ["ePSXe - Enhanced PSX emulator", "Seleccione Archivo", "Config Video", "Testing plugin", "Config Sound", "Config Cdrom", "Config Bios"
						  , "Config Netplay", "Config Memcards", "About ePSXe", "Config Controller", "Config Gamepads", "Select one or more files to open"
						  , "Add media", "Choose a file", "Open Image", "File Operation Progress", "Firefox Preferences", "Preferences", "Search Engines"
						  , "Set up sync", "Passwords and Exceptions", "Autofill Options", "Rename File", "Copying files", "Moving files", "File Properties", "Replace", ""]
		myFloatSN       = ["Event Tester"]
		myFocusDC       = ["Event Tester", "Notify-osd"]


--------------------------------------------------------------------------------------------
-- STATUS BARS CONFIG                                                                     --
--------------------------------------------------------------------------------------------

-- UrgencyHook
myUrgencyHook = withUrgencyHook dzenUrgencyHook
	{ args = ["-fn", dzenFont, "-bg", colorBlack, "-fg", colorGreen, "-h", show panelHeight] }

-- WorkspaceBar
myWorkspaceBar = "dzen2 -x 0 -y 752 -h 16 -w 380 -ta 'l' -fg '" ++ colorWhiteAlt ++ "' -bg '" ++ colorBlack ++ "' -fn '" ++ dzenFont ++ "' -p -e 'onstart=lower'"
myLogHook :: Handle -> X ()
myLogHook h = dynamicLogWithPP $ defaultPP
	{ ppOutput          = hPutStrLn h
	, ppSort            = fmap (namedScratchpadFilterOutWorkspace .) (ppSort defaultPP) --hide "NSP" from workspace list
	, ppOrder           = \(ws:l:_:x) -> [ws,l]
	, ppSep             = " "
	, ppWsSep           = ""
	, ppCurrent         = wrapTextBox colorBlack    colorBlue    colorBlack
	, ppUrgent          = wrapTextBox colorBlack    colorGreen   colorBlack . wrapClickWorkspace
	, ppVisible         = wrapTextBox colorBlack    colorGrayAlt colorBlack . wrapClickWorkspace
	, ppHiddenNoWindows = wrapTextBox colorBlack    colorGrayAlt colorBlack . wrapClickWorkspace
	, ppHidden          = wrapTextBox colorWhiteAlt colorGrayAlt colorBlack . wrapClickWorkspace
	, ppLayout          = \l -> (wrapClickLayout (wrapTextBox colorBlue colorGrayAlt colorBlack "LAYOUT")) ++ (wrapTextBox colorGray colorGrayAlt colorBlack $ layoutText $ removeWord $ removeWord l)
	}
	where
		removeWord = tail . dropWhile (/= ' ')
		layoutText xs
			| isPrefixOf "Mirror" xs   = layoutText $ removeWord xs ++ " [M]"
			| isPrefixOf "ReflectY" xs = layoutText $ removeWord xs ++ " [Y]"
			| isPrefixOf "ReflectX" xs = layoutText $ removeWord xs ++ " [X]"
			| isPrefixOf "Float" xs    = "^fg(" ++ colorRed ++ ")" ++ xs
			| isPrefixOf "Full" xs     = "^fg(" ++ colorGreen ++ ")" ++ xs
			| otherwise                = "^fg(" ++ colorWhiteAlt ++ ")" ++ xs

-- TopLeftBar
myTopLeftBar = "dzen2 -x 0 -y 0 -h 16 -w 1050 -ta 'l' -fg '" ++ colorWhiteAlt ++ "' -bg '" ++ colorBlack ++ "' -fn '" ++ dzenFont ++ "' -p -e 'onstart=lower'"
myLogHook2 :: Handle -> X ()
myLogHook2 h = dynamicLogWithPP $ defaultPP
	{ ppOutput          = hPutStrLn h
	, ppOrder           = \(_:_:_:x) -> x
	, ppSep             = " "
	, ppExtras          = [ wrapL (wrapClickGrid $ wrapTextBox colorBlue  colorGrayAlt  colorBlack "WORKSPACE") "" $ wrapLoggerBox colorWhiteAlt colorGrayAlt colorBlack $ onLogger namedWorkspaces logCurrent
						  , wrapL (wrapClickTitle $ wrapTextBox colorBlack colorWhiteAlt colorBlack "FOCUS") "" $ wrapLoggerBox colorWhiteAlt colorGrayAlt colorBlack $ shortenL 144 logTitle
						  ]
	}
	where
		namedWorkspaces w
			| w == "1"  = "^fg(" ++ colorGreen ++ ")1^fg(" ++ colorGray ++ ")|^fg()Terminal"
			| w == "2"  = "^fg(" ++ colorGreen ++ ")2^fg(" ++ colorGray ++ ")|^fg()Network"
			| w == "3"  = "^fg(" ++ colorGreen ++ ")3^fg(" ++ colorGray ++ ")|^fg()Development"
			| w == "4"  = "^fg(" ++ colorGreen ++ ")4^fg(" ++ colorGray ++ ")|^fg()Graphics"
			| w == "5"  = "^fg(" ++ colorGreen ++ ")5^fg(" ++ colorGray ++ ")|^fg()Chatting"
			| w == "6"  = "^fg(" ++ colorGreen ++ ")6^fg(" ++ colorGray ++ ")|^fg()Alternative"
			| w == "7"  = "^fg(" ++ colorGreen ++ ")7^fg(" ++ colorGray ++ ")|^fg()Alternative"
			| w == "8"  = "^fg(" ++ colorGreen ++ ")8^fg(" ++ colorGray ++ ")|^fg()Alternative"
			| w == "9"  = "^fg(" ++ colorGreen ++ ")9^fg(" ++ colorGray ++ ")|^fg()Alternative"
			| w == "0"  = "^fg(" ++ colorGreen ++ ")0^fg(" ++ colorGray ++ ")|^fg()Alternative"
			| otherwise = "^fg(" ++ colorRed   ++ ")x^fg(" ++ colorGray ++ ")|^fg()" ++ w

-- TopRightBar
myTopRightBar = "dzen2 -x 1050 -y 0 -h 16 -w 366 -ta 'r' -fg '" ++ colorWhiteAlt ++ "' -bg '" ++ colorBlack ++ "' -fn '" ++ dzenFont ++ "' -p -e 'onstart=lower'"
myLogHook3 :: Handle -> X ()
myLogHook3 h = dynamicLogWithPP $ defaultPP
	{ ppOutput          = hPutStrLn h
    , ppOrder           = \(_:_:_:x) -> x
	, ppSep             = " "
	, ppExtras          = [ date $ (wrapTextBox colorBlack colorWhiteAlt colorBlack "%A") ++ (wrapTextBox colorWhiteAlt colorGrayAlt colorBlack $ "%Y^fg(" ++ colorGray ++ ").^fg()%m^fg(" ++ colorGray ++ ").^fg()^fg(" ++ colorBlue ++ ")%d^fg() ^fg(" ++ colorGray ++ ")-^fg() %H^fg(" ++ colorGray ++"):^fg()%M^fg(" ++ colorGray ++ "):^fg()^fg(" ++ colorGreen ++ ")%S^fg()")
                          , return $ return $ wrapClickCalendar $ wrapTextBox colorBlue colorGrayAlt colorBlack "CALENDAR"
						  ]
	}

-- Wrap Clickable Area
wrapClickGrid x = "^ca(1,/usr/bin/xdotool key super+g)" ++ x ++ "^ca()"
wrapClickCalendar x = "^ca(1," ++ myBinPath ++ "dzencal.sh)" ++ x ++ "^ca()"
wrapClickLayout x = "^ca(1,/usr/bin/xdotool key super+space)^ca(3,/usr/bin/xdotool key super+shift+space)" ++ x ++ "^ca()^ca()"
wrapClickTitle x = "^ca(1,/usr/bin/xdotool key super+m)^ca(2,/usr/bin/xdotool key super+c)^ca(3,/usr/bin/xdotool key super+shift+m)" ++ x ++ "^ca()^ca()^ca()"
wrapClickWorkspace ws = "^ca(1," ++ xdo "w;" ++ xdo index ++ ")" ++ "^ca(3," ++ xdo "w;" ++ xdo index ++ ")" ++ ws ++ "^ca()^ca()"
	where
		wsIdxToString Nothing = "1"
		wsIdxToString (Just n) = show $ mod (n+1) $ length myWorkspaces
		index = wsIdxToString (elemIndex ws myWorkspaces)
		xdo key = "/usr/bin/xdotool key super+" ++ key

-- Wrap Box
wrapTextBox :: String -> String -> String -> String -> String
wrapTextBox fg bg1 bg2 t = "^fg(" ++ bg1 ++ ")^i(" ++ myIconPath  ++ "boxleft.xbm)^ib(1)^r(" ++ show xRes ++ "x" ++ show panelBoxHeight ++ ")^p(-" ++ show xRes ++ ")^fg(" ++ fg ++ ")" ++ t ++ "^fg(" ++ bg1 ++ ")^i(" ++ myIconPath ++ "boxright.xbm)^fg(" ++ bg2 ++ ")^r(" ++ show xRes ++ "x" ++ show panelBoxHeight ++ ")^p(-" ++ show xRes ++ ")^fg()^ib(0)"

wrapLoggerBox :: String -> String -> String -> Logger -> Logger
wrapLoggerBox fg bg1 bg2 l = do
	log <- l
	let text = do
		logStr <- log
		return $ wrapTextBox fg bg1 bg2 logStr
	return text


--------------------------------------------------------------------------------------------
-- BINDINGS CONFIG                                                                        --
--------------------------------------------------------------------------------------------

-- Key bindings
myKeys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
	--Xmonad bindings
	[((modMask .|. shiftMask, xK_q), io (exitWith ExitSuccess))                                 --Quit xmonad
	, ((modMask, xK_q), restart "xmonad" True)                                                  --Restart xmonad
	, ((mod1Mask, xK_F2), shellPrompt myXPConfig)                                               --Launch Xmonad shell prompt
	, ((modMask, xK_F2), xmonadPrompt myXPConfig)                                               --Launch Xmonad prompt
	, ((mod1Mask, xK_F3), manPrompt myXPConfig)                                                 --Launch man prompt
	, ((modMask, xK_g), goToSelected $ myGSConfig myColorizer)                                  --Launch GridSelect
	, ((modMask, xK_masculine), scratchPad)                                                     --Scratchpad
	, ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)                        --Launch default terminal
	--Window management bindings
	, ((modMask, xK_c), kill)                                                                   --Close focused window
	, ((mod1Mask, xK_F4), kill)
	, ((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_j), windows W.focusDown)
	, ((mod1Mask, xK_Tab), windows W.focusDown)
	, ((modMask, xK_k), windows W.focusUp)                                                      --Move focus to the previous window
	, ((modMask, xK_a), windows W.focusMaster)                                                  --Move focus to the master window
	, ((modMask .|. shiftMask, xK_a), windows W.swapMaster)                                     --Swap the focused window and the master window
	, ((modMask .|. shiftMask, xK_j), windows W.swapDown)                                       --Swap the focused window with the next window
	, ((modMask .|. shiftMask, xK_k), windows W.swapUp)                                         --Swap the focused window with the previous window
	, ((modMask, xK_h), sendMessage Shrink)                                                     --Shrink the master area
	, ((modMask .|. shiftMask, xK_Left), sendMessage Shrink)
	, ((modMask, xK_l), sendMessage Expand)                                                     --Expand the master area
	, ((modMask .|. shiftMask, xK_Right), sendMessage Expand)
	, ((modMask .|. shiftMask, xK_h), sendMessage MirrorShrink)                                 --MirrorShrink the master area
	, ((modMask .|. shiftMask, xK_Down), sendMessage MirrorShrink)
	, ((modMask .|. shiftMask, xK_l), sendMessage MirrorExpand)                                 --MirrorExpand the master area
	, ((modMask .|. shiftMask, xK_Up), sendMessage MirrorExpand)
	, ((modMask, xK_t), withFocused $ windows . W.sink)                                         --Push window back into tiling
	, ((modMask .|. shiftMask, xK_t), rectFloatFocused)                                         --Push window into float
	, ((modMask, xK_m), withFocused minimizeWindow)                                             --Minimize window
	, ((modMask, xK_b), withFocused (sendMessage . maximizeRestore))                            --Maximize window
	, ((modMask .|. shiftMask, xK_m), sendMessage RestoreNextMinimizedWin)                      --Restore window
	, ((modMask .|. shiftMask, xK_f), fullFloatFocused)                                         --Push window into full screen
	, ((modMask, xK_comma), sendMessage (IncMasterN 1))                                         --Increment the number of windows in the master area
	, ((modMask, xK_period), sendMessage (IncMasterN (-1)))                                     --Deincrement the number of windows in the master area
	, ((modMask, xK_Right), sendMessage $ Go R)                                                 --Change focus to right
	, ((modMask, xK_Left ), sendMessage $ Go L)                                                 --Change focus to left
	, ((modMask, xK_Up   ), sendMessage $ Go U)                                                 --Change focus to up
	, ((modMask, xK_Down ), sendMessage $ Go D)                                                 --Change focus to down
	, ((modMask .|. controlMask, xK_Right), sendMessage $ Swap R)                               --Swap focused window to right
	, ((modMask .|. controlMask, xK_Left ), sendMessage $ Swap L)                               --Swap focused window to left
	, ((modMask .|. controlMask, xK_Up   ), sendMessage $ Swap U)                               --Swap focused window to up
	, ((modMask .|. controlMask, xK_Down ), sendMessage $ Swap D)                               --Swap focused window to down
	--Layout management bindings
	, ((modMask, xK_space), sendMessage NextLayout)                                             --Rotate through the available layout algorithms
	, ((modMask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf)                  --Reset the layout on the current workspace to default
	, ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle TABBED)                  --Push layout into tabbed
	, ((modMask .|. controlMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle FLOATED) --Push layout into float
	, ((modMask .|. shiftMask, xK_z), sendMessage $ Toggle MIRROR)                              --Push layout into mirror
	, ((modMask .|. shiftMask, xK_x), sendMessage $ XMonad.Layout.MultiToggle.Toggle REFLECTX)  --Reflect layout by X
	, ((modMask .|. shiftMask, xK_y), sendMessage $ XMonad.Layout.MultiToggle.Toggle REFLECTY)  --Reflect layout by Y
	--Gaps management bindings
	, ((modMask .|. controlMask, xK_t), sendMessage $ ToggleGaps)                               --toogle all gaps
	, ((modMask .|. controlMask, xK_u), sendMessage $ ToggleGap U)                              --toogle the top gap
	, ((modMask .|. controlMask, xK_d), sendMessage $ ToggleGap D)                              --toogle the bottom gap
	--Scripts management bindings
	, ((modMask , xK_x), spawn "/usr/bin/xcalib -invert -alter")								--Invert colors in X
	, ((modMask , xK_d), spawn "/usr/bin/killall dzen2")                                        --Kill dzen2
	, ((0, xF86XK_AudioMute), spawn $ myBinPath ++ "voldzen.sh t -d")                           --Mute/unmute volume
	, ((0, xF86XK_AudioRaiseVolume), spawn $ myBinPath ++ "voldzen.sh + -d")                    --Raise volume
	, ((mod1Mask, xK_Up), spawn $ myBinPath ++ "voldzen.sh + -d")
	, ((0, xF86XK_AudioLowerVolume), spawn $ myBinPath ++ "voldzen.sh - -d")                    --Lower volume
	, ((mod1Mask, xK_Down), spawn $ myBinPath ++ "voldzen.sh - -d")
	, ((0, xF86XK_AudioNext), spawn "/usr/bin/ncmpcpp next")                                    --Next song
	, ((mod1Mask, xK_Right), spawn "/usr/bin/ncmpcpp next")
	, ((0, xF86XK_AudioPrev), spawn "/usr/bin/ncmpcpp prev")                                    --Prev song
	, ((mod1Mask, xK_Left), spawn "/usr/bin/ncmpcpp prev")
	, ((0, xF86XK_AudioPlay), spawn "/usr/bin/ncmpcpp toggle")                                  --Toggle song
	, ((mod1Mask .|. controlMask, xK_Down), spawn "/usr/bin/ncmpcpp toggle")
	, ((0, xF86XK_AudioStop), spawn "/usr/bin/ncmpcpp stop")                                    --Stop song
	, ((mod1Mask .|. controlMask, xK_Up), spawn "ncmpcpp stop")
	, ((0, xF86XK_MonBrightnessUp), spawn $ myBinPath ++ "bridzen.sh")                          --Raise brightness
	, ((0, xF86XK_MonBrightnessDown), spawn $ myBinPath ++ "bridzen.sh")                        --Lower brightness
	, ((0, xF86XK_ScreenSaver), spawn $ myBinPath ++ "turnoffscreen.sh")                        --Lock screen
	, ((0, xK_Print), spawn "/usr/bin/scrot '%Y-%m-%d_$wx$h.png'")                              --Take a screenshot
	, ((modMask , xK_s), spawn $ myBinPath ++ "turnoffscreen.sh")                               --Turn off screen
	--Workspaces management bindings
	, ((mod1Mask, xK_comma), toggleWS)                                                          --Toggle to the workspace displayed previously
	, ((mod1Mask, xK_masculine), toggleOrView (myWorkspaces !! 0))                              --If ws != 0 then move to workspace 0, else move to latest ws I was
	, ((mod1Mask .|. controlMask, xK_Left),  prevWS)                                            --Move to previous Workspace
	, ((mod1Mask .|. controlMask, xK_Right), nextWS)                                            --Move to next Workspace
	, ((modMask .|. shiftMask, xK_n), shiftToNext)                                              --Send client to next workspace
	, ((modMask .|. shiftMask, xK_p), shiftToPrev)                                              --Send client to previous workspace
	]
	++
	[((m .|. modMask, k), windows $ f i)                                                        --Switch to n workspaces and send client to n workspaces
		| (i, k) <- zip (XMonad.workspaces conf) ([xK_1 .. xK_9] ++ [xK_0])
		, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
	++
	[((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))                 --Switch to n screens and send client to n screens
		| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
		, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
	where
		fullFloatFocused = withFocused $ \f -> windows =<< appEndo `fmap` runQuery doFullFloat f
		rectFloatFocused = withFocused $ \f -> windows =<< appEndo `fmap` runQuery (doRectFloat $ RationalRect 0.05 0.05 0.9 0.9) f

-- Mouse bindings
myMouseBindings :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ())
myMouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
	[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w >> windows W.shiftMaster)) --Set the window to floating mode and move by dragging
	, ((modMask, button2), (\w -> focus w >> windows W.shiftMaster))                      --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
	, (((modMask .|. shiftMask), button4), (\_ -> shiftToPrev))                           --Send client  to previous workspace
	, (((modMask .|. shiftMask), button5), (\_ -> shiftToNext))                           --Send client  to next workspace
	]