aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--CopyWindow.hs6
-rw-r--r--DwmPromote.hs2
-rw-r--r--FindEmptyWorkspace.hs2
-rw-r--r--Warp.hs15
4 files changed, 14 insertions, 11 deletions
diff --git a/CopyWindow.hs b/CopyWindow.hs
index 8e6d8d5..901835d 100644
--- a/CopyWindow.hs
+++ b/CopyWindow.hs
@@ -47,7 +47,7 @@ import StackSet
copy :: WorkspaceId -> X ()
copy n = windows (copy' n)
-copy' :: (Ord a, Eq s, Integral i) => i -> StackSet i a s -> StackSet i a s
+copy' :: (Ord a, Eq s, Integral i) => i -> StackSet i a s sd -> StackSet i a s sd
copy' n s = if n `tagMember` s && n /= tag (workspace (current s))
then maybe s go (peek s)
else s
@@ -68,11 +68,11 @@ copy' n s = if n `tagMember` s && n /= tag (workspace (current s))
-- Semantics in Huet's paper is that insert doesn't move the cursor.
-- However, we choose to insert above, and move the focus.
-insertUp' :: Eq a => a -> StackSet i a s -> StackSet i a s
+insertUp' :: Eq a => a -> StackSet i a s sd -> StackSet i a s sd
insertUp' a s = modify (Just $ Stack a [] [])
(\(Stack t l r) -> Just $ Stack a (L.delete a l) (L.delete a (t:r))) s
-delete' :: Ord a => a -> StackSet i a s -> StackSet i a s
+delete' :: Ord a => a -> StackSet i a s sd -> StackSet i a s sd
delete' w = sink w . modify Nothing (filter (/= w))
-- | Remove the focussed window from this workspace. If it's present in no
diff --git a/DwmPromote.hs b/DwmPromote.hs
index b774133..7ec8fd6 100644
--- a/DwmPromote.hs
+++ b/DwmPromote.hs
@@ -39,7 +39,7 @@ import StackSet
dwmpromote :: X ()
dwmpromote = windows swap
-swap :: StackSet i a s -> StackSet i a s
+swap :: StackSet i a s sd -> StackSet i a s sd
swap = modify' $ \c -> case c of
Stack _ [] [] -> c
Stack t [] (x:rs) -> Stack x [] (t:rs)
diff --git a/FindEmptyWorkspace.hs b/FindEmptyWorkspace.hs
index 2240d41..5cb3964 100644
--- a/FindEmptyWorkspace.hs
+++ b/FindEmptyWorkspace.hs
@@ -46,7 +46,7 @@ import qualified Operations as O
-- Nothing if all workspaces are in use. Function searches currently
-- focused workspace, other visible workspaces (when in Xinerama) and
-- hidden workspaces in this order.
-findEmptyWorkspace :: StackSet i a s -> Maybe (Workspace i a)
+findEmptyWorkspace :: StackSet i a s sd -> Maybe (Workspace i a)
findEmptyWorkspace = find (isNothing . stack) . allWorkspaces
where
allWorkspaces ss = (workspace . current) ss :
diff --git a/Warp.hs b/Warp.hs
index 43a833f..df186e6 100644
--- a/Warp.hs
+++ b/Warp.hs
@@ -22,11 +22,13 @@ module XMonadContrib.Warp (
import Data.Ratio
import Data.Maybe
+import Data.List
import Control.Monad.RWS
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
import Operations
import XMonad
+import StackSet as W
{- $usage
This can be used to make a keybinding that warps the pointer to a given
@@ -59,10 +61,11 @@ warpToWindow h v =
wa <- io $ getWindowAttributes d w
warp w (fraction h (wa_width wa)) (fraction v (wa_height wa))
-warpToScreen :: Int -> Rational -> Rational -> X ()
+warpToScreen :: ScreenId -> Rational -> Rational -> X ()
warpToScreen n h v = do
- xScreens <- gets xineScreens
- root <- asks theRoot
- whenJust (ix n xScreens) $ \r ->
- warp root (rect_x r + fraction h (rect_width r))
- (rect_y r + fraction v (rect_height r))
+ root <- asks theRoot
+ (StackSet {current = x, visible = xs}) <- gets windowset
+ whenJust (fmap (screenRect . W.screenDetail) . find ((n==) . W.screen) $ x : xs)
+ $ \r ->
+ warp root (rect_x r + fraction h (rect_width r))
+ (rect_y r + fraction v (rect_height r))