aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-05-21 06:21:18 +0200
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-05-21 06:21:18 +0200
commitcd75c27ff2e3b20d3adf8dcc1de9894873314c04 (patch)
treef64c9d3105a391f1c654e635b22af1e2a9e10f21
parentce00db454082a51ec95c817e97757e2e56f4ef8e (diff)
downloadXMonadContrib-cd75c27ff2e3b20d3adf8dcc1de9894873314c04.tar.gz
XMonadContrib-cd75c27ff2e3b20d3adf8dcc1de9894873314c04.tar.xz
XMonadContrib-cd75c27ff2e3b20d3adf8dcc1de9894873314c04.zip
Fixes for windowset -> workspace rename
darcs-hash:20070521042118-a5988-a2f979585ee35d3905dbcf6244c22af67489caa6.gz
-rw-r--r--Dmenu.hs2
-rw-r--r--FindEmptyWorkspace.hs2
-rw-r--r--Mosaic.hs2
-rw-r--r--RotView.hs2
-rw-r--r--SwapFocus.hs6
-rw-r--r--TwoPane.hs2
6 files changed, 8 insertions, 8 deletions
diff --git a/Dmenu.hs b/Dmenu.hs
index c27fbe2..879d9ed 100644
--- a/Dmenu.hs
+++ b/Dmenu.hs
@@ -24,7 +24,7 @@ runProcessWithInput cmd args input = do
-- http://www.jcreigh.com/dmenu/dmenu-2.8-xinerama.patch
dmenuXinerama :: [String] -> X String
dmenuXinerama opts = do
- ws <- gets workspace
+ ws <- gets windowset
let curscreen = fromIntegral $ fromMaybe 0 (M.lookup (W.current ws) (W.ws2screen ws)) :: Int
io $ runProcessWithInput "dmenu" ["-xs", show (curscreen+1)] (unlines opts)
diff --git a/FindEmptyWorkspace.hs b/FindEmptyWorkspace.hs
index efd524f..860f8b7 100644
--- a/FindEmptyWorkspace.hs
+++ b/FindEmptyWorkspace.hs
@@ -41,7 +41,7 @@ findEmptyWorkspace = findKey (([],[]) ==) . W.stacks
withEmptyWorkspace :: (WorkspaceId -> X ()) -> X ()
withEmptyWorkspace f = do
- ws <- gets workspace
+ ws <- gets windowset
whenJust (findEmptyWorkspace ws) f
-- | Find and view an empty workspace. Do nothing if all workspaces are
diff --git a/Mosaic.hs b/Mosaic.hs
index 05bd903..f00825e 100644
--- a/Mosaic.hs
+++ b/Mosaic.hs
@@ -204,5 +204,5 @@ unName :: NamedWindow -> Window
unName (NW _ w) = w
withNamedWindow :: (NamedWindow -> X ()) -> X ()
-withNamedWindow f = do ws <- gets workspace
+withNamedWindow f = do ws <- gets windowset
whenJust (W.peek ws) $ \w -> getName w >>= f
diff --git a/RotView.hs b/RotView.hs
index 7505bb2..46ce0bf 100644
--- a/RotView.hs
+++ b/RotView.hs
@@ -18,7 +18,7 @@ import Data.Maybe ( listToMaybe )
import qualified StackSet as W ( stacks, current, visibleWorkspaces, index )
rotView :: Bool -> X ()
-rotView b = do ws <- gets workspace
+rotView b = do ws <- gets windowset
let m = W.current ws
vis = W.visibleWorkspaces ws
allws = if b then allWorkspaces ws else reverse $ allWorkspaces ws
diff --git a/SwapFocus.hs b/SwapFocus.hs
index 339f526..0c715ba 100644
--- a/SwapFocus.hs
+++ b/SwapFocus.hs
@@ -10,7 +10,7 @@ module XMonadContrib.SwapFocus ( swapFocus ) where
import Control.Monad.State
import Operations ( refresh )
-import XMonad ( X, WindowSet, workspace )
+import XMonad ( X, WindowSet, windowset )
import StackSet ( StackSet, peekStack, popFocus, pushFocus, current )
sf :: (Integral i, Integral j, Ord a) => StackSet i j a -> Maybe (StackSet i j a)
@@ -24,7 +24,7 @@ swapFocus = smartwindows sf
-- | smartwindows. Modify the current window list with a pure function, and only refresh if necesary
smartwindows :: (WindowSet -> Maybe WindowSet) -> X ()
-smartwindows f = do w <- gets workspace
- case (f w) of Just f' -> do modify $ \s -> s { workspace = f' }
+smartwindows f = do w <- gets windowset
+ case (f w) of Just f' -> do modify $ \s -> s { windowset = f' }
refresh
Nothing -> return ()
diff --git a/TwoPane.hs b/TwoPane.hs
index 56925c6..d70f49f 100644
--- a/TwoPane.hs
+++ b/TwoPane.hs
@@ -16,7 +16,7 @@ twoPane :: Rational -> Rational -> Layout
twoPane delta split = Layout { doLayout = arrange, modifyLayout = message }
where
arrange rect ws@(w:x:_) = do
- (Just f) <- gets (W.peek . workspace) -- safe because of pattern match above
+ (Just f) <- gets (W.peek . windowset) -- safe because of pattern match above
let y = if f == w then x else f
(left, right) = splitHorizontallyBy split rect
mapM_ hide . filter (\a -> a /= w && a /= y) $ ws