s/workspace/windowset/

This commit is contained in:
Jason Creighton
2007-05-21 04:03:30 +00:00
parent 5c44fa79fd
commit 02073c547b
3 changed files with 8 additions and 8 deletions

View File

@@ -56,7 +56,7 @@ main = do
, focusedBorder = fbc , focusedBorder = fbc
} }
st = XState st = XState
{ workspace = new (fromIntegral workspaces) (fromIntegral $ length xinesc) { windowset = new (fromIntegral workspaces) (fromIntegral $ length xinesc)
, layouts = M.fromList [(w, safeLayouts) | w <- [0 .. W workspaces - 1]] } , layouts = M.fromList [(w, safeLayouts) | w <- [0 .. W workspaces - 1]] }
xSetErrorHandler -- in C, I'm too lazy to write the binding: dons xSetErrorHandler -- in C, I'm too lazy to write the binding: dons

View File

@@ -68,7 +68,7 @@ view :: WorkspaceId -> X ()
view n = withWorkspace $ \w -> when (n /= (W.tag (W.current w))) $ do view n = withWorkspace $ \w -> when (n /= (W.tag (W.current w))) $ do
windows $ W.view n -- move in new workspace first, to avoid flicker windows $ W.view n -- move in new workspace first, to avoid flicker
-- Hide the old workspace if it is no longer visible -- Hide the old workspace if it is no longer visible
oldWsNotVisible <- (not . M.member (W.tag . W.current $ w) . W.screens) `liftM` gets workspace oldWsNotVisible <- (not . M.member (W.tag . W.current $ w) . W.screens) `liftM` gets windowset
when oldWsNotVisible $ mapM_ hide (W.index w) when oldWsNotVisible $ mapM_ hide (W.index w)
clearEnterEvents -- better clear any events from the old workspace clearEnterEvents -- better clear any events from the old workspace
@@ -94,7 +94,7 @@ kill = withDisplay $ \d -> withFocused $ \w -> do
-- | windows. Modify the current window list with a pure function, and refresh -- | windows. Modify the current window list with a pure function, and refresh
windows :: (WindowSet -> WindowSet) -> X () windows :: (WindowSet -> WindowSet) -> X ()
windows f = modify (\s -> s { workspace = f (workspace s) }) >> refresh windows f = modify (\s -> s { windowset = f (windowset s) }) >> refresh
-- | hide. Hide a window by moving it off screen. -- | hide. Hide a window by moving it off screen.
hide :: Window -> X () hide :: Window -> X ()
@@ -110,7 +110,7 @@ hide w = withDisplay $ \d -> do
-- --
refresh :: X () refresh :: X ()
refresh = do refresh = do
XState { workspace = ws, layouts = fls } <- get XState { windowset = ws, layouts = fls } <- get
XConf { xineScreens = xinesc, display = d } <- ask XConf { xineScreens = xinesc, display = d } <- ask
-- for each workspace, layout the currently visible workspaces -- for each workspace, layout the currently visible workspaces
@@ -168,7 +168,7 @@ setTopFocus = withWorkspace $ \ws -> maybe (asks theRoot >>= setFocusX) setFocus
-- | Set focus explicitly to window 'w' if it is managed by us, or root. -- | Set focus explicitly to window 'w' if it is managed by us, or root.
focus :: Window -> X () focus :: Window -> X ()
focus w = withWorkspace $ \s -> do focus w = withWorkspace $ \s -> do
if W.member w s then do modify $ \st -> st { workspace = W.focusWindow w s } -- avoid 'refresh' if W.member w s then do modify $ \st -> st { windowset = W.focusWindow w s } -- avoid 'refresh'
setFocusX w setFocusX w
else whenX (isRoot w) $ setFocusX w else whenX (isRoot w) $ setFocusX w
@@ -282,7 +282,7 @@ splitVerticallyBy f r = (\(a,b)->(mirrorRect a,mirrorRect b)) $ splitHorizontall
layout :: ((Layout, [Layout]) -> (Layout, [Layout])) -> X () layout :: ((Layout, [Layout]) -> (Layout, [Layout])) -> X ()
layout f = do layout f = do
modify $ \s -> modify $ \s ->
let n = W.tag . W.current . workspace $ s let n = W.tag . W.current . windowset $ s
(Just fl) = M.lookup n $ layouts s (Just fl) = M.lookup n $ layouts s
in s { layouts = M.insert n (f fl) (layouts s) } in s { layouts = M.insert n (f fl) (layouts s) }
refresh refresh

View File

@@ -38,7 +38,7 @@ import qualified Data.Map as M
-- | XState, the window manager state. -- | XState, the window manager state.
-- Just the display, width, height and a window list -- Just the display, width, height and a window list
data XState = XState data XState = XState
{ workspace :: !WindowSet -- ^ workspace list { windowset :: !WindowSet -- ^ workspace list
, layouts :: !(M.Map WorkspaceId (Layout, [Layout])) } , layouts :: !(M.Map WorkspaceId (Layout, [Layout])) }
-- ^ mapping of workspaces to descriptions of their layouts -- ^ mapping of workspaces to descriptions of their layouts
@@ -89,7 +89,7 @@ withDisplay f = asks display >>= f
-- | Run a monadic action with the current workspace -- | Run a monadic action with the current workspace
withWorkspace :: (WindowSet -> X a) -> X a withWorkspace :: (WindowSet -> X a) -> X a
withWorkspace f = gets workspace >>= f withWorkspace f = gets windowset >>= f
-- | True if the given window is the root window -- | True if the given window is the root window
isRoot :: Window -> X Bool isRoot :: Window -> X Bool