Compare commits
7 Commits
remove-dep
...
apps-on-wo
Author | SHA1 | Date | |
---|---|---|---|
83b096d18f | |||
2434602233 | |||
080c5b71f6 | |||
cbbef9723c | |||
9f59c99bc5 | |||
630d3cc08a | |||
cb257fe6be |
68
xmonad.hs
68
xmonad.hs
@ -1,6 +1,6 @@
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
--{-# OPTIONS_GHC -Wno-deprecations #-}
|
||||
{-# OPTIONS_GHC -Wno-deprecations #-}
|
||||
import XMonad
|
||||
import XMonad.Config.Desktop
|
||||
-- Actions
|
||||
@ -280,32 +280,31 @@ makeLauncher yargs run exec close = concat
|
||||
launcher = makeLauncher "-x" "eval" "\"exec " "\""
|
||||
|
||||
|
||||
main = do
|
||||
sc <- IS.countScreens
|
||||
dzenTopBar <- spawnPipe (getTopBar sc)
|
||||
dzenBarbicanBar <- spawnPipe (getBarbicanBar sc)
|
||||
dzenDeltachunkBar <- spawnPipe (getDeltachunkBar sc)
|
||||
dzenFerrumBar <- spawnPipe (getFerrumBar sc)
|
||||
-- dzenGammachunkBar <- spawnPipe (getGammachunkBar sc)
|
||||
dzenOsmiumBar <- spawnPipe (getOsmiumBar sc)
|
||||
dzenSodiumBar <- spawnPipe (getSodiumBar sc)
|
||||
dzenTennessineBar <- spawnPipe (getTennessineBar sc)
|
||||
dzenBlancherBar <- spawnPipe (getBlancherBar sc)
|
||||
xmonad $ docks $ ewmh $ desktopConfig {
|
||||
workspaces = ["shell","qb","pindrop","kofc","VM"]
|
||||
, terminal = myTerminal
|
||||
, focusFollowsMouse = True
|
||||
, manageHook = manageDocks <+> myManageHook <+> manageHook desktopConfig
|
||||
--, handleEventHook = docksEventHook <+> handleEventHook desktopConfig
|
||||
, handleEventHook = handleEventHook desktopConfig
|
||||
, layoutHook = avoidStruts $ gaps [(D,108)] $ layoutH
|
||||
, logHook = myLogHook dzenTopBar >> fadeHook >> updatePointer (0.5, 0.5) (0, 0)
|
||||
, borderWidth = 1
|
||||
, normalBorderColor = "#282828"
|
||||
, focusedBorderColor = "#ebdbb2"
|
||||
, modMask = winKey
|
||||
, startupHook = myStartup
|
||||
} `additionalKeys` myKeys
|
||||
main = do sc <- IS.countScreens
|
||||
dzenTopBar <- spawnPipe (getTopBar sc)
|
||||
dzenBarbicanBar <- spawnPipe (getBarbicanBar sc)
|
||||
dzenDeltachunkBar <- spawnPipe (getDeltachunkBar sc)
|
||||
dzenFerrumBar <- spawnPipe (getFerrumBar sc)
|
||||
dzenOsmiumBar <- spawnPipe (getOsmiumBar sc)
|
||||
dzenSodiumBar <- spawnPipe (getSodiumBar sc)
|
||||
dzenTennessineBar <- spawnPipe (getTennessineBar sc)
|
||||
dzenBlancherBar <- spawnPipe (getBlancherBar sc)
|
||||
xmonad $ desktopConfig {
|
||||
workspaces = ["shell","qb","pindrop","VM"]
|
||||
, terminal = myTerminal
|
||||
, focusFollowsMouse = True
|
||||
, manageHook = manageDocks <+> myManageHook -- <+> manageHook desktopConfig
|
||||
, handleEventHook = handleEventHook desktopConfig
|
||||
, layoutHook = avoidStruts $ gaps [(D,108)] $ layoutH
|
||||
, logHook = myLogHook dzenTopBar >> fadeHook >> updatePointer (0.5, 0.5) (0, 0)
|
||||
, borderWidth = 1
|
||||
, normalBorderColor = "#282828"
|
||||
, focusedBorderColor = "#ebdbb2"
|
||||
, modMask = winKey
|
||||
, startupHook = myStartup
|
||||
}
|
||||
`additionalKeys` myKeys
|
||||
`removeKeys` remKeys
|
||||
|
||||
|
||||
myStartup :: X ()
|
||||
@ -435,7 +434,9 @@ myKeys = [
|
||||
sendMessage $ ToggleGaps)
|
||||
, ((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-stable"))
|
||||
, ((winKey , xK_g), do
|
||||
windows (viewOnScreen 0 "pindrop")
|
||||
ifWindows (className =? "Google-chrome") (mapM_ focus) (spawnHere "google-chrome-stable"))
|
||||
--, ((winKey , xK_r), do
|
||||
-- windows (viewOnScreen 1 "wb")
|
||||
-- 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_i), spawnHere "iceweasel")
|
||||
--, ((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 =? "Xfce4-dict") (mapM_ killWindow) (spawnHere "xfce4-dict"))
|
||||
, ((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"))
|
||||
--windows (viewOnScreen 1 "vivaldi")
|
||||
--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 =? "Iceweasel") (mapM_ focus) (spawnHere "iceweasel"))
|
||||
, ((winKey .|. controlMask, xK_l), sendMessage Expand)
|
||||
--, ((winKey , xK_1), windows (viewOnScreen 0 "shell"))
|
||||
, ((winKey , xK_1), ifWindows (className =? "Alacritty") (mapM_ focus) (spawnHere myTerminal))
|
||||
, ((winKey , xK_2), windows (viewOnScreen 0 "chromium"))
|
||||
--, ((winKey , xK_1), ifWindows (className =? "Alacritty") (mapM_ focus) (spawnHere myTerminal))
|
||||
--, ((winKey , xK_2), windows (viewOnScreen 0 "chromium"))
|
||||
, ((winKey , xK_a), do
|
||||
windows (viewOnScreen 1 "pindrop")
|
||||
windows (viewOnScreen 0 "pindrop")
|
||||
--ifWindows (className =? "Pidgin") (mapM_ focus) (spawnHere "pidgin"))
|
||||
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
|
||||
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
|
||||
|
||||
remKeys = [(winKey, n) | n <- [xK_0 .. xK_9]]
|
||||
|
||||
--dXPConfig = defaultXPConfig {
|
||||
dXPConfig = def {
|
||||
|
Reference in New Issue
Block a user