aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/Plane.hs
blob: 92593c556168d865a511dd4fe00f9fbd78698635 (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.Plane
-- Copyright   :  (c) Malebria <malebria@riseup.net>,
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  Malebria <malebria@riseup.net>
-- Stability   :  unstable
-- Portability :  unportable
--
-- This module has functions to navigate through workspaces in a bidimensional
-- manner.  It allows the organization of workspaces in columns, and provides
-- functions to move and shift windows in all four directions (left, up, right
-- and down) possible in a surface.
--
-- This functionality was inspired by GNOME (finite) and KDE (infinite)
-- keybindings for workspace navigation, and by "XMonad.Actions.CycleWS" for
-- the idea of applying this approach to XMonad.
-----------------------------------------------------------------------------

module XMonad.Actions.Plane
    (
    -- * Usage
    -- $usage

    -- * Data types
    Direction (..)
    , Limits (..)

    -- * Navigating through workspaces
    -- $navigating
    , planeShift
    , planeMove
    )
    where

import Control.Monad
import Data.List hiding (union)
import Data.Maybe

import XMonad
import XMonad.StackSet hiding (workspaces)

-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@ file:
--
-- > import XMonad.Actions.Plane
-- >
-- > main = xmonad defaultConfig {keys = myKeys}
-- >
-- > myKeys conf = union (keys defaultConfig conf) $ myNewKeys conf
-- >
-- > myNewkeys (XConfig {modMask = m}) =
-- >     fromList
-- >     [ ((keyMask .|. m, keySym), function 3 Finite direction)
-- >     | (keySym, direction) <- zip [xK_Left .. xK_Down] $ enumFrom ToLeft
-- >     , (keyMask, function) <- [(0, planeMove), (shiftMask, planeShift)]
-- >     ]
--
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings".

-- | Direction to go in the plane.
data Direction =  ToLeft | ToUp | ToRight | ToDown deriving Enum

-- | Defines whether it's a finite or a circular organization of workspaces.
data Limits
    = Finite   -- ^ When you're at a edge of the plane, there's no way to move
               -- to the next region.
    | Circular -- ^ If you try to move, you'll get to the other edge, on the
               -- other side.
    deriving Eq

-- $navigating
--
-- There're two parameters that must be provided to navigate, and it's a good
-- idea to use them with the same values in each keybinding.
--
-- The first is the number of columns in which the workspaces are going to be
-- organized.  It's possible to use a number of columns that is not a divisor
-- of the number of workspaces, but the results are better when using a
-- divisor.  If it's not a divisor, the last line will have the remaining
-- workspaces.
--
-- The other one is 'Limits'.

-- | Shift a window to the next workspace in 'Direction'.  Note that this will
-- also move to the next workspace.
planeShift
    :: Int  -- ^ Number of columns.
    -> Limits
    -> Direction
    -> X ()
planeShift = plane shift'

shift' ::
    (Eq s, Eq i, Ord a) => i -> StackSet i l a s sd -> StackSet i l a s sd
shift' area = greedyView area . shift area

-- | Move to the next workspace in 'Direction'.
planeMove
    :: Int  -- ^ Number of columns.
    -> Limits
    -> Direction
    -> X ()
planeMove = plane greedyView

plane ::
    (WorkspaceId -> WindowSet -> WindowSet) -> Int -> Limits -> Direction ->
    X ()
plane function columns limits direction = do
    state <- get
    xconf <- ask
    let vertical f =
            if mod currentWS columns >= mod areas columns
                then mod (f currentWS columns) $ div areas columns * columns
                else mod (f currentWS columns) $ ((div areas columns + 1) * columns)
        horizontal f = mod (f currentWS) columns + line * columns
        line = div currentWS columns
        column = mod currentWS columns
        currentWS = fromJust mCurrentWS
        mCurrentWS = elemIndex (currentTag $ windowset state) areaNames
        run condition position =
            when (limits == Circular || condition) $
            windows $ function $ areaNames !! position
        areas = length areaNames
        areaNames = workspaces $ config $ xconf

    when (isJust mCurrentWS) $
        case direction of
            ToUp    -> run (line   /= 0                ) $ vertical (-)
            ToDown  -> run (currentWS + columns < areas) $ vertical (+)
            ToLeft  -> run (column /= 0                ) $ horizontal pred
            ToRight -> run (column /= columns - 1      ) $ horizontal succ