mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 00:20:22 -07:00
Replace 'findIndex' with 'findTag', which more accurately describes what the function does.
I realize this is a big change, but the name 'findIndex' was confusing for me, since I expected it to return some sort of integer. What it actually does, of course, is return a workspace tag, which might be more general than an index. Of course, this change breaks several contrib modules; I'll submit a patch to make the change there as well.
This commit is contained in:
parent
8971ab7fae
commit
e384a358b5
@ -564,7 +564,7 @@ float :: Window -> X ()
|
||||
float w = do
|
||||
(sc, rr) <- floatLocation w
|
||||
windows $ \ws -> W.float w rr . fromMaybe ws $ do
|
||||
i <- W.findIndex w ws
|
||||
i <- W.findTag w ws
|
||||
guard $ i `elem` map (W.tag . W.workspace) (W.screens ws)
|
||||
f <- W.peek ws
|
||||
sw <- W.lookupWorkspace sc ws
|
||||
|
14
StackSet.hs
14
StackSet.hs
@ -26,7 +26,7 @@ module StackSet (
|
||||
-- $stackOperations
|
||||
peek, index, integrate, integrate', differentiate,
|
||||
focusUp, focusDown, focusMaster, focusWindow,
|
||||
tagMember, renameTag, ensureTags, member, findIndex, mapWorkspace, mapLayout,
|
||||
tagMember, renameTag, ensureTags, member, findTag, mapWorkspace, mapLayout,
|
||||
-- * Modifying the stackset
|
||||
-- $modifyStackset
|
||||
insertUp, delete, delete', filter,
|
||||
@ -389,7 +389,7 @@ reverseStack (Stack t ls rs) = Stack t rs ls
|
||||
focusWindow :: (Eq s, Eq a, Eq i) => a -> StackSet i l a s sd -> StackSet i l a s sd
|
||||
focusWindow w s | Just w == peek s = s
|
||||
| otherwise = maybe s id $ do
|
||||
n <- findIndex w s
|
||||
n <- findTag w s
|
||||
return $ until ((Just w ==) . peek) focusUp (view n s)
|
||||
|
||||
-- | Get a list of all screens in the StackSet.
|
||||
@ -439,13 +439,13 @@ mapLayout f (StackSet v vs hs m) = StackSet (fScreen v) (map fScreen vs) (map fW
|
||||
|
||||
-- | /O(n)/. Is a window in the StackSet.
|
||||
member :: Eq a => a -> StackSet i l a s sd -> Bool
|
||||
member a s = maybe False (const True) (findIndex a s)
|
||||
member a s = maybe False (const True) (findTag a s)
|
||||
|
||||
-- | /O(1) on current window, O(n) in general/.
|
||||
-- Return Just the workspace index of the given window, or Nothing
|
||||
-- Return Just the workspace tag of the given window, or Nothing
|
||||
-- if the window is not in the StackSet.
|
||||
findIndex :: Eq a => a -> StackSet i l a s sd -> Maybe i
|
||||
findIndex a s = listToMaybe
|
||||
findTag :: Eq a => a -> StackSet i l a s sd -> Maybe i
|
||||
findTag a s = listToMaybe
|
||||
[ tag w | w <- workspaces s, has a (stack w) ]
|
||||
where has _ Nothing = False
|
||||
has x (Just (Stack t l r)) = x `elem` (t : l ++ r)
|
||||
@ -559,7 +559,7 @@ shiftWin :: (Ord a, Eq a, Eq s, Eq i) => i -> a -> StackSet i l a s sd -> StackS
|
||||
shiftWin n w s | from == Nothing = s -- not found
|
||||
| n `tagMember` s && (Just n) /= from = go
|
||||
| otherwise = s
|
||||
where from = findIndex w s
|
||||
where from = findTag w s
|
||||
|
||||
go = on n (insertUp w) . on (fromJust from) (delete' w) $ s
|
||||
curtag = tag (workspace (current s))
|
||||
|
@ -351,14 +351,14 @@ prop_focusWindow_local (n :: NonNegative Int) (x::T ) =
|
||||
in hidden_spaces (focusWindow (s !! i) x) == hidden_spaces x
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
-- member/findIndex
|
||||
-- member/findTag
|
||||
|
||||
--
|
||||
-- For all windows in the stackSet, findIndex should identify the
|
||||
-- For all windows in the stackSet, findTag should identify the
|
||||
-- correct workspace
|
||||
--
|
||||
prop_findIndex (x :: T) =
|
||||
and [ tag w == fromJust (findIndex i x)
|
||||
and [ tag w == fromJust (findTag i x)
|
||||
| w <- workspace (current x) : map workspace (visible x) ++ hidden x
|
||||
, t <- maybeToList (stack w)
|
||||
, i <- focus t : up t ++ down t
|
||||
@ -529,7 +529,7 @@ prop_shift_win_indentity i w (x :: T) =
|
||||
-- shiftWin leaves the current screen as it is, if neither i is the tag
|
||||
-- of the current workspace nor w on the current workspace
|
||||
prop_shift_win_fix_current i w (x :: T) =
|
||||
i `tagMember` x && w `member` x && i /= n && findIndex w x /= Just n
|
||||
i `tagMember` x && w `member` x && i /= n && findTag w x /= Just n
|
||||
==> (current $ x) == (current $ shiftWin i w x)
|
||||
where
|
||||
n = tag (workspace $ current x)
|
||||
@ -707,7 +707,7 @@ main = do
|
||||
,("focusWindow is local", mytest prop_focusWindow_local)
|
||||
,("focusWindow works" , mytest prop_focusWindow_works)
|
||||
|
||||
,("findIndex" , mytest prop_findIndex)
|
||||
,("findTag" , mytest prop_findIndex)
|
||||
,("allWindows/member" , mytest prop_allWindowsMember)
|
||||
|
||||
,("insert: invariant" , mytest prop_insertUp_I)
|
||||
|
Loading…
x
Reference in New Issue
Block a user