cleaner implementation of 'view'. Only hide the current list. And shortcut if we try to move to the same screen. No flicker

This commit is contained in:
Don Stewart 2007-03-08 00:21:34 +00:00
parent d373177a1f
commit aacf70eb46

30
Main.hs
View File

@ -189,24 +189,26 @@ kill = do
return () return ()
-- | Change the current workspace to workspce at offset 'n-1'. -- | Change the current workspace to workspce at offset 'n-1'.
-- Todo: refactor
view :: Int -> W () view :: Int -> W ()
view n = do view n = do
let m = n-1 let new = n-1
modifyWorkspaces $ \old@(_,wks) -> (old,wks) <- gets workspace
if m < S.length wks && m >= 0 then (m,wks) else old when (new /= old && new >= 0 && new < S.length wks) $ do
modifyWorkspaces $ \_ -> (new,wks)
hideWindows (wks `S.index` old)
showWindows (wks `S.index` new)
refresh
-- | Hide a list of windows by moving them offscreen.
hideWindows :: Windows -> W ()
hideWindows ws = do
dpy <- gets display dpy <- gets display
sw <- liftM fromIntegral (gets screenWidth) sw <- liftM fromIntegral (gets screenWidth)
sh <- liftM fromIntegral (gets screenHeight) sh <- liftM fromIntegral (gets screenHeight)
(i,wks) <- gets workspace forM_ ws $ \w -> io $ moveWindow dpy w (2*sw) (2*sh)
-- clear the screen: remove all window stacks -- | Expose a list of windows, moving them on screen
forM_ (concat $ F.toList wks) $ \win -> do showWindows :: Windows -> W ()
io $ moveWindow dpy win (2*sw) (2*sh) showWindows ws = do
dpy <- gets display
-- expose just the visible stack forM_ ws $ \w -> io $ moveWindow dpy w 0 0
forM_ (wks `S.index` i) $ \win -> do
io $ moveWindow dpy win 0 0
refresh