aboutsummaryrefslogtreecommitdiffstats
path: root/tests/Properties/Stack.hs
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2014-05-02 20:01:46 +0200
committerAdam Vogt <vogt.adam@gmail.com>2014-05-02 20:01:46 +0200
commit9660a7a64c749e181d2114cc4b66a8aa4f88be0f (patch)
tree1664b0ed1ee20f66cf3b7f550c33d49c897bed8c /tests/Properties/Stack.hs
parentb682eaf8fcbb548dacb35b4103e546cbd9fca3ed (diff)
downloadxmonad-9660a7a64c749e181d2114cc4b66a8aa4f88be0f.tar.gz
xmonad-9660a7a64c749e181d2114cc4b66a8aa4f88be0f.tar.xz
xmonad-9660a7a64c749e181d2114cc4b66a8aa4f88be0f.zip
update testsuite (mostly due Jesper Reenberg)
Ignore-this: a5e926aa4e397e70d56e3c9db7108d5b * use quickcheck2 * run them using cabal's test-suite field * split up Properties into separate files darcs-hash:20140502180146-1499c-dc8c09c3ec76a42a0e146925adce960435dc81db.gz
Diffstat (limited to 'tests/Properties/Stack.hs')
-rw-r--r--tests/Properties/Stack.hs51
1 files changed, 51 insertions, 0 deletions
diff --git a/tests/Properties/Stack.hs b/tests/Properties/Stack.hs
new file mode 100644
index 0000000..586df1d
--- /dev/null
+++ b/tests/Properties/Stack.hs
@@ -0,0 +1,51 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+module Properties.Stack where
+
+import Test.QuickCheck
+import Instances
+
+import XMonad.StackSet hiding (filter)
+import qualified XMonad.StackSet as S (filter)
+
+import Data.Maybe
+
+
+-- The list returned by index should be the same length as the actual
+-- windows kept in the zipper
+prop_index_length (x :: T) =
+ case stack . workspace . current $ x of
+ Nothing -> length (index x) == 0
+ Just it -> length (index x) == length (focus it : up it ++ down it)
+
+
+-- For all windows in the stackSet, findTag should identify the
+-- correct workspace
+prop_findIndex (x :: T) =
+ and [ tag w == fromJust (findTag i x)
+ | w <- workspace (current x) : map workspace (visible x) ++ hidden x
+ , t <- maybeToList (stack w)
+ , i <- focus t : up t ++ down t
+ ]
+
+prop_allWindowsMember (NonEmptyWindowsStackSet x) = do
+ -- Reimplementation of arbitraryWindow, but to make sure that
+ -- implementation doesn't change in the future, and stop using allWindows,
+ -- which is a key component in this test (together with member).
+ let ws = allWindows x
+ -- We know that there are at least 1 window in a NonEmptyWindowsStackSet.
+ idx <- choose(0, (length ws) - 1)
+ return $ member (ws!!idx) x
+
+
+-- preserve order
+prop_filter_order (x :: T) =
+ case stack $ workspace $ current x of
+ Nothing -> True
+ Just s@(Stack i _ _) -> integrate' (S.filter (/= i) s) == filter (/= i) (integrate' (Just s))
+
+-- differentiate should return Nothing if the list is empty or Just stack, with
+-- the first element of the list is current, and the rest of the list is down.
+prop_differentiate xs =
+ if null xs then differentiate xs == Nothing
+ else (differentiate xs) == Just (Stack (head xs) [] (tail xs))
+ where _ = xs :: [Int]