7 Commits

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,32 +280,31 @@ makeLauncher yargs run exec close = concat
launcher = makeLauncher "-x" "eval" "\"exec " "\"" launcher = makeLauncher "-x" "eval" "\"exec " "\""
main = do main = do sc <- IS.countScreens
sc <- IS.countScreens dzenTopBar <- spawnPipe (getTopBar sc)
dzenTopBar <- spawnPipe (getTopBar sc) dzenBarbicanBar <- spawnPipe (getBarbicanBar sc)
dzenBarbicanBar <- spawnPipe (getBarbicanBar sc) dzenDeltachunkBar <- spawnPipe (getDeltachunkBar sc)
dzenDeltachunkBar <- spawnPipe (getDeltachunkBar sc) dzenFerrumBar <- spawnPipe (getFerrumBar sc)
dzenFerrumBar <- spawnPipe (getFerrumBar sc) dzenOsmiumBar <- spawnPipe (getOsmiumBar sc)
-- dzenGammachunkBar <- spawnPipe (getGammachunkBar sc) dzenSodiumBar <- spawnPipe (getSodiumBar sc)
dzenOsmiumBar <- spawnPipe (getOsmiumBar sc) dzenTennessineBar <- spawnPipe (getTennessineBar sc)
dzenSodiumBar <- spawnPipe (getSodiumBar sc) dzenBlancherBar <- spawnPipe (getBlancherBar sc)
dzenTennessineBar <- spawnPipe (getTennessineBar sc) xmonad $ desktopConfig {
dzenBlancherBar <- spawnPipe (getBlancherBar sc) workspaces = ["shell","qb","pindrop","VM"]
xmonad $ docks $ ewmh $ desktopConfig { , terminal = myTerminal
workspaces = ["shell","qb","pindrop","kofc","VM"] , focusFollowsMouse = True
, terminal = myTerminal , manageHook = manageDocks <+> myManageHook -- <+> manageHook desktopConfig
, focusFollowsMouse = True , handleEventHook = handleEventHook desktopConfig
, manageHook = manageDocks <+> myManageHook <+> manageHook desktopConfig , layoutHook = avoidStruts $ gaps [(D,108)] $ layoutH
--, handleEventHook = docksEventHook <+> handleEventHook desktopConfig , logHook = myLogHook dzenTopBar >> fadeHook >> updatePointer (0.5, 0.5) (0, 0)
, handleEventHook = handleEventHook desktopConfig , borderWidth = 1
, layoutHook = avoidStruts $ gaps [(D,108)] $ layoutH , normalBorderColor = "#282828"
, logHook = myLogHook dzenTopBar >> fadeHook >> updatePointer (0.5, 0.5) (0, 0) , focusedBorderColor = "#ebdbb2"
, borderWidth = 1 , modMask = winKey
, normalBorderColor = "#282828" , startupHook = myStartup
, focusedBorderColor = "#ebdbb2" }
, modMask = winKey `additionalKeys` myKeys
, startupHook = myStartup `removeKeys` remKeys
} `additionalKeys` myKeys
myStartup :: X () myStartup :: X ()
@ -435,7 +434,9 @@ myKeys = [
sendMessage $ ToggleGaps) sendMessage $ ToggleGaps)
, ((lAlt , xK_g), spawnHere "~/bin/google_selection.sh") , ((lAlt , xK_g), spawnHere "~/bin/google_selection.sh")
--, ((winKey , xK_g), ifWindows (className =? "Google-chrome") (mapM_ focus) (spawnHere "google-chrome")) --, ((winKey , xK_g), ifWindows (className =? "Google-chrome") (mapM_ focus) (spawnHere "google-chrome"))
, ((winKey , xK_g), ifWindows (className =? "Google-chrome") (mapM_ focus) (spawnHere "google-chrome-stable")) , ((winKey , xK_g), do
windows (viewOnScreen 0 "pindrop")
ifWindows (className =? "Google-chrome") (mapM_ focus) (spawnHere "google-chrome-stable"))
--, ((winKey , xK_r), do --, ((winKey , xK_r), do
-- windows (viewOnScreen 1 "wb") -- windows (viewOnScreen 1 "wb")
-- ifWindows (className =? "Google-chrome-stable") (mapM_ focus) (spawnHere "google-chrome-stable")) -- ifWindows (className =? "Google-chrome-stable") (mapM_ focus) (spawnHere "google-chrome-stable"))
@ -443,7 +444,7 @@ myKeys = [
--, ((winKey , xK_g), spawnHere "google-chrome --purge-memory-button ") --, ((winKey , xK_g), spawnHere "google-chrome --purge-memory-button ")
--, ((winKey , xK_i), spawnHere "iceweasel") --, ((winKey , xK_i), spawnHere "iceweasel")
--, ((winKey , xK_i), spawnHere "clementine") --, ((winKey , xK_i), spawnHere "clementine")
, ((winKey , xK_i), ifWindows (className =? "Clementine") (mapM_ killWindow) (spawnHere "clementine")) -- , ((winKey , xK_i), ifWindows (className =? "Clementine") (mapM_ killWindow) (spawnHere "clementine"))
-- , ((winKey , xK_d ), ifWindows (className =? "Goldendict") (mapM_ killWindow) (spawnHere "goldendict")) -- , ((winKey , xK_d ), ifWindows (className =? "Goldendict") (mapM_ killWindow) (spawnHere "goldendict"))
-- , ((winKey , xK_d), ifWindows (className =? "Xfce4-dict") (mapM_ killWindow) (spawnHere "xfce4-dict")) -- , ((winKey , xK_d), ifWindows (className =? "Xfce4-dict") (mapM_ killWindow) (spawnHere "xfce4-dict"))
, ((winKey , xK_d), ifWindows (className =? "Org.gnome.Dictionary") (mapM_ killWindow) (spawnHere "gnome-dictionary")) , ((winKey , xK_d), ifWindows (className =? "Org.gnome.Dictionary") (mapM_ killWindow) (spawnHere "gnome-dictionary"))
@ -507,15 +508,15 @@ myKeys = [
--ifWindows (className =? "Chromium") (mapM_ focus) (spawnHere "chromium")) --ifWindows (className =? "Chromium") (mapM_ focus) (spawnHere "chromium"))
--windows (viewOnScreen 1 "vivaldi") --windows (viewOnScreen 1 "vivaldi")
--ifWindows (className =? "Vivaldi-stable") (mapM_ focus) (spawnHere "vivaldi-stable")) --ifWindows (className =? "Vivaldi-stable") (mapM_ focus) (spawnHere "vivaldi-stable"))
windows (viewOnScreen 1 "qb") windows (viewOnScreen 0 "qb")
ifWindows (className =? "qutebrowser") (mapM_ focus) (spawnHere "qutebrowser")) ifWindows (className =? "qutebrowser") (mapM_ focus) (spawnHere "qutebrowser"))
--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 0 "pindrop")
--ifWindows (className =? "Pidgin") (mapM_ focus) (spawnHere "pidgin")) --ifWindows (className =? "Pidgin") (mapM_ focus) (spawnHere "pidgin"))
ifWindows (className =? "Slack") (mapM_ focus) (spawnHere "slack")) ifWindows (className =? "Slack") (mapM_ focus) (spawnHere "slack"))
{- {-
@ -613,6 +614,7 @@ 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 {