Apply hlint 3.3 hints

This commit is contained in:
Tomas Janousek
2021-11-04 20:39:39 +00:00
parent e7f102bc9a
commit 5aff766a4c
20 changed files with 32 additions and 36 deletions

View File

@@ -53,5 +53,5 @@ newtype ButtonDecoration a = NFD Bool deriving (Show, Read)
instance Eq a => DecorationStyle ButtonDecoration a where
describeDeco _ = "ButtonDeco"
decorationCatchClicksHook _ mainw dFL dFR = titleBarButtonHandler mainw dFL dFR
decorationCatchClicksHook _ = titleBarButtonHandler
decorationAfterDraggingHook _ (mainw, _) decoWin = focus mainw >> handleScreenCrossing mainw decoWin >> return ()

View File

@@ -152,7 +152,7 @@ class (Read (ds a), Show (ds a), Eq a) => DecorationStyle ds a where
-- | The description that the 'Decoration' modifier will display.
describeDeco :: ds a -> String
describeDeco ds = show ds
describeDeco = show
-- | Shrink the window's rectangle when applying a decoration.
shrink :: ds a -> Rectangle -> Rectangle -> Rectangle
@@ -160,7 +160,7 @@ class (Read (ds a), Show (ds a), Eq a) => DecorationStyle ds a where
-- | The decoration event hook
decorationEventHook :: ds a -> DecorationState -> Event -> X ()
decorationEventHook ds s e = handleMouseFocusDrag ds s e
decorationEventHook = handleMouseFocusDrag
-- | A hook that can be used to catch the cases when the user
-- clicks on the decoration. If you return True here, the click event
@@ -176,7 +176,7 @@ class (Read (ds a), Show (ds a), Eq a) => DecorationStyle ds a where
-- The hook can be overwritten if a different way of handling the dragging
-- is required.
decorationWhileDraggingHook :: ds a -> CInt -> CInt -> (Window, Rectangle) -> Position -> Position -> X ()
decorationWhileDraggingHook _ ex ey (mainw, r) x y = handleDraggingInProgress ex ey (mainw, r) x y
decorationWhileDraggingHook _ = handleDraggingInProgress
-- | This hoook is called after a window has been dragged using the decoration.
decorationAfterDraggingHook :: ds a -> (Window, Rectangle) -> Window -> X ()

View File

@@ -239,7 +239,7 @@ removeDeleted z = filterZ_ (`elemZ` z)
findNewWindows :: Eq a => [a] -> Zipper (Group l a)
-> (Zipper (Group l a), [a])
findNewWindows as gs = (gs, foldrZ_ removePresent as gs)
where removePresent g as' = filter (not . flip elemZ (gZipper g)) as'
where removePresent g = filter (not . flip elemZ (gZipper g))
-- | Add windows to the focused group. If you need to create one,
-- use the given layout and an id from the given list.

View File

@@ -177,5 +177,5 @@ newtype ImageButtonDecoration a = NFD Bool deriving (Show, Read)
instance Eq a => DecorationStyle ImageButtonDecoration a where
describeDeco _ = "ImageButtonDeco"
decorationCatchClicksHook _ mainw dFL dFR = imageTitleBarButtonHandler mainw dFL dFR
decorationCatchClicksHook _ = imageTitleBarButtonHandler
decorationAfterDraggingHook _ (mainw, _) decoWin = focus mainw >> handleScreenCrossing mainw decoWin >> return ()

View File

@@ -164,7 +164,7 @@ applyHints s root (((w,lrect@(Rectangle a b c d)),adj):xs) =
$ if isInStack s w then Rectangle a b c' d' else lrect
ds = (fromIntegral c - fromIntegral c',fromIntegral d - fromIntegral d')
growOther' r = growOther ds lrect (freeDirs root lrect) r
growOther' = growOther ds lrect (freeDirs root lrect)
mapSnd f = map (first $ second f)
next = applyHints s root $ mapSnd growOther' xs
in (w,redr):next

View File

@@ -107,7 +107,7 @@ class (Show (m a), Read (m a)) => LayoutModifier m a where
-> Workspace WorkspaceId (l a) a -- ^ current workspace
-> Rectangle -- ^ screen rectangle
-> X ([(a, Rectangle)], Maybe (l a))
modifyLayout _ w r = runLayout w r
modifyLayout _ = runLayout
-- | Similar to 'modifyLayout', but this function also allows you
-- update the state of your layout modifier(the second value in the

View File

@@ -99,8 +99,8 @@ instance LayoutModifier LimitWindows a where
where pos x = guard (x>=1) >> return x
app f x = guard (f x /= x) >> return (f x)
modifyLayout (LimitWindows style n) ws r =
runLayout ws { W.stack = f n <$> W.stack ws } r
modifyLayout (LimitWindows style n) ws =
runLayout ws { W.stack = f n <$> W.stack ws }
where f = case style of
FirstN -> firstN
Slice -> slice
@@ -123,8 +123,8 @@ data Selection a = Sel { nMaster :: Int, start :: Int, nRest :: Int }
deriving (Read, Show, Eq)
instance LayoutModifier Selection a where
modifyLayout s w r =
runLayout (w { W.stack = updateAndSelect s <$> W.stack w }) r
modifyLayout s w =
runLayout (w { W.stack = updateAndSelect s <$> W.stack w })
pureModifier sel _ stk wins = (wins, update sel <$> stk)

View File

@@ -71,7 +71,7 @@ instance LayoutModifier ResizeScreen a where
| ResizeScreen T i <- m = resize $ Rectangle x (y + fi i) w (h - fi i)
| ResizeScreen B i <- m = resize $ Rectangle x y w (h - fi i)
| WithNewScreen r <- m = resize r
where resize nr = runLayout ws nr
where resize = runLayout ws
pureMess (ResizeScreen d _) m
| Just (SetTheme t) <- fromMessage m = Just $ ResizeScreen d (fi $ decoHeight t)

View File

@@ -77,7 +77,7 @@ instance Default SWNConfig where
}
instance LayoutModifier ShowWName a where
redoLayout sn r _ wrs = doShow sn r wrs
redoLayout sn r _ = doShow sn r
handleMess (SWN _ c (Just (i,w))) m
| Just e <- fromMessage m = handleTimer i e (deleteWindow w >> return Nothing)

View File

@@ -84,7 +84,7 @@ instance Eq a => DecorationStyle WindowSwitcherDecoration a where
decorationCatchClicksHook (WSD withButtons) mainw dFL dFR = if withButtons
then titleBarButtonHandler mainw dFL dFR
else return False
decorationWhileDraggingHook _ ex ey (mainw, r) x y = handleTiledDraggingInProgress ex ey (mainw, r) x y
decorationWhileDraggingHook _ = handleTiledDraggingInProgress
decorationAfterDraggingHook _ (mainw, _) decoWin = do focus mainw
hasCrossed <- handleScreenCrossing mainw decoWin
unless hasCrossed $ do sendMessage DraggingStopped
@@ -105,7 +105,7 @@ instance Eq a => DecorationStyle ImageWindowSwitcherDecoration a where
decorationCatchClicksHook (IWSD withButtons) mainw dFL dFR = if withButtons
then imageTitleBarButtonHandler mainw dFL dFR
else return False
decorationWhileDraggingHook _ ex ey (mainw, r) x y = handleTiledDraggingInProgress ex ey (mainw, r) x y
decorationWhileDraggingHook _ = handleTiledDraggingInProgress
decorationAfterDraggingHook _ (mainw, _) decoWin = do focus mainw
hasCrossed <- handleScreenCrossing mainw decoWin
unless hasCrossed $ do sendMessage DraggingStopped