aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/FixedColumn.hs
blob: ad0c004ed1a5d86baaa95a5e00a27882d4b1758e (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
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.FixedColumn
-- Copyright   :  (c) 2008 Justin Bogner <mail@justinbogner.com>
-- License     :  BSD3-style (as xmonad)
--
-- Maintainer  :  Justin Bogner <mail@justinbogner.com>
-- Stability   :  unstable
-- Portability :  unportable
--
-- A layout much like Tall, but using a multiple of a window's minimum
-- resize amount instead of a percentage of screen to decide where to
-- split. This is useful when you usually leave a text editor or
-- terminal in the master pane and like it to be 80 columns wide.
--
-----------------------------------------------------------------------------

module XMonad.Layout.FixedColumn (
    -- * Usage
    -- $usage
        FixedColumn(..)
) where

import Control.Monad (msum)
import Data.Maybe (fromMaybe)
import Graphics.X11.Xlib (Window, rect_width)
import Graphics.X11.Xlib.Extras ( getWMNormalHints
                                , getWindowAttributes
                                , sh_base_size
                                , sh_resize_inc
                                , wa_border_width)

import XMonad.Core (X, LayoutClass(..), fromMessage, io, withDisplay)
import XMonad.Layout (Resize(..), IncMasterN(..), tile)
import XMonad.StackSet as W

-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.FixedColumn
--
-- Then edit your @layoutHook@ by adding the FixedColumn layout:
--
-- > myLayout = FixedColumn 1 20 80 10 ||| Full ||| etc..
-- > main = xmonad defaultConfig { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
-- "XMonad.Doc.Extending#Editing_the_layout_hook"

-- | A tiling mode based on preserving a nice fixed width
--   window. Supports 'Shrink', 'Expand' and 'IncMasterN'.
data FixedColumn a = FixedColumn !Int -- Number of windows in the master pane
                                 !Int -- Number to increment by when resizing
                                 !Int -- Default width of master pane
                                 !Int -- Column width for normal windows
                        deriving (Read, Show)

instance LayoutClass FixedColumn Window where
    doLayout (FixedColumn nmaster _ ncol fallback) r s = do
            fws <- mapM (widthCols fallback ncol) ws
            let frac = maximum (take nmaster fws) // rect_width r
                rs   = tile frac r nmaster (length ws)
            return $ (zip ws rs, Nothing)
        where ws     = W.integrate s
              x // y = fromIntegral x / fromIntegral y

    pureMessage (FixedColumn nmaster delta ncol fallback) m =
            msum [fmap resize     (fromMessage m)
                 ,fmap incmastern (fromMessage m)]
        where resize Shrink
                  = FixedColumn nmaster delta (max 0 $ ncol - delta) fallback
              resize Expand
                  = FixedColumn nmaster delta (ncol + delta) fallback
              incmastern (IncMasterN d)
                  = FixedColumn (max 0 (nmaster+d)) delta ncol fallback

    description _ = "FixedColumn"

-- | Determine the width of @w@ given that we would like it to be @n@
--   columns wide, using @inc@ as a resize increment for windows that
--   don't have one
widthCols :: Int -> Int -> Window -> X Int
widthCols inc n w = withDisplay $ \d -> io $ do
    sh <- getWMNormalHints d w
    bw <- fmap (fromIntegral . wa_border_width) $ getWindowAttributes d w
    let widthHint f = f sh >>= return . fromIntegral . fst
        oneCol      = fromMaybe inc $ widthHint sh_resize_inc
        base        = fromMaybe 0 $ widthHint sh_base_size
    return $ 2 * bw + base + n * oneCol