From 0c642c3e9aeba4b4feaca0a594e2865308b87844 Mon Sep 17 00:00:00 2001
From: Sam Tay <sam.chong.tay@gmail.com>
Date: Thu, 14 May 2020 12:12:44 -0700
Subject: [PATCH] Add ResizableThreeColumns layout

Based on ThreeColumns and ResizableTile
---
 CHANGES.md                             |   5 +
 XMonad/Doc/Extending.hs                |   4 +
 XMonad/Layout/ResizableThreeColumns.hs | 163 +++++++++++++++++++++++++
 xmonad-contrib.cabal                   |   1 +
 4 files changed, 173 insertions(+)
 create mode 100644 XMonad/Layout/ResizableThreeColumns.hs

diff --git a/CHANGES.md b/CHANGES.md
index cd1b61dd..4a77b139 100644
--- a/CHANGES.md
+++ b/CHANGES.md
@@ -22,6 +22,11 @@
 
 ### New Modules
 
+  * `XMonad.Layout.ResizableThreeColumns`
+
+    A layout based on 'XMonad.Layout.ThreeColumns' but with each slave window's
+    height resizable.
+
   * `XMonad.Layout.TallMastersCombo`
 
     A layout combinator that support Shrink, Expand, and IncMasterN just as
diff --git a/XMonad/Doc/Extending.hs b/XMonad/Doc/Extending.hs
index 555e4bd7..b7b1b5df 100644
--- a/XMonad/Doc/Extending.hs
+++ b/XMonad/Doc/Extending.hs
@@ -899,6 +899,10 @@ For more information on using those modules for customizing your
     More useful tiled layout that allows you to change a width\/height of window.
     See also "XMonad.Layout.MouseResizableTile".
 
+* "XMonad.Layout.ResizableThreeColumns":
+    The same layout as ThreeColumns but, similar to ResizableTile, allows you
+    to change the width\/height of the slave windows.
+
 * "XMonad.Layout.ResizeScreen":
     A layout transformer to have a layout respect a given screen
     geometry. Mostly used with "Decoration" (the Horizontal and the
diff --git a/XMonad/Layout/ResizableThreeColumns.hs b/XMonad/Layout/ResizableThreeColumns.hs
new file mode 100644
index 00000000..7e6e6f4f
--- /dev/null
+++ b/XMonad/Layout/ResizableThreeColumns.hs
@@ -0,0 +1,163 @@
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Layout.ResizableThreeColumns
+-- Copyright   :  (c) Sam Tay <sam.chong.tay@gmail.com>
+-- License     :  BSD3-style (see LICENSE)
+--
+-- Maintainer  :  ?
+-- Stability   :  unstable
+-- Portability :  unportable
+--
+-- A layout similar to tall but with three columns. With 2560x1600 pixels this
+-- layout can be used for a huge main window and up to six reasonable sized
+-- resizable slave windows.
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.ResizableThreeColumns (
+                              -- * Usage
+                              -- $usage
+                              ResizableThreeCol(..), MirrorResize(..)
+                             ) where
+
+import XMonad hiding (splitVertically)
+import XMonad.Layout.ResizableTile(MirrorResize(..))
+import qualified XMonad.StackSet as W
+
+import Data.List ((\\))
+import qualified Data.Map as M
+import Data.Ratio
+
+import Control.Monad
+
+-- $usage
+-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.ResizableThreeColumns
+--
+-- Then edit your @layoutHook@ by adding the ResizableThreeCol layout:
+--
+-- > myLayout = ResizableThreeCol 1 (3/100) (1/2) [] ||| ResizableThreeColMid 1 (3/100) (1/2) [] ||| etc..
+-- > main = xmonad def { layoutHook = myLayout }
+--
+-- The first argument specifies how many windows initially appear in the main
+-- window. The second argument argument specifies the amount to resize while
+-- resizing and the third argument specifies the initial size of the columns.
+-- A positive size designates the fraction of the screen that the main window
+-- should occupy, but if the size is negative the absolute value designates the
+-- fraction a slave column should occupy. If both slave columns are visible,
+-- they always occupy the same amount of space.
+--
+-- You may also want to add the following key bindings:
+--
+-- > , ((modm,               xK_a), sendMessage MirrorShrink)
+-- > , ((modm,               xK_z), sendMessage MirrorExpand)
+--
+-- The ResizableThreeColMid variant places the main window between the slave columns.
+--
+-- For more detailed instructions on editing the layoutHook see:
+--
+-- "XMonad.Doc.Extending#Editing_the_layout_hook"
+
+
+-- | Arguments are nmaster, delta, fraction
+data ResizableThreeCol a
+  = ResizableThreeColMid
+    { threeColNMaster :: !Int
+    , threeColDelta :: !Rational
+    , threeColFrac :: !Rational
+    , threeColSlaves :: [Rational]
+    }
+  | ResizableThreeCol
+    { threeColNMaster :: !Int
+    , threeColDelta :: !Rational
+    , threeColFrac :: !Rational
+    , threeColSlaves :: [Rational]
+    } deriving (Show,Read)
+
+instance LayoutClass ResizableThreeCol a where
+  doLayout (ResizableThreeCol n _ f mf) r    = doL False n f mf r
+  doLayout (ResizableThreeColMid n _ f mf) r = doL True  n f mf r
+  handleMessage l m = do
+    ms <- (W.stack . W.workspace . W.current) <$> gets windowset
+    fs <- (M.keys . W.floating) <$> gets windowset
+    return $ do
+      s <- ms
+      -- make sure current stack isn't floating
+      guard . not $ W.focus s `elem` fs
+      -- remove floating windows from stack
+      let s' = s { W.up = (W.up s) \\ fs, W.down = (W.down s) \\ fs }
+      -- handle messages
+      msum [ fmap resize       (fromMessage m)
+           , fmap (mresize s') (fromMessage m)
+           , fmap incmastern   (fromMessage m)
+           ]
+    where
+      resize Shrink = l { threeColFrac = max (-0.5) $ frac-delta }
+      resize Expand = l { threeColFrac = min 1 $ frac+delta }
+      mresize s MirrorShrink = mresize' s delta
+      mresize s MirrorExpand = mresize' s (0-delta)
+      mresize' s delt =
+        let up = length $ W.up s
+            total = up + (length $ W.down s) + 1
+            pos = if up == (nmaster-1) || up == (total-1) then up-1 else up
+            mfrac' = modifymfrac (mfrac ++ repeat 1) delt pos
+        in l { threeColSlaves = take total mfrac'}
+      modifymfrac [] _ _ = []
+      modifymfrac (f:fx) d n
+        | n == 0    = f+d : fx
+        | otherwise = f : modifymfrac fx d (n-1)
+      incmastern (IncMasterN x) = l { threeColNMaster = max 0 (nmaster+x) }
+      nmaster = threeColNMaster l
+      delta = threeColDelta l
+      frac = threeColFrac l
+      mfrac = threeColSlaves l
+  description _ = "ResizableThreeCol"
+
+doL :: Bool -> Int -> Rational -> [Rational] -> Rectangle
+    -> W.Stack a -> X ([(a, Rectangle)], Maybe (layout a))
+doL middle nmaster f mf r =
+  return
+  . (\x -> (x, Nothing))
+  . ap zip (tile3 middle f (mf ++ repeat 1) r nmaster . length) . W.integrate
+
+-- | tile3.  Compute window positions using 3 panes
+tile3 :: Bool -> Rational -> [Rational] -> Rectangle -> Int -> Int -> [Rectangle]
+tile3 middle f mf r nmaster n
+  | n <= nmaster || nmaster == 0 = splitVertically mf n r
+  | n <= nmaster+1 = concat [ splitVertically mf nmaster s1
+                            , splitVertically (drop nmaster mf) (n-nmaster) s2
+                            ]
+  | otherwise = concat [ splitVertically mf nmaster r1
+                       , splitVertically (drop nmaster mf) nslave1 r2
+                       , splitVertically (drop (nmaster + nslave1) mf) nslave2 r3
+                       ]
+  where
+    (r1, r2, r3) = split3HorizontallyBy middle (if f<0 then 1+2*f else f) r
+    (s1, s2)     = splitHorizontallyBy (if f<0 then 1+f else f) r
+    nslave       = (n - nmaster)
+    nslave1      = ceiling (nslave % 2)
+    nslave2      = (n - nmaster - nslave1)
+
+splitVertically :: RealFrac r => [r] -> Int -> Rectangle -> [Rectangle]
+splitVertically [] _ r = [r]
+splitVertically _ n r | n < 2 = [r]
+splitVertically (f:fx) n (Rectangle sx sy sw sh) =
+  let smallh = min sh (floor $ fromIntegral (sh `div` fromIntegral n) * f)
+  in Rectangle sx sy sw smallh :
+       splitVertically fx (n-1) (Rectangle sx (sy+fromIntegral smallh) sw (sh-smallh))
+
+split3HorizontallyBy :: Bool -> Rational -> Rectangle -> (Rectangle, Rectangle, Rectangle)
+split3HorizontallyBy middle f (Rectangle sx sy sw sh) =
+  if middle
+  then ( Rectangle (sx + fromIntegral r3w) sy r1w sh
+       , Rectangle (sx + fromIntegral r3w + fromIntegral r1w) sy r2w sh
+       , Rectangle sx sy r3w sh )
+  else ( Rectangle sx sy r1w sh
+       , Rectangle (sx + fromIntegral r1w) sy r2w sh
+       , Rectangle (sx + fromIntegral r1w + fromIntegral r2w) sy r3w sh )
+  where
+    r1w = ceiling $ fromIntegral sw * f
+    r2w = ceiling $ (sw - r1w) % 2
+    r3w = sw - r1w - r2w
diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal
index 177635a8..01d6a964 100644
--- a/xmonad-contrib.cabal
+++ b/xmonad-contrib.cabal
@@ -266,6 +266,7 @@ library
                         XMonad.Layout.Reflect
                         XMonad.Layout.Renamed
                         XMonad.Layout.ResizableTile
+                        XMonad.Layout.ResizableThreeColumns
                         XMonad.Layout.ResizeScreen
                         XMonad.Layout.Roledex
                         XMonad.Layout.ShowWName