[XMonad] Fix lints

This commit is contained in:
Ivan Malison 2021-08-05 16:41:19 -06:00
parent db320bf060
commit b0b73d0705
No known key found for this signature in database
GPG Key ID: 62530EFBE99DC2F8

View File

@ -5,6 +5,7 @@
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE TupleSections #-}
module Main where module Main where
@ -110,7 +111,7 @@ myConfig = def
restartEventHook e@ClientMessageEvent { ev_message_type = mt } = do restartEventHook e@ClientMessageEvent { ev_message_type = mt } = do
a <- getAtom "XMONAD_RESTART" a <- getAtom "XMONAD_RESTART"
if (mt == a) if mt == a
then XMonad.Operations.restart "imalison-xmonad" True >> return (All True) then XMonad.Operations.restart "imalison-xmonad" True >> return (All True)
else return $ All True else return $ All True
restartEventHook _ = return $ All True restartEventHook _ = return $ All True
@ -119,7 +120,7 @@ myNavigation2DConfig = def { defaultTiledNavigation = centerNavigation }
main = do main = do
dirs <- getDirectories dirs <- getDirectories
(flip launch dirs) (`launch` dirs)
. docks . docks
. pagerHints . pagerHints
. ewmh . ewmh
@ -373,7 +374,7 @@ layoutsStart layout = (layout, [Layout layout])
(joined ||| newLayout, layouts ++ [Layout newLayout]) (joined ||| newLayout, layouts ++ [Layout newLayout])
layoutInfo = layoutInfo =
layoutsStart (rename "4 Columns" $ (multiCol [1, 1, 1] 2 0.0 (-0.5))) |||! layoutsStart (rename "4 Columns" (multiCol [1, 1, 1] 2 0.0 (-0.5))) |||!
rename "3 Columns" (multiCol [1, 1] 2 0.01 (-0.5)) |||! rename "3 Columns" (multiCol [1, 1] 2 0.01 (-0.5)) |||!
rename "Grid" Grid |||! rename "Grid" Grid |||!
rename "Large Main" (Tall 1 (3 / 100) (3 / 4)) |||! rename "Large Main" (Tall 1 (3 / 100) (3 / 4)) |||!
@ -421,6 +422,7 @@ getVirtualClass = flip findM virtualClasses . classIfMatches
getClass w = fromMaybe <$> getClassRaw w <*> getVirtualClass w getClass w = fromMaybe <$> getClassRaw w <*> getVirtualClass w
{-# NOINLINE desktopEntriesMap #-}
desktopEntriesMap :: MM.MultiMap String DesktopEntry desktopEntriesMap :: MM.MultiMap String DesktopEntry
desktopEntriesMap = desktopEntriesMap =
unsafePerformIO $ unsafePerformIO $
@ -466,13 +468,10 @@ myWindowAct c@WindowBringerConfig {menuCommand = cmd, menuArgs = args}
filterVisible action = do filterVisible action = do
visible <- visibleWindows visible <- visibleWindows
currentlyFullscreen <- isToggleActiveInCurrent NBFULL currentlyFullscreen <- isToggleActiveInCurrent NBFULL
let actualConfig = let actualConfig
if fromMaybe False currentlyFullscreen | fromMaybe False currentlyFullscreen = c
then c | filterVisible = c {windowFilter = not . flip elem visible}
else | otherwise = c
if filterVisible
then c {windowFilter = not . flip elem visible}
else c
ws <- M.toList <$> windowMap' actualConfig ws <- M.toList <$> windowMap' actualConfig
selection <- menuIndexArgs cmd args ws selection <- menuIndexArgs cmd args ws
whenJust selection action whenJust selection action
@ -486,11 +485,11 @@ myWindowAction filterVisible =
myGoToWindow = myGoToWindow =
myWindowAction False $ windows . greedyFocusWindow myWindowAction False $ windows . greedyFocusWindow
myBringWindow = myWindowAction True $ doBringWindow myBringWindow = myWindowAction True doBringWindow
myReplaceWindow = myReplaceWindow =
swapMinimizeStateAfter $ swapMinimizeStateAfter $
myWindowAct myWindowBringerConfig True $ (windows . swapFocusedWith) myWindowAct myWindowBringerConfig True $ windows . swapFocusedWith
-- Workspace Names for EWMH -- Workspace Names for EWMH
@ -555,8 +554,9 @@ toggleFading w = setFading' $ toggleInMap w
setFading w f = setFading' $ M.insert w f setFading w f = setFading' $ M.insert w f
setFading' f = setFading' f =
fmap (ToggleFade . f . fadesMap) XS.get >>= XS.put XS.get >>= XS.put . (ToggleFade . f . fadesMap)
-- Minimize not in class -- Minimize not in class
restoreFocus action = restoreFocus action =
@ -620,12 +620,12 @@ windowsMatchingClassPredicate predicate window workspace =
windowsSatisfyingPredicate workspace getPredicate = do windowsSatisfyingPredicate workspace getPredicate = do
predicate <- getPredicate predicate <- getPredicate
filterM (\w -> predicate <$> getClass w) (W.integrate workspace) filterM (fmap predicate . getClass) (W.integrate workspace)
getMatchingUnmatching = getMatchingUnmatching =
partition <$> ((. snd) <$> getClassMatchesCurrent) <*> getWindowClassPairs partition <$> ((. snd) <$> getClassMatchesCurrent) <*> getWindowClassPairs
getWindowClassPairs = join $ mapM windowToClassPair <$> workspaceWindows getWindowClassPairs = mapM windowToClassPair =<< workspaceWindows
windowToClassPair w = (,) w <$> getClass w windowToClassPair w = (,) w <$> getClass w
@ -648,13 +648,13 @@ restoreAll = mapM_ maximizeWindow
restoreAllMinimized = minimizedWindows >>= restoreAll restoreAllMinimized = minimizedWindows >>= restoreAll
restoreOrMinimizeOtherClasses = null <$> maximizedOtherClass >>= restoreOrMinimizeOtherClasses = maximizedOtherClass >>=
ifL restoreAllMinimized minimizeOtherClassesInWorkspace ifL restoreAllMinimized minimizeOtherClassesInWorkspace . null
restoreThisClassOrMinimizeOtherClasses = minimizedSameClass >>= \ws -> restoreThisClassOrMinimizeOtherClasses = minimizedSameClass >>= \ws ->
if' (null ws) minimizeOtherClassesInWorkspace $ restoreAll ws if' (null ws) minimizeOtherClassesInWorkspace $ restoreAll ws
getClassPair w = flip (,) w <$> getClass w getClassPair w = (, w) <$> getClass w
windowClassPairs = withWindowSet $ mapM getClassPair . W.allWindows windowClassPairs = withWindowSet $ mapM getClassPair . W.allWindows
classToWindowMap = MM.fromList <$> windowClassPairs classToWindowMap = MM.fromList <$> windowClassPairs
@ -669,15 +669,17 @@ nextClass = do
classWindow c = do classWindow c = do
m <- classToWindowMap m <- classToWindowMap
return $ join $ listToMaybe <$> (flip MM.lookup m <$> c) return (listToMaybe . flip MM.lookup m =<< c)
nextClassWindow = nextClass >>= classWindow nextClassWindow = nextClass >>= classWindow
focusNextClass' = focusNextClass' =
join $ windows . maybe id greedyFocusWindow <$> nextClassWindow (windows . maybe id greedyFocusWindow) =<< nextClassWindow
focusNextClass = sameClassOnly focusNextClass' focusNextClass = sameClassOnly focusNextClass'
selectClass = join $ myDmenu <$> allClasses selectClass = myDmenu =<< allClasses
-- Gather windows of same class -- Gather windows of same class
@ -705,7 +707,7 @@ shiftThenView i = W.greedyView i . W.shift i
greedyBringWindow w = greedyFocusWindow w . bringWindow w greedyBringWindow w = greedyFocusWindow w . bringWindow w
shiftToEmptyAndView = shiftToEmptyAndView =
doTo Next EmptyWS DWO.getSortByOrder (windows . shiftThenView) doTo Next emptyWS DWO.getSortByOrder (windows . shiftThenView)
setFocusedScreen :: ScreenId -> WindowSet -> WindowSet setFocusedScreen :: ScreenId -> WindowSet -> WindowSet
setFocusedScreen to ws = setFocusedScreen to ws =
@ -730,10 +732,10 @@ viewOtherScreen ws = W.greedyView ws . nextScreen
shiftThenViewOtherScreen ws w = viewOtherScreen ws . W.shiftWin ws w shiftThenViewOtherScreen ws w = viewOtherScreen ws . W.shiftWin ws w
shiftCurrentToWSOnOtherScreen ws s = shiftCurrentToWSOnOtherScreen ws s =
fromMaybe s (flip (shiftThenViewOtherScreen ws) s <$> W.peek s) maybe s (flip (shiftThenViewOtherScreen ws) s) (W.peek s)
shiftToEmptyNextScreen = shiftToEmptyNextScreen =
doTo Next EmptyWS DWO.getSortByOrder $ windows . shiftCurrentToWSOnOtherScreen doTo Next emptyWS DWO.getSortByOrder $ windows . shiftCurrentToWSOnOtherScreen
swapFocusedWith w ws = W.modify' (swapFocusedWith' w) (W.delete' w ws) swapFocusedWith w ws = W.modify' (swapFocusedWith' w) (W.delete' w ws)
@ -842,7 +844,7 @@ buildDirectionalBindings mask commandFn =
myWindowGo direction = do myWindowGo direction = do
layoutName <- description . W.layout <$> currentWorkspace layoutName <- description . W.layout <$> currentWorkspace
if isInfixOf "Tabbed" layoutName if "Tabbed" `isInfixOf` layoutName
then then
case direction of case direction of
D -> windows W.focusUp D -> windows W.focusUp
@ -855,18 +857,17 @@ addKeys conf@XConfig { modMask = modm } =
-- Directional navigation -- Directional navigation
(buildDirectionalBindings modm myWindowGo) ++ buildDirectionalBindings modm myWindowGo ++
(buildDirectionalBindings buildDirectionalBindings
(modm .|. shiftMask) $ flip windowSwap True) ++ (modm .|. shiftMask) (`windowSwap` True) ++
(buildDirectionalBindings buildDirectionalBindings
(modm .|. controlMask) $ followingWindow . (flip windowToScreen True)) ++ (modm .|. controlMask) (followingWindow . (`windowToScreen` True)) ++
(buildDirectionalBindings buildDirectionalBindings hyper (`screenGo` True) ++
hyper $ flip screenGo True) ++ buildDirectionalBindings
(buildDirectionalBindings (hyper .|. shiftMask) (followingWindow . (`screenSwap` True)) ++
(hyper .|. shiftMask) $ followingWindow . (flip screenSwap True)) ++ buildDirectionalBindings
(buildDirectionalBindings (hyper .|. controlMask) shiftToEmptyOnScreen ++
(hyper .|. controlMask) $ shiftToEmptyOnScreen) ++
-- Specific program spawning -- Specific program spawning
bindBringAndRaiseMany bindBringAndRaiseMany
[ (modalt, xK_c, spawn chromeCommand, chromeSelector) [ (modalt, xK_c, spawn chromeCommand, chromeSelector)
@ -917,8 +918,9 @@ addKeys conf@XConfig { modMask = modm } =
-- These need to be rebound to support boringWindows -- These need to be rebound to support boringWindows
, ((modm, xK_m), focusMaster) , ((modm, xK_m), focusMaster)
, ((modm, xK_Tab), focusNextClass) , ((modm, xK_Tab), focusNextClass)
, ((hyper, xK_e), moveTo Next EmptyWS) , ((hyper, xK_e), moveTo Next emptyWS)
-- Miscellaneous XMonad -- Miscellaneous XMonad
, ((hyper, xK_1), toggleFadingForActiveWindow) , ((hyper, xK_1), toggleFadingForActiveWindow)
@ -977,10 +979,6 @@ addKeys conf@XConfig { modMask = modm } =
, ((0, xF86XK_MonBrightnessUp), spawn "brightness.sh 5") , ((0, xF86XK_MonBrightnessUp), spawn "brightness.sh 5")
, ((0, xF86XK_MonBrightnessDown), spawn "brightness.sh -5") , ((0, xF86XK_MonBrightnessDown), spawn "brightness.sh -5")
-- LOL Broken keyboard
, ((hyper, xK_m), spawn "xdotool type .")
, ((hyper, xK_n), spawn "xdotool type /")
] ++ ] ++
-- Replace moving bindings -- Replace moving bindings