aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorNils Schweinsberg <mail@n-sch.de>2009-12-09 01:37:17 +0100
committerNils Schweinsberg <mail@n-sch.de>2009-12-09 01:37:17 +0100
commit3347990b42bf11930a9c1e05a7d31851cea929ae (patch)
tree3eafbd5292f25ed5a847c5a292588044c4788824 /XMonad
parent0f2022b0e3b9dbf60df871908cccdd759ba1cc18 (diff)
downloadXMonadContrib-3347990b42bf11930a9c1e05a7d31851cea929ae.tar.gz
XMonadContrib-3347990b42bf11930a9c1e05a7d31851cea929ae.tar.xz
XMonadContrib-3347990b42bf11930a9c1e05a7d31851cea929ae.zip
onScreen' variation for X () functions
Ignore-this: 6a9644c729c2b60f94398260f3640e4d darcs-hash:20091209003717-1f2e3-0f9b6f1f277e7b502d7d45dbb3175951ec9a99e3.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Actions/OnScreen.hs55
1 files changed, 40 insertions, 15 deletions
diff --git a/XMonad/Actions/OnScreen.hs b/XMonad/Actions/OnScreen.hs
index e5ff502..95bdec7 100644
--- a/XMonad/Actions/OnScreen.hs
+++ b/XMonad/Actions/OnScreen.hs
@@ -16,6 +16,7 @@ module XMonad.Actions.OnScreen (
-- * Usage
-- $usage
onScreen
+ , onScreen'
, Focus(..)
, viewOnScreen
, greedyViewOnScreen
@@ -24,11 +25,13 @@ module XMonad.Actions.OnScreen (
, toggleGreedyOnScreen
) where
+import XMonad
import XMonad.Core
-import XMonad.StackSet
+import XMonad.StackSet hiding (new)
import Control.Monad (guard)
-import Data.Maybe(fromMaybe)
+-- import Control.Monad.State.Class (gets)
+import Data.Maybe (fromMaybe)
-- | Focus data definitions
@@ -50,20 +53,43 @@ onScreen f foc sc st = fromMaybe st $ do
ws <- lookupWorkspace sc st
let fStack = f $ view ws st
- curScreen = screen $ current st
- focusCur = lookupWorkspace curScreen fStack >>= return . flip view fStack
- isVisible = (`elem` map (tag.workspace) (visible st))
- -- set focus for new stack
- setFocus FocusNew = return $ fStack
- setFocus FocusCurrent = focusCur
- setFocus (FocusTag i) = return $ view i fStack
- setFocus (FocusTagVisible i) =
- if isVisible i
- then setFocus (FocusTag i)
- else setFocus FocusCurrent
+ return $ setFocus foc st fStack
+
+
+-- set focus for new stack
+setFocus :: Focus
+ -> WindowSet -- ^ old stack
+ -> WindowSet -- ^ new stack
+ -> WindowSet
+setFocus FocusNew _ new = new
+setFocus FocusCurrent old new =
+ case lookupWorkspace (screen $ current old) new of
+ Nothing -> new
+ Just i -> view i new
+setFocus (FocusTag i) _ new = view i new
+setFocus (FocusTagVisible i) old new =
+ if i `elem` map (tag . workspace) (visible old)
+ then setFocus (FocusTag i) old new
+ else setFocus FocusCurrent old new
+
+-- | A variation of @onScreen@ which will take any @X ()@ function and run it
+-- on the given screen.
+-- Warning: This function will change focus even if the function it's supposed
+-- to run doesn't succeed.
+onScreen' :: X () -- ^ X function to run
+ -> Focus -- ^ focus
+ -> ScreenId -- ^ screen id
+ -> X ()
+onScreen' x foc sc = do
+ st <- gets windowset
+ case lookupWorkspace sc st of
+ Nothing -> return ()
+ Just ws -> do
+ windows $ view ws
+ x
+ windows $ setFocus foc st
- setFocus foc
-- | Switch to workspace @i@ on screen @sc@. If @i@ is visible use @view@ to
-- switch focus to the workspace @i@.
@@ -122,7 +148,6 @@ toggleOrView' f i st = fromMaybe (f i st) $ do
return $ f (tag . head $ st') st
-
-- $usage
--
-- This module provides an easy way to control, what you see on other screens in