mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-07-31 20:21: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:
@@ -29,7 +29,7 @@ import XMonad
|
||||
import XMonad.Util.PositionStore
|
||||
import qualified XMonad.StackSet as S
|
||||
import XMonad.Layout.WindowArranger
|
||||
import XMonad.Prelude (isJust, nub, when)
|
||||
import XMonad.Prelude (fromMaybe, isJust, nub, when)
|
||||
|
||||
-- $usage
|
||||
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
|
||||
@@ -52,7 +52,7 @@ import XMonad.Prelude (isJust, nub, when)
|
||||
positionStoreFloat :: PositionStoreFloat a
|
||||
positionStoreFloat = PSF (Nothing, [])
|
||||
|
||||
data PositionStoreFloat a = PSF (Maybe Rectangle, [a]) deriving (Show, Read)
|
||||
newtype PositionStoreFloat a = PSF (Maybe Rectangle, [a]) deriving (Show, Read)
|
||||
instance LayoutClass PositionStoreFloat Window where
|
||||
description _ = "PSF"
|
||||
doLayout (PSF (maybeChange, paintOrder)) sr (S.Stack w l r) = do
|
||||
@@ -67,9 +67,8 @@ instance LayoutClass PositionStoreFloat Window where
|
||||
updatePositionStore focused sr
|
||||
return (reorder wrs' paintOrder', Just $ PSF (Nothing, paintOrder'))
|
||||
where
|
||||
pSQ posStore w' sr' = case (posStoreQuery posStore w' sr') of
|
||||
Just rect -> rect
|
||||
Nothing -> (Rectangle 50 50 200 200) -- should usually not happen
|
||||
pSQ posStore w' sr' = fromMaybe (Rectangle 50 50 200 200) -- should usually not happen
|
||||
(posStoreQuery posStore w' sr')
|
||||
pureMessage (PSF (_, paintOrder)) m
|
||||
| Just (SetGeometry rect) <- fromMessage m =
|
||||
Just $ PSF (Just rect, paintOrder)
|
||||
@@ -81,10 +80,10 @@ updatePositionStore (w, rect) sr = modifyPosStore (\ps ->
|
||||
|
||||
reorder :: (Eq a) => [(a, b)] -> [a] -> [(a, b)]
|
||||
reorder wrs order =
|
||||
let ordered = concat $ map (pickElem wrs) order
|
||||
rest = filter (\(w, _) -> not (w `elem` order)) wrs
|
||||
let ordered = concatMap (pickElem wrs) order
|
||||
rest = filter (\(w, _) -> w `notElem` order) wrs
|
||||
in ordered ++ rest
|
||||
where
|
||||
pickElem list e = case (lookup e list) of
|
||||
pickElem list e = case lookup e list of
|
||||
Just result -> [(e, result)]
|
||||
Nothing -> []
|
||||
|
Reference in New Issue
Block a user