aboutsummaryrefslogtreecommitdiffstats
path: root/tests/Properties/GreedyView.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/GreedyView.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/GreedyView.hs')
-rw-r--r--tests/Properties/GreedyView.hs44
1 files changed, 44 insertions, 0 deletions
diff --git a/tests/Properties/GreedyView.hs b/tests/Properties/GreedyView.hs
new file mode 100644
index 0000000..3f2eb9b
--- /dev/null
+++ b/tests/Properties/GreedyView.hs
@@ -0,0 +1,44 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+module Properties.GreedyView where
+
+import Test.QuickCheck
+import Instances
+import Utils
+
+import XMonad.StackSet hiding (filter)
+
+import Data.List (sortBy)
+
+-- ---------------------------------------------------------------------
+-- greedyViewing workspaces
+
+-- greedyView sets the current workspace to 'n'
+prop_greedyView_current (x :: T) = do
+ n <- arbitraryTag x
+ return $ currentTag (greedyView n x) == n
+
+-- greedyView leaves things unchanged for invalid workspaces
+prop_greedyView_current_id (x :: T) = do
+ n <- arbitrary `suchThat` \n' -> not $ n' `tagMember` x
+ return $ currentTag (greedyView n x) == currentTag x
+
+-- greedyView *only* sets the current workspace, and touches Xinerama.
+-- no workspace contents will be changed.
+prop_greedyView_local (x :: T) = do
+ n <- arbitraryTag x
+ return $ workspaces x == workspaces (greedyView n x)
+ where
+ workspaces a = sortBy (\s t -> tag s `compare` tag t) $
+ workspace (current a)
+ : map workspace (visible a) ++ hidden a
+
+-- greedyView is idempotent
+prop_greedyView_idem (x :: T) = do
+ n <- arbitraryTag x
+ return $ greedyView n (greedyView n x) == (greedyView n x)
+
+-- greedyView is reversible, though shuffles the order of hidden/visible
+prop_greedyView_reversible (x :: T) = do
+ n <- arbitraryTag x
+ return $ normal (greedyView n' (greedyView n x)) == normal x
+ where n' = currentTag x