aboutsummaryrefslogtreecommitdiffstats
path: root/tests/Properties/Layout/Full.hs
blob: eca6ec39f7f5a2f95fdea15e43e6d3a848c11e6b (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
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