mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
reenable quickcheck properties for layouts (no overlap, fullscreen)
This commit is contained in:
parent
4bd9073937
commit
351de8d2b6
@ -15,9 +15,14 @@
|
||||
--
|
||||
-----------------------------------------------------------------------------
|
||||
|
||||
module XMonad.Layout (ChangeLayout(..), Choose, (|||), Resize(..), IncMasterN(..),
|
||||
Full(..), Tall(..), Mirror(..), mirrorRect, splitVertically,
|
||||
splitHorizontally, splitHorizontallyBy, splitVerticallyBy) where
|
||||
module XMonad.Layout (
|
||||
ChangeLayout(..), Choose, (|||), Resize(..), IncMasterN(..),
|
||||
Full(..), Tall(..), Mirror(..), mirrorRect, splitVertically,
|
||||
splitHorizontally, splitHorizontallyBy, splitVerticallyBy,
|
||||
|
||||
tile
|
||||
|
||||
) where
|
||||
|
||||
import XMonad.Core
|
||||
|
||||
|
@ -2,6 +2,7 @@
|
||||
module Properties where
|
||||
|
||||
import XMonad.StackSet hiding (filter)
|
||||
import XMonad.Layout
|
||||
import qualified XMonad.StackSet as S (filter)
|
||||
|
||||
import Debug.Trace
|
||||
@ -656,8 +657,8 @@ prop_mapLayoutInverse (x::T) = x == mapLayout pred (mapLayout succ x)
|
||||
-- some properties for layouts:
|
||||
|
||||
-- 1 window should always be tiled fullscreen
|
||||
{-
|
||||
prop_tile_fullscreen rect = tile pct rect 1 1 == [rect]
|
||||
where pct = 1/2
|
||||
|
||||
-- multiple windows
|
||||
prop_tile_non_overlap rect windows nmaster = noOverlaps (tile pct rect nmaster windows)
|
||||
@ -679,8 +680,6 @@ noOverlaps xs = and [ verts a `notOverlap` verts b
|
||||
= (top1 < bottom2 || top2 < bottom1)
|
||||
|| (right1 < left2 || right2 < left1)
|
||||
|
||||
-}
|
||||
|
||||
------------------------------------------------------------------------
|
||||
|
||||
main :: IO ()
|
||||
@ -808,10 +807,9 @@ main = do
|
||||
|
||||
-- renaming
|
||||
|
||||
{-
|
||||
,("tile 1 window fullsize", mytest prop_tile_fullscreen)
|
||||
,("tiles never overlap", mytest prop_tile_non_overlap)
|
||||
-}
|
||||
|
||||
|
||||
]
|
||||
|
||||
|
Loading…
x
Reference in New Issue
Block a user