mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-21 14:33:48 -07:00
added mirrorLayout to mirror arbitrary layouts
This commit is contained in:
@@ -82,13 +82,15 @@ tile r (Rectangle sx sy sw sh) (w:s)
|
|||||||
rh = fromIntegral sh `div` fromIntegral (length s)
|
rh = fromIntegral sh `div` fromIntegral (length s)
|
||||||
f i a = (a, Rectangle (sx + lw) i rw (fromIntegral rh))
|
f i a = (a, Rectangle (sx + lw) i rw (fromIntegral rh))
|
||||||
|
|
||||||
-- | vtile. Tile vertically.
|
-- | Mirror a rectangle
|
||||||
vtile :: Rational -> Rectangle -> [Window] -> [(Window, Rectangle)]
|
mirrorRect :: Rectangle -> Rectangle
|
||||||
vtile r rect = map (second flipRect) . tile r (flipRect rect)
|
mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
|
||||||
|
|
||||||
-- | Flip rectangles around
|
-- | Mirror a layout
|
||||||
flipRect :: Rectangle -> Rectangle
|
mirrorLayout :: Layout -> Layout
|
||||||
flipRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
|
mirrorLayout (Layout { doLayout = dl, modifyLayout = ml })
|
||||||
|
= Layout { doLayout = (\sc ws -> map (second mirrorRect) $ dl (mirrorRect sc) ws)
|
||||||
|
, modifyLayout = fmap mirrorLayout . ml }
|
||||||
|
|
||||||
-- | switchLayout. Switch to another layout scheme. Switches the
|
-- | switchLayout. Switch to another layout scheme. Switches the
|
||||||
-- current workspace. By convention, a window set as master in Tall mode
|
-- current workspace. By convention, a window set as master in Tall mode
|
||||||
@@ -114,10 +116,7 @@ tall delta tileFrac = Layout { doLayout = \sc -> tile tileFrac sc
|
|||||||
where m Shrink = tall delta (tileFrac-delta)
|
where m Shrink = tall delta (tileFrac-delta)
|
||||||
m Expand = tall delta (tileFrac+delta)
|
m Expand = tall delta (tileFrac+delta)
|
||||||
|
|
||||||
wide delta tileFrac = Layout { doLayout = \sc -> vtile tileFrac sc
|
wide delta tileFrac = mirrorLayout (tall delta tileFrac)
|
||||||
, modifyLayout = (fmap m) . fromDynamic }
|
|
||||||
where m Shrink = wide delta (tileFrac-delta)
|
|
||||||
m Expand = wide delta (tileFrac+delta)
|
|
||||||
|
|
||||||
-- | layout. Modify the current workspace's layout with a pure
|
-- | layout. Modify the current workspace's layout with a pure
|
||||||
-- function and refresh.
|
-- function and refresh.
|
||||||
|
@@ -1,7 +1,7 @@
|
|||||||
{-# OPTIONS -fglasgow-exts #-}
|
{-# OPTIONS -fglasgow-exts #-}
|
||||||
|
|
||||||
import StackSet
|
import StackSet
|
||||||
import Operations (tile,vtile)
|
import Operations (tile)
|
||||||
|
|
||||||
import Debug.Trace
|
import Debug.Trace
|
||||||
import Data.Word
|
import Data.Word
|
||||||
@@ -226,15 +226,10 @@ prop_push_local (x :: T) i = not (member i x) ==> hidden x == hidden (push i x)
|
|||||||
-- 1 window should always be tiled fullscreen
|
-- 1 window should always be tiled fullscreen
|
||||||
prop_tile_fullscreen rect = tile pct rect [1] == [(1, rect)]
|
prop_tile_fullscreen rect = tile pct rect [1] == [(1, rect)]
|
||||||
|
|
||||||
prop_vtile_fullscreen rect = vtile pct rect [1] == [(1, rect)]
|
|
||||||
|
|
||||||
-- multiple windows
|
-- multiple windows
|
||||||
prop_tile_non_overlap rect windows = noOverlaps (tile pct rect windows)
|
prop_tile_non_overlap rect windows = noOverlaps (tile pct rect windows)
|
||||||
where _ = rect :: Rectangle
|
where _ = rect :: Rectangle
|
||||||
|
|
||||||
prop_vtile_non_overlap rect windows = noOverlaps (vtile pct rect windows)
|
|
||||||
where _ = rect :: Rectangle
|
|
||||||
|
|
||||||
pct = 3 % 100
|
pct = 3 % 100
|
||||||
|
|
||||||
noOverlaps [] = True
|
noOverlaps [] = True
|
||||||
@@ -363,8 +358,7 @@ main = do
|
|||||||
------------------------------------------------------------------------
|
------------------------------------------------------------------------
|
||||||
|
|
||||||
,("tile 1 window fullsize", mytest prop_tile_fullscreen)
|
,("tile 1 window fullsize", mytest prop_tile_fullscreen)
|
||||||
,("vtile 1 window fullsize", mytest prop_vtile_fullscreen)
|
,("tiles never overlap", mytest prop_tile_non_overlap)
|
||||||
,("vtiles never overlap", mytest prop_vtile_non_overlap )
|
|
||||||
|
|
||||||
]
|
]
|
||||||
|
|
||||||
|
Reference in New Issue
Block a user