Apply hlint hints

All hints are applied in one single commit, as a commit per hint would
result in 80+ separate commits—tihs is really just too much noise.

Related: https://github.com/xmonad/xmonad-contrib/issues/537
This commit is contained in:
slotThe
2021-06-06 16:11:17 +02:00
parent b96899afb6
commit bd5b969d9b
222 changed files with 1119 additions and 1193 deletions

View File

@@ -1,5 +1,5 @@
{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances, PatternGuards, DeriveDataTypeable #-}
{-# LANGUAGE PatternGuards, DeriveDataTypeable #-}
{-# OPTIONS_GHC -Wno-dodgy-imports #-} -- singleton in Data.List since base 4.15
-----------------------------------------------------------------------------
@@ -144,7 +144,7 @@ data ConfigurableBorder p w = ConfigurableBorder
-- | Only necessary with 'BorderMessage' - remove non-existent windows from the
-- 'alwaysHidden' or 'neverHidden' lists.
borderEventHook :: Event -> X All
borderEventHook (DestroyWindowEvent { ev_window = w }) = do
borderEventHook DestroyWindowEvent{ ev_window = w } = do
broadcastMessage $ ResetBorder w
return $ All True
borderEventHook _ = return $ All True
@@ -153,7 +153,7 @@ instance (Read p, Show p, SetsAmbiguous p) => LayoutModifier (ConfigurableBorder
unhook (ConfigurableBorder _ _ _ ch) = asks (borderWidth . config) >>= setBorders ch
redoLayout cb@(ConfigurableBorder gh ah nh ch) lr mst wrs = do
let gh' wset = let lh = (hiddens gh wset lr mst wrs)
let gh' wset = let lh = hiddens gh wset lr mst wrs
in return $ (ah `union` lh) \\ nh
ch' <- withWindowSet gh'
asks (borderWidth . config) >>= setBorders (ch \\ ch')
@@ -164,7 +164,7 @@ instance (Read p, Show p, SetsAmbiguous p) => LayoutModifier (ConfigurableBorder
| Just (HasBorder b w) <- fromMessage m =
let consNewIf l True = if w `elem` l then Nothing else Just (w:l)
consNewIf l False = Just l
in (ConfigurableBorder gh) <$> consNewIf ah (not b)
in ConfigurableBorder gh <$> consNewIf ah (not b)
<*> consNewIf nh b
<*> pure ch
| Just (ResetBorder w) <- fromMessage m =