aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Selective.hs
blob: 5853c56abf3b37d57826f34753e2e452e65be3ef (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
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.Selective
-- Copyright   :  (c) 2009 Max Rabkin
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  Max Rabkin <max.rabkin@gmail.com>
-- Stability   :  unstable
-- Portability :  unportable
--
-- Provides a layout modifier that only shows the master pane and windows
-- around the focussed window.
--
-----------------------------------------------------------------------------

{-# LANGUAGE MultiParamTypeClasses,
             FlexibleInstances,
             NoMonomorphismRestriction,
             NamedFieldPuns #-}

module XMonad.Layout.Selective where

import XMonad.Core
import XMonad.StackSet
import XMonad.Layout.LayoutModifier
import Control.Applicative ((<$>))

-- invariant: 0 <= nMaster <= start; 1 <= nRest
data Selection = Sel { nMaster :: Int, start :: Int, nRest :: Int }
    deriving (Read, Show, Eq)

select :: Selection -> Stack a -> Stack a
select (Sel { nMaster, start, nRest }) stk
    | lups < nMaster
        = stk { down=take (nMaster - lups - 1) downs ++
                    (take nRest . drop (start - lups - 1) $ downs) }
    | otherwise
        = stk { up=reverse (take nMaster ups ++ drop start ups),
                down=take (nRest - (lups - start) - 1) downs }
    where
        downs = down stk
        ups = reverse $ up stk
        lups = length ups
    
{-
select :: Selection -> Stack a -> (Selection, Stack a)
select sel@(Sel { nMaster, start, nRest }) stk
    | lups < nMaster   -- the focussed window is in the master pane
        = let start' = start `min` (lups + ldown - nRest + 1)
                             `max` nMaster
            in (sel { start=start' }, 
                stk { down=take (nMaster - lups - 1) downs ++
                            (take nRest . drop (start' - lups - 1) $ downs) })
    | otherwise
        = let start' = start `min` lups
                             `max` (lups - nRest + 1) 
                             `min` (lups + ldown - nRest + 1)
                             `max` nMaster
            in (sel { start=start' },
                stk { up=reverse (take nMaster ups ++ drop start' ups),
                      down=take (nRest - (lups - start') - 1) downs })
    where
        downs = down stk
        ups = reverse $ up stk
        lups = length ups
        ldown = length downs
-}

updateStart :: Selection -> Stack a -> Int
updateStart (Sel { nMaster, start, nRest }) stk
    | lups < nMaster   -- the focussed window is in the master pane
        = start `min` (lups + ldown - nRest + 1) `max` nMaster
    | otherwise
        = start `min` lups 
                `max` (lups - nRest + 1) 
                `min` (lups + ldown - nRest + 1) 
                `max` nMaster
    where
        lups = length $ up stk
        ldown = length $ down stk

update :: Selection -> Stack a -> Selection
update sel stk = sel { start=updateStart sel stk }

updateAndSelect :: Selection -> Stack a -> Stack a
updateAndSelect sel stk = select (update sel stk) stk

data Selective a = Selective Selection
    deriving (Read, Show)

instance LayoutModifier Selective a where
    modifyLayout (Selective s) w r =
        runLayout (w { stack = updateAndSelect s <$> stack w }) r

    pureModifier (Selective sel) _ stk wins = (wins, Selective . update sel <$> stk)

selective :: Int -> Int -> l a -> ModifiedLayout Selective l a
selective m r = ModifiedLayout . Selective $ Sel { nMaster=m, start=m, nRest=r }