dots-of-war/files/.xmonad/lib/Config.hs

511 lines
22 KiB
Haskell
Raw Normal View History

2020-05-18 12:23:16 +00:00
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
2020-05-12 09:42:08 +00:00
{-# LANGUAGE FlexibleContexts #-}
{-# Language ScopedTypeVariables, LambdaCase #-}
2020-03-23 19:23:31 +00:00
{-# OPTIONS_GHC -fno-warn-missing-signatures -fno-warn-unused-binds #-}
-- Imports -------------------------------------------------------- {{{
2020-04-01 10:02:59 +00:00
2020-03-22 18:40:50 +00:00
module Config (main) where
2020-05-09 13:24:23 +00:00
import Control.Concurrent
2020-05-18 10:32:35 +00:00
import Control.Exception ( catch , SomeException)
2020-05-16 19:44:11 +00:00
import Control.Monad ( filterM )
2020-05-18 12:23:16 +00:00
import Control.Arrow ( second
, (***)
)
2020-05-18 10:32:35 +00:00
import Data.List ( isPrefixOf , isSuffixOf)
2020-03-25 10:05:44 +00:00
import System.Exit (exitSuccess)
2020-04-01 10:08:40 +00:00
import qualified Rofi
2020-05-18 10:08:22 +00:00
import qualified DescribedSubmap
2020-04-01 10:08:40 +00:00
2020-03-22 18:06:44 +00:00
2020-05-18 10:32:35 +00:00
import Data.Foldable ( for_ )
import Data.Function ((&))
2020-04-02 07:31:20 +00:00
2020-03-22 18:06:44 +00:00
import XMonad hiding ((|||))
import XMonad.Actions.CopyWindow
2020-05-18 10:32:35 +00:00
import XMonad.Actions.PhysicalScreens ( horizontalScreenOrderer )
import XMonad.Actions.SpawnOn
2020-03-22 18:06:44 +00:00
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.SetWMName (setWMName)
2020-04-01 10:08:40 +00:00
import XMonad.Layout.BinarySpacePartition
import XMonad.Layout.BorderResize
2020-03-22 18:06:44 +00:00
import XMonad.Layout.Gaps
2020-05-18 10:32:35 +00:00
import XMonad.Layout.IndependentScreens
2020-03-22 18:06:44 +00:00
import XMonad.Layout.LayoutCombinators ((|||))
2020-04-01 10:08:40 +00:00
import XMonad.Layout.LayoutHints
import XMonad.Layout.MouseResizableTile
2020-04-01 10:02:59 +00:00
import XMonad.Layout.NoBorders
2020-04-01 10:08:40 +00:00
import XMonad.Layout.Renamed (renamed, Rename(Replace))
2020-05-21 12:11:23 +00:00
--import qualified XMonad.Layout.MultiColumns as MultiCol
2020-04-01 10:02:59 +00:00
import XMonad.Layout.ResizableTile
2020-05-18 10:32:35 +00:00
import XMonad.Layout.Simplest
2020-05-21 13:05:39 +00:00
import XMonad.Layout.Reflect
2020-03-25 10:05:44 +00:00
import XMonad.Layout.Spacing (spacingRaw, Border(..), toggleWindowSpacingEnabled)
2020-05-18 10:32:35 +00:00
import XMonad.Layout.SubLayouts
import XMonad.Layout.Tabbed
import XMonad.Layout.WindowNavigation ( windowNavigation )
2020-03-23 19:23:31 +00:00
import XMonad.Layout.ZoomRow
2020-05-18 12:23:16 +00:00
import XMonad.Layout.ThreeColumns
import XMonad.Util.EZConfig ( additionalKeysP
, removeKeysP
, checkKeymap
)
2020-03-22 18:06:44 +00:00
import XMonad.Util.NamedScratchpad
2020-03-23 19:23:31 +00:00
import XMonad.Util.Run
2020-03-22 18:06:44 +00:00
import XMonad.Util.SpawnOnce (spawnOnce)
2020-05-18 10:32:35 +00:00
import XMonad.Util.WorkspaceCompare ( getSortByXineramaPhysicalRule , getSortByIndex)
import qualified Data.Monoid
2020-05-21 13:05:39 +00:00
import qualified XMonad.Layout.LayoutModifier
2020-05-18 12:23:16 +00:00
import qualified System.IO as SysIO
import qualified XMonad.Actions.Navigation2D as Nav2d
import qualified XMonad.Config.Desktop as Desktop
import qualified XMonad.Hooks.EwmhDesktops as Ewmh
import qualified XMonad.Hooks.ManageHelpers as ManageHelpers
import qualified XMonad.Layout.BoringWindows as BoringWindows
import qualified XMonad.Layout.MultiToggle as MTog
2020-05-18 10:32:35 +00:00
import qualified XMonad.Layout.MultiToggle.Instances as MTog
2020-05-18 12:23:16 +00:00
import qualified XMonad.Layout.ToggleLayouts as ToggleLayouts
import qualified XMonad.StackSet as W
import qualified XMonad.Util.XSelection as XSel
2020-05-21 13:05:39 +00:00
import qualified XMonad.Layout.PerScreen as PerScreen
2020-04-01 10:02:59 +00:00
{-# ANN module "HLint: ignore Redundant $" #-}
{-# ANN module "HLint: ignore Redundant bracket" #-}
{-# ANN module "HLint: ignore Move brackets to avoid $" #-}
2020-04-01 10:08:40 +00:00
{-# ANN module "HLint: ignore Unused LANGUAGE pragma" #-}
-- }}}
2020-04-01 10:02:59 +00:00
2020-03-22 18:06:44 +00:00
-- Values -------------------- {{{
myModMask = mod4Mask
2020-03-29 09:36:09 +00:00
myLauncher = Rofi.asCommand (def { Rofi.theme = Rofi.bigTheme }) ["-show run"]
2020-05-12 08:29:58 +00:00
myTerminal = "alacritty"
2020-03-29 17:39:21 +00:00
myBrowser = "qutebrowser"
useSharedWorkspaces = False
2020-03-29 17:39:21 +00:00
--myBrowser = "google-chrome-stable"
2020-03-22 18:06:44 +00:00
2020-03-25 10:05:44 +00:00
{-| adds the scripts-directory path to the filename of a script |-}
scriptFile :: String -> String
scriptFile script = "/home/leon/scripts/" ++ script
2020-05-18 10:08:22 +00:00
2020-03-22 18:06:44 +00:00
scratchpads :: [NamedScratchpad]
2020-03-23 19:23:31 +00:00
scratchpads =
2020-05-21 13:14:21 +00:00
[ NS "terminal" "termite --class sp_term" (className =? "sp_term") (customFloating $ W.RationalRect 0.66 0.7 0.34 0.3)
, NS "spotify" "spotify" (appName =? "spotify") defaultFloating
, NS "discord" "discord" (appName =? "discord") defaultFloating
, NS "whatsapp" "whatsapp-nativefier" (("WhatsApp" `isSuffixOf`) <$> title) defaultFloating
, NS "slack" "slack" (("Slack | " `isPrefixOf`) <$> title) defaultFloating
2020-03-22 18:06:44 +00:00
]
2020-05-18 10:08:22 +00:00
--launchWhatsapp = "gtk-launch chrome-hnpfjngllnobngcgfapefoaidbinmjnm-Default.desktop"
2020-03-22 18:06:44 +00:00
-- Colors ------ {{{
fg = "#ebdbb2"
bg = "#282828"
gray = "#888974"
2020-03-22 18:06:44 +00:00
bg1 = "#3c3836"
bg2 = "#504945"
bg3 = "#665c54"
bg4 = "#7c6f64"
green = "#b8bb26"
darkgreen = "#98971a"
red = "#fb4934"
darkred = "#cc241d"
yellow = "#fabd2f"
blue = "#83a598"
purple = "#d3869b"
aqua = "#8ec07c"
-- }}}
-- }}}
-- Layout ---------------------------------------- {{{
2020-05-12 08:29:58 +00:00
myTabTheme = def
2020-05-18 12:23:16 +00:00
{ activeColor = "#504945"
, inactiveColor = "#282828"
, activeBorderColor = "#fbf1c7"
, inactiveBorderColor = "#282828"
, activeTextColor = "#fbf1c7"
, inactiveTextColor = "#fbf1c7"
, fontName = "-*-jetbrains mono-medium-r-normal-12-0-0-0-0-m-0-ascii-1"
2020-05-12 08:29:58 +00:00
}
2020-05-12 09:42:08 +00:00
2020-05-18 12:23:16 +00:00
myLayout = avoidStruts
2020-05-21 13:05:39 +00:00
$ smartBorders
2020-05-13 08:47:11 +00:00
$ MTog.mkToggle1 MTog.FULL
2020-05-21 13:05:39 +00:00
$ ToggleLayouts.toggleLayouts (rename "Tabbed" . makeTabbed . spacingAndGaps $ ResizableTall 1 (3/100) (1/2) [])
2020-05-13 08:47:11 +00:00
$ layoutHintsToCenter
$ layouts
2020-03-23 19:23:31 +00:00
where
2020-05-21 13:05:39 +00:00
-- | if the screen is wider than 1900px it's horizontal, so use horizontal layouts.
-- if it's not, it's vertical, so use layouts for vertical screens.
layouts = PerScreen.ifWider 1900 horizScreenLayouts vertScreenLayouts
2020-03-23 19:23:31 +00:00
2020-05-21 13:05:39 +00:00
horizScreenLayouts =
((rename "Tall" $ onlySpacing $ mouseResizableTile {draggerType = dragger})
||| (rename "Horizon" $ onlySpacing $ mouseResizableTileMirrored {draggerType = dragger})
||| (rename "BSP" $ spacingAndGaps $ borderResize $ emptyBSP)
||| (rename "ThreeCol" $ makeTabbed $ spacingAndGaps $ ThreeCol 1 (3/100) (1/2))
||| (rename "TabbedRow" $ makeTabbed $ spacingAndGaps $ zoomRow))
2020-03-23 19:23:31 +00:00
2020-05-21 13:05:39 +00:00
vertScreenLayouts =
((rename "ThreeCol" $ makeTabbed $ spacingAndGaps $ Mirror $ reflectHoriz $ ThreeColMid 1 (3/100) (1/2))
||| (rename "Horizon" $ onlySpacing $ mouseResizableTileMirrored {draggerType = dragger}))
2020-05-12 11:02:54 +00:00
2020-05-21 13:05:39 +00:00
rename n = renamed [Replace n]
gap = 10
2020-05-21 13:05:39 +00:00
onlySpacing = gaps [ (dir, (gap*2)) | dir <- [L, R, D, U] ]
2020-03-27 08:06:13 +00:00
dragger = let x = fromIntegral gap * 2
2020-03-25 14:33:33 +00:00
in FixedDragger x x
spacingAndGaps = let intGap = fromIntegral gap
2020-05-12 08:29:58 +00:00
border = Border (intGap) (intGap) (intGap) (intGap)
2020-05-12 09:42:08 +00:00
in spacingRaw False border True border True
2020-05-12 11:02:54 +00:00
2020-05-21 13:05:39 +00:00
-- | transform a layout into supporting tabs
2020-05-18 09:17:04 +00:00
makeTabbed layout = BoringWindows.boringWindows . windowNavigation . addTabs shrinkText myTabTheme $ subLayout [] Simplest $ layout
2020-05-18 12:23:16 +00:00
2020-03-22 18:06:44 +00:00
-- }}}
-- Startuphook ----------------------------- {{{
2020-03-22 18:40:50 +00:00
myStartupHook :: X ()
2020-03-22 18:06:44 +00:00
myStartupHook = do
setWMName "LG3D" -- Java stuff hack
--spawnOnce "pasystray" -- just open the UI by right-clicking on polybar's pulseaudio module
spawnOnce "nm-applet &"
spawnOnce "udiskie -s &" -- Mount USB sticks automatically. -s is smart systray mode: systray icon if something is mounted
spawnOnce "xfce4-clipman &"
spawnOnce "mailspring --background &"
spawnOnce "redshift -P -O 5000 &"
spawn "xset r rate 300 50 &" -- make key repeat quicker
2020-05-16 15:30:38 +00:00
spawn "/home/leon/.screenlayout/dualscreen.sh "
io $ threadDelay $ 1000 * 100
spawnOnce "picom --config ~/.config/picom.conf" --no-fading-openclose"
2020-05-18 09:17:04 +00:00
spawn "/home/leon/.config/polybar/launch.sh"
2020-05-16 19:44:11 +00:00
spawnOnce "nitrogen --restore"
2020-03-22 18:06:44 +00:00
2020-05-21 13:05:39 +00:00
2020-03-22 18:06:44 +00:00
-- }}}
-- Keymap --------------------------------------- {{{
2020-05-07 14:05:16 +00:00
multiMonitorOperation :: (WorkspaceId -> WindowSet -> WindowSet) -> ScreenId -> X ()
multiMonitorOperation operation n = do
monitor <- screenWorkspace n
2020-05-09 13:24:23 +00:00
case monitor of
2020-05-18 09:17:04 +00:00
Just mon -> windows $ operation mon
2020-05-07 14:05:16 +00:00
Nothing -> return ()
2020-05-21 13:05:39 +00:00
-- Default mappings that need to be removed
removedKeys :: [String]
removedKeys = ["M-<Tab>", "M-S-c", "M-S-q", "M-h", "M-l", "M-j", "M-k", "M-S-<Return>"]
++ if useSharedWorkspaces then [key ++ show n | key <- ["M-", "M-S-", "M-C-"], n <- [1..9 :: Int]] else []
2020-05-07 14:05:16 +00:00
2020-05-12 09:42:08 +00:00
myKeys :: [(String, X ())]
2020-05-13 08:47:11 +00:00
myKeys =
-- ZoomRow
2020-05-13 08:47:11 +00:00
[ ("M-+", sendMessage zoomIn)
, ("M--", sendMessage zoomOut)
, ("M-#", sendMessage zoomReset)
2020-05-12 08:29:58 +00:00
2020-05-18 12:23:16 +00:00
, ("M-S-<Space>", for_ [1..6 :: Int] $ \_ -> sendMessage $ NextLayout)
2020-05-12 09:42:08 +00:00
-- Tabs
2020-05-12 11:02:54 +00:00
, ("M-j", ifLayoutName ("Tabbed" `isPrefixOf`) (BoringWindows.focusDown) (windows W.focusDown))
, ("M-k", ifLayoutName ("Tabbed" `isPrefixOf`) (BoringWindows.focusUp) (windows W.focusUp))
2020-05-12 09:42:08 +00:00
, ("M-C-S-h", sendMessage $ pullGroup L)
, ("M-C-S-j", sendMessage $ pullGroup D)
, ("M-C-S-k", sendMessage $ pullGroup U)
, ("M-C-S-l", sendMessage $ pullGroup R)
, ("M-S-C-m", withFocused (sendMessage . MergeAll))
, ("M-S-C-<Backspace>", withFocused (sendMessage . UnMerge))
, ("M-<Tab>", onGroup W.focusDown')
, ("M-C-<Tab>", onGroup W.focusUp')
2020-05-12 11:03:41 +00:00
, ("M-S-t", toggleTabbedLayout)
2020-05-12 08:29:58 +00:00
-- In tabbed mode, while focussing master pane, cycle tabs on the first slave
2020-05-13 08:47:11 +00:00
, ("M-S-<Tab>", do windows W.focusMaster
BoringWindows.focusDown
onGroup W.focusDown'
windows W.focusMaster)
2020-05-12 08:29:58 +00:00
2020-05-18 10:08:22 +00:00
, ("M-f", do sendMessage $ MTog.Toggle MTog.FULL
sendMessage ToggleStruts)
2020-05-12 08:29:58 +00:00
2020-05-16 19:44:11 +00:00
, ("M-b", launchWithBackgroundInstance (className =? "qutebrowser") "bwrap --bind / / --dev-bind /dev /dev --tmpfs /tmp --tmpfs /run qutebrowser")
2020-05-16 20:02:51 +00:00
, ("M-S-<Return>", launchWithBackgroundInstance (className =? "Alacritty") "alacritty")
2020-05-09 13:24:23 +00:00
2020-05-12 11:02:54 +00:00
, ("M-S-C-c", kill1)
, ("M-S-C-q", io exitSuccess)
2020-05-09 13:24:23 +00:00
-- Binary space partitioning
2020-05-12 11:02:54 +00:00
, ("M-<Backspace>", sendMessage Swap)
2020-05-09 13:24:23 +00:00
, ("M-M1-<Backspace>", sendMessage Rotate)
-- Media
, ("<XF86AudioRaiseVolume>", spawn "amixer sset Master 5%+")
, ("<XF86AudioLowerVolume>", spawn "amixer sset Master 5%-")
-- Multi monitor
, ("M-s", multiMonitorOperation W.view 1)
, ("M-d", multiMonitorOperation W.view 0)
, ("M-S-s", (multiMonitorOperation W.shift 1) >> multiMonitorOperation W.view 1)
, ("M-S-d", (multiMonitorOperation W.shift 0) >> multiMonitorOperation W.view 0)
-- programs
, ("M-p", spawn myLauncher)
, ("M-S-p", Rofi.showCombi (def { Rofi.theme = Rofi.bigTheme }) [ "drun", "window", "ssh" ])
2020-05-21 12:11:23 +00:00
, ("M-S-e", Rofi.showNormal (def { Rofi.theme = Rofi.bigTheme, Rofi.fuzzy = False }) "emoji")
2020-05-09 13:24:23 +00:00
--, ("M-s", spawn $ scriptFile "rofi-search.sh")
, ("M-S-o", spawn $ scriptFile "rofi-open.sh")
2020-05-18 09:17:04 +00:00
, ("M-n", scratchpadSubmap)
2020-05-09 13:24:23 +00:00
, ("M-e", Rofi.promptRunCommand def specialCommands)
, ("M-o", Rofi.promptRunCommand def withSelectionCommands)
2020-05-18 10:08:22 +00:00
, ("M-S-C-g", spawn "killall -INT -g giph" >> notify "gif" "saved gif in ~/Bilder/gifs") -- stop gif recording
2020-05-09 13:24:23 +00:00
] ++ generatedMappings
2020-03-22 18:06:44 +00:00
where
2020-03-27 08:06:13 +00:00
generatedMappings :: [(String, X ())]
2020-05-09 13:24:23 +00:00
generatedMappings = windowGoMappings ++ windowSwapMappings ++ resizeMappings ++ workspaceMappings
2020-03-27 08:06:13 +00:00
where
2020-05-09 13:24:23 +00:00
workspaceMappings =
if useSharedWorkspaces then [] else
[ (mappingPrefix ++ show wspNum,
do
-- get all workspaces from the config by running an X action to query the config
wsps <- workspaces' <$> asks config
windows $ onCurrentScreen action (wsps !! (wspNum - 1))
)
| (wspNum) <- [1..9 :: Int]
, (mappingPrefix, action) <- [("M-", W.greedyView), ("M-S-", W.shift), ("M-C-", copy)]
]
2020-04-01 12:37:33 +00:00
keyDirPairs = [("h", L), ("j", D), ("k", U), ("l", R)]
windowGoMappings = [ ("M-M1-" ++ key, Nav2d.windowGo dir False) | (key, dir) <- keyDirPairs ]
windowSwapMappings = [ ("M-S-M1-" ++ key, Nav2d.windowSwap dir False) | (key, dir) <- keyDirPairs ]
2020-04-02 07:31:20 +00:00
resizeMappings =
2020-05-07 14:05:16 +00:00
[ ("M-C-h", ifLayoutIs "BSP" (sendMessage $ ExpandTowards L) (ifLayoutIs "Horizon" (sendMessage ShrinkSlave) (sendMessage Shrink)))
, ("M-C-j", ifLayoutIs "BSP" (sendMessage $ ExpandTowards D) (ifLayoutIs "Horizon" (sendMessage Expand) (sendMessage MirrorShrink >> sendMessage ExpandSlave)))
, ("M-C-k", ifLayoutIs "BSP" (sendMessage $ ExpandTowards U) (ifLayoutIs "Horizon" (sendMessage Shrink) (sendMessage MirrorExpand >> sendMessage ShrinkSlave)))
, ("M-C-l", ifLayoutIs "BSP" (sendMessage $ ExpandTowards R) (ifLayoutIs "Horizon" (sendMessage ExpandSlave) (sendMessage Expand)))
2020-03-27 08:06:13 +00:00
]
2020-05-13 08:47:11 +00:00
2020-05-18 10:08:22 +00:00
scratchpadSubmap :: X ()
scratchpadSubmap = DescribedSubmap.describedSubmap "Scratchpads"
[ ("M-n", "terminal", namedScratchpadAction scratchpads "terminal")
, ("M-w", "whatsapp", namedScratchpadAction scratchpads "whatsapp")
, ("M-s", "slack", namedScratchpadAction scratchpads "slack")
, ("M-m", "spotify", namedScratchpadAction scratchpads "spotify")
, ("M-d", "discord", namedScratchpadAction scratchpads "discord")
]
-- | toggle tabbed Tall layout, merging all non-master windows
-- into a single tab group when initializing the tabbed layout.
2020-05-12 11:02:54 +00:00
toggleTabbedLayout :: X ()
2020-05-13 08:47:11 +00:00
toggleTabbedLayout = do
2020-05-12 11:02:54 +00:00
sendMessage $ ToggleLayouts.Toggle "Tabbed"
ifLayoutIs "Tabbed" (do BoringWindows.focusMaster
withFocused (sendMessage . MergeAll)
withFocused (sendMessage . UnMerge)
-- refresh the tabs, so they draw correctly
windows W.focusUp
windows W.focusDown)
(return ())
2020-05-09 13:24:23 +00:00
2020-05-18 09:17:04 +00:00
-- | launch a program by starting an instance in a hidden workspace,
2020-05-16 19:44:11 +00:00
-- and just raising an already running instance. This allows for super quick "startup" time.
-- For this to work, the window needs to have the `_NET_WM_PID` set and unique!
launchWithBackgroundInstance :: (Query Bool) -> String -> X ()
launchWithBackgroundInstance windowQuery commandToRun = withWindowSet $ \winSet -> do
2020-05-21 13:05:39 +00:00
fittingHiddenWindows <- (W.allWindows winSet) |> filter (\win -> Just "NSP" == W.findTag win winSet)
|> filterM (runQuery windowQuery)
case fittingHiddenWindows of
2020-05-16 19:44:11 +00:00
[] -> do spawnHere commandToRun
spawnOn "NSP" commandToRun
[winId] -> do windows $ W.shiftWin (W.currentTag winSet) winId
spawnOn "NSP" commandToRun
(winId:_) -> windows $ W.shiftWin (W.currentTag winSet) winId
2020-03-31 16:38:27 +00:00
withSelectionCommands :: [(String, X ())]
2020-04-01 10:02:59 +00:00
withSelectionCommands =
[ ("Google", XSel.transformPromptSelection ("https://google.com/search?q=" ++) "qutebrowser")
, ("Hoogle", XSel.transformPromptSelection ("https://hoogle.haskell.org/?hoogle=" ++) "qutebrowser")
, ("Translate", XSel.transformPromptSelection ("https://translate.google.com/#view=home&op=translate&sl=auto&tl=en&text=" ++) "qutebrowser")
2020-03-31 16:38:27 +00:00
]
2020-03-22 18:06:44 +00:00
specialCommands :: [(String, X ())]
specialCommands =
2020-03-29 17:39:21 +00:00
[ ("screenshot", spawn $ scriptFile "screenshot.sh")
2020-04-02 07:31:20 +00:00
, ("screenshot to file", spawn $ scriptFile "screenshot.sh --tofile")
, ("screenshot full to file", spawn $ scriptFile "screenshot.sh --tofile --fullscreen")
2020-05-18 10:08:22 +00:00
, ("screengif to file", spawn (scriptFile "screengif.sh") >> notify "gif" "stop gif-recording with M-S-C-g")
2020-03-29 18:47:50 +00:00
, ("toggleOptimal", sendMessage ToggleGaps >> toggleWindowSpacingEnabled)
2020-03-29 17:39:21 +00:00
, ("toggleSpacing", toggleWindowSpacingEnabled)
, ("toggleGaps", sendMessage ToggleGaps)
2020-05-18 09:17:04 +00:00
, ("Copy to all workspaces", windows copyToAll)
2020-03-29 17:39:21 +00:00
, ("Kill all other copies", killAllOtherCopies)
2020-05-18 10:08:22 +00:00
, ("toggle polybar", sendMessage ToggleStruts >> safeSpawn "polybar-msg" ["cmd", "toggle"])
2020-03-22 18:06:44 +00:00
]
2020-03-31 16:38:27 +00:00
2020-03-22 18:06:44 +00:00
-- }}}
-- ManageHook -------------------------------{{{
myManageHook :: Query (Data.Monoid.Endo WindowSet)
myManageHook = composeAll
[ resource =? "Dialog" --> ManageHelpers.doCenterFloat
, appName =? "pavucontrol" --> ManageHelpers.doCenterFloat
, className =? "mpv" --> ManageHelpers.doRectFloat (W.RationalRect 0.9 0.9 0.1 0.1)
, title =? "Something" --> doFloat
, className =? "termite_floating" --> ManageHelpers.doRectFloat(W.RationalRect 0.2 0.2 0.6 0.6)
2020-05-13 22:50:42 +00:00
, className =? "bar_system_status_indicator" --> ManageHelpers.doRectFloat (W.RationalRect 0.7 0.05 0.29 0.26)
2020-03-23 19:23:31 +00:00
, manageDocks
, namedScratchpadManageHook scratchpads
2020-03-22 18:40:50 +00:00
]
2020-03-22 18:06:44 +00:00
-- }}}
-- Main ------------------------------------ {{{
2020-03-22 18:40:50 +00:00
main :: IO ()
2020-03-22 18:06:44 +00:00
main = do
2020-05-09 13:24:23 +00:00
currentScreenCount :: Int <- countScreens
let monitorIndices = [0..currentScreenCount - 1]
-- create a fifo named pipe for every monitor (called /tmp/xmonad-state-bar0, etc)
for_ monitorIndices (\idx -> safeSpawn "mkfifo" ["/tmp/xmonad-state-bar" ++ show idx])
-- create polybarLogHooks for every monitor and combine them using the <+> monoid instance
2020-05-16 15:30:38 +00:00
let polybarLogHooks = composeAll $ map polybarLogHook monitorIndices
2020-05-09 13:24:23 +00:00
2020-05-18 12:23:16 +00:00
let myConfig = flip additionalKeysP myKeys
. flip removeKeysP removedKeys
$ Desktop.desktopConfig
2020-05-09 13:24:23 +00:00
{ terminal = myTerminal
2020-05-18 09:17:04 +00:00
, workspaces = if useSharedWorkspaces
then (map show [1..9 :: Int]) ++ ["NSP"]
else (withScreens (fromIntegral currentScreenCount) (map show [1..6 :: Int])) ++ ["NSP"]
2020-05-09 13:24:23 +00:00
, modMask = myModMask
, borderWidth = 2
, layoutHook = myLayout
2020-05-18 10:32:35 +00:00
, logHook = polybarLogHooks <+> logHook Desktop.desktopConfig <+> logHook def
, startupHook = myStartupHook <+> return () >> checkKeymap myConfig myKeys
2020-05-16 19:44:11 +00:00
, manageHook = manageSpawn <+> myManageHook <+> manageHook def
2020-05-09 13:24:23 +00:00
, focusedBorderColor = aqua
, normalBorderColor = "#282828"
2020-05-18 10:32:35 +00:00
, handleEventHook = handleEventHook Desktop.desktopConfig
2020-05-09 13:24:23 +00:00
--, handleEventHook = minimizeEventHook <+> handleEventHook def <+> hintsEventHook -- <+> Ewmh.fullscreenEventHook
2020-05-18 12:23:16 +00:00
}
2020-05-09 13:24:23 +00:00
2020-03-22 18:06:44 +00:00
2020-03-27 08:06:13 +00:00
xmonad
$ Ewmh.ewmh
2020-03-25 10:05:44 +00:00
$ Nav2d.withNavigation2DConfig def { Nav2d.defaultTiledNavigation = Nav2d.sideNavigation }
2020-05-18 10:32:35 +00:00
$ docks
2020-05-09 13:24:23 +00:00
$ myConfig
2020-03-22 18:06:44 +00:00
-- }}}
-- POLYBAR Kram -------------------------------------- {{{
2020-05-09 13:24:23 +00:00
-- | Loghook for polybar on a given monitor.
-- Will write the polybar formatted string to /tmp/xmonad-state-bar${monitor}
polybarLogHook :: Int -> X ()
polybarLogHook monitor = do
2020-05-18 09:17:04 +00:00
barOut <- dynamicLogString $ polybarPP $ fromIntegral monitor
2020-05-09 13:24:23 +00:00
io $ SysIO.appendFile ("/tmp/xmonad-state-bar" ++ show monitor) (barOut ++ "\n")
2020-03-22 18:06:44 +00:00
2020-05-09 13:24:23 +00:00
-- swapping namedScratchpadFilterOutWorkspacePP and marshallPP will throw "Prelude.read no Parse" errors..... wtf
-- | create a polybar Pretty printer, marshalled for given monitor.
2020-05-18 09:17:04 +00:00
polybarPP :: ScreenId -> PP
polybarPP monitor = namedScratchpadFilterOutWorkspacePP . (if useSharedWorkspaces then id else marshallPP $ fromIntegral monitor) $ def
{ ppCurrent = withFG aqua . withMargin . withFont 5 . const "__active__"
, ppVisible = withFG aqua . withMargin . withFont 5 . const "__active__"
, ppUrgent = withFG red . withMargin . withFont 5 . const "__urgent__"
, ppHidden = withFG gray . withMargin . withFont 5 . (`wrapClickableWorkspace` "__hidden__")
, ppHiddenNoWindows = withFG gray . withMargin . withFont 5 . (`wrapClickableWorkspace` "__empty__")
, ppWsSep = ""
, ppSep = ""
2020-05-18 09:17:04 +00:00
, ppLayout = \l -> if l == "Tall" || l == "Horizon" then ""
else (withFG gray " | ") ++ (removeWords ["Minimize", "Hinted", "Spacing", "Tall"] . withFG purple . withMargin $ l)
, ppExtras = []
, ppTitle = const "" -- withFG aqua . (shorten 40)
2020-05-18 09:17:04 +00:00
, ppSort = if useSharedWorkspaces then getSortByXineramaPhysicalRule horizontalScreenOrderer
else onlyRelevantWspsSorter
2020-03-22 18:06:44 +00:00
}
where
withMargin = wrap " " " "
removeWord substr = unwords . filter (/= substr) . words
2020-05-18 09:17:04 +00:00
removeWords wrds = unwords . filter (`notElem` wrds). words
withFont fNum = wrap ("%{T" ++ show (fNum :: Int) ++ "}") "%{T}"
withBG col = wrap ("%{B" ++ col ++ "}") "%{B-}"
withFG col = wrap ("%{F" ++ col ++ "}") "%{F-}"
wrapOnClickCmd command = wrap ("%{A1:" ++ command ++ ":}") "%{A}"
wrapClickableWorkspace wsp = wrapOnClickCmd ("xdotool key super+" ++ wsp)
2020-05-18 09:17:04 +00:00
onlyRelevantWspsSorter = do
sortByIndex <- getSortByIndex
visibleWorkspaceTags <- getVisibleWorkspacesTagsOnMonitor monitor
let isEmptyAndNotOpened wsp = (null $ W.stack wsp) && (W.tag wsp) `notElem` visibleWorkspaceTags
return $ dropEndWhile isEmptyAndNotOpened . sortByIndex
2020-03-22 18:06:44 +00:00
-- }}}
2020-03-23 19:23:31 +00:00
2020-03-25 10:05:44 +00:00
-- Utilities --------------------------------------------------- {{{
2020-05-09 13:24:23 +00:00
2020-05-16 15:30:38 +00:00
(|>) :: a -> (a -> b) -> b
(|>) = (&)
infixl 1 |>
2020-05-09 13:24:23 +00:00
2020-05-18 09:17:04 +00:00
dropEndWhile :: (a -> Bool) -> [a] -> [a]
dropEndWhile _ [] = []
dropEndWhile test xs = if test $ last xs then dropEndWhile test (init xs) else xs
2020-05-09 13:24:23 +00:00
catchAndNotifyAny :: IO () -> IO ()
2020-05-18 10:08:22 +00:00
catchAndNotifyAny ioAction = catch ioAction (\(e :: SomeException) -> notify "Xmonad exception" (show e))
2020-05-09 13:24:23 +00:00
2020-05-18 09:17:04 +00:00
getVisibleWorkspacesTagsOnMonitor :: ScreenId -> X [VirtualWorkspace]
getVisibleWorkspacesTagsOnMonitor monitor = do
ws <- gets windowset
return $ W.current ws : W.visible ws
|> map (W.tag . W.workspace)
|> filter (\tag -> monitor == fromIntegral (unmarshallS tag))
|> map unmarshallW
2020-05-18 10:08:22 +00:00
notify :: MonadIO m => String -> String -> m ()
notify notificationTitle notificationMsg = safeSpawn "notify-send" [notificationTitle, notificationMsg]
2020-03-25 10:05:44 +00:00
2020-04-01 12:37:33 +00:00
ifLayoutIs :: String -> X a -> X a -> X a
2020-05-12 11:02:54 +00:00
ifLayoutIs layoutAName = ifLayoutName (== layoutAName)
ifLayoutName :: (String -> Bool) -> X a -> X a -> X a
ifLayoutName check onLayoutA onLayoutB = do
2020-05-13 08:47:11 +00:00
layout <- getActiveLayoutDescription
2020-05-12 11:02:54 +00:00
if (check layout) then onLayoutA else onLayoutB
2020-04-01 12:37:33 +00:00
-- Get the name of the active layout.
getActiveLayoutDescription :: X String
getActiveLayoutDescription = (description . W.layout . W.workspace . W.current) <$> gets windowset
2020-03-25 10:05:44 +00:00
-- }}}