formatting only

This commit is contained in:
Don Stewart
2007-04-01 00:47:26 +00:00
parent 93cf0950e8
commit b3dbe98e64
2 changed files with 11 additions and 6 deletions

View File

@@ -61,9 +61,9 @@ numlockMask = lockMask
-- left pane should be in the tiled layout. See LayoutDesc and -- left pane should be in the tiled layout. See LayoutDesc and
-- friends in XMonad.hs for options. -- friends in XMonad.hs for options.
startingLayoutDesc :: LayoutDesc startingLayoutDesc :: LayoutDesc
startingLayoutDesc = LayoutDesc { layoutType = Full startingLayoutDesc =
, tileFraction = 1%2 LayoutDesc { layoutType = Full
} , tileFraction = 1%2 }
-- The keys list. -- The keys list.
keys :: M.Map (KeyMask, KeySym) (X ()) keys :: M.Map (KeyMask, KeySym) (X ())

View File

@@ -158,9 +158,13 @@ insert k n old = new { cache = M.insert k n (cache new)
-- If the element doesn't exist, the original StackSet is returned unmodified. -- If the element doesn't exist, the original StackSet is returned unmodified.
delete :: Ord a => a -> StackSet a -> StackSet a delete :: Ord a => a -> StackSet a -> StackSet a
delete k w = maybe w tweak (M.lookup k (cache w)) delete k w = maybe w tweak (M.lookup k (cache w))
where tweak i = w { cache = M.delete k (cache w) where
, stacks = M.adjust (L.delete k) i (stacks w) tweak i = w { cache = M.delete k (cache w)
, focus = M.update (\k' -> if k == k' then elemAfter k (stacks w M.! i) else Just k') i (focus w) } , stacks = M.adjust (L.delete k) i (stacks w)
, focus = M.update (\k' -> if k == k' then elemAfter k (stacks w M.! i)
else Just k') i
(focus w)
}
-- | /O(log n)/. If the given window is contained in a workspace, make it the -- | /O(log n)/. If the given window is contained in a workspace, make it the
-- focused window of that workspace, and make that workspace the current one. -- focused window of that workspace, and make that workspace the current one.
@@ -175,5 +179,6 @@ promote k w = case M.lookup k (cache w) of
Nothing -> w Nothing -> w
Just i -> w { stacks = M.adjust (\ks -> k : filter (/= k) ks) i (stacks w) } Just i -> w { stacks = M.adjust (\ks -> k : filter (/= k) ks) i (stacks w) }
-- |
elemAfter :: Eq a => a -> [a] -> Maybe a elemAfter :: Eq a => a -> [a] -> Maybe a
elemAfter w ws = listToMaybe . filter (/= w) . dropWhile (/= w) $ ws ++ ws elemAfter w ws = listToMaybe . filter (/= w) . dropWhile (/= w) $ ws ++ ws