aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/FixedColumn.hs
diff options
context:
space:
mode:
authorJustin Bogner <mail@justinbogner.com>2008-12-13 08:30:54 +0100
committerJustin Bogner <mail@justinbogner.com>2008-12-13 08:30:54 +0100
commit684e82d091d9e79017a3aedd373ff0c585880991 (patch)
treedb5a44f41834f0b44de98278430c1017e8c6c41f /XMonad/Layout/FixedColumn.hs
parent262331d567a2cd4a2680977f81e8b2eb92b0b371 (diff)
downloadXMonadContrib-684e82d091d9e79017a3aedd373ff0c585880991.tar.gz
XMonadContrib-684e82d091d9e79017a3aedd373ff0c585880991.tar.xz
XMonadContrib-684e82d091d9e79017a3aedd373ff0c585880991.zip
Add FixedColumn, a layout like Tall but based on the resize hints of windows
darcs-hash:20081213073054-18f27-8d98235fe49f631ded0dbe21c7f3e1df3dec6531.gz
Diffstat (limited to 'XMonad/Layout/FixedColumn.hs')
-rw-r--r--XMonad/Layout/FixedColumn.hs91
1 files changed, 91 insertions, 0 deletions
diff --git a/XMonad/Layout/FixedColumn.hs b/XMonad/Layout/FixedColumn.hs
new file mode 100644
index 0000000..912a92d
--- /dev/null
+++ b/XMonad/Layout/FixedColumn.hs
@@ -0,0 +1,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:
+--
+-- > myLayouts = FixedColumn 20 80 10 ||| Full ||| etc..
+-- > main = xmonad defaultConfig { layoutHook = myLayouts }
+--
+-- 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