mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 00:20:22 -07:00
some tests for the size increment handling in Operations.hs
This commit is contained in:
parent
750544fda9
commit
dbbd934b0b
@ -4,6 +4,7 @@ module Properties where
|
||||
import XMonad.StackSet hiding (filter)
|
||||
import XMonad.Layout
|
||||
import XMonad.Core hiding (workspaces,trace)
|
||||
import XMonad.Operations ( applyResizeIncHint )
|
||||
import qualified XMonad.StackSet as S (filter)
|
||||
|
||||
import Debug.Trace
|
||||
@ -809,6 +810,19 @@ noOverlaps xs = and [ verts a `notOverlap` verts b
|
||||
= (top1 < bottom2 || top2 < bottom1)
|
||||
|| (right1 < left2 || right2 < left1)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- Aspect ratios
|
||||
|
||||
prop_resize_inc (NonZero (NonNegative inc_w),NonZero (NonNegative inc_h)) b@(w,h) =
|
||||
w' `mod` inc_w == 0 && h' `mod` inc_h == 0
|
||||
where (w',h') = applyResizeIncHint a b
|
||||
a = (inc_w,inc_h)
|
||||
|
||||
prop_resize_inc_extra ((NonNegative inc_w)) b@(w,h) =
|
||||
(w,h) == (w',h')
|
||||
where (w',h') = applyResizeIncHint a b
|
||||
a = (-inc_w,0::Dimension)-- inc_h)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
|
||||
main :: IO ()
|
||||
@ -954,6 +968,10 @@ main = do
|
||||
|
||||
,("describe mirror", mytest prop_desc_mirror)
|
||||
|
||||
-- resize hints
|
||||
,("window hints: inc", mytest prop_resize_inc)
|
||||
,("window hints: inc all", mytest prop_resize_inc_extra)
|
||||
|
||||
]
|
||||
|
||||
------------------------------------------------------------------------
|
||||
|
Loading…
x
Reference in New Issue
Block a user