aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions
diff options
context:
space:
mode:
authormail <mail@n-sch.de>2009-07-02 12:16:21 +0200
committermail <mail@n-sch.de>2009-07-02 12:16:21 +0200
commit255755124eddbf99296574681b775ded8282bf8b (patch)
treea0daa9e331512a27c8e31a1c03ce1bd51acbfe63 /XMonad/Actions
parent7d0ac5c6129d3ec0765597bd9494347dda377888 (diff)
downloadXMonadContrib-255755124eddbf99296574681b775ded8282bf8b.tar.gz
XMonadContrib-255755124eddbf99296574681b775ded8282bf8b.tar.xz
XMonadContrib-255755124eddbf99296574681b775ded8282bf8b.zip
Added XMonad.Actions.OnScreen
Ignore-this: 605666aeba92e1d53f03a480506ddf2f darcs-hash:20090702101621-e34a6-ab74a39d4262778767e7df721f9e6d41cb3c6997.gz
Diffstat (limited to 'XMonad/Actions')
-rw-r--r--XMonad/Actions/OnScreen.hs118
1 files changed, 118 insertions, 0 deletions
diff --git a/XMonad/Actions/OnScreen.hs b/XMonad/Actions/OnScreen.hs
new file mode 100644
index 0000000..3b37300
--- /dev/null
+++ b/XMonad/Actions/OnScreen.hs
@@ -0,0 +1,118 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Actions.OnScreen
+-- Copyright : (c) 2009 Nils Schweinsberg
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : Nils Schweinsberg <mail@n-sch.de>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- Control workspaces on different screens (in xinerama mode).
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Actions.OnScreen (
+ -- * Usage
+ -- $usage
+ onScreen
+ , viewOnScreen
+ , greedyViewOnScreen
+ , onlyOnScreen
+ ) where
+
+import XMonad.StackSet
+import Data.List
+
+-- $usage
+--
+-- This module provides an easy way to control, what you see on other screens in
+-- xinerama mode without having to focus them. Put this into your
+-- @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Actions.OnScreen
+--
+-- Then add the appropriate keybindings, for example replace your current keys
+-- to switch the workspaces with this at the bottom of your keybindings:
+--
+-- > ++
+-- > [ ((m .|. modMask, k), windows (f i))
+-- > | (i, k) <- zip (workspaces conf) ([xK_1 .. xK_9] ++ [xK_0])
+-- > , (f, m) <- [ (viewOnScreen 0, 0)
+-- > , (viewOnScreen 1, controlMask)
+-- > , (greedyView, controlMask .|. shiftMask) ]
+-- > ]
+--
+-- This will provide you with the following keybindings:
+--
+-- * modkey + 1-0:
+-- Switch to workspace 1-0 on screen 0
+--
+-- * modkey + control + 1-0:
+-- Switch to workspace 1-0 on screen 1
+--
+-- * modkey + control + shift + 1-0:
+-- Default greedyView behaviour
+--
+--
+-- A more basic version inside the default keybindings would be:
+--
+-- > , ((modMask .|. controlMask, xK_1) windows (viewOnScreen 0 "1"))
+--
+-- where 0 is the first screen and "1" the workspace with the tag "1".
+--
+-- For detailed instructions on editing your key bindings, see
+-- "XMonad.Doc.Extending#Editing_key_bindings".
+
+-- | Switch to the (hidden) workspace with index 'i' on the screen 'sc'.
+-- A default function (for example 'view' or 'greedyView') will be run if 'sc' is
+-- the current screen, no valid screen id or workspace 'i' is already visible.
+onScreen :: (Eq sid, Eq i)
+ => (i -> StackSet i l a sid sd -> StackSet i l a sid sd) -- ^ default action
+ -> sid -- ^ screen id
+ -> i -- ^ index of the workspace
+ -> StackSet i l a sid sd -- ^ current stack
+ -> StackSet i l a sid sd
+onScreen defFunc sc i st
+ | screen (current st) /= sc =
+ case ( find ((i==) . tag) (hidden st)
+ , find ((sc==) . screen) (screens st)
+ , find ((sc==) . screen) (visible st)) of
+
+ (Just x, Just s, Just o) ->
+ let newScreen = s { workspace = x }
+ in st { visible = newScreen : (deleteBy (equating screen) newScreen (visible st))
+ , hidden = (workspace o) : (deleteBy (equating tag) x (hidden st))
+ }
+ _ -> defFunc i st -- no valid screen id/workspace already visible
+
+ | otherwise = defFunc i st -- on current screen
+
+ where equating f x y = f x == f y
+
+-- | Switch to workspace 'i' on screen 'sc'. If 'i' is visible use 'greedyView'
+-- to switch the current workspace with workspace 'i'.
+greedyViewOnScreen :: (Eq sid, Eq i)
+ => sid -- ^ screen id
+ -> i -- ^ index of the workspace
+ -> StackSet i l a sid sd -- ^ current stack
+ -> StackSet i l a sid sd
+greedyViewOnScreen = onScreen greedyView
+
+-- | Switch to workspace 'i' on screen 'sc'. If 'i' is visible use 'view' to
+-- switch focus to the workspace 'i'.
+viewOnScreen :: (Eq sid, Eq i)
+ => sid -- ^ screen id
+ -> i -- ^ index of the workspace
+ -> StackSet i l a sid sd -- ^ current stack
+ -> StackSet i l a sid sd
+viewOnScreen = onScreen view
+
+-- | Switch to workspace 'i' on screen 'sc'. If 'i' is visible do nothing.
+onlyOnScreen :: (Eq sid, Eq i)
+ => sid -- ^ screen id
+ -> i -- ^ index of the workspace
+ -> StackSet i l a sid sd -- ^ current stack
+ -> StackSet i l a sid sd
+onlyOnScreen = onScreen doNothing
+ where doNothing _ st = st