Skip to content

Commit b57212c

Browse files
jecarogeekosaur
authored andcommitted
Make the width of the fst column configurable
1 parent da3e4be commit b57212c

File tree

1 file changed

+22
-20
lines changed

1 file changed

+22
-20
lines changed

XMonad/Layout/Columns.hs

Lines changed: 22 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -17,12 +17,11 @@
1717
-- A layout which tiles the windows in columns. The windows can be moved and
1818
-- resized in every directions.
1919
--
20-
-- The first window appears:
20+
-- The first window appears in a single column in the center of the screen. Its
21+
-- width is configurable (See 'coOneWindowWidth').
2122
--
22-
-- * in the center on wide screens
23-
-- * fullscreen otherwise
24-
--
25-
-- The second window appears on a second column.
23+
-- The second window appears in a second column. Starting with two columns, they
24+
-- fill up the screen.
2625
--
2726
-- Subsequent windows appear on the bottom of the last columns.
2827
module XMonad.Layout.Columns
@@ -78,7 +77,7 @@ import qualified XMonad.StackSet as StackSet
7877
-- $usage
7978
-- Add 'Columns' to your @layoutHook@ with an initial empty state:
8079
--
81-
-- > myLayout = Full ||| Columns []
80+
-- > myLayout = Full ||| Columns 1 []
8281
--
8382
-- Here is an example of keybindings:
8483
--
@@ -156,37 +155,40 @@ type Column = [(Rational, Window)]
156155
-- | The layout is a list of 'Column' with their relative horizontal dimensions.
157156
type Columns = [(Rational, Column)]
158157

159-
newtype ColumnsLayout a = Columns Columns
158+
data ColumnsLayout a = Columns
159+
{ -- | With of the first column when there is only one window. Usefull on wide
160+
-- screens.
161+
coOneWindowWidth :: Rational,
162+
-- | The current state
163+
coColumns :: Columns
164+
}
160165
deriving (Show, Read)
161166

162167
instance LayoutClass ColumnsLayout Window where
163168
description _ = layoutDescription
164169

165-
emptyLayout _ _ = pure ([], Just $ Columns [])
166-
167-
doLayout (Columns columns) rectangle stack =
168-
pure (rectangles, Just (Columns columns'))
170+
doLayout (Columns oneWindowWidth columns) rectangle stack =
171+
pure (rectangles, Just (Columns oneWindowWidth columns'))
169172
where
170173
hackedColumns = hackForTabs columns stack
171174
columns' = updateWindowList hackedColumns stack
172175
rectangles = toRectangles rectangle' columns'
173-
-- If there is only one window and the screen is big, we reduce the
174-
-- destination rectangle to put the window on the center of the screen.
176+
-- If there is only one window, we set the destination rectangle according
177+
-- to the width in the layout setting.
175178
rectangle'
176-
| rect_width rectangle > 2000 && (length . toList $ stack) == 1 =
179+
| (length . toList $ stack) == 1 =
177180
scaleRationalRect rectangle singleColumnRR
178181
| otherwise = rectangle
179-
singleColumnWidth = 1 % 2
180-
singleColumnOffset = (1 - singleColumnWidth) / 2
181-
singleColumnRR = RationalRect singleColumnOffset 0 singleColumnWidth 1
182+
singleColumnOffset = (1 - oneWindowWidth) / 2
183+
singleColumnRR = RationalRect singleColumnOffset 0 oneWindowWidth 1
182184

183-
handleMessage layout@(Columns columns) message = do
185+
handleMessage layout@(Columns oneWindowWidth columns) message = do
184186
mbStack <- runMaybeT $ handleFocus' =<< getStack
185187
changedFocus <- traverse updateStack' mbStack
186188

187189
movedOrResized <-
188190
runMaybeT $
189-
Columns
191+
Columns oneWindowWidth
190192
<$> (handleMoveOrResize' =<< peekFocus)
191193

192194
pure $ movedOrResized <|> changedFocus
@@ -358,7 +360,7 @@ mapWindow :: (Window -> Window) -> Columns -> Columns
358360
mapWindow = fmap . fmap . fmap . fmap
359361

360362
columnsToWindows :: Columns -> [Window]
361-
columnsToWindows = foldMap ((:[]) . snd) . foldMap snd
363+
columnsToWindows = foldMap ((: []) . snd) . foldMap snd
362364

363365
swapWindowBetween ::
364366
Window ->

0 commit comments

Comments
 (0)