Compare commits

..

No commits in common. "080c5b71f6ad5fed2f75f931bcdf00646dfdd26b" and "5ba5b728a44c94310fff8d740dd5ec25d7065611" have entirely different histories.

View File

@ -1,6 +1,6 @@
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
{-# OPTIONS_GHC -Wno-deprecations #-} --{-# OPTIONS_GHC -Wno-deprecations #-}
import XMonad import XMonad
import XMonad.Config.Desktop import XMonad.Config.Desktop
-- Actions -- Actions
@ -280,31 +280,32 @@ makeLauncher yargs run exec close = concat
launcher = makeLauncher "-x" "eval" "\"exec " "\"" launcher = makeLauncher "-x" "eval" "\"exec " "\""
main = do sc <- IS.countScreens main = do
dzenTopBar <- spawnPipe (getTopBar sc) sc <- IS.countScreens
dzenBarbicanBar <- spawnPipe (getBarbicanBar sc) dzenTopBar <- spawnPipe (getTopBar sc)
dzenDeltachunkBar <- spawnPipe (getDeltachunkBar sc) dzenBarbicanBar <- spawnPipe (getBarbicanBar sc)
dzenFerrumBar <- spawnPipe (getFerrumBar sc) dzenDeltachunkBar <- spawnPipe (getDeltachunkBar sc)
dzenOsmiumBar <- spawnPipe (getOsmiumBar sc) dzenFerrumBar <- spawnPipe (getFerrumBar sc)
dzenSodiumBar <- spawnPipe (getSodiumBar sc) -- dzenGammachunkBar <- spawnPipe (getGammachunkBar sc)
dzenTennessineBar <- spawnPipe (getTennessineBar sc) dzenOsmiumBar <- spawnPipe (getOsmiumBar sc)
dzenBlancherBar <- spawnPipe (getBlancherBar sc) dzenSodiumBar <- spawnPipe (getSodiumBar sc)
xmonad $ docks $ ewmh $ desktopConfig { dzenTennessineBar <- spawnPipe (getTennessineBar sc)
workspaces = ["shell","qb","pindrop","kofc","VM"] dzenBlancherBar <- spawnPipe (getBlancherBar sc)
, terminal = myTerminal xmonad $ docks $ ewmh $ desktopConfig {
, focusFollowsMouse = True workspaces = ["shell","qb","pindrop","kofc","VM"]
, manageHook = manageDocks <+> myManageHook -- <+> manageHook desktopConfig , terminal = myTerminal
, handleEventHook = handleEventHook desktopConfig , focusFollowsMouse = True
, layoutHook = avoidStruts $ gaps [(D,108)] $ layoutH , manageHook = manageDocks <+> myManageHook <+> manageHook desktopConfig
, logHook = myLogHook dzenTopBar >> fadeHook >> updatePointer (0.5, 0.5) (0, 0) --, handleEventHook = docksEventHook <+> handleEventHook desktopConfig
, borderWidth = 1 , handleEventHook = handleEventHook desktopConfig
, normalBorderColor = "#282828" , layoutHook = avoidStruts $ gaps [(D,108)] $ layoutH
, focusedBorderColor = "#ebdbb2" , logHook = myLogHook dzenTopBar >> fadeHook >> updatePointer (0.5, 0.5) (0, 0)
, modMask = winKey , borderWidth = 1
, startupHook = myStartup , normalBorderColor = "#282828"
} , focusedBorderColor = "#ebdbb2"
`additionalKeys` myKeys , modMask = winKey
`removeKeys` remKeys , startupHook = myStartup
} `additionalKeys` myKeys
myStartup :: X () myStartup :: X ()
@ -511,8 +512,8 @@ myKeys = [
--ifWindows (className =? "Iceweasel") (mapM_ focus) (spawnHere "iceweasel")) --ifWindows (className =? "Iceweasel") (mapM_ focus) (spawnHere "iceweasel"))
, ((winKey .|. controlMask, xK_l), sendMessage Expand) , ((winKey .|. controlMask, xK_l), sendMessage Expand)
--, ((winKey , xK_1), windows (viewOnScreen 0 "shell")) --, ((winKey , xK_1), windows (viewOnScreen 0 "shell"))
--, ((winKey , xK_1), ifWindows (className =? "Alacritty") (mapM_ focus) (spawnHere myTerminal)) , ((winKey , xK_1), ifWindows (className =? "Alacritty") (mapM_ focus) (spawnHere myTerminal))
--, ((winKey , xK_2), windows (viewOnScreen 0 "chromium")) , ((winKey , xK_2), windows (viewOnScreen 0 "chromium"))
, ((winKey , xK_a), do , ((winKey , xK_a), do
windows (viewOnScreen 1 "pindrop") windows (viewOnScreen 1 "pindrop")
--ifWindows (className =? "Pidgin") (mapM_ focus) (spawnHere "pidgin")) --ifWindows (className =? "Pidgin") (mapM_ focus) (spawnHere "pidgin"))
@ -612,7 +613,6 @@ myKeys = [
-- | (key, sc) <- zip [xK_w, xK_r] [1,0] -- For w,r keys in backwards order -- | (key, sc) <- zip [xK_w, xK_r] [1,0] -- For w,r keys in backwards order
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]] , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
remKeys = [(winKey, n) | n <- [xK_0 .. xK_9]]
--dXPConfig = defaultXPConfig { --dXPConfig = defaultXPConfig {
dXPConfig = def { dXPConfig = def {