Add a new layout MultiDishes, which behaves like Dishes, but allows a configurable number windows within each stack.

This commit is contained in:
Nathan Fairhurst 2018-03-04 12:12:25 -08:00
parent 0bde284129
commit b42a1392da
3 changed files with 98 additions and 0 deletions

View File

@ -89,6 +89,11 @@
Currently needs manual setting of the session start flag. This could be Currently needs manual setting of the session start flag. This could be
automated when this moves to the core repository. automated when this moves to the core repository.
* `XMonad.Layout.MultiDishes`
A new layout based on Dishes, however it accepts additional configuration
to allow multiple windows within a single stack.
### Bug Fixes and Minor Changes ### Bug Fixes and Minor Changes
* `XMonad.Actions.Navigation2D` * `XMonad.Actions.Navigation2D`

View File

@ -0,0 +1,92 @@
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.MultiDishes
-- Copyright : (c) Jeremy Apthorp, Nathan Fairhurst
-- License : BSD-style (see LICENSE)
--
-- Maintainer : Nathan Fairhurst <nathan.p3pictures@gmail.com>
-- Stability : unstable
-- Portability : portable
--
-- MultiDishes is a layout that stacks groups of extra windows underneath
-- the master windows.
--
-----------------------------------------------------------------------------
module XMonad.Layout.MultiDishes (
-- * Usage
-- $usage
MultiDishes (..)
) where
import XMonad
import XMonad.StackSet (integrate)
import Control.Monad (ap)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.MultiDishes
--
-- Then edit your @layoutHook@ by adding the MultiDishes layout:
--
-- > myLayout = MultiDishes 2 3 (1/6) ||| Full ||| etc..
-- > main = xmonad def { layoutHook = myLayout }
--
-- This is based on the Layout Dishes, but accepts another parameter for
-- the maximum number of dishes allowed within a stack.
--
-- > MultiDishes x 1 y
-- is equivalent to
-- > Dishes x y
--
-- The stack with the fewest dishes is always on top, so 4 windows
-- with the layout `MultiDishes 1 2 (1/5)` would look like this:
--
-- > _________
-- > | |
-- > | M |
-- > |_______|
-- > |_______|
-- > |___|___|
--
-- For more detailed instructions on editing the layoutHook see:
--
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
data MultiDishes a = MultiDishes Int Int Rational deriving (Show, Read)
instance LayoutClass MultiDishes a where
pureLayout (MultiDishes nmaster dishesPerStack h) r =
ap zip (multiDishes h r nmaster dishesPerStack . length) . integrate
pureMessage (MultiDishes nmaster dishesPerStack h) m = fmap incmastern (fromMessage m)
where incmastern (IncMasterN d) = MultiDishes (max 0 (nmaster+d)) dishesPerStack h
multiDishes :: Rational -> Rectangle -> Int -> Int -> Int -> [Rectangle]
multiDishes h s nmaster dishesPerStack n = if n <= nmaster
then splitHorizontally n s
else ws
where
(filledDishStackCount, remainder) =
(n - nmaster) `quotRem` (max 1 dishesPerStack)
(firstDepth, dishStackCount) =
if remainder == 0 then
(dishesPerStack, filledDishStackCount)
else
(remainder, filledDishStackCount + 1)
(masterRect, dishesRect) =
splitVerticallyBy (1 - (fromIntegral dishStackCount) * h) s
dishStackRects =
splitVertically dishStackCount dishesRect
allDishRects = case dishStackRects of
(firstStack:bottomDishStacks) ->
splitHorizontally firstDepth firstStack ++ (bottomDishStacks >>= splitHorizontally dishesPerStack)
[] -> []
ws =
splitHorizontally nmaster masterRect ++ allDishRects

View File

@ -207,6 +207,7 @@ library
XMonad.Layout.DecorationAddons XMonad.Layout.DecorationAddons
XMonad.Layout.DecorationMadness XMonad.Layout.DecorationMadness
XMonad.Layout.Dishes XMonad.Layout.Dishes
XMonad.Layout.MultiDishes
XMonad.Layout.DragPane XMonad.Layout.DragPane
XMonad.Layout.DraggingVisualizer XMonad.Layout.DraggingVisualizer
XMonad.Layout.Drawer XMonad.Layout.Drawer