aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/MultiColumns.hs
blob: bea4be35cec163c79ceab44f1bc2245d8cc2c7e1 (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
135
136
137
138
139
140
141
142
143
144
145
146
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.MultiColumns
-- Copyright   :  (c) Anders Engstrom <ankaan@gmail.com>
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  Anders Engstrom <ankaan@gmail.com>
-- Stability   :  unstable
-- Portability :  unportable
--
-- This layout tiles windows in a growing number of columns. The number of
-- windows in each column can be controlled by messages.
-----------------------------------------------------------------------------

module XMonad.Layout.MultiColumns (
                              -- * Usage
                              -- $usage

                              multiCol,
                              MultiCol,
                             ) where

import XMonad
import qualified XMonad.StackSet as W

import Control.Monad

-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.MultiColumns
--
-- Then edit your @layoutHook@ by adding the multiCol layout:
--
-- > myLayouts = multiCol [1] 4 0.01 0.5 ||| etc..
-- > main = xmonad def { layoutHook = myLayouts }
--
-- Or alternatively:
--
-- > myLayouts = Mirror (multiCol [1] 2 0.01 (-0.25)) ||| etc..
-- > main = xmonad def { layoutHook = myLayouts }
--
-- The maximum number of windows in a column can be controlled using the
-- IncMasterN messages and the column containing the focused window will be
-- modified. If the value is 0, all remaining windows will be placed in that
-- column when all columns before that has been filled.
--
-- The size can be set to between 1 and -0.5. If the value is positive, the
-- master column will be of that size. The rest of the screen is split among
-- the other columns. But if the size is negative, it instead indicates the
-- size of all non-master columns and the master column will cover the rest of
-- the screen. If the master column would become smaller than the other
-- columns, the screen is instead split equally among all columns. Therefore,
-- if equal size among all columns are desired, set the size to -0.5.
--
-- For more detailed instructions on editing the layoutHook see:
--
-- "XMonad.Doc.Extending#Editing_the_layout_hook"

-- | Layout constructor.
multiCol
  :: [Int]    -- ^ Windows in each column, starting with master. Set to 0 to catch the rest.
  -> Int      -- ^ Default value for all following columns.
  -> Rational -- ^ How much to change size each time.
  -> Rational -- ^ Initial size of master area, or column area if the size is negative.
  -> MultiCol a
multiCol n defn ds s = MultiCol (map (max 0) n) (max 0 defn) ds s 0

data MultiCol a = MultiCol
  { multiColNWin      :: ![Int]
  , multiColDefWin    :: !Int
  , multiColDeltaSize :: !Rational
  , multiColSize      :: !Rational
  , multiColActive    :: !Int
  } deriving (Show,Read,Eq)

instance LayoutClass MultiCol a where
    doLayout l r s = return (zip w rlist, resl)
        where rlist = doL (multiColNWin l') (multiColSize l') r wlen
              w = W.integrate s
              wlen = length w
              -- Make sure the list of columns is big enough and update active column
              nw = multiColNWin l ++ repeat (multiColDefWin l)
              l' = l { multiColNWin = take (max (length $ multiColNWin l) $ getCol (wlen-1) nw + 1) nw
                     , multiColActive = getCol (length $ W.up s) nw
                     }
              -- Only return new layout if it has been modified
              resl = if l'==l
                     then Nothing
                     else Just l'
    handleMessage l m =
        return $ msum [fmap resize     (fromMessage m)
                      ,fmap incmastern (fromMessage m)]
            where resize Shrink = l { multiColSize = max (-0.5) $ s-ds }
                  resize Expand = l { multiColSize = min 1 $ s+ds }
                  incmastern (IncMasterN x) = l { multiColNWin = take a n ++ [newval] ++ tail r }
                      where newval =  max 0 $ head r + x
                            r = drop a n
                  n = multiColNWin l
                  ds = multiColDeltaSize l
                  s = multiColSize l
                  a = multiColActive l
    description _ = "MultiCol"


-- | Get which column a window is in, starting at 0.
getCol :: Int -> [Int] -> Int
getCol w (n:ns) = if n<1 || w < n
                  then 0
                  else 1 + getCol (w-n) ns
-- Should never occur...
getCol _ _ = -1

doL :: [Int] -> Rational -> Rectangle -> Int -> [Rectangle]
doL nwin s r n = rlist
    where -- Number of columns to tile
          ncol = getCol (n-1) nwin + 1
          -- Compute the actual size
          size = floor $ abs s * fromIntegral (rect_width r)
          -- Extract all but last column to tile
          c = take (ncol-1) nwin
          -- Compute number of windows in last column and add it to the others
          col = c ++ [n-sum c]
          -- Compute width of columns
          width = if s>0
                  then if ncol==1
                       -- Only one window
                       then [fromIntegral $ rect_width r]
                       -- Give the master it's space and split the rest equally for the other columns
                       else size:replicate (ncol-1) ((fromIntegral (rect_width r) - size) `div` (ncol-1))
                  else if fromIntegral ncol * abs s >= 1
                       -- Split equally
                       then replicate ncol $ fromIntegral (rect_width r) `div` ncol
                       -- Let the master cover what is left...
                       else (fromIntegral (rect_width r) - (ncol-1)*size):replicate (ncol-1) size
          -- Compute the horizontal position of columns
          xpos = accumEx (fromIntegral $ rect_x r) width
          -- Exclusive accumulation
          accumEx a (x:xs) = a:accumEx (a+x) xs
          accumEx _ _ = []
          -- Create a rectangle for each column
          cr = zipWith (\x w -> r { rect_x=fromIntegral x, rect_width=fromIntegral w }) xpos width
          -- Split the columns into the windows
          rlist = concat $ zipWith (\num rect -> splitVertically num rect) col cr