[xmonad] Is there a better way to write new layout? (Also modified Tall layout inside)

Brandon Allbery allbery.b at gmail.com
Mon Jan 6 17:30:03 UTC 2020


In general, we do things like this with layout modifiers so they can be
applied to more than one layout. In this case, you might get some ideas
from X.L.Magnifier or X.L.Maximize: the former enlarges the focused window
in a layout, the latter lets you pop out a window to "almost fullscreen"
(it has a gap which IIRC can be configured in recent versions). There's
also X.L.IfMax which lets you conditionalize on how many windows a layout
has, so you almost have the pieces needed to build what you want
(X.L.Magnifier with X.L.IfMax is not quite it because there's no gap, and
X.L.Maximize needs to be triggered by a keypress).

On Sat, Jan 4, 2020 at 4:41 AM Dusan Popovic <dpx at binaryapparatus.com>
wrote:

> Hi,
>
> With being near impossible to get any non 16:9 monitor, and using big
> monitor (27" or bigger), any single terminal/editor takes entire screen
> when using Tall layout. This makes all the text aligned at the left edge
> of the monitor, which forces me to either sit facing the left half of
> the monitor or stretch my neck 90+% of time. I decided to modify Tall
> layout, so that with single window open it doesn't take all the space,
> while with more than one window open it behaves exactly as Tall already
> does.
>
> I am really beginner in haskell but I can do basic stuff, so I chopped
> built in Tall layout, modified it a bit, added to xmonad.hs. While it
> works well I am convinced there must be more elegant way to do the same,
> so I am curious how to do it better.
>
> Steps I took to make it work:
>
> 1. Chop LANGUAGE directive from xmonad-git/src/XMonad/Layout.hs and add
> to my xmonad.hs at the top. I would love to avoid having
> FlexibleInstances in my xmonad.hs.
>
>         {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses,
> PatternGuards, TypeSynonymInstances, DeriveDataTypeable #-}
>
> 2. Chop and modify Tall layout, add it to xmonad.sh, most important part
> being 'tile54 f (Rectangle sx sy sw sh) nmaster 1' function that matches
> when there is only one window.
>
>         import Control.Arrow ((***), second)
>         import Control.Monad
>         import Graphics.X11 (Rectangle(..))
>
>         data Tall54 a = Tall54 { tallNMaster :: !Int               -- ^
> The default number of windows in the master pane (default: 1)
>                                , tallRatioIncrement :: !Rational   -- ^
> Percent of screen to increment by when resizing panes (default: 3/100)
>                                , tallRatio :: !Rational            -- ^
> Default proportion of screen occupied by master pane (default: 1/2)
>                                }
>                             deriving (Show, Read)
>
>         instance LayoutClass Tall54 a where
>             pureLayout (Tall54 nmaster _ frac) r s = zip ws rs
>               where ws = W.integrate s
>                     rs = tile54 frac r nmaster (length ws)
>
>             pureMessage (Tall54 nmaster delta frac) m =
>                     msum [fmap resize     (fromMessage m)
>                          ,fmap incmastern (fromMessage m)]
>
>               where resize Shrink             = Tall54 nmaster delta (max
> 0 $ frac-delta)
>                     resize Expand             = Tall54 nmaster delta (min
> 1 $ frac+delta)
>                     incmastern (IncMasterN d) = Tall54 (max 0 (nmaster+d))
> delta frac
>
>             description _ = "Tall54"
>
>         tile54
>             :: Rational  -- ^ @frac@, what proportion of the screen to
> devote to the master area
>             -> Rectangle -- ^ @r@, the rectangle representing the screen
>             -> Int       -- ^ @nmaster@, the number of windows in the
> master pane
>             -> Int       -- ^ @n@, the total number of windows to tile
>             -> [Rectangle]
>         tile54 f (Rectangle sx sy sw sh) nmaster 1 = [Rectangle sx1 sy sw1
> sh]
>           where sx1 = sx + sm1
>                 sm1 = fromIntegral (sw - sw1) `div` 2
>                 sw1 = 5 * fromIntegral (sh `div` 4)
>         tile54 f r nmaster n = if n <= nmaster || nmaster == 0
>             then splitVertically n r
>             else splitVertically nmaster r1 ++ splitVertically (n-nmaster)
> r2 -- two columns
>           where (r1,r2) = splitHorizontallyBy f r
>
> 3. Add new layout in the list, keeping standard Tall as second one. In
> rare cases when I want single window taking entire screen I can switch
> to Tall.
>
> As a result, when I open single terminal or editor window it is
> centered, simulating old 5:4 monitors. More than one window and it is
> standard Tall layout. I have attached my xmonad.hs if somebody wants to
> try.
>
> So finally questions:
>
> 1. Anybody needs this apart from me? How do you cope with
> 'teaminal/editor being too far to the left'?
>
> 2. Is there a better way to write this layout (in xmonad.hs) without
> butchering parts of code from Layout.hs? Since I am learning haskell I
> believe any pointers would be very useful.
>
> Cheers,
> Dusan
> _______________________________________________
> xmonad mailing list
> xmonad at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad
>


-- 
brandon s allbery kf8nh
allbery.b at gmail.com
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/xmonad/attachments/20200106/a31ff61c/attachment.html>


More information about the xmonad mailing list