mirror of
https://github.com/xmonad/xmonad.git
synced 2025-07-31 04:01:52 -07:00
Make 'index' return Nothing, rather than error
This commit is contained in:
@@ -48,7 +48,7 @@ refresh = do
|
||||
flip mapM_ (M.assocs (W.screen2ws ws)) $ \(scn, n) -> do
|
||||
let sc = genericIndex xinesc scn -- temporary coercion!
|
||||
(Just l) = fmap fst $ M.lookup n fls
|
||||
mapM_ (\(w, rect) -> io $ moveWindowInside d w rect) $ (doLayout l) sc $ W.index n ws
|
||||
whenJust (W.index n ws) $ mapM_ (\(w, rect) -> io $ moveWindowInside d w rect) . doLayout l sc
|
||||
whenJust (W.peekStack n ws) (io . raiseWindow d)
|
||||
whenJust (W.peek ws) setFocus
|
||||
clearEnterEvents
|
||||
@@ -235,7 +235,7 @@ setFocus w = do
|
||||
|
||||
-- clear mouse button grab and border on other windows
|
||||
flip mapM_ (W.visibleWorkspaces ws) $ \n -> do
|
||||
flip mapM_ (W.index n ws) $ \otherw -> do
|
||||
flip mapM_ (fromMaybe [] $ W.index n ws) $ \otherw -> do
|
||||
setButtonGrab True otherw
|
||||
io $ setWindowBorder dpy otherw (color_pixel nbc)
|
||||
|
||||
@@ -297,7 +297,7 @@ view n = do
|
||||
ws' <- gets workspace
|
||||
-- If the old workspace isn't visible anymore, we have to hide the windows
|
||||
-- in case we're switching to an empty workspace.
|
||||
when (m `notElem` W.visibleWorkspaces ws') (mapM_ hide (W.index m ws))
|
||||
when (m `notElem` W.visibleWorkspaces ws') $ maybe (return ()) (mapM_ hide) $ W.index m ws
|
||||
clearEnterEvents
|
||||
setTopFocus
|
||||
|
||||
|
@@ -98,9 +98,9 @@ peekStack :: Integral i => i -> StackSet i j a -> Maybe a
|
||||
peekStack i w = M.lookup i (focus w)
|
||||
|
||||
-- | /O(log s)/. Index. Extract the stack at workspace 'n'.
|
||||
-- If the index is invalid, an exception is thrown.
|
||||
index :: Integral i => i -> StackSet i j a -> [a]
|
||||
index k w = uncurry (++) $ fromJust $ M.lookup k (stacks w)
|
||||
-- If the index is invalid, returns Nothing.
|
||||
index :: Integral i => i -> StackSet i j a -> Maybe [a]
|
||||
index k w = fmap (uncurry (++)) $ M.lookup k (stacks w)
|
||||
|
||||
-- | view. Set the stack specified by the argument as being visible and the
|
||||
-- current StackSet. If the stack wasn't previously visible, it will become
|
||||
@@ -173,7 +173,7 @@ delete k w = maybe w del (M.lookup k (cache w))
|
||||
where
|
||||
del i = w { cache = M.delete k (cache w)
|
||||
, stacks = M.adjust (\(xs, ys) -> (L.delete k xs, L.delete k ys)) i (stacks w)
|
||||
, focus = M.update (\k' -> if k == k' then elemAfter k (index i w)
|
||||
, focus = M.update (\k' -> if k == k' then elemAfter k =<< index i w
|
||||
else Just k') i (focus w) }
|
||||
|
||||
-- | /O(log n)/. If the given window is contained in a workspace, make it the
|
||||
|
Reference in New Issue
Block a user