aboutsummaryrefslogtreecommitdiffstats
path: root/tests/Properties/Layout/Full.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/Layout/Full.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/Layout/Full.hs')
-rw-r--r--tests/Properties/Layout/Full.hs34
1 files changed, 34 insertions, 0 deletions
diff --git a/tests/Properties/Layout/Full.hs b/tests/Properties/Layout/Full.hs
new file mode 100644
index 0000000..eca6ec3
--- /dev/null
+++ b/tests/Properties/Layout/Full.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+module Properties.Layout.Full where
+
+import Test.QuickCheck
+import Instances
+
+import XMonad.StackSet hiding (filter)
+import XMonad.Core
+import XMonad.Layout
+
+import Data.Maybe
+
+------------------------------------------------------------------------
+-- Full layout
+
+-- pureLayout works for Full
+prop_purelayout_full rect = do
+ x <- (arbitrary :: Gen T) `suchThat` (isJust . peek)
+ let layout = Full
+ st = fromJust . stack . workspace . current $ x
+ ts = pureLayout layout rect st
+ return $
+ length ts == 1 -- only one window to view
+ &&
+ snd (head ts) == rect -- and sets fullscreen
+ &&
+ fst (head ts) == fromJust (peek x) -- and the focused window is shown
+
+
+-- what happens when we send an IncMaster message to Full --- Nothing
+prop_sendmsg_full (NonNegative k) =
+ isNothing (Full `pureMessage` (SomeMessage (IncMasterN k)))
+
+prop_desc_full = description Full == show Full