xmonad-contrib/XMonad/Layout/BinaryColumn.hs
Adam Plaice ca866229f6 Fix most remaining broken inter-module docs links
The links were broken due to:

1. Incorrect quotes (' instead of " for module links and occasionally
vice-versa).

2. Changes in the name of the "target" module not reflected in the
"source" docs.

3. Typos to begin with.

4. Use of `<foo>` in the docs is rendered as just `foo` with a link to
`/foo`.

5. Similarly for `"Foo"` if it starts with a capital letter (and hence
could be a module).

6. Markup inside `@` code blocks still being applied.

e.g. `@M-<arrow-keys>@` is rendered as `M-arrow-keys` with a spurious
hyperlink from arrow-keys to `/arrow-keys`, which is confusing.

Three links from XMonad.Util.Run have been removed outright, since
they're no longer examples of the usage of 'runProcessWithInput'.
WmiiActions has been gone since 2008, while XMonad.Prompt.Directory
and XMonad.Layout.WorkspaceDir haven't been using
'runProcessWithInput' since 2020 and 2012, respectively.

In some cases the `<foo>` were surrounded with @, especially in the
case of key definitions, for consistency.  (This wasn't done
everywhere, because it looks ugly in the source.)

MoreManageHelpers has never been in xmonad-contrib.  ManageHelpers
seems to fill the expected role.

In the case of the module description for X.H.ManageDebug the quotes
were simply removed because none of the likely options to make the
link work were successful.
2022-11-01 19:35:55 +01:00

137 lines
4.6 KiB
Haskell

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.BinaryColumn
-- Description : A layout that places all windows in one column.
-- Copyright : (c) 2009 Ilya Portnov, (c) 2018 Campbell Barton
-- License : BSD3-style (see LICENSE)
--
-- Maintainer : Campbell Barton <ideasman42@gmail.com>
-- Stability : unstable
-- Portability : unportable
--
-- Provides Column layout that places all windows in one column.
-- Each window is half the height of the previous,
-- except for the last pair of windows.
--
-- Note: Originally based on "XMonad.Layout.Column" with changes:
--
-- * Adding/removing windows doesn't resize all other windows.
-- (last window pair exception).
-- * Minimum window height option.
--
-----------------------------------------------------------------------------
module XMonad.Layout.BinaryColumn (
-- * Usage
-- $usage
BinaryColumn (..)
) where
import XMonad
import qualified XMonad.StackSet
import qualified Data.List
-- $usage
-- This module defines layout named BinaryColumn.
-- It places all windows in one column.
-- Windows heights are calculated to prevent window resizing whenever
-- a window is added or removed.
-- This is done by keeping the last two windows in the stack the same height.
--
-- You can use this module by adding following in your @xmonad.hs@:
--
-- > import XMonad.Layout.BinaryColumn
--
-- Then add layouts to your layoutHook:
--
-- > myLayoutHook = BinaryColumn 1.0 32 ||| ...
--
-- The first value causes the master window to take exactly half of the screen,
-- the second ensures that windows are no less than 32 pixels tall.
--
-- Shrink/Expand can be used to adjust the first value by increments of 0.1.
--
-- * 2.0 uses all space for the master window
-- (minus the space for windows which get their fixed height).
-- * 0.0 gives an evenly spaced grid.
-- Negative values reverse the sizes so the last
-- window in the stack becomes larger.
--
data BinaryColumn a = BinaryColumn Float Int
deriving (Read, Show)
instance XMonad.LayoutClass BinaryColumn a where
pureLayout = columnLayout
pureMessage = columnMessage
columnMessage :: BinaryColumn a -> SomeMessage -> Maybe (BinaryColumn a)
columnMessage (BinaryColumn q min_size) m = fmap resize (fromMessage m)
where
resize Shrink = BinaryColumn (max (-2.0) (q - 0.1)) min_size
resize Expand = BinaryColumn (min 2.0 (q + 0.1)) min_size
columnLayout :: BinaryColumn a
-> XMonad.Rectangle
-> XMonad.StackSet.Stack a
-> [(a, XMonad.Rectangle)]
columnLayout (BinaryColumn scale min_size) rect stack = zip ws rects
where
ws = XMonad.StackSet.integrate stack
n = length ws
scale_abs = abs scale
heights_noflip =
let
-- Regular case: check for min size.
f m size divide False = let
m_fl = fromIntegral m
m_prev_fl = fromIntegral (m + 1)
div_test = min divide m_prev_fl
value_test = round (fromIntegral size / div_test) :: Integer
value_max = size - toInteger (min_size * m)
(value, divide_next, no_room) =
if value_test < value_max then
(value_test, divide, False)
else
(value_max, m_fl, True)
size_next = size - value
m_next = m - 1
in value
: f m_next size_next divide_next no_room
-- Fallback case: when windows have reached min size
-- simply create an even grid with the remaining space.
f m size divide True = let
divide_next = fromIntegral m
value_even = (fromIntegral size / divide)
value = round value_even :: Integer
m_next = m - 1
size_next = size - value
in value
: f m_next size_next divide_next True
in f
n_init size_init divide_init False
where
n_init = n - 1
size_init = toInteger (rect_height rect)
divide_init =
if scale_abs == 0.0 then
fromIntegral n
else
1.0 / (0.5 * scale_abs)
heights =
if scale < 0.0 then
Data.List.reverse (take n heights_noflip)
else
heights_noflip
ys = [fromIntegral $ sum $ take k heights | k <- [0..n - 1]]
rects = zipWith (curry (mkRect rect)) heights ys
mkRect :: XMonad.Rectangle
-> (Integer,XMonad.Position)
-> XMonad.Rectangle
mkRect (XMonad.Rectangle xs ys ws _) (h, y) =
XMonad.Rectangle xs (ys + fromIntegral y) ws (fromInteger h)