Compare commits

..

No commits in common. "master" and "remove-win+num" have entirely different histories.

1 changed files with 126 additions and 148 deletions

274
xmonad.hs
View File

@ -1,4 +1,5 @@
{-# 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
@ -25,8 +26,6 @@ import XMonad.Hooks.FadeInactive
import XMonad.Hooks.ManageDocks import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers import XMonad.Hooks.ManageHelpers
import XMonad.Hooks.SetWMName import XMonad.Hooks.SetWMName
import XMonad.Hooks.UrgencyHook
-- Layout -- Layout
import XMonad.Layout import XMonad.Layout
@ -35,12 +34,10 @@ import XMonad.Layout.IM as IM -- GIMP stuff
import qualified XMonad.Layout.IndependentScreens as IS import qualified XMonad.Layout.IndependentScreens as IS
import XMonad.Layout.LayoutHints (layoutHints) import XMonad.Layout.LayoutHints (layoutHints)
import XMonad.Layout.NoBorders (smartBorders, noBorders) import XMonad.Layout.NoBorders (smartBorders, noBorders)
import XMonad.Layout.PerScreen
import XMonad.Layout.PerWorkspace import XMonad.Layout.PerWorkspace
import XMonad.Layout.Reflect -- GIMP stuff import XMonad.Layout.Reflect -- GIMP stuff
import XMonad.Layout.ResizableTile import XMonad.Layout.ResizableTile
import XMonad.Layout.SimpleFloat import XMonad.Layout.SimpleFloat
import XMonad.Layout.Spacing
import XMonad.Layout.Tabbed import XMonad.Layout.Tabbed
import XMonad.Layout.TrackFloating -- GIMP stuff import XMonad.Layout.TrackFloating -- GIMP stuff
@ -88,56 +85,52 @@ instance ExtensionClass RightScreen where
initialValue = RightScreen [] initialValue = RightScreen []
extensionType = PersistentExtension extensionType = PersistentExtension
genWorkspaces :: ScreenId -> [IS.PhysicalWorkspace]
genWorkspaces sc = if sc == 3
then IS.withScreen 0 ["pindrop"] ++ IS.withScreen 2 ["shell", "VM"] ++ IS.withScreen 1 ["qb"]
else IS.withScreens sc ["shell", "qb", "pindrop", "VM"]
-- End DynamicWorkspaces code (keybindings are below) -- -- End DynamicWorkspaces code (keybindings are below) --
getTopBar :: Int -> String getTopBar :: Int -> String
getTopBar sc = if sc == 1 getTopBar sc = if sc == 1
then "dzen2 -dock -p -x 0 -ta l -w 1024 -e 'onstart:lower;button2=togglehide;sigusr1=togglehide'" then "dzen2 -dock -p -x 0 -ta l -w 1024 -e 'onstart:lower;button2=togglehide;sigusr1=togglehide'"
else "dzen2 -dock -p -x 2880 -ta l -w 1024 -e 'onstart:lower;button2=togglehide;sigusr1=togglehide'" else "dzen2 -dock -p -x 1920 -ta l -w 1024 -e 'onstart:lower;button2=togglehide;sigusr1=togglehide'"
--getBarbicanBar :: Int -> String getBarbicanBar :: Int -> String
--getBarbicanBar sc = if sc == 1 getBarbicanBar sc = if sc == 1
-- then "ssh barbican 'conky' | dzen2 -dock -p -x 0 -h 16 -y -112 -ta l -w 1920 -e 'sigusr1=togglehide'" then "ssh barbican 'conky' | dzen2 -dock -p -x 0 -y -126 -ta l -w 1920 -e 'sigusr1=togglehide'"
-- else "ssh barbican 'conky' | dzen2 -dock -p -x 1920 -h 16 -y -112 -ta l -w 1920 -e 'sigusr1=togglehide'" else "ssh barbican 'conky' | dzen2 -dock -p -x 1920 -y -126 -ta l -w 1920 -e 'sigusr1=togglehide'"
--getDeltachunkBar :: Int -> String getDeltachunkBar :: Int -> String
--getDeltachunkBar sc = if sc == 1 getDeltachunkBar sc = if sc == 1
-- then "ssh deltachunk 'conky' | dzen2 -dock -p -x 0 -h 16 -y -96 -ta l -w 1920 -e 'sigusr1=togglehide'" then "ssh deltachunk 'conky' | dzen2 -dock -p -x 0 -y -108 -ta l -w 1920 -e 'sigusr1=togglehide'"
-- else "ssh deltachunk 'conky' | dzen2 -dock -p -x 1920 -h 16 -y -96 -ta l -w 1920 -e 'sigusr1=togglehide'" else "ssh deltachunk 'conky' | dzen2 -dock -p -x 1920 -y -108 -ta l -w 1920 -e 'sigusr1=togglehide'"
--getFerrumBar :: Int -> String getFerrumBar :: Int -> String
--getFerrumBar sc = if sc == 1 getFerrumBar sc = if sc == 1
-- then "conky | dzen2 -dock -p -x 0 -h 16 -y -80 -ta l -w 1920 -e 'sigusr1=togglehide'" then "conky | dzen2 -dock -p -x 0 -y -90 -ta l -w 1920 -e 'sigusr1=togglehide'"
-- else "conky | dzen2 -dock -p -x 1920 -h 16 -y -80 -ta l -w 1920 -e 'sigusr1=togglehide'" else "conky | dzen2 -dock -p -x 1920 -y -90 -ta l -w 1920 -e 'sigusr1=togglehide'"
-- getGammachunkBar :: Int -> String -- getGammachunkBar :: Int -> String
-- getGammachunkBar sc = if sc == 1 -- getGammachunkBar sc = if sc == 1
-- then "ssh gammachunk 'conky' | dzen2 -dock -p -x 0 -y -72 -ta l -w 1920 -e 'sigusr1=togglehide'" -- then "ssh gammachunk 'conky' | dzen2 -dock -p -x 0 -y -72 -ta l -w 1920 -e 'sigusr1=togglehide'"
-- else "ssh gammachunk 'conky' | dzen2 -dock -p -x 1920 -y -72 -ta l -w 1920 -e 'sigusr1=togglehide'" -- else "ssh gammachunk 'conky' | dzen2 -dock -p -x 1920 -y -72 -ta l -w 1920 -e 'sigusr1=togglehide'"
--getOsmiumBar :: Int -> String getOsmiumBar :: Int -> String
--getOsmiumBar sc = if sc == 1 getOsmiumBar sc = if sc == 1
-- then "ssh osmium 'conky' | dzen2 -dock -p -x 0 -h 16 -y -64 -ta l -w 1920 -e 'sigusr1=togglehide'" then "ssh osmium 'conky' | dzen2 -dock -p -x 0 -y -72 -ta l -w 1920 -e 'sigusr1=togglehide'"
-- else "ssh osmium 'conky' | dzen2 -dock -p -x 1920 -h 16 -y -64 -ta l -w 1920 -e 'sigusr1=togglehide'" else "ssh osmium 'conky' | dzen2 -dock -p -x 1920 -y -72 -ta l -w 1920 -e 'sigusr1=togglehide'"
--
--getSodiumBar :: Int -> String getSodiumBar :: Int -> String
--getSodiumBar sc = if sc == 1 getSodiumBar sc = if sc == 1
-- then "ssh sodium 'conky' | dzen2 -dock -p -x 0 -h 16 -y -48 -ta l -w 1920 -e 'sigusr1=togglehide'" then "ssh sodium 'conky' | dzen2 -dock -p -x 0 -y -54 -ta l -w 1920 -e 'sigusr1=togglehide'"
-- else "ssh sodium 'conky' | dzen2 -dock -p -x 1920 -h 16 -y -48 -ta l -w 1920 -e 'sigusr1=togglehide'" else "ssh sodium 'conky' | dzen2 -dock -p -x 1920 -y -54 -ta l -w 1920 -e 'sigusr1=togglehide'"
--
--getTennessineBar :: Int -> String getTennessineBar :: Int -> String
--getTennessineBar sc = if sc == 1 getTennessineBar sc = if sc == 1
-- then "ssh tennessine 'conky' | dzen2 -dock -p -x 0 -h 16 -y -32 -ta l -w 1920 -e 'sigusr1=togglehide'" then "ssh tennessine 'conky' | dzen2 -dock -p -x 0 -y -36 -ta l -w 1920 -e 'sigusr1=togglehide'"
-- else "ssh tennessine 'conky' | dzen2 -dock -p -x 1920 -h 16 -y -32 -ta l -w 1920 -e 'sigusr1=togglehide'" else "ssh tennessine 'conky' | dzen2 -dock -p -x 1920 -y -36 -ta l -w 1920 -e 'sigusr1=togglehide'"
--
--getBlancherBar :: Int -> String getBlancherBar :: Int -> String
--getBlancherBar sc = if sc == 1 getBlancherBar sc = if sc == 1
-- then "ssh blancher 'conky' | dzen2 -dock -p -x 0 -h 16 -y -16 -ta l -w 1920 -e 'sigusr1=togglehide'" then "ssh blancher 'conky' | dzen2 -dock -p -x 0 -y -1 -ta l -w 1920 -e 'sigusr1=togglehide'"
-- else "ssh blancher 'conky' | dzen2 -dock -p -x 1920 -h 16 -y -16 -ta l -w 1920 -e 'sigusr1=togglehide'" else "ssh blancher 'conky' | dzen2 -dock -p -x 1920 -y -1 -ta l -w 1920 -e 'sigusr1=togglehide'"
toggleHomeScreens :: X () toggleHomeScreens :: X ()
toggleHomeScreens = do toggleHomeScreens = do
@ -153,28 +146,20 @@ toggleHomeScreens = do
\date \"+%a, %b %d %T\"; \n\ \date \"+%a, %b %d %T\"; \n\
\/usr/bin/sed -E \"s/($(date +%_d)\b)/^fg(green)\1^fg()/\" ; \n\ \/usr/bin/sed -E \"s/($(date +%_d)\b)/^fg(green)\1^fg()/\" ; \n\
\sleep 1; \n\ \sleep 1; \n\
\done | dzen2 -dock -p -x 2400 -w 480 -u -h 24 -ta r -sa c -e 'sigusr1=togglehide' &" \done | dzen2 -dock -p -x 1600 -w 325 -u -h 24 -ta r -sa c -e 'sigusr1=togglehide' &"
else if sc == 3 else if sc == 3
then do then do
--spawn "xrandr --output eDP-1 --primary --auto --output DVI-I-3-2 --auto --left-of eDP-1 --output DVI-I-2-1 --auto --right-of eDP-1" spawn "xrandr --output eDP-1-1 --primary --auto --output DVI-I-3-2 --auto --left-of eDP-1-1 --output DVI-I-2-1 --auto --right-of eDP-1-1"
-- spawn "xrandr --output eDP-1-1 --primary --auto --output DVI-I-2-1 --auto --left-of eDP-1-1 --output DVI-I-3-2 --auto --right-of eDP-1-1" -- spawn "xrandr --output eDP-1-1 --primary --auto --output DVI-I-2-1 --auto --left-of eDP-1-1 --output DVI-I-3-2 --auto --right-of eDP-1-1"
--spawn "while true; do \n\ spawn "while true; do \n\
-- \~/bin/battery; \n\ \~/bin/battery; \n\
-- \echo -n ' '; \n\ \echo -n ' '; \n\
-- \~/bin/temp.sh; \n\ \~/bin/temp.sh; \n\
-- \echo -n ' '; \n\ \echo -n ' '; \n\
-- \date '+%a, %b %d %T'; \n\ \date '+%a, %b %d %T'; \n\
-- \sleep 1; \n\ \sleep 1; \n\
-- \done | dzen2 -dock -p -x 1602 -w 325 -h 24 -ta l -fn 'xos4 Terminus:style=Regular:Pixelsize=12' &" \done | dzen2 -dock -p -x 1602 -w 325 -h 24 -ta l -fn 'xos4 Terminus:style=Regular:Pixelsize=12' &"
-- spawn "while true; do \n\
-- \~/bin/battery; \n\
-- \echo -n ' '; \n\
-- \~/bin/temp.sh; \n\
-- \echo -n ' '; \n\
-- \date '+%a, %b %d %T'; \n\
-- \sleep 1; \n\
-- \done | dzen2 -dock -p -x 3522 -w 325 -h 24 -ta l -fn 'xos4 Terminus:style=Regular:Pixelsize=12' &"
spawn "while true; do \n\ spawn "while true; do \n\
\~/bin/battery; \n\ \~/bin/battery; \n\
\echo -n ' '; \n\ \echo -n ' '; \n\
@ -182,7 +167,15 @@ toggleHomeScreens = do
\echo -n ' '; \n\ \echo -n ' '; \n\
\date '+%a, %b %d %T'; \n\ \date '+%a, %b %d %T'; \n\
\sleep 1; \n\ \sleep 1; \n\
\done | dzen2 -dock -p -x 5399 -w 480 -h 24 -ta l -fg #ebdbb2 -bg #000000 -fn 'xft:monospace:style=Regular:Pixelsize=10' &" \done | dzen2 -dock -p -x 3522 -w 325 -h 24 -ta l -fn 'xos4 Terminus:style=Regular:Pixelsize=12' &"
spawn "while true; do \n\
\~/bin/battery; \n\
\echo -n ' '; \n\
\~/bin/temp.sh; \n\
\echo -n ' '; \n\
\date '+%a, %b %d %T'; \n\
\sleep 1; \n\
\done | dzen2 -dock -p -x 5442 -w 325 -h 24 -ta l -fg #ebdbb2 -bg #282828 -fn 'xos4 Terminus:style=Regular:Pixelsize=12' &"
{- spawn "while true; do echo -n $(cat /tmp/temp); echo -n ' '; date '+%a, %b %d %T'; sleep 1; done | dzen2 -dock -p -x 1710 -w 210 -e 'onstart:lower;button2=togglehide' -h 24 -ta l -fg #aaaaaa -bg #282828 -fn Terminus-10 -xs 1 &" {- spawn "while true; do echo -n $(cat /tmp/temp); echo -n ' '; date '+%a, %b %d %T'; sleep 1; done | dzen2 -dock -p -x 1710 -w 210 -e 'onstart:lower;button2=togglehide' -h 24 -ta l -fg #aaaaaa -bg #282828 -fn Terminus-10 -xs 1 &"
spawn "while true; do echo -n $(cat /tmp/temp); echo -n ' '; date '+%a, %b %d %T'; sleep 1; done | dzen2 -dock -p -x 3630 -w 210 -e 'onstart:lower;button2=togglehide' -h 24 -ta l -fg #aaaaaa -bg #282828 -fn Terminus-10 -xs 0 &" spawn "while true; do echo -n $(cat /tmp/temp); echo -n ' '; date '+%a, %b %d %T'; sleep 1; done | dzen2 -dock -p -x 3630 -w 210 -e 'onstart:lower;button2=togglehide' -h 24 -ta l -fg #aaaaaa -bg #282828 -fn Terminus-10 -xs 0 &"
spawn "while true; do echo -n $(cat /tmp/temp); echo -n ' '; date '+%a, %b %d %T'; sleep 1; done | dzen2 -dock -p -x 5550 -w 210 -e 'onstart:lower;button2=togglehide' -h 24 -ta r -fg #aaaaaa -bg #282828 -fn Terminus-10 -xs 2 &" -} spawn "while true; do echo -n $(cat /tmp/temp); echo -n ' '; date '+%a, %b %d %T'; sleep 1; done | dzen2 -dock -p -x 5550 -w 210 -e 'onstart:lower;button2=togglehide' -h 24 -ta r -fg #aaaaaa -bg #282828 -fn Terminus-10 -xs 2 &" -}
@ -275,7 +268,7 @@ myTheme :: Theme
myTheme = def { myTheme = def {
fontName = myFont fontName = myFont
} }
myFont = "xft:monospace:style=Regular:Pixelsize=18" myFont = "xft:Terminus:style=Regular:Pixelsize=12"
fadeHook = fadeInactiveLogHook fadeAmount fadeHook = fadeInactiveLogHook fadeAmount
where fadeAmount = 0.8 where fadeAmount = 0.8
@ -286,67 +279,43 @@ makeLauncher yargs run exec close = concat
--launcher = makeLauncher "-x -- -nf grey -nb black -fn 'xos4 Terminus:Pixelsize=8'" "eval" "\"exec " "\"" --launcher = makeLauncher "-x -- -nf grey -nb black -fn 'xos4 Terminus:Pixelsize=8'" "eval" "\"exec " "\""
launcher = makeLauncher "-x" "eval" "\"exec " "\"" launcher = makeLauncher "-x" "eval" "\"exec " "\""
startTrayer sc = do
if sc == 3
then
"trayer --edge top --align right --widthtype request --margin 490 --expand false --SetDockType true --SetPartialStrut false --tint 0x000000 --transparent true --alpha 0 --height 24 --monitor 2"
else
"trayer --edge top --align right --widthtype request --margin 490 --expand false --SetDockType true --SetPartialStrut false --tint 0x000000 --transparent true --alpha 0 --height 24 --monitor 'primary'"
main = do sc <- IS.countScreens main = do 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) dzenOsmiumBar <- spawnPipe (getOsmiumBar sc)
--dzenSodiumBar <- spawnPipe (getSodiumBar sc) dzenSodiumBar <- spawnPipe (getSodiumBar sc)
--dzenTennessineBar <- spawnPipe (getTennessineBar sc) dzenTennessineBar <- spawnPipe (getTennessineBar sc)
--dzenBlancherBar <- spawnPipe (getBlancherBar sc) dzenBlancherBar <- spawnPipe (getBlancherBar sc)
xmonad $ ewmhFullscreen . ewmh $ def { xmonad $ docks $ ewmh $ desktopConfig {
workspaces = genWorkspaces (S sc) workspaces = ["shell","qb","pindrop","kofc","VM"]
, terminal = myTerminal , terminal = myTerminal
, focusFollowsMouse = True , focusFollowsMouse = True
, manageHook = manageDocks <+> myManageHook -- <+> manageHook desktopConfig , manageHook = manageDocks <+> myManageHook <+> manageHook desktopConfig
, handleEventHook = handleEventHook desktopConfig , handleEventHook = handleEventHook desktopConfig
--, layoutHook = avoidStruts $ gaps [(D,108)] $ layoutH , layoutHook = avoidStruts $ gaps [(D,108)] $ layoutH
, layoutHook = avoidStruts $ layoutH
, logHook = myLogHook dzenTopBar >> fadeHook >> updatePointer (0.5, 0.5) (0, 0) , logHook = myLogHook dzenTopBar >> fadeHook >> updatePointer (0.5, 0.5) (0, 0)
, borderWidth = 1 , borderWidth = 1
, normalBorderColor = "#000000" , normalBorderColor = "#282828"
, focusedBorderColor = "#ebdbb2" , focusedBorderColor = "#ebdbb2"
, modMask = winKey , modMask = winKey
, startupHook = myStartup , startupHook = myStartup
} }
`additionalKeys` myKeys `additionalKeys` myKeys
`removeKeys` remKeys `removeKeys` remKeys
myStartup :: X () myStartup :: X ()
myStartup = do myStartup = do
--setWMName "LG3D" --setWMName "LG3D"
sc <- IS.countScreens
toggleHomeScreens toggleHomeScreens
--spawn "xset dpms 600" spawn "trayer --edge top --align right --widthtype request --margin 318 --expand false --SetDockType true --SetPartialStrut false --tint 0x282828 --transparent true --alpha 0 --height 24 --monitor 'primary'"
--spawn "gnome-gmail-notifier"
spawn "xset dpms 600"
--spawn "xautolock -secure -time 10 -locker 'i3lock -c 000000 -i /home/trey/images/black.png'"
spawn "xautolock -secure -time 10 -locker 'i3lock -c 000000'" spawn "xautolock -secure -time 10 -locker 'i3lock -c 000000'"
spawn (startTrayer sc)
-- --spawn "trayer --edge top --align right --widthtype request --margin 318 --expand false --SetDockType true --SetPartialStrut false --tint 0x282828 --transparent true --alpha 0 --height 24 --monitor 'primary'"
-- --spawn "stalonetray"
-- --spawn "gnome-gmail-notifier"
-- --spawn "xautolock -secure -time 10 -locker 'i3lock -c 000000 -i /home/trey/images/black.png'"
--
-- --spawn "trayer --edge top --align right --widthtype request --margin 318 --expand false --SetDockType true --SetPartialStrut false --tint 0x282828 --transparent true --alpha 0 --height 24 --monitor 2"
activateMyTerminal :: X ()
activateMyTerminal = do
sc <- IS.countScreens
if sc == 1
then do
windows (viewOnScreen 0 "shell")
else if sc == 3
then do
windows (viewOnScreen 2 "shell")
else
return ()
myBitmapsDir = "/home/trey/.xmonad/dzen2" myBitmapsDir = "/home/trey/.xmonad/dzen2"
--centerBar = fmap getCenterBar IS.countScreens --centerBar = fmap getCenterBar IS.countScreens
@ -358,16 +327,16 @@ myBitmapsDir = "/home/trey/.xmonad/dzen2"
myLogHook :: Handle -> X () myLogHook :: Handle -> X ()
--myLogHook h = dynamicLogWithPP $ defaultPP --myLogHook h = dynamicLogWithPP $ defaultPP
myLogHook h = dynamicLogWithPP $ IS.marshallPP (S 0) $ def myLogHook h = dynamicLogWithPP $ def
{ {
ppCurrent = dzenColor "#8AE234" "#000000" . pad ppCurrent = dzenColor "#8AE234" "#282828" . pad
, ppVisible = dzenColor "#555753" "#000000" . pad , ppVisible = dzenColor "#555753" "#282828" . pad
, ppHidden = dzenColor "#ebdbb2" "#000000" . pad , ppHidden = dzenColor "#ebdbb2" "#282828" . pad
, ppHiddenNoWindows = dzenColor "#555753" "#000000" . pad , ppHiddenNoWindows = dzenColor "#555753" "#282828" . pad
, ppUrgent = dzenColor "#cc0000" "#000000" . pad , ppUrgent = dzenColor "#cc0000" "#282828" . pad
, ppWsSep = "." , ppWsSep = "."
, ppSep = " | " , ppSep = " | "
, ppLayout = dzenColor "#666600" "#000000" . , ppLayout = dzenColor "#666600" "#282828" .
(\x -> case x of (\x -> case x of
"Tall" -> "^i(" ++ myBitmapsDir ++ "/tall.xbm)" "Tall" -> "^i(" ++ myBitmapsDir ++ "/tall.xbm)"
"Mirror Tall" -> "^i(" ++ myBitmapsDir ++ "/mtall.xbm)" "Mirror Tall" -> "^i(" ++ myBitmapsDir ++ "/mtall.xbm)"
@ -376,7 +345,7 @@ myLogHook h = dynamicLogWithPP $ IS.marshallPP (S 0) $ def
"IM Grid" -> "IM" "IM Grid" -> "IM"
_ -> x _ -> x
) )
, ppTitle = ("" ++) . dzenColor "#ff6600" "#000000" . dzenEscape , ppTitle = ("" ++) . dzenColor "#ff6600" "#282828" . dzenEscape
, ppOutput = hPutStrLn h , ppOutput = hPutStrLn h
} }
@ -435,21 +404,17 @@ myKeys = [
-- ((winKey , xK_l), spawnHere "xscreensaver-command --lock") -- ((winKey , xK_l), spawnHere "xscreensaver-command --lock")
-- ((winKey , xK_l), spawnHere "qdbus org.kde.krunner /ScreenSaver Lock") -- ((winKey , xK_l), spawnHere "qdbus org.kde.krunner /ScreenSaver Lock")
, ((winKey , xK_Return), do , ((winKey , xK_Return), do
ifWindows (resource =? "Alacritty") (mapM_ focus) (spawnHere myTerminal) windows (viewOnScreen 0 "shell")
activateMyTerminal)
, ((winKey , xK_v), do
ifWindows (resource =? "Alacritty") (mapM_ focus) (spawnHere myTerminal)
activateMyTerminal)
--ifWindows (resource =? "main") (mapM_ focus) (spawnHere myTerminal)) --ifWindows (resource =? "main") (mapM_ focus) (spawnHere myTerminal))
ifWindows (resource =? "Alacritty") (mapM_ focus) (spawnHere myTerminal))
, ((controlMask .|. lAlt, xK_BackSpace), (spawnHere "xfdesktop --quit")) , ((controlMask .|. lAlt, xK_BackSpace), (spawnHere "xfdesktop --quit"))
, ((controlMask .|. lAlt, xK_Delete), (spawnHere "pkill -9 chromium")) , ((controlMask .|. lAlt, xK_Delete), (spawnHere "pkill -9 chromium"))
, ((controlMask .|. shiftMask, xK_Return), (spawnHere myTerminal)) , ((controlMask .|. shiftMask, xK_Return), (spawnHere myTerminal))
, ((controlMask .|. shiftMask, xK_3), spawn "scrot --exec 'mkdir -p ~/images && mv $f ~/images' && paplay ~/wav/camera.wav") , ((controlMask .|. shiftMask, xK_3), spawn "scrot --exec 'mkdir -p ~/Desktop && mv $f ~/Desktop' && paplay ~/wav/camera.wav")
, ((controlMask .|. shiftMask, xK_4), unGrab >> spawn "scrot --exec 'mkdir -p ~/images && mv $f ~/images' --select && paplay ~/wav/camera.wav") , ((controlMask .|. shiftMask, xK_4), unGrab >> spawn "scrot --exec 'mkdir -p ~/Desktop && mv $f ~/Desktop' --select && paplay ~/wav/camera.wav")
, ((controlMask .|. winKey, xK_z), ifWindows (resource =? "Zoom") (mapM_ focus) (spawnHere "zoom"))
-- windows (viewOnScreen 1 "ws") -- windows (viewOnScreen 1 "ws")
-- ifWindows (resource =? "altUrxvt") (mapM_ focus) (spawnHere altTerminal)) -- ifWindows (resource =? "altUrxvt") (mapM_ focus) (spawnHere altTerminal))
, ((lAlt, xK_v), spawn "CM_HISTLENGTH=20 clipmenu && xdotool key Ctrl+v") , ((lAlt, xK_v), spawn "clipmenu && xdotool key Ctrl+v")
--, ((winKey .|. shiftMask, xK_v), do --, ((winKey .|. shiftMask, xK_v), do
-- windows (viewOnScreen 1 "virtualbox") -- windows (viewOnScreen 1 "virtualbox")
-- ifWindows (className =? "Gvim") (mapM_ focus) (spawnHere "gvim")) -- ifWindows (className =? "Gvim") (mapM_ focus) (spawnHere "gvim"))
@ -467,12 +432,9 @@ myKeys = [
spawnHere "pkill trayer" spawnHere "pkill trayer"
sendMessage $ ToggleStruts sendMessage $ ToggleStruts
sendMessage $ ToggleGaps) sendMessage $ ToggleGaps)
--sendMessage $ ToggleStruts)
, ((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), do , ((winKey , xK_g), ifWindows (className =? "Google-chrome") (mapM_ focus) (spawnHere "google-chrome-stable"))
windows (viewOnScreen 0 "pindrop")
ifWindows (className =? "Vivaldi-stable") (mapM_ focus) (spawnHere "vivaldi"))
--, ((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"))
@ -480,11 +442,11 @@ 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"))
--, ((winKey , xK_f), spawnHere (myTerminal ++ " -e vifm . ~")) , ((winKey , xK_f), spawnHere (myTerminal ++ " -e vifm . ~"))
--, ((winKey , xK_f), spawnHere ("export SHELL=/bin/bash && " ++ myTerminal ++ " -e mc")) --, ((winKey , xK_f), spawnHere ("export SHELL=/bin/bash && " ++ myTerminal ++ " -e mc"))
--, ((winKey , xK_e), spawnHere ("export SHELL=/bin/bash && " ++ myTerminal ++ " -e mc")) -- key stroke matches Win+E (from Win7) --, ((winKey , xK_e), spawnHere ("export SHELL=/bin/bash && " ++ myTerminal ++ " -e mc")) -- key stroke matches Win+E (from Win7)
, ((winKey , xK_o), do , ((winKey , xK_o), do
@ -498,10 +460,8 @@ myKeys = [
-- windows (viewOnScreen 1 "hng") -- windows (viewOnScreen 1 "hng")
-- ifWindows (className =? "Skype") (mapM_ focus) (spawnHere "skype")) -- ifWindows (className =? "Skype") (mapM_ focus) (spawnHere "skype"))
, ((winKey , xK_s), ifWindows (className =? "Pavucontrol") (mapM_ killWindow) (spawnHere "pavucontrol")) , ((winKey , xK_s), ifWindows (className =? "Pavucontrol") (mapM_ killWindow) (spawnHere "pavucontrol"))
-- , ((winKey , xK_t), do
-- spawn "pkill trayer"
-- spawn (startTrayer sc))
, ((winKey , xK_c), kill) , ((winKey , xK_c), kill)
, ((winKey .|. controlMask , xK_c), spawn "gnome-calendar")
--, ((winKey , xK_m), windows W.focusMaster) --, ((winKey , xK_m), windows W.focusMaster)
, ((winKey , xK_comma), sendMessage (IncMasterN 1)) , ((winKey , xK_comma), sendMessage (IncMasterN 1))
, ((winKey , xK_period), sendMessage (IncMasterN (-1))) , ((winKey , xK_period), sendMessage (IncMasterN (-1)))
@ -523,15 +483,13 @@ myKeys = [
--, ((winKey .|. controlMask , xK_k), spawn ("sleep 1 && cat ~/.macros/code.macro | xmacroplay -d 0.1 $DISPLAY")) --, ((winKey .|. controlMask , xK_k), spawn ("sleep 1 && cat ~/.macros/code.macro | xmacroplay -d 0.1 $DISPLAY"))
--, ((shiftMask, xK_Insert), withFocused shiftInsert) --, ((shiftMask, xK_Insert), withFocused shiftInsert)
--, ((controlMask, xK_n), raiseMaybe (spawnHere myTerminal) (className =? "URxvt")) --, ((controlMask, xK_n), raiseMaybe (spawnHere myTerminal) (className =? "URxvt"))
-- , ((winKey , xK_Print), spawnHere "xfce4-screenshooter") , ((winKey , xK_Print), spawnHere "xfce4-screenshooter")
, ((winKey , xK_Left), prevWS) , ((winKey , xK_Left), prevWS)
, ((winKey , xK_Right), nextWS) , ((winKey , xK_Right), nextWS)
, ((winKey , xK_Up), spawnHere "skippy-xd --paging") , ((winKey , xK_Up), spawnHere "skippy-xd")
--, ((0, xF86XK_Calculator), spawnHere "/home/trey/bin/calc") --, ((0, xF86XK_Calculator), spawnHere "/home/trey/bin/calc")
--, ((0, xF86XK_Calculator), ifWindows (className =? "Gcalctool") (mapM_ killWindow) (spawnHere "gcalctool")) --, ((0, xF86XK_Calculator), ifWindows (className =? "Gcalctool") (mapM_ killWindow) (spawnHere "gcalctool"))
, ((winKey , xK_y), spawn "dunstctl close-all") , ((0, xF86XK_Calculator), ifWindows (className =? "Gnome-calculator") (mapM_ killWindow) (spawnHere "gnome-calculator"))
, ((winKey , xK_x), spawn "dunstctl close")
-- , ((0, xF86XK_Calculator), ifWindows (className =? "Gnome-calculator") (mapM_ killWindow) (spawnHere "gnome-calculator"))
, ((0, xF86XK_AudioPlay), spawn "clementine --play-pause") , ((0, xF86XK_AudioPlay), spawn "clementine --play-pause")
--, ((0, xF86XK_AudioMute), spawn "amixer -c 0 set Master toggle") --, ((0, xF86XK_AudioMute), spawn "amixer -c 0 set Master toggle")
, ((0, xF86XK_AudioMute), spawn "pamixer --toggle-mute") , ((0, xF86XK_AudioMute), spawn "pamixer --toggle-mute")
@ -548,7 +506,7 @@ 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 0 "qb") windows (viewOnScreen 1 "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)
@ -556,26 +514,46 @@ myKeys = [
--, ((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 0 "pindrop") windows (viewOnScreen 1 "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"))
, ((winKey , xK_q), spawn "killall dzen2 stalonetray; xmonad --recompile; xmonad --restart") {-
, ((winKey .|. shiftMask , xK_q), io (exitWith ExitSuccess)) , ((winKey , xK_2), windows (viewOnScreen 0 "02:jobs"))
, ((winKey , xK_3), windows (viewOnScreen 0 "03:is660"))
, ((winKey , xK_4), windows (viewOnScreen 0 "04:office"))
, ((winKey , xK_5), windows (viewOnScreen 0 "05:sysadmin"))
, ((winKey , xK_6), windows (viewOnScreen 0 "06:irc"))
, ((winKey , xK_7), windows (viewOnScreen 0 "07:digium"))
, ((winKey , xK_8), windows (viewOnScreen 0 "08:vm"))
, ((winKey , xK_9), windows (viewOnScreen 0 "09:dump"))
, ((winKey , xK_0), windows (viewOnScreen 0 "10:music"))
, ((winKey , xK_F1), windows (viewOnScreen 1 "F1:man"))
, ((winKey , xK_F2), windows (viewOnScreen 1 "F2:jobs"))
, ((winKey , xK_F3), windows (viewOnScreen 1 "F3:isovr"))
, ((winKey , xK_F4), windows (viewOnScreen 1 "F4:offovr"))
, ((winKey , xK_F5), windows (viewOnScreen 1 "F5:sysovr"))
, ((winKey , xK_F6), windows (viewOnScreen 1 "F6:ircovr"))
, ((winKey , xK_F7), windows (viewOnScreen 1 "F7:dgmovr"))
, ((winKey , xK_F8), windows (viewOnScreen 1 "F8:vmovr"))
, ((winKey , xK_F9), windows (viewOnScreen 1 "F9:dmpovr"))
, ((winKey , xK_F10), windows (viewOnScreen 1 "F10:musovr"))-}
, ((winKey , xK_q), spawn "killall dzen2 trayer; xmonad --recompile; xmonad --restart")
, ((winKey .|. shiftMask , xK_q), io (exitWith ExitSuccess))
-- win+h shows the selected workspace -- win+h shows the selected workspace
, ((winKey, xK_h), DW.withWorkspace myXPConfigSelect $ \wk -> do , ((winKey , xK_h), DW.withWorkspace myXPConfigSelect $ \wk -> do
--sc <- screenBy 0 sc <- screenBy 0
--if sc == 0 if sc == 0
--then XS.modify $ LeftScreen . (wk :) . getLeftScreen -- prefix to list --then XS.modify $ LeftScreen . (wk :) . getLeftScreen -- prefix to list
-- then XS.modify $ LeftScreen . (++ [wk]) . getLeftScreen -- append to list then XS.modify $ LeftScreen . (++ [wk]) . getLeftScreen -- append to list
--else XS.modify $ RightScreen . (wk :) . getRightScreen -- prefix to list --else XS.modify $ RightScreen . (wk :) . getRightScreen -- prefix to list
-- else XS.modify $ RightScreen . (++ [wk]) . getRightScreen -- append to list else XS.modify $ RightScreen . (++ [wk]) . getRightScreen -- append to list
windows $ W.view wk) windows $ W.view wk)
-- win+z moves the current window to the selected workspace -- win+z moves the current window to the selected workspace
, ((winKey, xK_z), DW.withWorkspace myXPConfigSelect (\ws -> do , ((winKey , xK_z), DW.withWorkspace myXPConfigSelect (\ws -> do
--sc <- screenBy 0 sc <- screenBy 0
--if sc == 0 if sc == 0
-- then XS.modify $ LeftScreen . nub . (ws :) . getLeftScreen -- prefix to list then XS.modify $ LeftScreen . nub . (ws :) . getLeftScreen -- prefix to list
-- else XS.modify $ RightScreen . nub . (ws :) . getRightScreen -- prefix to list else XS.modify $ RightScreen . nub . (ws :) . getRightScreen -- prefix to list
--then XS.modify $ LeftScreen . nub . (++ [ws]) . getLeftScreen -- append to list --then XS.modify $ LeftScreen . nub . (++ [ws]) . getLeftScreen -- append to list
--else XS.modify $ RightScreen . nub . (++ [ws]) . getRightScreen -- append to list --else XS.modify $ RightScreen . nub . (++ [ws]) . getRightScreen -- append to list