mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-07-31 04:01:51 -07:00
Fix GHC warning: -Wname-shadowing
Related: https://github.com/xmonad/xmonad-contrib/issues/537
This commit is contained in:
@@ -130,9 +130,9 @@ renameWorkspaceByName w = do old <- gets (currentTag . windowset)
|
||||
sets q = q { current = setscr $ current q }
|
||||
in sets $ removeWorkspace' w s
|
||||
updateIndexMap old w
|
||||
where updateIndexMap old new = do
|
||||
where updateIndexMap oldIM newIM = do
|
||||
wmap <- XS.gets workspaceIndexMap
|
||||
XS.modify $ \s -> s {workspaceIndexMap = Map.map (\t -> if t == old then new else t) wmap}
|
||||
XS.modify $ \s -> s {workspaceIndexMap = Map.map (\t -> if t == oldIM then newIM else t) wmap}
|
||||
|
||||
toNthWorkspace :: (String -> X ()) -> Int -> X ()
|
||||
toNthWorkspace job wnum = do sort <- getSortByIndex
|
||||
|
@@ -940,16 +940,16 @@ sortedScreens :: WindowSet -> [Screen]
|
||||
sortedScreens winset = L.sortBy cmp
|
||||
$ W.screens winset
|
||||
where
|
||||
cmp s1 s2 | x1 < x2 = LT
|
||||
| x1 > x2 = GT
|
||||
| y1 < x2 = LT
|
||||
| y1 > y2 = GT
|
||||
cmp s1 s2 | x < x' = LT
|
||||
| x > x' = GT
|
||||
| y < x' = LT
|
||||
| y > y' = GT
|
||||
| otherwise = EQ
|
||||
where
|
||||
(x1, y1) = centerOf (screenRect . W.screenDetail $ s1)
|
||||
(x2, y2) = centerOf (screenRect . W.screenDetail $ s2)
|
||||
(x , y ) = centerOf (screenRect . W.screenDetail $ s1)
|
||||
(x', y') = centerOf (screenRect . W.screenDetail $ s2)
|
||||
|
||||
|
||||
-- | Calculates the L1-distance between two points.
|
||||
lDist :: (Position, Position) -> (Position, Position) -> Int
|
||||
lDist (x1, y1) (x2, y2) = abs (fi $ x1 - x2) + abs (fi $ y1 - y2)
|
||||
lDist (x, y) (x', y') = abs (fi $ x - x') + abs (fi $ y - y')
|
||||
|
@@ -73,8 +73,8 @@ instance ExtensionClass Spawner where
|
||||
|
||||
|
||||
getPPIDOf :: ProcessID -> Maybe ProcessID
|
||||
getPPIDOf pid =
|
||||
case unsafePerformIO . tryJust (guard . isDoesNotExistError) . readFile . printf "/proc/%d/stat" $ toInteger pid of
|
||||
getPPIDOf thisPid =
|
||||
case unsafePerformIO . tryJust (guard . isDoesNotExistError) . readFile . printf "/proc/%d/stat" $ toInteger thisPid of
|
||||
Left _ -> Nothing
|
||||
Right contents -> case lines contents of
|
||||
[] -> Nothing
|
||||
@@ -83,11 +83,11 @@ getPPIDOf pid =
|
||||
_ -> Nothing
|
||||
|
||||
getPPIDChain :: ProcessID -> [ProcessID]
|
||||
getPPIDChain pid' = ppid_chain pid' []
|
||||
where ppid_chain pid acc =
|
||||
if pid == 0
|
||||
getPPIDChain thisPid = ppid_chain thisPid []
|
||||
where ppid_chain pid' acc =
|
||||
if pid' == 0
|
||||
then acc
|
||||
else case getPPIDOf pid of
|
||||
else case getPPIDOf pid' of
|
||||
Nothing -> acc
|
||||
Just ppid -> ppid_chain ppid (ppid : acc)
|
||||
|
||||
|
Reference in New Issue
Block a user