aboutsummaryrefslogtreecommitdiffstats
path: root/tests/Properties/Swap.hs
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Properties/Swap.hs')
-rw-r--r--tests/Properties/Swap.hs47
1 files changed, 47 insertions, 0 deletions
diff --git a/tests/Properties/Swap.hs b/tests/Properties/Swap.hs
new file mode 100644
index 0000000..a516f2c
--- /dev/null
+++ b/tests/Properties/Swap.hs
@@ -0,0 +1,47 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+module Properties.Swap where
+
+import Test.QuickCheck
+import Instances
+import Utils
+
+import XMonad.StackSet hiding (filter)
+
+-- ---------------------------------------------------------------------
+-- swapUp, swapDown, swapMaster: reordiring windows
+
+-- swap is trivially reversible
+prop_swap_left (x :: T) = (swapUp (swapDown x)) == x
+prop_swap_right (x :: T) = (swapDown (swapUp x)) == x
+-- TODO swap is reversible
+-- swap is reversible, but involves moving focus back the window with
+-- master on it. easy to do with a mouse...
+{-
+prop_promote_reversible x b = (not . null . fromMaybe [] . flip index x . current $ x) ==>
+ (raiseFocus y . promote . raiseFocus z . promote) x == x
+ where _ = x :: T
+ dir = if b then LT else GT
+ (Just y) = peek x
+ (Just (z:_)) = flip index x . current $ x
+-}
+
+-- swap doesn't change focus
+prop_swap_master_focus (x :: T) = peek x == (peek $ swapMaster x)
+-- = case peek x of
+-- Nothing -> True
+-- Just f -> focus (stack (workspace $ current (swap x))) == f
+prop_swap_left_focus (x :: T) = peek x == (peek $ swapUp x)
+prop_swap_right_focus (x :: T) = peek x == (peek $ swapDown x)
+
+-- swap is local
+prop_swap_master_local (x :: T) = hidden_spaces x == hidden_spaces (swapMaster x)
+prop_swap_left_local (x :: T) = hidden_spaces x == hidden_spaces (swapUp x)
+prop_swap_right_local (x :: T) = hidden_spaces x == hidden_spaces (swapDown x)
+
+-- rotation through the height of a stack gets us back to the start
+prop_swap_all_l (x :: T) = (foldr (const swapUp) x [1..n]) == x
+ where n = length (index x)
+prop_swap_all_r (x :: T) = (foldr (const swapDown) x [1..n]) == x
+ where n = length (index x)
+
+prop_swap_master_idempotent (x :: T) = swapMaster (swapMaster x) == swapMaster x