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

From HaskellWiki
Jump to navigation Jump to search
(fixed mod+q crash)
(14 intermediate revisions by the same user not shown)
Line 3: Line 3:
 
<haskell>
 
<haskell>
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
-- ~/.xmonad/xmonad.hs --
+
-- File : ~/.xmonad/xmonad.hs --
-- validate syntax: xmonad --recompile --
+
-- Author : Nnoell <nnoell3[at]gmail.com> --
  +
-- Deps : DzenBoxLogger.hs --
  +
-- Desc : My XMonad config --
  +
-- Note : Do not use "xmonad --recompile", it will throw errors because of non-official --
  +
-- modules. Compile it manually with "ghc -o <outputName> xmonad.hs". EG: --
  +
-- $ cd ~/.xmonad/ --
  +
-- $ ghc -o xmonad-x86_64-linux xmonad.hs --
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
   
-- Misc
+
-- Options
{-# LANGUAGE DeriveDataTypeable, NoMonomorphismRestriction, TypeSynonymInstances, MultiParamTypeClasses #-}
+
{-# LANGUAGE DeriveDataTypeable, NoMonomorphismRestriction, MultiParamTypeClasses, ImplicitParams #-}
   
  +
-- Modules
-- Imported libraries
 
 
import XMonad
 
import XMonad
import XMonad.Core
+
import XMonad.StackSet (RationalRect(..), currentTag)
 
import XMonad.Layout
 
import XMonad.Layout
 
import XMonad.Layout.IM
 
import XMonad.Layout.IM
import XMonad.Layout.Gaps
 
 
import XMonad.Layout.Named
 
import XMonad.Layout.Named
 
import XMonad.Layout.Tabbed
 
import XMonad.Layout.Tabbed
Line 22: Line 27:
 
import XMonad.Layout.Reflect
 
import XMonad.Layout.Reflect
 
import XMonad.Layout.MosaicAlt
 
import XMonad.Layout.MosaicAlt
import XMonad.Layout.NoBorders (noBorders,smartBorders,withBorder)
+
import XMonad.Layout.NoFrillsDecoration
  +
import XMonad.Layout.SimplestFloat
  +
import XMonad.Layout.NoBorders
 
import XMonad.Layout.ResizableTile
 
import XMonad.Layout.ResizableTile
 
import XMonad.Layout.MultiToggle
 
import XMonad.Layout.MultiToggle
Line 28: Line 35:
 
import XMonad.Layout.PerWorkspace (onWorkspace)
 
import XMonad.Layout.PerWorkspace (onWorkspace)
 
import XMonad.Layout.Minimize
 
import XMonad.Layout.Minimize
import XMonad.StackSet (RationalRect (..), currentTag)
+
import XMonad.Layout.Maximize
  +
import XMonad.Layout.ToggleLayouts
  +
import XMonad.Layout.ComboP
  +
import XMonad.Layout.MagicFocus
  +
import XMonad.Layout.WindowNavigation
  +
import XMonad.Layout.WindowSwitcherDecoration
  +
import XMonad.Layout.DraggingVisualizer
 
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.Loggers
 
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.ShowText
 
import XMonad.Actions.GridSelect
 
import XMonad.Actions.GridSelect
  +
import XMonad.Actions.MouseResize
 
import XMonad.Actions.FloatKeys
 
import XMonad.Actions.FloatKeys
 
import Data.Monoid
 
import Data.Monoid
Line 50: Line 69:
 
import System.Exit
 
import System.Exit
 
import System.IO (Handle, hPutStrLn)
 
import System.IO (Handle, hPutStrLn)
  +
import Control.Concurrent (threadDelay)
  +
import Control.Exception as E
 
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
  +
  +
-- Non-official modules
  +
import DzenBoxLoggers
  +
  +
  +
--------------------------------------------------------------------------------------------
  +
-- MAIN --
  +
--------------------------------------------------------------------------------------------
   
-- Main
 
 
main :: IO ()
 
main :: IO ()
 
main = do
 
main = do
workspaceBar <- spawnPipe myWorkspaceBar
+
topLeftBar <- spawnPipe $ dzenFlagsToStr dzenTopLeftFlags
bottomStatusBar <- spawnPipe myBottomStatusBar
+
topRightBar <- spawnPipe $ dzenFlagsToStr dzenTopRightFlags
topStatusBar <- spawnPipe myTopStatusBar
+
botLeftBar <- spawnPipe $ dzenFlagsToStr dzenBotLeftFlags
  +
botRightBar <- spawnPipe $ dzenFlagsToStr dzenBotRightFlags
 
xmonad $ myUrgencyHook $ defaultConfig
 
xmonad $ myUrgencyHook $ defaultConfig
 
{ terminal = "urxvtc"
 
{ terminal = "urxvtc"
 
, modMask = mod4Mask
 
, modMask = mod4Mask
 
, focusFollowsMouse = True
 
, focusFollowsMouse = True
  +
, clickJustFocuses = True
 
, borderWidth = 1
 
, borderWidth = 1
, normalBorderColor = myNormalBorderColor
+
, normalBorderColor = colorBlackAlt
, focusedBorderColor = myFocusedBorderColor
+
, focusedBorderColor = colorWhiteAlt2
 
, 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 = myBotLeftLogHook botLeftBar <+> myBotRightLogHook botRightBar <+> myTopLeftLogHook topLeftBar <+> myTopRightLogHook 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 = myStartupHook
 
}
 
}
   
   
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
-- APPEARANCE CONFIG --
+
-- LOOK AND FEEL CONFIG --
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
   
-- 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-*-*-*-*-*-*-*"
  +
colorBlack = "#020202" --Background
dzenFont = "-*-montecarlo-medium-r-normal-*-11-*-*-*-*-*-*-*"
 
  +
colorBlackAlt = "#1c1c1c" --Black Xdefaults
colorBlack = "#020202" --Background (Dzen_BG)
 
colorBlackAlt = "#1c1c1c" --Black Xdefaults
+
colorGray = "#444444" --Gray
colorGray = "#444444" --Gray (Dzen_FG2)
+
colorGrayAlt = "#101010" --Gray dark
  +
colorGrayAlt2 = "#404040"
colorGrayAlt = "#161616" --Gray dark
 
  +
colorGrayAlt3 = "#252525"
colorWhite = "#a9a6af" --Foreground (Shell_FG)
 
colorWhiteAlt = "#9d9d9d" --White dark (Dzen_FG)
+
colorWhite = "#a9a6af" --Foreground
  +
colorWhiteAlt = "#9d9d9d" --White dark
colorMagenta = "#8e82a2"
 
  +
colorWhiteAlt2 = "#b5b3b3"
colorBlue = "#3475aa"
 
  +
colorWhiteAlt3 = "#707070"
colorRed = "#d74b73"
 
colorGreen = "#99cc66"
+
colorMagenta = "#8e82a2"
  +
colorBlue = "#44aacc"
myArrow = "^fg(" ++ colorWhiteAlt ++ ")>^fg(" ++ colorBlue ++ ")>^fg(" ++ colorGray ++ ")>"
 
  +
colorBlueAlt = "#3955c4"
myNormalBorderColor = colorBlackAlt
 
  +
colorRed = "#f7a16e"
myFocusedBorderColor = colorGray
 
  +
colorRedAlt = "#e0105f"
  +
colorGreen = "#66ff66"
  +
colorGreenAlt = "#558965"
  +
boxLeftIcon = "/home/nnoell/.icons/xbm_icons/subtle/boxleft.xbm" --left icon of dzen logger boxes
  +
boxLeftIcon2 = "/home/nnoell/.icons/xbm_icons/subtle/boxleft2.xbm" --left icon2 of dzen logger boxes
  +
boxRightIcon = "/home/nnoell/.icons/xbm_icons/subtle/boxright.xbm" --right icon of dzen logger boxes
  +
xRes = 1366
  +
yRes = 768
  +
panelHeight = 14 --height of top and bottom panels
  +
boxHeight = 14 --height of dzen logger box
  +
topPanelSepPos = 950 --left-right alignment pos of top panel
  +
botPanelSepPos = 400 --left-right alignment pos of bottom panel
   
-- Tab theme
+
-- Title theme
myTabTheme :: Theme
+
myTitleTheme :: Theme
myTabTheme = defaultTheme
+
myTitleTheme = defaultTheme
{ fontName = myFont
+
{ fontName = dzenFont
, inactiveBorderColor = colorBlackAlt
+
, inactiveBorderColor = colorGrayAlt2
, inactiveColor = colorBlack
+
, inactiveColor = colorGrayAlt3
, inactiveTextColor = colorGray
+
, inactiveTextColor = colorWhiteAlt3
, activeBorderColor = colorGray
+
, activeBorderColor = colorGrayAlt2
, activeColor = colorBlackAlt
+
, activeColor = colorGrayAlt2
, activeTextColor = colorWhiteAlt
+
, activeTextColor = colorWhiteAlt2
 
, urgentBorderColor = colorGray
 
, urgentBorderColor = colorGray
 
, urgentTextColor = colorGreen
 
, urgentTextColor = colorGreen
Line 117: Line 160:
 
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
, height = 16
+
, height = panelHeight
, position = Top
+
, position = Top
, historySize = 100
+
, historySize = 100
, historyFilter = deleteConsecutive
+
, historyFilter = deleteConsecutive
, autoComplete = Nothing
+
, autoComplete = Nothing
 
}
 
}
   
Line 134: Line 177:
 
myColorizer :: Window -> Bool -> X (String, String)
 
myColorizer :: Window -> Bool -> X (String, String)
 
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
   
 
-- GridSelect theme
 
-- GridSelect theme
Line 146: Line 189:
 
, gs_cellwidth = 200
 
, gs_cellwidth = 200
 
, gs_cellpadding = 10
 
, gs_cellpadding = 10
, gs_font = myFont
+
, gs_font = dzenFont
 
}
 
}
   
  +
-- Flash text config
-- Workspaces
 
  +
myTextConfig :: ShowTextConfig
  +
myTextConfig = STC
  +
{ st_font = dzenFont
  +
, st_bg = colorBlack
  +
, st_fg = colorWhite
  +
}
  +
  +
-- Dzen logger box pretty printing themes
  +
gray2BoxPP :: BoxPP
  +
gray2BoxPP = BoxPP
  +
{ bgColorBPP = colorBlack
  +
, fgColorBPP = colorGray
  +
, boxColorBPP = colorGrayAlt
  +
, leftIconBPP = boxLeftIcon2
  +
, rightIconBPP = boxRightIcon
  +
, boxHeightBPP = boxHeight
  +
}
  +
  +
blueBoxPP :: BoxPP
  +
blueBoxPP = BoxPP
  +
{ bgColorBPP = colorBlack
  +
, fgColorBPP = colorBlue
  +
, boxColorBPP = colorGrayAlt
  +
, leftIconBPP = boxLeftIcon
  +
, rightIconBPP = boxRightIcon
  +
, boxHeightBPP = boxHeight
  +
}
  +
  +
blue2BoxPP :: BoxPP
  +
blue2BoxPP = BoxPP
  +
{ bgColorBPP = colorBlack
  +
, fgColorBPP = colorBlue
  +
, boxColorBPP = colorGrayAlt
  +
, leftIconBPP = boxLeftIcon2
  +
, rightIconBPP = boxRightIcon
  +
, boxHeightBPP = boxHeight
  +
}
  +
  +
whiteBoxPP :: BoxPP
  +
whiteBoxPP = BoxPP
  +
{ bgColorBPP = colorBlack
  +
, fgColorBPP = colorWhiteAlt
  +
, boxColorBPP = colorGrayAlt
  +
, leftIconBPP = boxLeftIcon
  +
, rightIconBPP = boxRightIcon
  +
, boxHeightBPP = boxHeight
  +
}
  +
  +
blackBoxPP :: BoxPP
  +
blackBoxPP = BoxPP
  +
{ bgColorBPP = colorBlack
  +
, fgColorBPP = colorBlack
  +
, boxColorBPP = colorGrayAlt
  +
, leftIconBPP = boxLeftIcon
  +
, rightIconBPP = boxRightIcon
  +
, boxHeightBPP = boxHeight
  +
}
  +
  +
white2BBoxPP :: BoxPP
  +
white2BBoxPP = BoxPP
  +
{ bgColorBPP = colorBlack
  +
, fgColorBPP = colorBlack
  +
, boxColorBPP = colorWhiteAlt
  +
, leftIconBPP = boxLeftIcon2
  +
, rightIconBPP = boxRightIcon
  +
, boxHeightBPP = boxHeight
  +
}
  +
  +
blue2BBoxPP :: BoxPP --current workspace
  +
blue2BBoxPP = BoxPP
  +
{ bgColorBPP = colorBlack
  +
, fgColorBPP = colorBlack
  +
, boxColorBPP = colorBlue
  +
, leftIconBPP = boxLeftIcon2
  +
, rightIconBPP = boxRightIcon
  +
, boxHeightBPP = boxHeight
  +
}
  +
  +
green2BBoxPP :: BoxPP --urgent workspace
  +
green2BBoxPP = BoxPP
  +
{ bgColorBPP = colorBlack
  +
, fgColorBPP = colorBlack
  +
, boxColorBPP = colorGreen
  +
, leftIconBPP = boxLeftIcon2
  +
, rightIconBPP = boxRightIcon
  +
, boxHeightBPP = boxHeight
  +
}
  +
  +
-- Dzen logger clickable areas
  +
calendarCA :: CA
  +
calendarCA = CA
  +
{ leftClickCA = "/home/nnoell/bin/dzencal.sh"
  +
, middleClickCA = "/home/nnoell/bin/dzencal.sh"
  +
, rightClickCA = "/home/nnoell/bin/dzencal.sh"
  +
, wheelUpCA = "/home/nnoell/bin/dzencal.sh"
  +
, wheelDownCA = "/home/nnoell/bin/dzencal.sh"
  +
}
  +
  +
layoutCA :: CA
  +
layoutCA = CA
  +
{ leftClickCA = "/usr/bin/xdotool key super+space"
  +
, middleClickCA = "/usr/bin/xdotool key super+v"
  +
, rightClickCA = "/usr/bin/xdotool key super+shift+space"
  +
, wheelUpCA = "/usr/bin/xdotool key super+f"
  +
, wheelDownCA = "/usr/bin/xdotool key super+control+f"
  +
}
  +
  +
workspaceCA :: CA
  +
workspaceCA = CA
  +
{ leftClickCA = "/usr/bin/xdotool key super+1"
  +
, middleClickCA = "/usr/bin/xdotool key super+g"
  +
, rightClickCA = "/usr/bin/xdotool key super+0"
  +
, wheelUpCA = "/usr/bin/xdotool key ctrl+alt+Right"
  +
, wheelDownCA = "/usr/bin/xdotool key ctrl+alt+Left"
  +
}
  +
  +
focusCA :: CA
  +
focusCA = CA
  +
{ leftClickCA = "/usr/bin/xdotool key super+m"
  +
, middleClickCA = "/usr/bin/xdotool key super+c"
  +
, rightClickCA = "/usr/bin/xdotool key super+shift+m"
  +
, wheelUpCA = "/usr/bin/xdotool key super+shift+j"
  +
, wheelDownCA = "/usr/bin/xdotool key super+shift+k"
  +
}
  +
  +
-- Workspace index
 
myWorkspaces :: [WorkspaceId]
 
myWorkspaces :: [WorkspaceId]
myWorkspaces = ["TERM", "WEBS", "CODE", "GRFX", "CHAT", "GAME", "VIDS", "OTHR"]
+
myWorkspaces = map show $ [1..9] ++ [0]
  +
  +
-- Workspace names
  +
workspaceNames :: [WorkspaceId]
  +
workspaceNames = ["Terminal", "Network", "Development", "Graphics", "Chatting", "Video", "Alternate", "Alternate", "Alternate", "Alternate"]
  +
  +
-- Layout names (must be one word name and not equal to: Mirror, ReflectX, ReflectY, Switcher, Normal and Unique)
  +
myTileName = "Tiled"
  +
myMirrName = "Mirror"
  +
myMosAName = "Mosaic"
  +
myOneBName = "OneBig"
  +
myMTabName = "MstrTab"
  +
myChatName = "Chat"
  +
myTabbName = "Tabbed"
  +
myTTabName = "TwoTab"
  +
myFTabName = "Full"
  +
myFloaName = "Float"
   
   
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
-- LAYOUT CONFIG --
+
-- STARTUP HOOK CONFIG --
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
   
  +
-- Startup Hook
-- Layouts
 
  +
myStartupHook = spawn "/home/nnoell/.xmonad/apps/haskell-cpu-usage.out 5" <+> setDefaultCursor xC_left_ptr <+> startDelayTimer where
myTile = named "T" $ smartBorders $ ResizableTall 1 0.03 0.5 []
 
  +
startDelayTimer = do
myMirr = named "MT" $ smartBorders $ Mirror myTile
 
  +
liftIO $ threadDelay $ 1000000 --needed so that xmonad can be recompiled and launched on the fly without crashing
myMosA = named "M" $ smartBorders $ MosaicAlt M.empty
 
  +
startTimer 1 >>= XS.put . TID
myObig = named "O" $ smartBorders $ OneBig 0.75 0.65
 
myTabs = named "TS" $ smartBorders $ tabbed shrinkText myTabTheme
 
myFull = named "TS" $ smartBorders $ tabbedAlways shrinkText myTabTheme
 
myTabM = named "TM" $ smartBorders $ mastered 0.01 0.4 $ tabbed shrinkText myTabTheme
 
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 []
 
   
  +
-- Transformers (Ctrl+f)
 
  +
--------------------------------------------------------------------------------------------
  +
-- 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 = fullscreenEventHook <+> docksEventHook <+> clockEventHook <+> handleTimerEvent <+> notFocusFloat where
  +
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
  +
notFocusFloat = followOnlyIf (fmap not isFloat) where --Do not focusFollowMouse on Float layout
  +
isFloat = fmap (isSuffixOf myFloaName) $ gets (description . W.layout . W.workspace . W.current . windowset)
  +
  +
  +
--------------------------------------------------------------------------------------------
  +
-- LAYOUT CONFIG --
  +
--------------------------------------------------------------------------------------------
  +
  +
-- 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 myFTab (\_ -> x)
  +
  +
-- Floated transformer (W+ctl+f)
  +
data FLOATED = FLOATED deriving (Read, Show, Eq, Typeable)
  +
instance Transformer FLOATED Window where
  +
transform FLOATED x k = k myFloa (\_ -> x)
  +
  +
-- Switcher Layouts
  +
myTile = smartBorders $ toggleLayouts (named ("Switcher " ++ myTileName) myTileS) $ named ("Normal " ++ myTileName) $ ResizableTall 1 0.03 0.5 [] where
  +
myTileS = windowSwitcherDecoration shrinkText myTitleTheme (draggingVisualizer $ ResizableTall 1 0.03 0.5 [])
  +
myMirr = smartBorders $ toggleLayouts (named ("Switcher " ++ myMirrName) myMirrS) $ named ("Normal " ++ myMirrName) $ Mirror $ ResizableTall 1 0.03 0.5 [] where
  +
myMirrS = windowSwitcherDecoration shrinkText myTitleTheme (draggingVisualizer $ Mirror $ ResizableTall 1 0.03 0.5 [])
  +
myMosA = smartBorders $ toggleLayouts (named ("Switcher " ++ myMosAName) myMosAS) $ named ("Normal " ++ myMosAName) $ MosaicAlt M.empty where
  +
myMosAS = windowSwitcherDecoration shrinkText myTitleTheme (draggingVisualizer $ MosaicAlt M.empty)
  +
myOneB = smartBorders $ toggleLayouts (named ("Switcher " ++ myOneBName) myOneBS) $ named ("Normal " ++ myOneBName) $ OneBig 0.75 0.65 where
  +
myOneBS = windowSwitcherDecoration shrinkText myTitleTheme (draggingVisualizer $ OneBig 0.75 0.65)
  +
myMTab = smartBorders $ toggleLayouts (named ("Switcher " ++ myMTabName) myMTabS) $ named ("Normal " ++ myMTabName) $ mastered 0.01 0.4 $ tabbed shrinkText myTitleTheme where
  +
myMTabS = windowSwitcherDecoration shrinkText myTitleTheme (draggingVisualizer $ mastered 0.01 0.4 $ tabbed shrinkText myTitleTheme)
  +
myChat = smartBorders $ toggleLayouts (named ("Switcher " ++ myChatName) $ withIM (0.20) (Title "Buddy List") myChatS) (named ("Normal " ++ myChatName) $ withIM (0.20) (Title "Buddy List") $ MosaicAlt M.empty) where
  +
myChatS = windowSwitcherDecoration shrinkText myTitleTheme (draggingVisualizer $ MosaicAlt M.empty)
  +
  +
-- Unique Layouts
  +
myTabb = smartBorders $ named ("Unique " ++ myTabbName) $ tabbed shrinkText myTitleTheme
  +
myTTab = smartBorders $ named ("Unique " ++ myTTabName) $ combineTwoP (OneBig 0.75 0.75) (tabbed shrinkText myTitleTheme) (tabbed shrinkText myTitleTheme) (ClassName "Chromium")
  +
myFTab = smartBorders $ named ("Unique " ++ myFTabName) $ tabbedAlways shrinkText myTitleTheme
  +
myFloa = named ("Unique " ++ myFloaName) $ mouseResize $ noFrillsDeco shrinkText myTitleTheme simplestFloat
   
 
-- Layout hook
 
-- Layout hook
myLayoutHook = id
+
myLayoutHook = avoidStruts
  +
$ configurableNavigation noNavigateBorders
$ gaps [(U,16), (D,16), (L,0), (R,0)]
 
$ avoidStruts
 
 
$ minimize
 
$ minimize
  +
$ maximize
 
$ mkToggle (single TABBED)
 
$ mkToggle (single TABBED)
  +
$ mkToggle (single FLOATED)
 
$ mkToggle (single MIRROR)
 
$ mkToggle (single MIRROR)
 
$ mkToggle (single REFLECTX)
 
$ mkToggle (single REFLECTX)
 
$ mkToggle (single REFLECTY)
 
$ mkToggle (single REFLECTY)
$ onWorkspace (myWorkspaces !! 1) webLayouts --Workspace 1 layouts
+
$ onWorkspace (myWorkspaces !! 1) webLayouts
$ onWorkspace (myWorkspaces !! 2) codeLayouts --Workspace 2 layouts
+
$ onWorkspace (myWorkspaces !! 2) codeLayouts
$ onWorkspace (myWorkspaces !! 3) gimpLayouts --Workspace 3 layouts
+
$ onWorkspace (myWorkspaces !! 4) chatLayouts
  +
$ allLayouts where
$ onWorkspace (myWorkspaces !! 4) chatLayouts --Workspace 4 layouts
 
  +
webLayouts = myTabb ||| myTTab
$ allLayouts
 
  +
codeLayouts = myMTab ||| myOneB ||| myTile
where
 
allLayouts = myTile ||| myObig ||| myMirr ||| myMosA ||| myTabM
 
webLayouts = myTabs ||| myTabM
 
codeLayouts = myTabM ||| myTile
 
gimpLayouts = myGimp
 
 
chatLayouts = myChat
 
chatLayouts = myChat
  +
allLayouts = myTile ||| myOneB ||| myMirr ||| myMosA ||| myMTab
   
   
Line 200: Line 431:
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
   
-- Scratchpad (Alt+º)
+
-- Scratchpad (W+º)
 
manageScratchPad :: ManageHook
 
manageScratchPad :: ManageHook
manageScratchPad = scratchpadManageHook (W.RationalRect (0) (1/50) (1) (3/4))
+
manageScratchPad = scratchpadManageHook $ W.RationalRect (0) (panelHeight/yRes) (1) (3/4)
 
scratchPad = scratchpadSpawnActionCustom "urxvtc -name scratchpad"
 
scratchPad = scratchpadSpawnActionCustom "urxvtc -name scratchpad"
   
 
-- 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 ]
, [className =? c --> doShift (myWorkspaces !! 1) | c <- myWebS ] --move myWebS windows to workspace 1 by classname
+
, [ className =? c --> doShift (myWorkspaces !! 1) | c <- myWebS ]
, [className =? c --> doShift (myWorkspaces !! 4) | c <- myChatS ] --move myChatS windows to workspace 4 by classname
+
, [ className =? c --> doShift (myWorkspaces !! 2) | c <- myCodeS ]
, [className =? c --> doShift (myWorkspaces !! 3) | c <- myGfxS ] --move myGfxS windows to workspace 4 by classname
+
, [ className =? c --> doShift (myWorkspaces !! 3) | c <- myGfxS ]
, [className =? c --> doShiftAndGo (myWorkspaces !! 5) | c <- myGameS ] --move myGameS windows to workspace 5 by classname and shift
+
, [ className =? c --> doShift (myWorkspaces !! 4) | c <- myChatS ]
, [className =? c --> doShiftAndGo (myWorkspaces !! 7) | c <- myOtherS ] --move myOtherS windows to workspace 5 by classname and shift
+
, [ className =? c --> doShift (myWorkspaces !! 7) | c <- myAlt3S ]
, [className =? c --> doCenterFloat | c <- myFloatCC] --float center geometry by classname
+
, [ className =? c --> doCenterFloat | c <- myFloatCC ]
, [name =? n --> doCenterFloat | n <- myFloatCN] --float center geometry by name
+
, [ name =? n --> doCenterFloat | n <- myFloatCN ]
, [name =? n --> doSideFloat NW | n <- myFloatSN] --float side NW geometry by name
+
, [ name =? n --> doSideFloat NW | n <- myFloatSN ]
, [className =? c --> doF W.focusDown | c <- myFocusDC] --dont focus on launching by classname
+
, [ className =? c --> doF W.focusDown | c <- myFocusDC ]
, [isFullscreen --> doFullFloat]
+
, [ isFullscreen --> doFullFloat ]
  +
] where
]) <+> manageScratchPad
 
  +
name = stringProperty "WM_NAME"
where
 
  +
myIgnores = ["desktop","desktop_window"]
doShiftAndGo ws = doF (W.greedyView ws) <+> doShift ws
 
  +
myWebS = ["Chromium","Firefox", "Opera"]
role = stringProperty "WM_WINDOW_ROLE"
 
  +
myCodeS = ["NetBeans IDE 7.3"]
name = stringProperty "WM_NAME"
 
myIgnores = ["desktop","desktop_window"]
+
myChatS = ["Pidgin", "Xchat"]
myWebS = ["Chromium","Firefox"]
+
myGfxS = ["Gimp", "gimp", "GIMP"]
myGfxS = ["gimp-2.6", "Gimp-2.6", "Gimp", "gimp", "GIMP"]
+
myAlt3S = ["Amule", "Transmission-gtk"]
  +
myFloatCC = ["MPlayer", "mplayer2", "File-roller", "zsnes", "Gcalctool", "Exo-helper-1", "Gksu", "PSX", "Galculator", "Nvidia-settings", "XFontSel"
myChatS = ["Pidgin", "Xchat"]
 
myGameS = ["zsnes", "jpcsp-MainGUI", "Desmume"]
+
, "XCalc", "XClock", "Ossxmix", "Xvidcap", "Main", "Wicd-client.py"]
  +
myFloatCN = ["Choose a file", "Open Image", "File Operation Progress", "Firefox Preferences", "Preferences", "Search Engines", "Set up sync"
myOtherS = ["Amule", "Transmission-gtk"]
 
  +
,"Passwords and Exceptions", "Autofill Options", "Rename File", "Copying files", "Moving files", "File Properties", "Replace", ""]
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"]
 
  +
myFloatSN = ["Event Tester"]
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"]
myFocusDC = ["Event Tester", "Notify-osd"]
 
   
   
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
-- STATUS BARS CONFIG --
+
-- DZEN STATUS BARS CONFIG --
 
--------------------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------------------
   
-- UrgencyHook
+
-- urgencyHook
  +
myUrgencyHook :: LayoutClass l Window => XConfig l -> XConfig l
 
myUrgencyHook = withUrgencyHook dzenUrgencyHook
 
myUrgencyHook = withUrgencyHook dzenUrgencyHook
  +
{ duration = 2000000
{ args = ["-fn", dzenFont, "-bg", colorBlack, "-fg", colorGreen] }
 
  +
, args = ["-x", "0", "-y", "0", "-h", show panelHeight, "-w", show topPanelSepPos, "-fn", dzenFont, "-bg", colorBlack, "-fg", colorGreen]
  +
}
   
  +
-- Dzen top left bar flags
-- StatusBars
 
  +
dzenTopLeftFlags :: DF
myWorkspaceBar, myBottomStatusBar, myTopStatusBar :: String
 
  +
dzenTopLeftFlags = DF
myWorkspaceBar = "dzen2 -x '0' -y '784' -h '16' -w '870' -ta 'l' -fg '" ++ colorWhiteAlt ++ "' -bg '" ++ colorBlack ++ "' -fn '" ++ dzenFont ++ "' -p -e ''"
 
  +
{ xPosDF = 0
myBottomStatusBar = "/home/nnoell/bin/bottomstatusbar.sh"
 
  +
, yPosDF = 0
myTopStatusBar = "/home/nnoell/bin/topstatusbar.sh"
 
  +
, widthDF = topPanelSepPos
  +
, heightDF = panelHeight
  +
, alignementDF = "l"
  +
, fgColorDF = colorWhiteAlt
  +
, bgColorDF = colorBlack
  +
, fontDF = dzenFont
  +
, eventDF = "onstart=lower"
  +
, extrasDF = "-p"
  +
}
   
  +
-- Top left bar logHook
-- myWorkspaceBar config
 
myLogHook :: Handle -> X ()
+
myTopLeftLogHook :: Handle -> X ()
myLogHook h = dynamicLogWithPP $ defaultPP
+
myTopLeftLogHook h = dynamicLogWithPP $ defaultPP
  +
{ ppOutput = hPutStrLn h
  +
, ppOrder = \(_:_:_:x) -> x
  +
, ppSep = " "
  +
, ppExtras = [ myLayoutL, myWorkspaceL, myFocusL ]
  +
}
  +
  +
-- Dzen top right bar flags
  +
dzenTopRightFlags :: DF
  +
dzenTopRightFlags = DF
  +
{ xPosDF = topPanelSepPos
  +
, yPosDF = 0
  +
, widthDF = xRes - topPanelSepPos
  +
, heightDF = panelHeight
  +
, alignementDF = "r"
  +
, fgColorDF = colorWhiteAlt
  +
, bgColorDF = colorBlack
  +
, fontDF = dzenFont
  +
, eventDF = "onstart=lower"
  +
, extrasDF = "-p"
  +
}
  +
  +
-- Top right bar logHook
  +
myTopRightLogHook :: Handle -> X ()
  +
myTopRightLogHook h = dynamicLogWithPP $ defaultPP
  +
{ ppOutput = hPutStrLn h
  +
, ppOrder = \(_:_:_:x) -> x
  +
, ppSep = " "
  +
, ppExtras = [ myUptimeL, myDateL ]
  +
}
  +
  +
-- Dzen bottom left bar flags
  +
dzenBotLeftFlags :: DF
  +
dzenBotLeftFlags = DF
  +
{ xPosDF = 0
  +
, yPosDF = yRes - panelHeight
  +
, widthDF = botPanelSepPos
  +
, heightDF = panelHeight
  +
, alignementDF = "l"
  +
, fgColorDF = colorWhiteAlt
  +
, bgColorDF = colorBlack
  +
, fontDF = dzenFont
  +
, eventDF = "onstart=lower"
  +
, extrasDF = "-p"
  +
}
  +
  +
-- Bottom left bar logHook
  +
myBotLeftLogHook :: Handle -> X ()
  +
myBotLeftLogHook h = dynamicLogWithPP . namedScratchpadFilterOutWorkspacePP $ defaultPP
 
{ ppOutput = hPutStrLn h
 
{ ppOutput = hPutStrLn h
  +
, ppOrder = \(ws:l:_:x) -> [ws] ++ x
, ppSort = fmap (namedScratchpadFilterOutWorkspace.) (ppSort defaultPP) -- hide "NSP" from workspace list
 
, ppOrder = orderText
+
, ppSep = " "
, ppExtras = []
 
, ppSep = "^fg(" ++ colorGray ++ ")|"
 
 
, ppWsSep = ""
 
, ppWsSep = ""
, ppCurrent = dzenColor colorBlue colorBlack . pad
+
, ppCurrent = dzenBoxStyle blue2BBoxPP
, ppUrgent = dzenColor colorGreen colorBlack . pad . wrapClickWorkSpace . (\a -> (a,a))
+
, ppUrgent = dzenBoxStyle green2BBoxPP . dzenClickWorkspace
, ppVisible = dzenColor colorGray colorBlack . pad . wrapClickWorkSpace . (\a -> (a,a))
+
, ppVisible = dzenBoxStyle blackBoxPP . dzenClickWorkspace
  +
, ppHiddenNoWindows = dzenBoxStyle blackBoxPP . dzenClickWorkspace
, ppHidden = dzenColor colorWhiteAlt colorBlack . pad . wrapClickWorkSpace . (\a -> (a,a))
 
  +
, ppHidden = dzenBoxStyle whiteBoxPP . dzenClickWorkspace
, ppHiddenNoWindows = dzenColor colorGray colorBlack . pad . wrapClickWorkSpace . (\a -> (a,a))
 
  +
, ppExtras = [ myFsL ]
, ppLayout = dzenColor colorBlue colorBlack . pad . wrapClickLayout . layoutText
 
  +
} where
, ppTitle = dzenColor colorWhiteAlt colorBlack . pad . wrapClickTitle . titleText . dzenEscape
 
  +
dzenClickWorkspace 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
  +
  +
-- Dzen bottom right bar flags
  +
dzenBotRightFlags :: DF
  +
dzenBotRightFlags = DF
  +
{ xPosDF = botPanelSepPos
  +
, yPosDF = yRes - panelHeight
  +
, widthDF = xRes - botPanelSepPos
  +
, heightDF = panelHeight
  +
, alignementDF = "r"
  +
, fgColorDF = colorWhiteAlt
  +
, bgColorDF = colorBlack
  +
, fontDF = dzenFont
  +
, eventDF = "onstart=lower"
  +
, extrasDF = "-p"
 
}
 
}
  +
where
 
  +
-- Bottom right bar logHook
--display config
 
  +
myBotRightLogHook :: Handle -> X ()
orderText (ws:l:t:_) = [ws,l,t]
 
  +
myBotRightLogHook h = dynamicLogWithPP $ defaultPP
titleText [] = "Desktop" ++ myArrow
 
  +
{ ppOutput = hPutStrLn h
titleText x = (shorten 82 x) ++ " " ++ myArrow
 
  +
, ppOrder = \(_:_:_:x) -> x
layoutText "Minimize T" = "ReTall"
 
  +
, ppSep = " "
layoutText "Minimize O" = "OneBig"
 
  +
, ppExtras = [ myCpuL, myMemL, myTempL, myBrightL, myWifiL, myBatL ]
layoutText "Minimize TS" = "Tabbed"
 
  +
}
layoutText "Minimize TM" = "Master"
 
  +
layoutText "Minimize M" = "Mosaic"
 
  +
layoutText "Minimize MT" = "Mirror"
 
  +
--------------------------------------------------------------------------------------------
layoutText "Minimize G" = "Mosaic"
 
  +
-- LOGGERS CONFIG --
layoutText "Minimize C" = "Mirror"
 
  +
--------------------------------------------------------------------------------------------
layoutText "Minimize ReflectX T" = "^fg(" ++ colorGreen ++ ")ReTall X^fg()"
 
  +
layoutText "Minimize ReflectX O" = "^fg(" ++ colorGreen ++ ")OneBig X^fg()"
 
  +
myBatL = (dzenBoxStyleL gray2BoxPP $ labelL "BATTERY") ++! (dzenBoxStyleL blueBoxPP batPercent) ++! (dzenBoxStyleL whiteBoxPP batStatus)
layoutText "Minimize ReflectX TS" = "^fg(" ++ colorGreen ++ ")Tabbed X^fg()"
 
  +
myWifiL = (dzenBoxStyleL gray2BoxPP $ labelL "WIFI") ++! (dzenBoxStyleL blueBoxPP wifiSignal)
layoutText "Minimize ReflectX TM" = "^fg(" ++ colorGreen ++ ")Master X^fg()"
 
  +
myBrightL = (dzenBoxStyleL gray2BoxPP $ labelL "BRIGHT") ++! (dzenBoxStyleL blueBoxPP brightPerc)
layoutText "Minimize ReflectX M" = "^fg(" ++ colorGreen ++ ")Mosaic X^fg()"
 
  +
myTempL = (dzenBoxStyleL gray2BoxPP $ labelL "TEMP") ++! (dzenBoxStyleL blueBoxPP cpuTemp)
layoutText "Minimize ReflectX MT" = "^fg(" ++ colorGreen ++ ")Mirror X^fg()"
 
  +
myMemL = (dzenBoxStyleL gray2BoxPP $ labelL "MEM") ++! (dzenBoxStyleL blueBoxPP memUsage)
layoutText "Minimize ReflectX G" = "^fg(" ++ colorGreen ++ ")Mosaic X^fg()"
 
  +
myCpuL = (dzenBoxStyleL gray2BoxPP $ labelL "CPU") ++! (dzenBoxStyleL blueBoxPP $ cpuUsage "/tmp/haskell-cpu-usage.txt")
layoutText "Minimize ReflectX C" = "^fg(" ++ colorGreen ++ ")Mirror X^fg()"
 
  +
myFsL = (dzenBoxStyleL blue2BoxPP $ labelL "ROOT") ++! (dzenBoxStyleL whiteBoxPP $ fsPerc "/") ++! (dzenBoxStyleL blueBoxPP $ labelL "HOME") ++! (dzenBoxStyleL whiteBoxPP $ fsPerc "/home")
layoutText "Minimize ReflectY T" = "^fg(" ++ colorGreen ++ ")ReTall Y^fg()"
 
  +
myDateL = (dzenBoxStyleL white2BBoxPP $ date "%A") ++! (dzenBoxStyleL whiteBoxPP $ date $ "%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()") ++! (dzenClickStyleL calendarCA $ dzenBoxStyleL blueBoxPP $ labelL "CALENDAR")
layoutText "Minimize ReflectY O" = "^fg(" ++ colorGreen ++ ")OneBig Y^fg()"
 
  +
myUptimeL = (dzenBoxStyleL blue2BoxPP $ labelL "UPTIME") ++! (dzenBoxStyleL whiteBoxPP uptime)
layoutText "Minimize ReflectY TS" = "^fg(" ++ colorGreen ++ ")Tabbed Y^fg()"
 
  +
myFocusL = (dzenClickStyleL focusCA $ dzenBoxStyleL white2BBoxPP $ labelL "FOCUS") ++! (dzenBoxStyleL whiteBoxPP $ shortenL 100 logTitle)
layoutText "Minimize ReflectY TM" = "^fg(" ++ colorGreen ++ ")Master Y^fg()"
 
  +
myLayoutL = (dzenClickStyleL layoutCA $ dzenBoxStyleL blue2BoxPP $ labelL "LAYOUT") ++! (dzenBoxStyleL whiteBoxPP $ onLogger (layoutText . removeWord . removeWord) logLayout) where
layoutText "Minimize ReflectY M" = "^fg(" ++ colorGreen ++ ")Mosaic Y^fg()"
 
  +
removeWord xs = tail $ dropWhile (/= ' ') xs
layoutText "Minimize ReflectY MT" = "^fg(" ++ colorGreen ++ ")Mirror Y^fg()"
 
  +
layoutText xs
layoutText "Minimize ReflectY G" = "^fg(" ++ colorGreen ++ ")Mosaic Y^fg()"
 
  +
| isPrefixOf "Mirror" xs = layoutText $ removeWord xs ++ " ^fg(" ++ colorBlue ++ ")M^fg(" ++ colorGray ++ ")|^fg(" ++ colorWhiteAlt ++ ")"
layoutText "Minimize ReflectY C" = "^fg(" ++ colorGreen ++ ")Mirror Y^fg()"
 
layoutText "Minimize ReflectX ReflectY T" = "^fg(" ++ colorGreen ++ ")ReTall XY^fg()"
+
| isPrefixOf "ReflectY" xs = layoutText $ removeWord xs ++ " ^fg(" ++ colorBlue ++ ")Y^fg(" ++ colorGray ++ ")|^fg(" ++ colorWhiteAlt ++ ")"
layoutText "Minimize ReflectX ReflectY O" = "^fg(" ++ colorGreen ++ ")OneBig XY^fg()"
+
| isPrefixOf "ReflectX" xs = layoutText $ removeWord xs ++ " ^fg(" ++ colorBlue ++ ")X^fg(" ++ colorGray ++ ")|^fg(" ++ colorWhiteAlt ++ ")"
  +
| isPrefixOf "Switcher" xs = layoutText $ removeWord xs ++ " ^fg(" ++ colorRed ++ ")S^fg(" ++ colorGray ++ ")|^fg(" ++ colorWhiteAlt ++ ")"
layoutText "Minimize ReflectX ReflectY TS" = "^fg(" ++ colorGreen ++ ")Tabbed XY^fg()"
 
layoutText "Minimize ReflectX ReflectY TM" = "^fg(" ++ colorGreen ++ ")Master XY^fg()"
+
| isPrefixOf "Normal" xs = layoutText $ removeWord xs ++ " ^fg(" ++ colorGreen ++ ")N^fg(" ++ colorGray ++ ")|^fg(" ++ colorWhiteAlt ++ ")"
layoutText "Minimize ReflectX ReflectY M" = "^fg(" ++ colorGreen ++ ")Mosaic XY^fg()"
+
| isPrefixOf "Unique" xs = layoutText $ removeWord xs ++ " ^fg(" ++ colorGreen ++ ")U^fg(" ++ colorGray ++ ")|^fg(" ++ colorWhiteAlt ++ ")"
  +
| otherwise = concat $ reverse $ words xs
layoutText "Minimize ReflectX ReflectY MT" = "^fg(" ++ colorGreen ++ ")Mirror XY^fg()"
 
  +
myWorkspaceL = (dzenClickStyleL workspaceCA $ dzenBoxStyleL blue2BoxPP $ labelL "WORKSPACE") ++! (dzenBoxStyleL whiteBoxPP $ onLogger namedWorkspaces logCurrent) where
layoutText "Minimize ReflectX ReflectY G" = "^fg(" ++ colorGreen ++ ")Mosaic XY^fg()"
 
  +
namedWorkspaces w
layoutText "Minimize ReflectX ReflectY C" = "^fg(" ++ colorGreen ++ ")Mirror XY^fg()"
 
layoutText x = "^fg(" ++ colorGreen ++ ")" ++ x ++ "^fg()"
+
| (elem w $ map show [0..9]) == True = "^fg(" ++ colorGreen ++ ")" ++ w ++ "^fg(" ++ colorGray ++ ")|^fg()" ++ workspaceNames !! (mod ((read w::Int) - 1) 10)
  +
| otherwise = "^fg(" ++ colorRed ++ ")x^fg(" ++ colorGray ++ ")|^fg()" ++ w
--clickable config
 
wrapClickLayout content = "^ca(1,xdotool key super+space)" ++ content ++ "^ca()" --clickable layout
 
wrapClickTitle content = "^ca(1,xdotool key super+j)" ++ content ++ "^ca()" --clickable title
 
wrapClickWorkSpace (idx,str) = "^ca(1," ++ xdo "w;" ++ xdo index ++ ")" ++ "^ca(3," ++ xdo "e;" ++ xdo index ++ ")" ++ str ++ "^ca()^ca()" --clickable workspaces
 
where
 
wsIdxToString Nothing = "1"
 
wsIdxToString (Just n) = show (n+1)
 
index = wsIdxToString (elemIndex idx myWorkspaces)
 
xdo key = "xdotool key super+" ++ key
 
   
   
Line 323: Line 622:
 
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
 
  +
[((modMask .|. shiftMask, xK_q), io (exitWith ExitSuccess)) --Quit xmonad
, ((mod1Mask, xK_F2), shellPrompt myXPConfig) --Launch Xmonad shell prompt
 
, ((modMask, xK_F2), xmonadPrompt myXPConfig) --Launch Xmonad prompt
+
, ((modMask, xK_q), killAndRestart) --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 .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf) --Launch default terminal
, ((modMask, xK_c), kill) --Close focused window
 
  +
--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 .|. controlMask, xK_Right), withFocused (keysResizeWindow (30,0) (0,0))) --Expand floated window horizontally by 50 pixels
+
, ((modMask .|. shiftMask, xK_t), rectFloatFocused) --Push window into float
, ((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
  +
, ((modMask .|. mod1Mask, xK_Left), withFocused (keysMoveWindow (-30,0))) -- move floated window 10 pixels left
, ((modMask , xK_s), spawn "xscreensaver-command -lock") --Lock screen
 
, ((modMask .|. shiftMask, xK_q), io (exitWith ExitSuccess)) --Quit xmonad
+
, ((modMask .|. mod1Mask, xK_Right), withFocused (keysMoveWindow (30,0))) -- move floated window 10 pixels right
  +
, ((modMask .|. mod1Mask, xK_Up), withFocused (keysMoveWindow (0,-30))) -- move floated window 10 pixels up
, ((modMask, xK_q), restart "xmonad" True) --Restart xmonad
 
  +
, ((modMask .|. mod1Mask, xK_Down), withFocused (keysMoveWindow (0,30))) -- move floated window 10 pixels down
, ((modMask, xK_comma), toggleWS) --Toggle to the workspace displayed previously
 
  +
--Layout management bindings
, ((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, xK_space), sendMessage NextLayout) --Rotate through the available layout algorithms
  +
, ((modMask, xK_v ), sendMessage ToggleLayout) --Toggle window titles (can click drag to move windows)
, ((modMask, xK_Left), prevWS)
 
  +
, ((modMask .|. shiftMask, xK_space ), flashText myTextConfig 1 " Set to Default Layout " >> (setLayout $ XMonad.layoutHook conf)) --Reset layout to workspaces default
, ((modMask, xK_Right), nextWS) --Move to next Workspace
 
  +
, ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle TABBED) --Push layout into tabbed
, ((mod1Mask .|. controlMask, xK_Right), nextWS)
 
, ((0, xF86XK_AudioMute), spawn "sh /home/nnoell/bin/voldzen.sh t -d") --Mute/unmute volume
+
, ((modMask .|. controlMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle FLOATED) --Push layout into float
  +
, ((modMask .|. shiftMask, xK_z), sendMessage $ XMonad.Layout.MultiToggle.Toggle MIRROR) --Push layout into mirror
, ((0, xF86XK_AudioRaiseVolume), spawn "sh /home/nnoell/bin/voldzen.sh + -d") --Raise volume
 
  +
, ((modMask .|. shiftMask, xK_x), sendMessage $ XMonad.Layout.MultiToggle.Toggle REFLECTX) --Reflect layout by X
, ((0, xF86XK_AudioLowerVolume), spawn "sh /home/nnoell/bin/voldzen.sh - -d") --Lower volume
 
, ((0, xF86XK_AudioNext), spawn "ncmpcpp next") --next song
+
, ((modMask .|. shiftMask, xK_y), sendMessage $ XMonad.Layout.MultiToggle.Toggle REFLECTY) --Reflect layout by Y
  +
--Gaps management bindings
, ((0, xF86XK_AudioPrev), spawn "ncmpcpp prev") --prev song
 
  +
, ((modMask .|. controlMask, xK_t), sendMessage $ ToggleStruts ) --toogle the all struts
, ((0, xF86XK_AudioPlay), spawn "ncmpcpp toggle") --toggle song
 
  +
, ((modMask .|. controlMask, xK_u), sendMessage $ ToggleStrut U) --toogle the top strut
, ((0, xF86XK_AudioStop), spawn "ncmpcpp stop") --stop song
 
  +
, ((modMask .|. controlMask, xK_d), sendMessage $ ToggleStrut D) --toogle the bottom strut
, ((0, xF86XK_MonBrightnessUp), spawn "sh /home/nnoell/bin/bridzen.sh") --Raise brightness
 
  +
--Scripts management bindings
, ((0, xF86XK_MonBrightnessDown), spawn "sh /home/nnoell/bin/bridzen.sh") --Lower brightness
 
, ((0, xF86XK_ScreenSaver), spawn "xscreensaver-command -lock") --Lock screen
+
, ((modMask, xK_x), spawn "/usr/bin/xcalib -invert -alter") --Invert colors in X
, ((0, xK_Print), spawn "scrot '%Y-%m-%d_$wx$h.png'") --Take a screenshot
+
, ((modMask, xK_d), spawn "/usr/bin/killall dzen2 haskell-cpu-usage.out") --Kill dzen2
  +
, ((0, 0x1008ffa9), spawn "/home/nnoell/bin/touchpadtoggle.sh") --Toggle touchpad (xmodmap -pk | grep -i toggle)
]
 
  +
, ((0, xF86XK_AudioMute), spawn "/home/nnoell/bin/voldzen.sh t -d") --Mute/unmute volume
++
 
[((m .|. modMask, k), windows $ f i) --Switch to n workspaces and send client to n workspaces
+
, ((0, xF86XK_AudioRaiseVolume), spawn "/home/nnoell/bin/voldzen.sh + -d") --Raise volume
  +
, ((mod1Mask, xK_Up), spawn "/home/nnoell/bin/voldzen.sh + -d")
| (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
 
  +
, ((0, xF86XK_AudioLowerVolume), spawn "/home/nnoell/bin/voldzen.sh - -d") --Lower volume
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
 
  +
, ((mod1Mask, xK_Down), spawn "/home/nnoell/bin/voldzen.sh - -d")
++
 
  +
, ((0, xF86XK_AudioNext), flashText myTextConfig 1 " Next Song " >> spawn "/usr/bin/ncmpcpp next") --Next song
[((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f)) --Switch to n screens and send client to n screens
 
  +
, ((mod1Mask, xK_Right), flashText myTextConfig 1 " Next Song " >> spawn "/usr/bin/ncmpcpp next")
| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
 
  +
, ((0, xF86XK_AudioPrev), flashText myTextConfig 1 " Previous Song " >> spawn "/usr/bin/ncmpcpp prev") --Prev song
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
 
  +
, ((mod1Mask, xK_Left), flashText myTextConfig 1 " Previous Song " >> spawn "/usr/bin/ncmpcpp prev")
where
 
  +
, ((0, xF86XK_AudioPlay), flashText myTextConfig 1 " Song Toggled " >> spawn "/usr/bin/ncmpcpp toggle") --Toggle song
  +
, ((mod1Mask .|. controlMask, xK_Down), flashText myTextConfig 1 " Song Toggled " >> spawn "/usr/bin/ncmpcpp toggle")
  +
, ((0, xF86XK_AudioStop), flashText myTextConfig 1 " Song Stopped " >> spawn "/usr/bin/ncmpcpp stop") --Stop song
  +
, ((mod1Mask .|. controlMask, xK_Up), flashText myTextConfig 1 " Song Stopped " >> spawn "ncmpcpp stop")
  +
, ((0, xF86XK_MonBrightnessUp), spawn "/home/nnoell/bin/bridzen.sh") --Raise brightness
  +
, ((0, xF86XK_MonBrightnessDown), spawn "/home/nnoell/bin/bridzen.sh") --Lower brightness
  +
, ((0, xF86XK_ScreenSaver), spawn "/home/nnoell/bin/turnoffscreen.sh") --Lock screen
  +
, ((0, xK_Print), spawn "/usr/bin/scrot '%Y-%m-%d_$wx$h.png'") --Take a screenshot
  +
, ((modMask , xK_s), spawn "/home/nnoell/bin/turnoffscreen.sh") --Turn off screen
  +
--Workspaces management bindings
  +
, ((mod1Mask, xK_comma), flashText myTextConfig 1 " Toggled to Previous Workspace " >> toggleWS) --Toggle to the workspace displayed previously
  +
, ((mod1Mask, xK_masculine), flashText myTextConfig 1 " Switching with Workspace 1 " >> toggleOrView (myWorkspaces !! 0)) --If ws != 0 then move to workspace 0, else move to latest ws I was
  +
, ((mod1Mask .|. controlMask, xK_Left), flashText myTextConfig 1 " Moved to Previous Workspace " >> prevWS) --Move to previous Workspace
  +
, ((mod1Mask .|. controlMask, xK_Right), flashText myTextConfig 1 " Moved to Next Workspace " >> nextWS) --Move to next Workspace
  +
, ((modMask .|. shiftMask, xK_n), flashText myTextConfig 1 " Shifted to Next Workspace " >> shiftToNext) --Send client to next workspace
  +
, ((modMask .|. shiftMask, xK_p), flashText myTextConfig 1 " Shifted to Previous Workspace " >> 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
 
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
 
rectFloatFocused = withFocused $ \f -> windows =<< appEndo `fmap` runQuery (doRectFloat $ RationalRect 0.05 0.05 0.9 0.9) f
  +
killAndRestart = do
  +
spawn "/usr/bin/killall dzen2 haskell-cpu-usage.out"
  +
liftIO $ threadDelay 1000000
  +
restart "xmonad" True
   
 
-- Mouse bindings
 
-- Mouse bindings
 
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 21:31, 19 August 2013

xmonad.hs

--------------------------------------------------------------------------------------------
-- File   : ~/.xmonad/xmonad.hs                                                           --
-- Author : Nnoell <nnoell3[at]gmail.com>                                                 --
-- Deps   : DzenBoxLogger.hs                                                              --
-- Desc   : My XMonad config                                                              --
-- Note   : Do not use "xmonad --recompile", it will throw errors because of non-official --
--          modules. Compile it manually with "ghc -o <outputName> xmonad.hs". EG:        --
--          $ cd ~/.xmonad/                                                               --
--          $ ghc -o xmonad-x86_64-linux xmonad.hs                                        --
--------------------------------------------------------------------------------------------

-- Options
{-# LANGUAGE DeriveDataTypeable, NoMonomorphismRestriction, MultiParamTypeClasses, ImplicitParams #-}

-- Modules
import XMonad
import XMonad.StackSet (RationalRect(..), currentTag)
import XMonad.Layout
import XMonad.Layout.IM
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
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.ToggleLayouts
import XMonad.Layout.ComboP
import XMonad.Layout.MagicFocus
import XMonad.Layout.WindowNavigation
import XMonad.Layout.WindowSwitcherDecoration
import XMonad.Layout.DraggingVisualizer
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.Loggers
import XMonad.Util.Run (spawnPipe)
import XMonad.Util.Scratchpad
import XMonad.Util.NamedScratchpad
import XMonad.Actions.CycleWS
import XMonad.Actions.ShowText
import XMonad.Actions.GridSelect
import XMonad.Actions.MouseResize
import XMonad.Actions.FloatKeys
import Data.Monoid
import Data.List
import Graphics.X11.ExtraTypes.XF86
import System.Exit
import System.IO (Handle, hPutStrLn)
import Control.Concurrent (threadDelay)
import Control.Exception as E
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

-- Non-official modules
import DzenBoxLoggers


--------------------------------------------------------------------------------------------
-- MAIN                                                                                   --
--------------------------------------------------------------------------------------------

main :: IO ()
main = do
	topLeftBar  <- spawnPipe $ dzenFlagsToStr dzenTopLeftFlags
	topRightBar <- spawnPipe $ dzenFlagsToStr dzenTopRightFlags
	botLeftBar  <- spawnPipe $ dzenFlagsToStr dzenBotLeftFlags
	botRightBar <- spawnPipe $ dzenFlagsToStr dzenBotRightFlags
	xmonad $ myUrgencyHook $ defaultConfig
		{ terminal           = "urxvtc"
		, modMask            = mod4Mask
		, focusFollowsMouse  = True
		, clickJustFocuses   = True
		, borderWidth        = 1
		, normalBorderColor  = colorBlackAlt
		, focusedBorderColor = colorWhiteAlt2
		, layoutHook         = myLayoutHook
		, workspaces         = myWorkspaces
		, manageHook         = myManageHook <+> manageScratchPad <+> manageDocks <+> dynamicMasterHook
		, logHook            = myBotLeftLogHook botLeftBar <+> myBotRightLogHook botRightBar <+> myTopLeftLogHook topLeftBar <+> myTopRightLogHook topRightBar <+> ewmhDesktopsLogHook >> setWMName "LG3D"
		, handleEventHook    = myHandleEventHook
		, keys               = myKeys
		, mouseBindings      = myMouseBindings
		, startupHook        = myStartupHook
		}


--------------------------------------------------------------------------------------------
-- LOOK AND FEEL CONFIG                                                                   --
--------------------------------------------------------------------------------------------

-- Colors, fonts and paths
dzenFont       = "-*-montecarlo-medium-r-normal-*-11-*-*-*-*-*-*-*"
colorBlack     = "#020202" --Background
colorBlackAlt  = "#1c1c1c" --Black Xdefaults
colorGray      = "#444444" --Gray
colorGrayAlt   = "#101010" --Gray dark
colorGrayAlt2  = "#404040"
colorGrayAlt3  = "#252525"
colorWhite     = "#a9a6af" --Foreground
colorWhiteAlt  = "#9d9d9d" --White dark
colorWhiteAlt2 = "#b5b3b3"
colorWhiteAlt3 = "#707070"
colorMagenta   = "#8e82a2"
colorBlue      = "#44aacc"
colorBlueAlt   = "#3955c4"
colorRed       = "#f7a16e"
colorRedAlt    = "#e0105f"
colorGreen     = "#66ff66"
colorGreenAlt  = "#558965"
boxLeftIcon    = "/home/nnoell/.icons/xbm_icons/subtle/boxleft.xbm"   --left icon of dzen logger boxes
boxLeftIcon2   = "/home/nnoell/.icons/xbm_icons/subtle/boxleft2.xbm"  --left icon2 of dzen logger boxes
boxRightIcon   = "/home/nnoell/.icons/xbm_icons/subtle/boxright.xbm"  --right icon of dzen logger boxes
xRes           = 1366
yRes           = 768
panelHeight    = 14  --height of top and bottom panels
boxHeight      = 14  --height of dzen logger box
topPanelSepPos = 950 --left-right alignment pos of top panel
botPanelSepPos = 400 --left-right alignment pos of bottom panel

-- Title theme
myTitleTheme :: Theme
myTitleTheme = defaultTheme
	{ fontName            = dzenFont
	, inactiveBorderColor = colorGrayAlt2
	, inactiveColor       = colorGrayAlt3
	, inactiveTextColor   = colorWhiteAlt3
	, activeBorderColor   = colorGrayAlt2
	, activeColor         = colorGrayAlt2
	, activeTextColor     = colorWhiteAlt2
	, 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            = panelHeight
	, 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
	}

-- Flash text config
myTextConfig :: ShowTextConfig
myTextConfig = STC
	{ st_font = dzenFont
	, st_bg   = colorBlack
	, st_fg   = colorWhite
	}

-- Dzen logger box pretty printing themes
gray2BoxPP :: BoxPP
gray2BoxPP = BoxPP
	{ bgColorBPP   = colorBlack
	, fgColorBPP   = colorGray
	, boxColorBPP  = colorGrayAlt
	, leftIconBPP  = boxLeftIcon2
	, rightIconBPP = boxRightIcon
	, boxHeightBPP = boxHeight
	}

blueBoxPP :: BoxPP
blueBoxPP = BoxPP
	{ bgColorBPP   = colorBlack
	, fgColorBPP   = colorBlue
	, boxColorBPP  = colorGrayAlt
	, leftIconBPP  = boxLeftIcon
	, rightIconBPP = boxRightIcon
	, boxHeightBPP = boxHeight
	}

blue2BoxPP :: BoxPP
blue2BoxPP = BoxPP
	{ bgColorBPP   = colorBlack
	, fgColorBPP   = colorBlue
	, boxColorBPP  = colorGrayAlt
	, leftIconBPP  = boxLeftIcon2
	, rightIconBPP = boxRightIcon
	, boxHeightBPP = boxHeight
	}

whiteBoxPP :: BoxPP
whiteBoxPP = BoxPP
	{ bgColorBPP   = colorBlack
	, fgColorBPP   = colorWhiteAlt
	, boxColorBPP  = colorGrayAlt
	, leftIconBPP  = boxLeftIcon
	, rightIconBPP = boxRightIcon
	, boxHeightBPP = boxHeight
	}

blackBoxPP :: BoxPP
blackBoxPP = BoxPP
	{ bgColorBPP   = colorBlack
	, fgColorBPP   = colorBlack
	, boxColorBPP  = colorGrayAlt
	, leftIconBPP  = boxLeftIcon
	, rightIconBPP = boxRightIcon
	, boxHeightBPP = boxHeight
	}

white2BBoxPP :: BoxPP
white2BBoxPP = BoxPP
	{ bgColorBPP   = colorBlack
	, fgColorBPP   = colorBlack
	, boxColorBPP  = colorWhiteAlt
	, leftIconBPP  = boxLeftIcon2
	, rightIconBPP = boxRightIcon
	, boxHeightBPP = boxHeight
	}

blue2BBoxPP :: BoxPP --current workspace
blue2BBoxPP = BoxPP
	{ bgColorBPP   = colorBlack
	, fgColorBPP   = colorBlack
	, boxColorBPP  = colorBlue
	, leftIconBPP  = boxLeftIcon2
	, rightIconBPP = boxRightIcon
	, boxHeightBPP = boxHeight
	}

green2BBoxPP :: BoxPP --urgent workspace
green2BBoxPP = BoxPP
	{ bgColorBPP   = colorBlack
	, fgColorBPP   = colorBlack
	, boxColorBPP  = colorGreen
	, leftIconBPP  = boxLeftIcon2
	, rightIconBPP = boxRightIcon
	, boxHeightBPP = boxHeight
	}

-- Dzen logger clickable areas
calendarCA :: CA
calendarCA = CA
	{ leftClickCA   = "/home/nnoell/bin/dzencal.sh"
	, middleClickCA = "/home/nnoell/bin/dzencal.sh"
	, rightClickCA  = "/home/nnoell/bin/dzencal.sh"
	, wheelUpCA     = "/home/nnoell/bin/dzencal.sh"
	, wheelDownCA   = "/home/nnoell/bin/dzencal.sh"
	}

layoutCA :: CA
layoutCA = CA
	{ leftClickCA   = "/usr/bin/xdotool key super+space"
	, middleClickCA = "/usr/bin/xdotool key super+v"
	, rightClickCA  = "/usr/bin/xdotool key super+shift+space"
	, wheelUpCA     = "/usr/bin/xdotool key super+f"
	, wheelDownCA   = "/usr/bin/xdotool key super+control+f"
	}

workspaceCA :: CA
workspaceCA = CA
	{ leftClickCA   = "/usr/bin/xdotool key super+1"
	, middleClickCA = "/usr/bin/xdotool key super+g"
	, rightClickCA  = "/usr/bin/xdotool key super+0"
	, wheelUpCA     = "/usr/bin/xdotool key ctrl+alt+Right"
	, wheelDownCA   = "/usr/bin/xdotool key ctrl+alt+Left"
	}

focusCA :: CA
focusCA = CA
	{ leftClickCA   = "/usr/bin/xdotool key super+m"
	, middleClickCA = "/usr/bin/xdotool key super+c"
	, rightClickCA  = "/usr/bin/xdotool key super+shift+m"
	, wheelUpCA     = "/usr/bin/xdotool key super+shift+j"
	, wheelDownCA   = "/usr/bin/xdotool key super+shift+k"
	}

-- Workspace index
myWorkspaces :: [WorkspaceId]
myWorkspaces = map show $ [1..9] ++ [0]

-- Workspace names
workspaceNames :: [WorkspaceId]
workspaceNames = ["Terminal", "Network", "Development", "Graphics", "Chatting", "Video", "Alternate", "Alternate", "Alternate", "Alternate"]

-- Layout names (must be one word name and not equal to: Mirror, ReflectX, ReflectY, Switcher, Normal and Unique)
myTileName = "Tiled"
myMirrName = "Mirror"
myMosAName = "Mosaic"
myOneBName = "OneBig"
myMTabName = "MstrTab"
myChatName = "Chat"
myTabbName = "Tabbed"
myTTabName = "TwoTab"
myFTabName = "Full"
myFloaName = "Float"


--------------------------------------------------------------------------------------------
-- STARTUP HOOK CONFIG                                                                    --
--------------------------------------------------------------------------------------------

-- Startup Hook
myStartupHook = spawn "/home/nnoell/.xmonad/apps/haskell-cpu-usage.out 5" <+> setDefaultCursor xC_left_ptr <+> startDelayTimer where
	startDelayTimer = do
		liftIO $ threadDelay $ 1000000 --needed so that xmonad can be recompiled and launched on the fly without crashing
		startTimer 1 >>= XS.put . TID


--------------------------------------------------------------------------------------------
-- 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 = fullscreenEventHook <+> docksEventHook <+> clockEventHook <+> handleTimerEvent <+> notFocusFloat where
	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
	notFocusFloat = followOnlyIf (fmap not isFloat) where --Do not focusFollowMouse on Float layout
		isFloat = fmap (isSuffixOf myFloaName) $ gets (description . W.layout . W.workspace . W.current . windowset)


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

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

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

-- Switcher Layouts
myTile = smartBorders $ toggleLayouts (named ("Switcher " ++ myTileName) myTileS) $ named ("Normal " ++ myTileName) $ ResizableTall 1 0.03 0.5 [] where
	myTileS = windowSwitcherDecoration shrinkText myTitleTheme (draggingVisualizer $ ResizableTall 1 0.03 0.5 [])
myMirr = smartBorders $ toggleLayouts (named ("Switcher " ++ myMirrName) myMirrS) $ named ("Normal " ++ myMirrName) $ Mirror $ ResizableTall 1 0.03 0.5 [] where
	myMirrS = windowSwitcherDecoration shrinkText myTitleTheme (draggingVisualizer $ Mirror $ ResizableTall 1 0.03 0.5 [])
myMosA = smartBorders $ toggleLayouts (named ("Switcher " ++ myMosAName) myMosAS) $ named ("Normal " ++ myMosAName) $ MosaicAlt M.empty where
	myMosAS = windowSwitcherDecoration shrinkText myTitleTheme (draggingVisualizer $ MosaicAlt M.empty)
myOneB = smartBorders $ toggleLayouts (named ("Switcher " ++ myOneBName) myOneBS) $ named ("Normal " ++ myOneBName) $ OneBig 0.75 0.65 where
	myOneBS = windowSwitcherDecoration shrinkText myTitleTheme (draggingVisualizer $ OneBig 0.75 0.65)
myMTab = smartBorders $ toggleLayouts (named ("Switcher " ++ myMTabName) myMTabS) $ named ("Normal " ++ myMTabName) $ mastered 0.01 0.4 $ tabbed shrinkText myTitleTheme where
	myMTabS = windowSwitcherDecoration shrinkText myTitleTheme (draggingVisualizer $ mastered 0.01 0.4 $ tabbed shrinkText myTitleTheme)
myChat = smartBorders $ toggleLayouts (named ("Switcher " ++ myChatName) $ withIM (0.20) (Title "Buddy List") myChatS) (named ("Normal " ++ myChatName) $ withIM (0.20) (Title "Buddy List") $ MosaicAlt M.empty) where
	myChatS = windowSwitcherDecoration shrinkText myTitleTheme (draggingVisualizer $ MosaicAlt M.empty)

-- Unique Layouts
myTabb = smartBorders $ named ("Unique " ++ myTabbName) $ tabbed shrinkText myTitleTheme
myTTab = smartBorders $ named ("Unique " ++ myTTabName) $ combineTwoP (OneBig 0.75 0.75) (tabbed shrinkText myTitleTheme) (tabbed shrinkText myTitleTheme) (ClassName "Chromium")
myFTab = smartBorders $ named ("Unique " ++ myFTabName) $ tabbedAlways shrinkText myTitleTheme
myFloa = named ("Unique " ++ myFloaName) $ mouseResize $ noFrillsDeco shrinkText myTitleTheme simplestFloat

-- Layout hook
myLayoutHook = avoidStruts
	$ configurableNavigation noNavigateBorders
	$ minimize
	$ maximize
	$ mkToggle (single TABBED)
	$ mkToggle (single FLOATED)
	$ mkToggle (single MIRROR)
	$ mkToggle (single REFLECTX)
	$ mkToggle (single REFLECTY)
	$ onWorkspace (myWorkspaces !! 1) webLayouts
	$ onWorkspace (myWorkspaces !! 2) codeLayouts
	$ onWorkspace (myWorkspaces !! 4) chatLayouts
	$ allLayouts where
		webLayouts  = myTabb ||| myTTab
		codeLayouts = myMTab ||| myOneB ||| myTile
		chatLayouts = myChat
		allLayouts  = myTile ||| myOneB ||| myMirr ||| myMosA ||| myMTab


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

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

-- Manage hook
myManageHook :: ManageHook
myManageHook = composeAll . concat $
	[ [ resource  =? r --> doIgnore                    | r <- myIgnores ]
	, [ className =? c --> doShift (myWorkspaces !! 1) | c <- myWebS    ]
	, [ className =? c --> doShift (myWorkspaces !! 2) | c <- myCodeS   ]
	, [ className =? c --> doShift (myWorkspaces !! 3) | c <- myGfxS    ]
	, [ className =? c --> doShift (myWorkspaces !! 4) | c <- myChatS   ]
	, [ className =? c --> doShift (myWorkspaces !! 7) | c <- myAlt3S   ]
	, [ className =? c --> doCenterFloat               | c <- myFloatCC ]
	, [ name      =? n --> doCenterFloat               | n <- myFloatCN ]
	, [ name      =? n --> doSideFloat NW              | n <- myFloatSN ]
	, [ className =? c --> doF W.focusDown             | c <- myFocusDC ]
	, [ isFullscreen   --> doFullFloat ]
	] where
		name      = stringProperty "WM_NAME"
		myIgnores = ["desktop","desktop_window"]
		myWebS    = ["Chromium","Firefox", "Opera"]
		myCodeS   = ["NetBeans IDE 7.3"]
		myChatS   = ["Pidgin", "Xchat"]
		myGfxS    = ["Gimp", "gimp", "GIMP"]
		myAlt3S   = ["Amule", "Transmission-gtk"]
		myFloatCC = ["MPlayer", "mplayer2", "File-roller", "zsnes", "Gcalctool", "Exo-helper-1", "Gksu", "PSX", "Galculator", "Nvidia-settings", "XFontSel"
				    , "XCalc", "XClock", "Ossxmix", "Xvidcap", "Main", "Wicd-client.py"]
		myFloatCN = ["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"]


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

-- urgencyHook
myUrgencyHook :: LayoutClass l Window => XConfig l -> XConfig l
myUrgencyHook = withUrgencyHook dzenUrgencyHook
	{ duration = 2000000
	, args     = ["-x", "0", "-y", "0", "-h", show panelHeight, "-w", show topPanelSepPos, "-fn", dzenFont, "-bg", colorBlack, "-fg", colorGreen]
	}

-- Dzen top left bar flags
dzenTopLeftFlags :: DF
dzenTopLeftFlags = DF
	{ xPosDF       = 0
	, yPosDF       = 0
	, widthDF      = topPanelSepPos
	, heightDF     = panelHeight
	, alignementDF = "l"
	, fgColorDF    = colorWhiteAlt
	, bgColorDF    = colorBlack
	, fontDF       = dzenFont
	, eventDF      = "onstart=lower"
	, extrasDF     = "-p"
	}

-- Top left bar logHook
myTopLeftLogHook :: Handle -> X ()
myTopLeftLogHook h = dynamicLogWithPP $ defaultPP
	{ ppOutput = hPutStrLn h
	, ppOrder = \(_:_:_:x) -> x
	, ppSep = " "
	, ppExtras = [ myLayoutL, myWorkspaceL, myFocusL ]
	}

-- Dzen top right bar flags
dzenTopRightFlags :: DF
dzenTopRightFlags = DF
	{ xPosDF       = topPanelSepPos
	, yPosDF       = 0
	, widthDF      = xRes - topPanelSepPos
	, heightDF     = panelHeight
	, alignementDF = "r"
	, fgColorDF    = colorWhiteAlt
	, bgColorDF    = colorBlack
	, fontDF       = dzenFont
	, eventDF      = "onstart=lower"
	, extrasDF     = "-p"
	}

-- Top right bar logHook
myTopRightLogHook :: Handle -> X ()
myTopRightLogHook h = dynamicLogWithPP $ defaultPP
	{ ppOutput  = hPutStrLn h
	, ppOrder = \(_:_:_:x) -> x
	, ppSep = " "
	, ppExtras  = [ myUptimeL, myDateL ]
	}

-- Dzen bottom left bar flags
dzenBotLeftFlags :: DF
dzenBotLeftFlags = DF
	{ xPosDF       = 0
	, yPosDF       = yRes - panelHeight
	, widthDF      = botPanelSepPos
	, heightDF     = panelHeight
	, alignementDF = "l"
	, fgColorDF    = colorWhiteAlt
	, bgColorDF    = colorBlack
	, fontDF       = dzenFont
	, eventDF      = "onstart=lower"
	, extrasDF     = "-p"
	}

-- Bottom left bar logHook
myBotLeftLogHook :: Handle -> X ()
myBotLeftLogHook h = dynamicLogWithPP . namedScratchpadFilterOutWorkspacePP $ defaultPP
	{ ppOutput          = hPutStrLn h
	, ppOrder           = \(ws:l:_:x) -> [ws] ++ x
	, ppSep             = " "
	, ppWsSep           = ""
	, ppCurrent         = dzenBoxStyle blue2BBoxPP
	, ppUrgent          = dzenBoxStyle green2BBoxPP . dzenClickWorkspace
	, ppVisible         = dzenBoxStyle blackBoxPP . dzenClickWorkspace
	, ppHiddenNoWindows = dzenBoxStyle blackBoxPP . dzenClickWorkspace
	, ppHidden          = dzenBoxStyle whiteBoxPP . dzenClickWorkspace
	, ppExtras          = [ myFsL ]
	} where
		dzenClickWorkspace 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

-- Dzen bottom right bar flags
dzenBotRightFlags :: DF
dzenBotRightFlags = DF
	{ xPosDF       = botPanelSepPos
	, yPosDF       = yRes - panelHeight
	, widthDF      = xRes - botPanelSepPos
	, heightDF     = panelHeight
	, alignementDF = "r"
	, fgColorDF    = colorWhiteAlt
	, bgColorDF    = colorBlack
	, fontDF       = dzenFont
	, eventDF      = "onstart=lower"
	, extrasDF     = "-p"
	}

-- Bottom right bar logHook
myBotRightLogHook :: Handle -> X ()
myBotRightLogHook h = dynamicLogWithPP $ defaultPP
	{ ppOutput          = hPutStrLn h
	, ppOrder           = \(_:_:_:x) -> x
	, ppSep             = " "
	, ppExtras          = [ myCpuL, myMemL, myTempL, myBrightL, myWifiL, myBatL ]
	}


--------------------------------------------------------------------------------------------
-- LOGGERS CONFIG                                                                         --
--------------------------------------------------------------------------------------------

myBatL       = (dzenBoxStyleL gray2BoxPP $ labelL "BATTERY") ++! (dzenBoxStyleL blueBoxPP batPercent) ++! (dzenBoxStyleL whiteBoxPP batStatus)
myWifiL      = (dzenBoxStyleL gray2BoxPP $ labelL "WIFI") ++! (dzenBoxStyleL blueBoxPP wifiSignal)
myBrightL    = (dzenBoxStyleL gray2BoxPP $ labelL "BRIGHT") ++! (dzenBoxStyleL blueBoxPP brightPerc)
myTempL      = (dzenBoxStyleL gray2BoxPP $ labelL "TEMP") ++! (dzenBoxStyleL blueBoxPP cpuTemp)
myMemL       = (dzenBoxStyleL gray2BoxPP $ labelL "MEM") ++! (dzenBoxStyleL blueBoxPP memUsage)
myCpuL       = (dzenBoxStyleL gray2BoxPP $ labelL "CPU") ++! (dzenBoxStyleL blueBoxPP $ cpuUsage "/tmp/haskell-cpu-usage.txt")
myFsL        = (dzenBoxStyleL blue2BoxPP $ labelL "ROOT") ++! (dzenBoxStyleL whiteBoxPP $ fsPerc "/") ++! (dzenBoxStyleL blueBoxPP $ labelL "HOME") ++! (dzenBoxStyleL whiteBoxPP $ fsPerc "/home")
myDateL      = (dzenBoxStyleL white2BBoxPP $ date "%A") ++! (dzenBoxStyleL whiteBoxPP $ date $ "%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()") ++! (dzenClickStyleL calendarCA $ dzenBoxStyleL blueBoxPP $ labelL "CALENDAR")
myUptimeL    = (dzenBoxStyleL blue2BoxPP $ labelL "UPTIME") ++! (dzenBoxStyleL whiteBoxPP uptime)
myFocusL     = (dzenClickStyleL focusCA $ dzenBoxStyleL white2BBoxPP $ labelL "FOCUS") ++! (dzenBoxStyleL whiteBoxPP $ shortenL 100 logTitle)
myLayoutL    = (dzenClickStyleL layoutCA $ dzenBoxStyleL blue2BoxPP $ labelL "LAYOUT") ++! (dzenBoxStyleL whiteBoxPP $ onLogger (layoutText . removeWord . removeWord) logLayout) where
	removeWord xs = tail $ dropWhile (/= ' ') xs
	layoutText xs
		| isPrefixOf "Mirror" xs   = layoutText $ removeWord xs ++ " ^fg(" ++ colorBlue ++ ")M^fg(" ++ colorGray ++ ")|^fg(" ++ colorWhiteAlt ++ ")"
		| isPrefixOf "ReflectY" xs = layoutText $ removeWord xs ++ " ^fg(" ++ colorBlue ++ ")Y^fg(" ++ colorGray ++ ")|^fg(" ++ colorWhiteAlt ++ ")"
		| isPrefixOf "ReflectX" xs = layoutText $ removeWord xs ++ " ^fg(" ++ colorBlue ++ ")X^fg(" ++ colorGray ++ ")|^fg(" ++ colorWhiteAlt ++ ")"
		| isPrefixOf "Switcher" xs = layoutText $ removeWord xs ++ " ^fg(" ++ colorRed ++ ")S^fg(" ++ colorGray ++ ")|^fg(" ++ colorWhiteAlt ++ ")"
		| isPrefixOf "Normal" xs   = layoutText $ removeWord xs ++ " ^fg(" ++ colorGreen ++ ")N^fg(" ++ colorGray ++ ")|^fg(" ++ colorWhiteAlt ++ ")"
		| isPrefixOf "Unique" xs   = layoutText $ removeWord xs ++ " ^fg(" ++ colorGreen ++ ")U^fg(" ++ colorGray ++ ")|^fg(" ++ colorWhiteAlt ++ ")"
		| otherwise                = concat $ reverse $ words xs
myWorkspaceL = (dzenClickStyleL workspaceCA $ dzenBoxStyleL blue2BoxPP $ labelL "WORKSPACE") ++! (dzenBoxStyleL whiteBoxPP $ onLogger namedWorkspaces logCurrent) where
	namedWorkspaces w
		| (elem w $ map show [0..9]) == True = "^fg(" ++ colorGreen ++ ")" ++ w ++ "^fg(" ++ colorGray ++ ")|^fg()" ++ workspaceNames !! (mod ((read w::Int) - 1) 10)
		| otherwise                          = "^fg(" ++ colorRed ++ ")x^fg(" ++ colorGray ++ ")|^fg()" ++ w


--------------------------------------------------------------------------------------------
-- 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), killAndRestart)                                  --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
	, ((modMask .|. mod1Mask, xK_Left), withFocused (keysMoveWindow (-30,0))) -- move floated window 10 pixels left
	, ((modMask .|. mod1Mask, xK_Right), withFocused (keysMoveWindow (30,0))) -- move floated window 10 pixels right
	, ((modMask .|. mod1Mask, xK_Up), withFocused (keysMoveWindow (0,-30)))   -- move floated window 10 pixels up
	, ((modMask .|. mod1Mask, xK_Down), withFocused (keysMoveWindow (0,30)))  -- move floated window 10 pixels down
	--Layout management bindings
	, ((modMask, xK_space), sendMessage NextLayout)                                                                                    --Rotate through the available layout algorithms
	, ((modMask, xK_v ), sendMessage ToggleLayout)                                                                                     --Toggle window titles (can click drag to move windows)
	, ((modMask .|. shiftMask, xK_space ), flashText myTextConfig 1 " Set to Default Layout " >> (setLayout $ XMonad.layoutHook conf)) --Reset layout to workspaces 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 $ XMonad.Layout.MultiToggle.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 $ ToggleStruts ) --toogle the all struts
	, ((modMask .|. controlMask, xK_u), sendMessage $ ToggleStrut U) --toogle the top strut
	, ((modMask .|. controlMask, xK_d), sendMessage $ ToggleStrut D) --toogle the bottom strut
	--Scripts management bindings
	, ((modMask, xK_x), spawn "/usr/bin/xcalib -invert -alter")                                                           --Invert colors in X
	, ((modMask, xK_d), spawn "/usr/bin/killall dzen2 haskell-cpu-usage.out")                                             --Kill dzen2
	, ((0, 0x1008ffa9), spawn "/home/nnoell/bin/touchpadtoggle.sh")                                                       --Toggle touchpad (xmodmap -pk | grep -i toggle)
	, ((0, xF86XK_AudioMute), spawn "/home/nnoell/bin/voldzen.sh t -d")                                                   --Mute/unmute volume
	, ((0, xF86XK_AudioRaiseVolume), spawn "/home/nnoell/bin/voldzen.sh + -d")                                            --Raise volume
	, ((mod1Mask, xK_Up), spawn "/home/nnoell/bin/voldzen.sh + -d")
	, ((0, xF86XK_AudioLowerVolume), spawn "/home/nnoell/bin/voldzen.sh - -d")                                            --Lower volume
	, ((mod1Mask, xK_Down), spawn "/home/nnoell/bin/voldzen.sh - -d")
	, ((0, xF86XK_AudioNext),  flashText myTextConfig 1 " Next Song " >> spawn "/usr/bin/ncmpcpp next")                   --Next song
	, ((mod1Mask, xK_Right), flashText myTextConfig 1 " Next Song " >> spawn "/usr/bin/ncmpcpp next")
	, ((0, xF86XK_AudioPrev), flashText myTextConfig 1 " Previous Song " >> spawn "/usr/bin/ncmpcpp prev")                --Prev song
	, ((mod1Mask, xK_Left), flashText myTextConfig 1 " Previous Song " >> spawn "/usr/bin/ncmpcpp prev")
	, ((0, xF86XK_AudioPlay), flashText myTextConfig 1 " Song Toggled " >> spawn "/usr/bin/ncmpcpp toggle")               --Toggle song
	, ((mod1Mask .|. controlMask, xK_Down), flashText myTextConfig 1 " Song Toggled " >> spawn "/usr/bin/ncmpcpp toggle")
	, ((0, xF86XK_AudioStop), flashText myTextConfig 1 " Song Stopped " >> spawn "/usr/bin/ncmpcpp stop")                 --Stop song
	, ((mod1Mask .|. controlMask, xK_Up), flashText myTextConfig 1 " Song Stopped " >> spawn "ncmpcpp stop")
	, ((0, xF86XK_MonBrightnessUp), spawn "/home/nnoell/bin/bridzen.sh")                                                  --Raise brightness
	, ((0, xF86XK_MonBrightnessDown), spawn "/home/nnoell/bin/bridzen.sh")                                                --Lower brightness
	, ((0, xF86XK_ScreenSaver), spawn "/home/nnoell/bin/turnoffscreen.sh")                                                --Lock screen
	, ((0, xK_Print), spawn "/usr/bin/scrot '%Y-%m-%d_$wx$h.png'")                                                        --Take a screenshot
	, ((modMask , xK_s), spawn "/home/nnoell/bin/turnoffscreen.sh")                                                       --Turn off screen
	--Workspaces management bindings
	, ((mod1Mask, xK_comma), flashText myTextConfig 1 " Toggled to Previous Workspace " >> toggleWS)                          --Toggle to the workspace displayed previously
	, ((mod1Mask, xK_masculine), flashText myTextConfig 1 " Switching with Workspace 1 " >> toggleOrView (myWorkspaces !! 0)) --If ws != 0 then move to workspace 0, else move to latest ws I was
	, ((mod1Mask .|. controlMask, xK_Left), flashText myTextConfig 1 " Moved to Previous Workspace " >> prevWS)               --Move to previous Workspace
	, ((mod1Mask .|. controlMask, xK_Right), flashText myTextConfig 1 " Moved to Next Workspace " >> nextWS)                  --Move to next Workspace
	, ((modMask .|. shiftMask, xK_n), flashText myTextConfig 1 " Shifted to Next Workspace " >> shiftToNext)                  --Send client to next workspace
	, ((modMask .|. shiftMask, xK_p), flashText myTextConfig 1 " Shifted to Previous Workspace " >> 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
		killAndRestart = do
			spawn "/usr/bin/killall dzen2 haskell-cpu-usage.out"
			liftIO $ threadDelay 1000000
			restart "xmonad" True

-- 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
	]