aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/CycleWS.hs
blob: 38a8d5330b1c6d0f94827b5ed3dedd9bc9ef0bf0 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Actions.CycleWS
-- Copyright   :  (c) Joachim Breitner <mail@joachim-breitner.de>,
--                    Nelson Elhage <nelhage@mit.edu> (`toggleWS' function)
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  Joachim Breitner <mail@joachim-breitner.de>
-- Stability   :  unstable
-- Portability :  unportable
--
-- Provides bindings to cycle forward or backward through the list
-- of workspaces, and to move windows there, and to cycle between the screens.
--
-----------------------------------------------------------------------------

module XMonad.Actions.CycleWS (
                              -- * Usage
                              -- $usage
                              nextWS,
                              prevWS,
                              shiftToNext,
                              shiftToPrev,
                              toggleWS,
                              nextScreen,
                              prevScreen,
                              shiftNextScreen,
                              shiftPrevScreen
                             ) where

import Data.List ( findIndex )
import Data.Maybe ( fromMaybe )

import XMonad hiding (workspaces)
import XMonad.StackSet hiding (filter)
import XMonad.Util.WorkspaceCompare

-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@ file:
--
-- > import XMonad.Actions.CycleWS
--
-- >   , ((modMask x,               xK_Down),  nextWS)
-- >   , ((modMask x,               xK_Up),    prevWS)
-- >   , ((modMask x .|. shiftMask, xK_Down),  shiftToNext)
-- >   , ((modMask x .|. shiftMask, xK_Up),    shiftToPrev)
-- >   , ((modMask x,               xK_Right), nextScreen)
-- >   , ((modMask x,               xK_Left),  prevScreen)
-- >   , ((modMask x .|. shiftMask, xK_Right), shiftNextScreen)
-- >   , ((modMask x .|. shiftMask, xK_Left),  shiftPrevScreen)
-- >   , ((modMask x,               xK_t),     toggleWS)
--
-- If you want to follow the moved window, you can use both actions:
--
-- >   , ((modMask x .|. shiftMask, xK_Down), shiftToNext >> nextWS)
-- >   , ((modMask x .|. shiftMask, xK_Up),   shiftToPrev >> prevWS)
--
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings".


-- | Switch to next workspace
nextWS :: X ()
nextWS = switchWorkspace 1

-- | Switch to previous workspace
prevWS :: X ()
prevWS = switchWorkspace (-1)

-- | Move focused window to next workspace
shiftToNext :: X ()
shiftToNext = shiftBy 1

-- | Move focused window to previous workspace
shiftToPrev :: X ()
shiftToPrev = shiftBy (-1)

-- | Toggle to the workspace displayed previously
toggleWS :: X ()
toggleWS = windows $ view =<< tag . head . hidden

switchWorkspace :: Int -> X ()
switchWorkspace d = wsBy d >>= windows . greedyView

shiftBy :: Int -> X ()
shiftBy d = wsBy d >>= windows . shift

wsBy :: Int -> X (WorkspaceId)
wsBy d = do
    ws <- gets windowset
    sort' <- getSortByTag
    let orderedWs = sort' (workspaces ws)
    let now = fromMaybe 0 $ findWsIndex (workspace (current ws)) orderedWs
    let next = orderedWs !! ((now + d) `mod` length orderedWs)
    return $ tag next

findWsIndex :: WindowSpace -> [WindowSpace] -> Maybe Int
findWsIndex ws wss = findIndex ((== tag ws) . tag) wss

-- | View next screen
nextScreen :: X ()
nextScreen = switchScreen 1

-- | View prev screen
prevScreen :: X ()
prevScreen = switchScreen (-1)

switchScreen :: Int -> X ()
switchScreen d = do s <- screenBy d
                    mws <- screenWorkspace s
                    case mws of
                         Nothing -> return ()
                         Just ws -> windows (view ws)

screenBy :: Int -> X (ScreenId)
screenBy d = do ws <- gets windowset
                --let ss = sortBy screen (screens ws)
                let now = screen (current ws)
                return $ (now + fromIntegral d) `mod` fromIntegral (length (screens ws))

-- | Move focused window to workspace on next screen
shiftNextScreen :: X ()
shiftNextScreen = shiftScreenBy 1

-- | Move focused window to workspace on prev screen
shiftPrevScreen :: X ()
shiftPrevScreen = shiftScreenBy (-1)

shiftScreenBy :: Int -> X ()
shiftScreenBy d = do s <- screenBy d
                     mws <- screenWorkspace s
                     case mws of
                         Nothing -> return ()
                         Just ws -> windows (shift ws)