mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-07-30 19:51:51 -07:00
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:
@@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses, PatternGuards, TypeSynonymInstances #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses, PatternGuards, TypeSynonymInstances #-}
|
||||
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
@@ -56,7 +56,7 @@ import XMonad.Util.XUtils
|
||||
mouseResize :: l a -> ModifiedLayout MouseResize l a
|
||||
mouseResize = ModifiedLayout (MR [])
|
||||
|
||||
data MouseResize a = MR [((a,Rectangle),Maybe a)]
|
||||
newtype MouseResize a = MR [((a,Rectangle),Maybe a)]
|
||||
instance Show (MouseResize a) where show _ = ""
|
||||
instance Read (MouseResize a) where readsPrec _ s = [(MR [], s)]
|
||||
|
||||
@@ -68,7 +68,7 @@ instance LayoutModifier MouseResize Window where
|
||||
where
|
||||
wrs' = wrs_to_state [] . filter (isInStack s . fst) $ wrs
|
||||
initState = mapM createInputWindow wrs'
|
||||
processState = mapM (deleteInputWin . snd) st >> mapM createInputWindow wrs'
|
||||
processState = mapM_ (deleteInputWin . snd) st >> mapM createInputWindow wrs'
|
||||
|
||||
inputRectangle (Rectangle x y wh ht) = Rectangle (x + fi wh - 5) (y + fi ht - 5) 10 10
|
||||
|
||||
|
Reference in New Issue
Block a user