Compare commits
4 Commits
83b096d18f
...
66ca5a5213
Author | SHA1 | Date | |
---|---|---|---|
66ca5a5213 | |||
34af6add9d | |||
a4df5a3df2 | |||
7fcdd496d3 |
88
xmonad.hs
88
xmonad.hs
@ -1,5 +1,4 @@
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# OPTIONS_GHC -Wno-deprecations #-}
|
||||
import XMonad
|
||||
import XMonad.Config.Desktop
|
||||
@ -34,10 +33,12 @@ import XMonad.Layout.IM as IM -- GIMP stuff
|
||||
import qualified XMonad.Layout.IndependentScreens as IS
|
||||
import XMonad.Layout.LayoutHints (layoutHints)
|
||||
import XMonad.Layout.NoBorders (smartBorders, noBorders)
|
||||
import XMonad.Layout.PerScreen
|
||||
import XMonad.Layout.PerWorkspace
|
||||
import XMonad.Layout.Reflect -- GIMP stuff
|
||||
import XMonad.Layout.ResizableTile
|
||||
import XMonad.Layout.SimpleFloat
|
||||
import XMonad.Layout.Spacing
|
||||
import XMonad.Layout.Tabbed
|
||||
import XMonad.Layout.TrackFloating -- GIMP stuff
|
||||
|
||||
@ -85,6 +86,10 @@ instance ExtensionClass RightScreen where
|
||||
initialValue = RightScreen []
|
||||
extensionType = PersistentExtension
|
||||
|
||||
genWorkspaces :: ScreenId -> [IS.PhysicalWorkspace]
|
||||
genWorkspaces sc = if sc == 3
|
||||
then IS.withScreen 0 ["pindrop"] ++ IS.withScreen 1 ["qb"] ++ IS.withScreen 2 ["shell", "VM"]
|
||||
else IS.withScreens sc ["shell", "qb", "pindrop", "VM"]
|
||||
|
||||
-- End DynamicWorkspaces code (keybindings are below) --
|
||||
getTopBar :: Int -> String
|
||||
@ -150,24 +155,24 @@ toggleHomeScreens = do
|
||||
|
||||
else if sc == 3
|
||||
then do
|
||||
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 --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-2-1 --auto --left-of eDP-1-1 --output DVI-I-3-2 --auto --right-of eDP-1-1"
|
||||
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 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\
|
||||
-- \~/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 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\
|
||||
\~/bin/battery; \n\
|
||||
\echo -n ' '; \n\
|
||||
@ -290,12 +295,13 @@ main = do sc <- IS.countScreens
|
||||
dzenTennessineBar <- spawnPipe (getTennessineBar sc)
|
||||
dzenBlancherBar <- spawnPipe (getBlancherBar sc)
|
||||
xmonad $ desktopConfig {
|
||||
workspaces = ["shell","qb","pindrop","VM"]
|
||||
workspaces = genWorkspaces (S sc)
|
||||
, terminal = myTerminal
|
||||
, focusFollowsMouse = True
|
||||
, manageHook = manageDocks <+> myManageHook -- <+> manageHook desktopConfig
|
||||
, handleEventHook = handleEventHook desktopConfig
|
||||
, layoutHook = avoidStruts $ gaps [(D,108)] $ layoutH
|
||||
--, layoutHook = avoidStruts $ layoutH
|
||||
, logHook = myLogHook dzenTopBar >> fadeHook >> updatePointer (0.5, 0.5) (0, 0)
|
||||
, borderWidth = 1
|
||||
, normalBorderColor = "#282828"
|
||||
@ -310,12 +316,34 @@ main = do sc <- IS.countScreens
|
||||
myStartup :: X ()
|
||||
myStartup = do
|
||||
--setWMName "LG3D"
|
||||
sc <- IS.countScreens
|
||||
toggleHomeScreens
|
||||
spawn "xset dpms 600"
|
||||
spawn "xautolock -secure -time 10 -locker 'i3lock -c 000000'"
|
||||
if sc == 1
|
||||
then do
|
||||
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'"
|
||||
|
||||
else if sc == 3
|
||||
then do
|
||||
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"
|
||||
|
||||
else
|
||||
return ()
|
||||
|
||||
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"
|
||||
--centerBar = fmap getCenterBar IS.countScreens
|
||||
@ -327,7 +355,7 @@ myBitmapsDir = "/home/trey/.xmonad/dzen2"
|
||||
|
||||
myLogHook :: Handle -> X ()
|
||||
--myLogHook h = dynamicLogWithPP $ defaultPP
|
||||
myLogHook h = dynamicLogWithPP $ def
|
||||
myLogHook h = dynamicLogWithPP $ IS.marshallPP (S 0) $ def
|
||||
{
|
||||
ppCurrent = dzenColor "#8AE234" "#282828" . pad
|
||||
, ppVisible = dzenColor "#555753" "#282828" . pad
|
||||
@ -404,14 +432,18 @@ myKeys = [
|
||||
-- ((winKey , xK_l), spawnHere "xscreensaver-command --lock")
|
||||
-- ((winKey , xK_l), spawnHere "qdbus org.kde.krunner /ScreenSaver Lock")
|
||||
, ((winKey , xK_Return), do
|
||||
windows (viewOnScreen 0 "shell")
|
||||
ifWindows (resource =? "Alacritty") (mapM_ focus) (spawnHere myTerminal)
|
||||
activateMyTerminal)
|
||||
, ((winKey , xK_v), do
|
||||
ifWindows (resource =? "Alacritty") (mapM_ focus) (spawnHere myTerminal)
|
||||
activateMyTerminal)
|
||||
--ifWindows (resource =? "main") (mapM_ focus) (spawnHere myTerminal))
|
||||
ifWindows (resource =? "Alacritty") (mapM_ focus) (spawnHere myTerminal))
|
||||
, ((controlMask .|. lAlt, xK_BackSpace), (spawnHere "xfdesktop --quit"))
|
||||
, ((controlMask .|. lAlt, xK_Delete), (spawnHere "pkill -9 chromium"))
|
||||
, ((controlMask .|. shiftMask, xK_Return), (spawnHere myTerminal))
|
||||
, ((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 ~/Desktop && mv $f ~/Desktop' --select && paplay ~/wav/camera.wav")
|
||||
, ((controlMask .|. winKey, xK_z), ifWindows (resource =? "Zoom") (mapM_ focus) (spawnHere "zoom"))
|
||||
-- windows (viewOnScreen 1 "ws")
|
||||
-- ifWindows (resource =? "altUrxvt") (mapM_ focus) (spawnHere altTerminal))
|
||||
, ((lAlt, xK_v), spawn "clipmenu && xdotool key Ctrl+v")
|
||||
@ -432,6 +464,7 @@ myKeys = [
|
||||
spawnHere "pkill trayer"
|
||||
sendMessage $ ToggleStruts
|
||||
sendMessage $ ToggleGaps)
|
||||
--sendMessage $ ToggleStruts)
|
||||
, ((lAlt , xK_g), spawnHere "~/bin/google_selection.sh")
|
||||
--, ((winKey , xK_g), ifWindows (className =? "Google-chrome") (mapM_ focus) (spawnHere "google-chrome"))
|
||||
, ((winKey , xK_g), do
|
||||
@ -463,7 +496,6 @@ myKeys = [
|
||||
-- ifWindows (className =? "Skype") (mapM_ focus) (spawnHere "skype"))
|
||||
, ((winKey , xK_s), ifWindows (className =? "Pavucontrol") (mapM_ killWindow) (spawnHere "pavucontrol"))
|
||||
, ((winKey , xK_c), kill)
|
||||
, ((winKey .|. controlMask , xK_c), spawn "gnome-calendar")
|
||||
--, ((winKey , xK_m), windows W.focusMaster)
|
||||
, ((winKey , xK_comma), sendMessage (IncMasterN 1))
|
||||
, ((winKey , xK_period), sendMessage (IncMasterN (-1)))
|
||||
@ -485,13 +517,15 @@ myKeys = [
|
||||
--, ((winKey .|. controlMask , xK_k), spawn ("sleep 1 && cat ~/.macros/code.macro | xmacroplay -d 0.1 $DISPLAY"))
|
||||
--, ((shiftMask, xK_Insert), withFocused shiftInsert)
|
||||
--, ((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_Right), nextWS)
|
||||
, ((winKey , xK_Up), spawnHere "skippy-xd")
|
||||
--, ((0, xF86XK_Calculator), spawnHere "/home/trey/bin/calc")
|
||||
--, ((0, xF86XK_Calculator), ifWindows (className =? "Gcalctool") (mapM_ killWindow) (spawnHere "gcalctool"))
|
||||
, ((0, xF86XK_Calculator), ifWindows (className =? "Gnome-calculator") (mapM_ killWindow) (spawnHere "gnome-calculator"))
|
||||
, ((winKey , xK_y), spawn "dunstctl close-all")
|
||||
, ((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_AudioMute), spawn "amixer -c 0 set Master toggle")
|
||||
, ((0, xF86XK_AudioMute), spawn "pamixer --toggle-mute")
|
||||
|
Loading…
Reference in New Issue
Block a user