X.L.CenteredIfSingle: Allow specifying ratio in both dimensions

While monitors are, more often than not, wider than they are high,
specifying a ratio in the vertical direction can also make sense; e.g.,
when flipping a monitor by 90 degrees.  Thus, we should definitely
support both.
This commit is contained in:
Jon Roberts 2022-06-17 14:28:51 -05:00 committed by Tony Zorman
parent 0d5a952035
commit accea5b1d8

View File

@ -1,5 +1,5 @@
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@ -26,8 +26,8 @@ module XMonad.Layout.CenteredIfSingle
) where ) where
import XMonad import XMonad
import XMonad.Prelude (fi)
import XMonad.Layout.LayoutModifier import XMonad.Layout.LayoutModifier
import XMonad.Prelude (fi)
-- $usage -- $usage
-- You can use this module by including the following in your @~\/.xmonad/xmonad.hs@: -- You can use this module by including the following in your @~\/.xmonad/xmonad.hs@:
@ -36,30 +36,46 @@ import XMonad.Layout.LayoutModifier
-- --
-- and adding the 'centeredIfSingle' layoutmodifier to your layouts. -- and adding the 'centeredIfSingle' layoutmodifier to your layouts.
-- --
-- > myLayoutHook = centeredIfSingle 0.7 Grid ||| ... -- > myLayoutHook = centeredIfSingle 0.7 0.8 Grid ||| ...
-- --
-- For more information on configuring your layouts see "XMonad.Doc.Extending". -- For more information on configuring your layouts see "XMonad.Doc.Extending".
-- | Layout Modifier that places a window in the center of the screen, -- | Layout Modifier that places a window in the center of the screen,
-- leaving room on the left and right if there is only a single window -- leaving room on the left and right if there is only a single window.
newtype CenteredIfSingle a = CenteredIfSingle Double deriving (Show, Read) -- The first argument is the horizontal and the second one the vertical
-- ratio of the screen the centered window should take up. Both numbers
-- should be between 0.0 and 1.0.
data CenteredIfSingle a = CenteredIfSingle !Double !Double
deriving (Show, Read)
instance LayoutModifier CenteredIfSingle Window where instance LayoutModifier CenteredIfSingle Window where
pureModifier (CenteredIfSingle ratio) r _ [(onlyWindow, _)] = ([(onlyWindow, rectangleCenterPiece ratio r)], Nothing) pureModifier (CenteredIfSingle ratioX ratioY) r _ [(onlyWindow, _)] = ([(onlyWindow, rectangleCenterPiece ratioX ratioY r)], Nothing)
pureModifier _ _ _ winRects = (winRects, Nothing) pureModifier _ _ _ winRects = (winRects, Nothing)
-- | Layout Modifier that places a window in the center of the screen, -- | Layout Modifier that places a window in the center of the screen,
-- leaving room on the left and right if there is only a single window -- leaving room on all sides if there is only a single window
centeredIfSingle :: Double -- ^ Ratio of the screen the centered window should take up. Should be a value between 0.0 and 1.0 centeredIfSingle :: Double -- ^ Horizontal ratio of the screen the centered window should take up; should be a value between 0.0 and 1.0
-> Double -- ^ Vertical ratio; should also be a value between 0.0 and 1.0
-> l a -- ^ The layout that will be used if more than one window is open -> l a -- ^ The layout that will be used if more than one window is open
-> ModifiedLayout CenteredIfSingle l a -> ModifiedLayout CenteredIfSingle l a
centeredIfSingle ratio = ModifiedLayout (CenteredIfSingle ratio) centeredIfSingle ratioX ratioY = ModifiedLayout (CenteredIfSingle ratioX ratioY)
-- | Calculate the center piece of a rectangle given the percentage of the outer rectangle it should occupy. -- | Calculate the center piece of a rectangle given the percentage of the outer rectangle it should occupy.
rectangleCenterPiece :: Double -> Rectangle -> Rectangle rectangleCenterPiece :: Double -> Double -> Rectangle -> Rectangle
rectangleCenterPiece ratio (Rectangle rx ry rw rh) = Rectangle start ry width rh rectangleCenterPiece ratioX ratioY (Rectangle rx ry rw rh) = Rectangle startX startY width height
where where
sides = floor $ fi rw * (1.0 - ratio) / 2 startX = rx + left
start = fi rx + sides startY = ry + top
width = fi $ fi rw - sides * 2
width = newSize rw left
height = newSize rh top
left = rw `scaleBy` ratioX
top = rh `scaleBy` ratioY
newSize :: Dimension -> Position -> Dimension
newSize dim pos = fi $ fi dim - pos * 2
scaleBy :: Dimension -> Double -> Position
scaleBy dim ratio = floor $ fi dim * (1.0 - ratio) / 2