{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.FixedColumn
-- Description :  Like Tall, but split at a fixed column (or a window's smallest resize amount).
-- 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 XMonad
import XMonad.Prelude
import qualified 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 def { 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 (ReadPrec [FixedColumn a]
ReadPrec (FixedColumn a)
Int -> ReadS (FixedColumn a)
ReadS [FixedColumn a]
(Int -> ReadS (FixedColumn a))
-> ReadS [FixedColumn a]
-> ReadPrec (FixedColumn a)
-> ReadPrec [FixedColumn a]
-> Read (FixedColumn a)
forall a. ReadPrec [FixedColumn a]
forall a. ReadPrec (FixedColumn a)
forall a. Int -> ReadS (FixedColumn a)
forall a. ReadS [FixedColumn a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FixedColumn a]
$creadListPrec :: forall a. ReadPrec [FixedColumn a]
readPrec :: ReadPrec (FixedColumn a)
$creadPrec :: forall a. ReadPrec (FixedColumn a)
readList :: ReadS [FixedColumn a]
$creadList :: forall a. ReadS [FixedColumn a]
readsPrec :: Int -> ReadS (FixedColumn a)
$creadsPrec :: forall a. Int -> ReadS (FixedColumn a)
Read, Int -> FixedColumn a -> ShowS
[FixedColumn a] -> ShowS
FixedColumn a -> String
(Int -> FixedColumn a -> ShowS)
-> (FixedColumn a -> String)
-> ([FixedColumn a] -> ShowS)
-> Show (FixedColumn a)
forall a. Int -> FixedColumn a -> ShowS
forall a. [FixedColumn a] -> ShowS
forall a. FixedColumn a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FixedColumn a] -> ShowS
$cshowList :: forall a. [FixedColumn a] -> ShowS
show :: FixedColumn a -> String
$cshow :: forall a. FixedColumn a -> String
showsPrec :: Int -> FixedColumn a -> ShowS
$cshowsPrec :: forall a. Int -> FixedColumn a -> ShowS
Show)

instance LayoutClass FixedColumn Window where
    doLayout :: FixedColumn Window
-> Rectangle
-> Stack Window
-> X ([(Window, Rectangle)], Maybe (FixedColumn Window))
doLayout (FixedColumn Int
nmaster Int
_ Int
ncol Int
fallback) Rectangle
r Stack Window
s = do
            [Int]
fws <- (Window -> X Int) -> [Window] -> X [Int]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Int -> Int -> Window -> X Int
widthCols Int
fallback Int
ncol) [Window]
ws
            let frac :: Rational
frac = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
nmaster [Int]
fws) Int -> Dimension -> Rational
forall {a} {a} {a}.
(Fractional a, Integral a, Integral a) =>
a -> a -> a
// Rectangle -> Dimension
rect_width Rectangle
r
                rs :: [Rectangle]
rs   = Rational -> Rectangle -> Int -> Int -> [Rectangle]
tile Rational
frac Rectangle
r Int
nmaster ([Window] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Window]
ws)
            ([(Window, Rectangle)], Maybe (FixedColumn Window))
-> X ([(Window, Rectangle)], Maybe (FixedColumn Window))
forall (m :: * -> *) a. Monad m => a -> m a
return ([Window] -> [Rectangle] -> [(Window, Rectangle)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Window]
ws [Rectangle]
rs, Maybe (FixedColumn Window)
forall a. Maybe a
Nothing)
        where ws :: [Window]
ws     = Stack Window -> [Window]
forall a. Stack a -> [a]
W.integrate Stack Window
s
              a
x // :: a -> a -> a
// a
y = a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
x a -> a -> a
forall a. Fractional a => a -> a -> a
/ a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
y

    pureMessage :: FixedColumn Window -> SomeMessage -> Maybe (FixedColumn Window)
pureMessage (FixedColumn Int
nmaster Int
delta Int
ncol Int
fallback) SomeMessage
m =
            [Maybe (FixedColumn Window)] -> Maybe (FixedColumn Window)
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [(Resize -> FixedColumn Window)
-> Maybe Resize -> Maybe (FixedColumn Window)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Resize -> FixedColumn Window
forall {a}. Resize -> FixedColumn a
resize     (SomeMessage -> Maybe Resize
forall m. Message m => SomeMessage -> Maybe m
fromMessage SomeMessage
m)
                 ,(IncMasterN -> FixedColumn Window)
-> Maybe IncMasterN -> Maybe (FixedColumn Window)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IncMasterN -> FixedColumn Window
forall {a}. IncMasterN -> FixedColumn a
incmastern (SomeMessage -> Maybe IncMasterN
forall m. Message m => SomeMessage -> Maybe m
fromMessage SomeMessage
m)]
        where resize :: Resize -> FixedColumn a
resize Resize
Shrink
                  = Int -> Int -> Int -> Int -> FixedColumn a
forall a. Int -> Int -> Int -> Int -> FixedColumn a
FixedColumn Int
nmaster Int
delta (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
ncol Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
delta) Int
fallback
              resize Resize
Expand
                  = Int -> Int -> Int -> Int -> FixedColumn a
forall a. Int -> Int -> Int -> Int -> FixedColumn a
FixedColumn Int
nmaster Int
delta (Int
ncol Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
delta) Int
fallback
              incmastern :: IncMasterN -> FixedColumn a
incmastern (IncMasterN Int
d)
                  = Int -> Int -> Int -> Int -> FixedColumn a
forall a. Int -> Int -> Int -> Int -> FixedColumn a
FixedColumn (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
nmasterInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
d)) Int
delta Int
ncol Int
fallback

    description :: FixedColumn Window -> String
description FixedColumn Window
_ = String
"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 :: Int -> Int -> Window -> X Int
widthCols Int
inc Int
n Window
w = do
    Display
d  <- (XConf -> Display) -> X Display
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> Display
display
    Int
bw <- (XConf -> Int) -> X Int
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ((XConf -> Int) -> X Int) -> (XConf -> Int) -> X Int
forall a b. (a -> b) -> a -> b
$ Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fi (Dimension -> Int) -> (XConf -> Dimension) -> XConf -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConfig Layout -> Dimension
forall (l :: * -> *). XConfig l -> Dimension
borderWidth (XConfig Layout -> Dimension)
-> (XConf -> XConfig Layout) -> XConf -> Dimension
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> XConfig Layout
config
    SizeHints
sh <- IO SizeHints -> X SizeHints
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO SizeHints -> X SizeHints) -> IO SizeHints -> X SizeHints
forall a b. (a -> b) -> a -> b
$ Display -> Window -> IO SizeHints
getWMNormalHints Display
d Window
w
    let widthHint :: (SizeHints -> f (b, b)) -> f b
widthHint SizeHints -> f (b, b)
f = SizeHints -> f (b, b)
f SizeHints
sh f (b, b) -> ((b, b) -> b) -> f b
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> b -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral (b -> b) -> ((b, b) -> b) -> (b, b) -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (b, b) -> b
forall a b. (a, b) -> a
fst
        oneCol :: Int
oneCol      = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
inc (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ (SizeHints -> Maybe (Dimension, Dimension)) -> Maybe Int
forall {f :: * -> *} {b} {b} {b}.
(Functor f, Integral b, Num b) =>
(SizeHints -> f (b, b)) -> f b
widthHint SizeHints -> Maybe (Dimension, Dimension)
sh_resize_inc
        base :: Int
base        = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
0 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ (SizeHints -> Maybe (Dimension, Dimension)) -> Maybe Int
forall {f :: * -> *} {b} {b} {b}.
(Functor f, Integral b, Num b) =>
(SizeHints -> f (b, b)) -> f b
widthHint SizeHints -> Maybe (Dimension, Dimension)
sh_base_size
    Int -> X Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> X Int) -> Int -> X Int
forall a b. (a -> b) -> a -> b
$ Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
bw Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
base Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
oneCol