mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
commit
f4d25fcef4
@ -10,6 +10,8 @@
|
||||
|
||||
* Exported `buildLaunch` from `XMonad.Main`.
|
||||
|
||||
* `Tall` does not draw windows with zero area.
|
||||
|
||||
### Bug Fixes
|
||||
|
||||
## 0.17.1 (September 3, 2022)
|
||||
|
@ -62,9 +62,13 @@ data Tall a = Tall { tallNMaster :: !Int -- ^ The default number o
|
||||
|
||||
-- a nice pure layout, lots of properties for the layout, and its messages, in Properties.hs
|
||||
instance LayoutClass Tall a where
|
||||
pureLayout (Tall nmaster _ frac) r s = zip ws rs
|
||||
pureLayout (Tall nmaster _ frac) r s
|
||||
| frac == 0 = drop nmaster layout
|
||||
| frac == 1 = take nmaster layout
|
||||
| otherwise = layout
|
||||
where ws = W.integrate s
|
||||
rs = tile frac r nmaster (length ws)
|
||||
layout = zip ws rs
|
||||
|
||||
pureMessage (Tall nmaster delta frac) m =
|
||||
msum [fmap resize (fromMessage m)
|
||||
|
@ -166,11 +166,16 @@ tests =
|
||||
-- tall layout
|
||||
|
||||
,("tile 1 window fullsize", property prop_tile_fullscreen)
|
||||
,("tile max ratio", property prop_tile_max_ratio)
|
||||
,("tile min ratio", property prop_tile_min_ratio)
|
||||
,("tiles never overlap", property prop_tile_non_overlap)
|
||||
,("split horizontal", property prop_split_horizontal)
|
||||
,("split vertical", property prop_split_vertical)
|
||||
|
||||
,("pure layout tall", property prop_purelayout_tall)
|
||||
{- Following two test cases should be automatically generated by QuickCheck ideally, but it fails. -}
|
||||
,("pure layout tall: ratio = 0", property (\n d rect -> prop_purelayout_tall n d 0 rect))
|
||||
,("pure layout tall: ratio = 1", property (\n d rect -> prop_purelayout_tall n d 1 rect))
|
||||
,("send shrink tall", property prop_shrink_tall)
|
||||
,("send expand tall", property prop_expand_tall)
|
||||
,("send incmaster tall", property prop_incmaster_tall)
|
||||
|
@ -11,8 +11,9 @@ import XMonad.Layout
|
||||
|
||||
import Graphics.X11.Xlib.Types (Rectangle(..))
|
||||
|
||||
import Data.Maybe
|
||||
import Control.Applicative
|
||||
import Data.List (sort)
|
||||
import Data.Maybe
|
||||
import Data.Ratio
|
||||
|
||||
------------------------------------------------------------------------
|
||||
@ -27,6 +28,22 @@ prop_tile_non_overlap rect windows nmaster = noOverlaps (tile pct rect nmaster w
|
||||
where _ = rect :: Rectangle
|
||||
pct = 3 % 100
|
||||
|
||||
-- with a ratio of 1, no stack windows are drawn of there is at least
|
||||
-- one master window around.
|
||||
prop_tile_max_ratio = extremeRatio 1 drop
|
||||
|
||||
-- with a ratio of 0, no master windows are drawn at all if there are
|
||||
-- any stack windows around.
|
||||
prop_tile_min_ratio = extremeRatio 0 take
|
||||
|
||||
extremeRatio amount getRects rect = do
|
||||
w@(NonNegative windows) <- arbitrary `suchThat` (> NonNegative 0)
|
||||
NonNegative nmaster <- arbitrary `suchThat` (< w)
|
||||
let tiled = tile amount rect nmaster windows
|
||||
pure $ if nmaster == 0
|
||||
then prop_tile_non_overlap rect windows nmaster
|
||||
else all ((== 0) . rect_width) $ getRects nmaster tiled
|
||||
|
||||
-- splitting horizontally yields sensible results
|
||||
prop_split_horizontal (NonNegative n) x =
|
||||
noOverflows (+) (rect_x x) (rect_width x) ==>
|
||||
@ -49,13 +66,20 @@ prop_split_vertical (r :: Rational) x =
|
||||
|
||||
|
||||
-- pureLayout works.
|
||||
prop_purelayout_tall n r1 r2 rect = do
|
||||
prop_purelayout_tall n d r rect = do
|
||||
x <- (arbitrary :: Gen T) `suchThat` (isJust . peek)
|
||||
let layout = Tall n r1 r2
|
||||
let layout = Tall n d r
|
||||
st = fromJust . stack . workspace . current $ x
|
||||
ts = pureLayout layout rect st
|
||||
ntotal = length (index x)
|
||||
return $
|
||||
length ts == length (index x)
|
||||
(if r == 0 then
|
||||
-- (<=) for Bool is the logical implication
|
||||
(0 <= n && n <= ntotal) <= (length ts == ntotal - n)
|
||||
else if r == 1 then
|
||||
(0 <= n && n <= ntotal) <= (length ts == n)
|
||||
else
|
||||
length ts == ntotal)
|
||||
&&
|
||||
noOverlaps (map snd ts)
|
||||
&&
|
||||
|
Loading…
x
Reference in New Issue
Block a user