reenable quickcheck properties for layouts (no overlap, fullscreen)

This commit is contained in:
Don Stewart 2008-03-21 23:40:15 +00:00
parent 4bd9073937
commit 351de8d2b6
2 changed files with 11 additions and 8 deletions

View File

@ -15,9 +15,14 @@
-- --
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
module XMonad.Layout (ChangeLayout(..), Choose, (|||), Resize(..), IncMasterN(..), module XMonad.Layout (
Full(..), Tall(..), Mirror(..), mirrorRect, splitVertically, ChangeLayout(..), Choose, (|||), Resize(..), IncMasterN(..),
splitHorizontally, splitHorizontallyBy, splitVerticallyBy) where Full(..), Tall(..), Mirror(..), mirrorRect, splitVertically,
splitHorizontally, splitHorizontallyBy, splitVerticallyBy,
tile
) where
import XMonad.Core import XMonad.Core

View File

@ -2,6 +2,7 @@
module Properties where module Properties where
import XMonad.StackSet hiding (filter) import XMonad.StackSet hiding (filter)
import XMonad.Layout
import qualified XMonad.StackSet as S (filter) import qualified XMonad.StackSet as S (filter)
import Debug.Trace import Debug.Trace
@ -656,8 +657,8 @@ prop_mapLayoutInverse (x::T) = x == mapLayout pred (mapLayout succ x)
-- some properties for layouts: -- some properties for layouts:
-- 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]
where pct = 1/2
-- multiple windows -- multiple windows
prop_tile_non_overlap rect windows nmaster = noOverlaps (tile pct rect nmaster 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) = (top1 < bottom2 || top2 < bottom1)
|| (right1 < left2 || right2 < left1) || (right1 < left2 || right2 < left1)
-}
------------------------------------------------------------------------ ------------------------------------------------------------------------
main :: IO () main :: IO ()
@ -808,10 +807,9 @@ main = do
-- renaming -- renaming
{-
,("tile 1 window fullsize", mytest prop_tile_fullscreen) ,("tile 1 window fullsize", mytest prop_tile_fullscreen)
,("tiles never overlap", mytest prop_tile_non_overlap) ,("tiles never overlap", mytest prop_tile_non_overlap)
-}
] ]