mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-02 13:11:53 -07:00
tests: Apply hlint hints
This commit is contained in:
@@ -36,7 +36,7 @@ instance (Integral i, Integral s, Eq a, Arbitrary a, Arbitrary l, Arbitrary sd)
|
|||||||
-- Pick a random window "number" in each workspace, to give focus.
|
-- Pick a random window "number" in each workspace, to give focus.
|
||||||
focus <- sequence [ if null windows
|
focus <- sequence [ if null windows
|
||||||
then return Nothing
|
then return Nothing
|
||||||
else liftM Just $ choose (0, length windows - 1)
|
else Just <$> choose (0, length windows - 1)
|
||||||
| windows <- wsWindows ]
|
| windows <- wsWindows ]
|
||||||
|
|
||||||
let tags = [1 .. fromIntegral numWs]
|
let tags = [1 .. fromIntegral numWs]
|
||||||
@@ -80,7 +80,7 @@ newtype NonEmptyWindowsStackSet = NonEmptyWindowsStackSet T
|
|||||||
|
|
||||||
instance Arbitrary NonEmptyWindowsStackSet where
|
instance Arbitrary NonEmptyWindowsStackSet where
|
||||||
arbitrary =
|
arbitrary =
|
||||||
NonEmptyWindowsStackSet `fmap` (arbitrary `suchThat` (not . null . allWindows))
|
NonEmptyWindowsStackSet <$> (arbitrary `suchThat` (not . null . allWindows))
|
||||||
|
|
||||||
instance Arbitrary Rectangle where
|
instance Arbitrary Rectangle where
|
||||||
arbitrary = Rectangle <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
|
arbitrary = Rectangle <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
|
||||||
@@ -99,7 +99,7 @@ newtype NonEmptyNubList a = NonEmptyNubList [a]
|
|||||||
deriving ( Eq, Ord, Show, Read )
|
deriving ( Eq, Ord, Show, Read )
|
||||||
|
|
||||||
instance (Eq a, Arbitrary a) => Arbitrary (NonEmptyNubList a) where
|
instance (Eq a, Arbitrary a) => Arbitrary (NonEmptyNubList a) where
|
||||||
arbitrary = NonEmptyNubList `fmap` ((liftM nub arbitrary) `suchThat` (not . null))
|
arbitrary = NonEmptyNubList <$> ((nub <$> arbitrary) `suchThat` (not . null))
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
@@ -116,7 +116,7 @@ arbitraryTag :: T -> Gen Tag
|
|||||||
arbitraryTag x = do
|
arbitraryTag x = do
|
||||||
let ts = tags x
|
let ts = tags x
|
||||||
-- There must be at least 1 workspace, thus at least 1 tag.
|
-- There must be at least 1 workspace, thus at least 1 tag.
|
||||||
idx <- choose (0, (length ts) - 1)
|
idx <- choose (0, length ts - 1)
|
||||||
return $ ts!!idx
|
return $ ts!!idx
|
||||||
|
|
||||||
-- | Pull out an arbitrary window from a StackSet that is guaranteed to have a
|
-- | Pull out an arbitrary window from a StackSet that is guaranteed to have a
|
||||||
@@ -136,5 +136,5 @@ arbitraryWindow :: NonEmptyWindowsStackSet -> Gen Window
|
|||||||
arbitraryWindow (NonEmptyWindowsStackSet x) = do
|
arbitraryWindow (NonEmptyWindowsStackSet x) = do
|
||||||
let ws = allWindows x
|
let ws = allWindows x
|
||||||
-- We know that there are at least 1 window in a NonEmptyWindowsStackSet.
|
-- We know that there are at least 1 window in a NonEmptyWindowsStackSet.
|
||||||
idx <- choose(0, (length ws) - 1)
|
idx <- choose (0, length ws - 1)
|
||||||
return $ ws!!idx
|
return $ ws!!idx
|
||||||
|
@@ -64,7 +64,7 @@ prop_delete_focus_not_end = do
|
|||||||
-- last one in the stack.
|
-- last one in the stack.
|
||||||
`suchThat` \(x' :: T) ->
|
`suchThat` \(x' :: T) ->
|
||||||
let currWins = index x'
|
let currWins = index x'
|
||||||
in length (currWins) >= 2 && peek x' /= Just (last currWins)
|
in length currWins >= 2 && peek x' /= Just (last currWins)
|
||||||
-- This is safe, as we know there are >= 2 windows
|
-- This is safe, as we know there are >= 2 windows
|
||||||
let Just n = peek x
|
let Just n = peek x
|
||||||
return $ peek (delete n x) == peek (focusDown x)
|
return $ peek (delete n x) == peek (focusDown x)
|
||||||
|
@@ -32,8 +32,8 @@ prop_focusWindow_master (NonNegative n) (x :: T) =
|
|||||||
in index (focusWindow (s !! i) x) == index x
|
in index (focusWindow (s !! i) x) == index x
|
||||||
|
|
||||||
-- shifting focus is trivially reversible
|
-- shifting focus is trivially reversible
|
||||||
prop_focus_left (x :: T) = (focusUp (focusDown x)) == x
|
prop_focus_left (x :: T) = focusUp (focusDown x) == x
|
||||||
prop_focus_right (x :: T) = (focusDown (focusUp x)) == x
|
prop_focus_right (x :: T) = focusDown (focusUp x) == x
|
||||||
|
|
||||||
-- focus master is idempotent
|
-- focus master is idempotent
|
||||||
prop_focusMaster_idem (x :: T) = focusMaster x == focusMaster (focusMaster x)
|
prop_focusMaster_idem (x :: T) = focusMaster x == focusMaster (focusMaster x)
|
||||||
@@ -47,9 +47,9 @@ prop_focusWindow_works (NonNegative (n :: Int)) (x :: T) =
|
|||||||
in (focus . fromJust . stack . workspace . current) (focusWindow (s !! i) x) == (s !! i)
|
in (focus . fromJust . stack . workspace . current) (focusWindow (s !! i) x) == (s !! i)
|
||||||
|
|
||||||
-- rotation through the height of a stack gets us back to the start
|
-- rotation through the height of a stack gets us back to the start
|
||||||
prop_focus_all_l (x :: T) = (foldr (const focusUp) x [1..n]) == x
|
prop_focus_all_l (x :: T) = foldr (const focusUp) x [1..n] == x
|
||||||
where n = length (index x)
|
where n = length (index x)
|
||||||
prop_focus_all_r (x :: T) = (foldr (const focusDown) x [1..n]) == x
|
prop_focus_all_r (x :: T) = foldr (const focusDown) x [1..n] == x
|
||||||
where n = length (index x)
|
where n = length (index x)
|
||||||
|
|
||||||
-- prop_rotate_all (x :: T) = f (f x) == f x
|
-- prop_rotate_all (x :: T) = f (f x) == f x
|
||||||
|
@@ -35,7 +35,7 @@ prop_greedyView_local (x :: T) = do
|
|||||||
-- greedyView is idempotent
|
-- greedyView is idempotent
|
||||||
prop_greedyView_idem (x :: T) = do
|
prop_greedyView_idem (x :: T) = do
|
||||||
n <- arbitraryTag x
|
n <- arbitraryTag x
|
||||||
return $ greedyView n (greedyView n x) == (greedyView n x)
|
return $ greedyView n (greedyView n x) == greedyView n x
|
||||||
|
|
||||||
-- greedyView is reversible, though shuffles the order of hidden/visible
|
-- greedyView is reversible, though shuffles the order of hidden/visible
|
||||||
prop_greedyView_reversible (x :: T) = do
|
prop_greedyView_reversible (x :: T) = do
|
||||||
|
@@ -46,7 +46,7 @@ prop_insert_delete x = do
|
|||||||
|
|
||||||
-- inserting n elements increases current stack size by n
|
-- inserting n elements increases current stack size by n
|
||||||
prop_size_insert is (EmptyStackSet x) =
|
prop_size_insert is (EmptyStackSet x) =
|
||||||
size (foldr insertUp x ws ) == (length ws)
|
size (foldr insertUp x ws) == length ws
|
||||||
where
|
where
|
||||||
ws = nub is
|
ws = nub is
|
||||||
size = length . index
|
size = length . index
|
||||||
|
@@ -29,6 +29,6 @@ prop_purelayout_full rect = do
|
|||||||
|
|
||||||
-- what happens when we send an IncMaster message to Full --- Nothing
|
-- what happens when we send an IncMaster message to Full --- Nothing
|
||||||
prop_sendmsg_full (NonNegative k) =
|
prop_sendmsg_full (NonNegative k) =
|
||||||
isNothing (Full `pureMessage` (SomeMessage (IncMasterN k)))
|
isNothing (Full `pureMessage` SomeMessage (IncMasterN k))
|
||||||
|
|
||||||
prop_desc_full = description Full == show Full
|
prop_desc_full = description Full == show Full
|
||||||
|
@@ -29,12 +29,12 @@ prop_tile_non_overlap rect windows nmaster = noOverlaps (tile pct rect nmaster w
|
|||||||
|
|
||||||
-- splitting horizontally yields sensible results
|
-- splitting horizontally yields sensible results
|
||||||
prop_split_horizontal (NonNegative n) x =
|
prop_split_horizontal (NonNegative n) x =
|
||||||
(noOverflows (+) (rect_x x) (rect_width x)) ==>
|
noOverflows (+) (rect_x x) (rect_width x) ==>
|
||||||
sum (map rect_width xs) == rect_width x
|
sum (map rect_width xs) == rect_width x
|
||||||
&&
|
&&
|
||||||
all (== rect_height x) (map rect_height xs)
|
all (\s -> rect_height s == rect_height x) xs
|
||||||
&&
|
&&
|
||||||
(map rect_x xs) == (sort $ map rect_x xs)
|
map rect_x xs == sort (map rect_x xs)
|
||||||
|
|
||||||
where
|
where
|
||||||
xs = splitHorizontally n x
|
xs = splitHorizontally n x
|
||||||
@@ -72,7 +72,7 @@ prop_shrink_tall (NonNegative n) (Positive delta) (NonNegative frac) =
|
|||||||
-- remaining fraction should shrink
|
-- remaining fraction should shrink
|
||||||
where
|
where
|
||||||
l1 = Tall n delta frac
|
l1 = Tall n delta frac
|
||||||
Just l2@(Tall n' delta' frac') = l1 `pureMessage` (SomeMessage Shrink)
|
Just l2@(Tall n' delta' frac') = l1 `pureMessage` SomeMessage Shrink
|
||||||
-- pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
|
-- pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
|
||||||
|
|
||||||
|
|
||||||
@@ -93,7 +93,7 @@ prop_expand_tall (NonNegative n)
|
|||||||
where
|
where
|
||||||
frac = min 1 (n1 % d1)
|
frac = min 1 (n1 % d1)
|
||||||
l1 = Tall n delta frac
|
l1 = Tall n delta frac
|
||||||
Just l2@(Tall n' delta' frac') = l1 `pureMessage` (SomeMessage Expand)
|
Just l2@(Tall n' delta' frac') = l1 `pureMessage` SomeMessage Expand
|
||||||
-- pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
|
-- pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
|
||||||
|
|
||||||
-- what happens when we send an IncMaster message to Tall
|
-- what happens when we send an IncMaster message to Tall
|
||||||
@@ -102,7 +102,7 @@ prop_incmaster_tall (NonNegative n) (Positive delta) (NonNegative frac)
|
|||||||
delta == delta' && frac == frac' && n' == n + k
|
delta == delta' && frac == frac' && n' == n + k
|
||||||
where
|
where
|
||||||
l1 = Tall n delta frac
|
l1 = Tall n delta frac
|
||||||
Just l2@(Tall n' delta' frac') = l1 `pureMessage` (SomeMessage (IncMasterN k))
|
Just l2@(Tall n' delta' frac') = l1 `pureMessage` SomeMessage (IncMasterN k)
|
||||||
-- pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
|
-- pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
|
||||||
|
|
||||||
|
|
||||||
|
@@ -53,8 +53,8 @@ prop_aspect_hint_shrink hint (w,h) = case applyAspectHint hint (w,h) of
|
|||||||
-- the desired range
|
-- the desired range
|
||||||
prop_aspect_fits =
|
prop_aspect_fits =
|
||||||
forAll ((,,,) <$> pos <*> pos <*> pos <*> pos) $ \ (x,y,a,b) ->
|
forAll ((,,,) <$> pos <*> pos <*> pos <*> pos) $ \ (x,y,a,b) ->
|
||||||
let f v = applyAspectHint ((x, y+a), (x+b, y)) v
|
let f = applyAspectHint ((x, y+a), (x+b, y))
|
||||||
in and [ noOverflows (*) x (y+a), noOverflows (*) (x+b) y ]
|
in noOverflows (*) x (y+a) && noOverflows (*) (x+b) y
|
||||||
==> f (x,y) == (x,y)
|
==> f (x,y) == (x,y)
|
||||||
|
|
||||||
where pos = choose (0, 65535)
|
where pos = choose (0, 65535)
|
||||||
|
@@ -27,7 +27,7 @@ prop_shift_reversible (x :: T) = do
|
|||||||
-- shiftMaster
|
-- shiftMaster
|
||||||
|
|
||||||
-- focus/local/idempotent same as swapMaster:
|
-- focus/local/idempotent same as swapMaster:
|
||||||
prop_shift_master_focus (x :: T) = peek x == (peek $ shiftMaster x)
|
prop_shift_master_focus (x :: T) = peek x == peek (shiftMaster x)
|
||||||
prop_shift_master_local (x :: T) = hidden_spaces x == hidden_spaces (shiftMaster x)
|
prop_shift_master_local (x :: T) = hidden_spaces x == hidden_spaces (shiftMaster x)
|
||||||
prop_shift_master_idempotent (x :: T) = shiftMaster (shiftMaster x) == shiftMaster x
|
prop_shift_master_idempotent (x :: T) = shiftMaster (shiftMaster x) == shiftMaster x
|
||||||
-- ordering is constant modulo the focused window:
|
-- ordering is constant modulo the focused window:
|
||||||
@@ -57,14 +57,14 @@ prop_shift_win_fix_current = do
|
|||||||
x <- arbitrary `suchThat` \(x' :: T) ->
|
x <- arbitrary `suchThat` \(x' :: T) ->
|
||||||
-- Invariant, otherWindows are NOT in the current workspace.
|
-- Invariant, otherWindows are NOT in the current workspace.
|
||||||
let otherWindows = allWindows x' L.\\ index x'
|
let otherWindows = allWindows x' L.\\ index x'
|
||||||
in length(tags x') >= 2 && length(otherWindows) >= 1
|
in length (tags x') >= 2 && not (null otherWindows)
|
||||||
-- Sadly we have to construct `otherWindows` again, for the actual StackSet
|
-- Sadly we have to construct `otherWindows` again, for the actual StackSet
|
||||||
-- that got chosen.
|
-- that got chosen.
|
||||||
let otherWindows = allWindows x L.\\ index x
|
let otherWindows = allWindows x L.\\ index x
|
||||||
-- We know such tag must exists, due to the precondition
|
-- We know such tag must exists, due to the precondition
|
||||||
n <- arbitraryTag x `suchThat` (/= currentTag x)
|
n <- arbitraryTag x `suchThat` (/= currentTag x)
|
||||||
-- we know length is >= 1, from above precondition
|
-- we know length is >= 1, from above precondition
|
||||||
idx <- choose(0, length(otherWindows) - 1)
|
idx <- choose (0, length otherWindows - 1)
|
||||||
let w = otherWindows !! idx
|
let w = otherWindows !! idx
|
||||||
return $ (current $ x) == (current $ shiftWin n w x)
|
return $ current x == current (shiftWin n w x)
|
||||||
|
|
||||||
|
@@ -1,6 +1,10 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
|
||||||
|
#ifdef VERSION_quickcheck_classes
|
||||||
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
|
#endif
|
||||||
|
|
||||||
module Properties.Stack where
|
module Properties.Stack where
|
||||||
|
|
||||||
import Test.QuickCheck
|
import Test.QuickCheck
|
||||||
@@ -24,7 +28,7 @@ import Test.QuickCheck.Classes (
|
|||||||
-- windows kept in the zipper
|
-- windows kept in the zipper
|
||||||
prop_index_length (x :: T) =
|
prop_index_length (x :: T) =
|
||||||
case stack . workspace . current $ x of
|
case stack . workspace . current $ x of
|
||||||
Nothing -> length (index x) == 0
|
Nothing -> null (index x)
|
||||||
Just it -> length (index x) == length (focus it : up it ++ down it)
|
Just it -> length (index x) == length (focus it : up it ++ down it)
|
||||||
|
|
||||||
|
|
||||||
@@ -43,7 +47,7 @@ prop_allWindowsMember (NonEmptyWindowsStackSet x) = do
|
|||||||
-- which is a key component in this test (together with member).
|
-- which is a key component in this test (together with member).
|
||||||
let ws = allWindows x
|
let ws = allWindows x
|
||||||
-- We know that there are at least 1 window in a NonEmptyWindowsStackSet.
|
-- We know that there are at least 1 window in a NonEmptyWindowsStackSet.
|
||||||
idx <- choose(0, (length ws) - 1)
|
idx <- choose (0, length ws - 1)
|
||||||
return $ member (ws!!idx) x
|
return $ member (ws!!idx) x
|
||||||
|
|
||||||
|
|
||||||
@@ -56,8 +60,8 @@ prop_filter_order (x :: T) =
|
|||||||
-- differentiate should return Nothing if the list is empty or Just stack, with
|
-- 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.
|
-- the first element of the list is current, and the rest of the list is down.
|
||||||
prop_differentiate xs =
|
prop_differentiate xs =
|
||||||
if null xs then differentiate xs == Nothing
|
if null xs then isNothing (differentiate xs)
|
||||||
else (differentiate xs) == Just (Stack (head xs) [] (tail xs))
|
else differentiate xs == Just (Stack (head xs) [] (tail xs))
|
||||||
where _ = xs :: [Int]
|
where _ = xs :: [Int]
|
||||||
|
|
||||||
|
|
||||||
|
@@ -58,7 +58,7 @@ invariant (s :: T) = and
|
|||||||
-- inBounds = and [ w >=0 && w < size s | (w,sc) <- M.assocs (screens s) ]
|
-- inBounds = and [ w >=0 && w < size s | (w,sc) <- M.assocs (screens s) ]
|
||||||
|
|
||||||
monotonic [] = True
|
monotonic [] = True
|
||||||
monotonic (x:[]) = True
|
monotonic [x] = True
|
||||||
monotonic (x:y:zs) | x == y-1 = monotonic (y:zs)
|
monotonic (x:y:zs) | x == y-1 = monotonic (y:zs)
|
||||||
| otherwise = False
|
| otherwise = False
|
||||||
|
|
||||||
@@ -126,7 +126,7 @@ prop_empty (EmptyStackSet x) =
|
|||||||
prop_empty_current (EmptyStackSet x) = currentTag x == head (tags x)
|
prop_empty_current (EmptyStackSet x) = currentTag x == head (tags x)
|
||||||
|
|
||||||
-- no windows will be a member of an empty workspace
|
-- no windows will be a member of an empty workspace
|
||||||
prop_member_empty i (EmptyStackSet x) = member i x == False
|
prop_member_empty i (EmptyStackSet x) = not (member i x)
|
||||||
|
|
||||||
-- peek either yields nothing on the Empty workspace, or Just a valid window
|
-- peek either yields nothing on the Empty workspace, or Just a valid window
|
||||||
prop_member_peek (x :: T) =
|
prop_member_peek (x :: T) =
|
||||||
|
@@ -11,8 +11,8 @@ import XMonad.StackSet hiding (filter)
|
|||||||
-- swapUp, swapDown, swapMaster: reordiring windows
|
-- swapUp, swapDown, swapMaster: reordiring windows
|
||||||
|
|
||||||
-- swap is trivially reversible
|
-- swap is trivially reversible
|
||||||
prop_swap_left (x :: T) = (swapUp (swapDown x)) == x
|
prop_swap_left (x :: T) = swapUp (swapDown x) == x
|
||||||
prop_swap_right (x :: T) = (swapDown (swapUp x)) == x
|
prop_swap_right (x :: T) = swapDown (swapUp x) == x
|
||||||
-- TODO swap is reversible
|
-- TODO swap is reversible
|
||||||
-- swap is reversible, but involves moving focus back the window with
|
-- swap is reversible, but involves moving focus back the window with
|
||||||
-- master on it. easy to do with a mouse...
|
-- master on it. easy to do with a mouse...
|
||||||
@@ -26,12 +26,12 @@ prop_promote_reversible x b = (not . null . fromMaybe [] . flip index x . curren
|
|||||||
-}
|
-}
|
||||||
|
|
||||||
-- swap doesn't change focus
|
-- swap doesn't change focus
|
||||||
prop_swap_master_focus (x :: T) = peek x == (peek $ swapMaster x)
|
prop_swap_master_focus (x :: T) = peek x == peek (swapMaster x)
|
||||||
-- = case peek x of
|
-- = case peek x of
|
||||||
-- Nothing -> True
|
-- Nothing -> True
|
||||||
-- Just f -> focus (stack (workspace $ current (swap x))) == f
|
-- Just f -> focus (stack (workspace $ current (swap x))) == f
|
||||||
prop_swap_left_focus (x :: T) = peek x == (peek $ swapUp x)
|
prop_swap_left_focus (x :: T) = peek x == peek (swapUp x)
|
||||||
prop_swap_right_focus (x :: T) = peek x == (peek $ swapDown x)
|
prop_swap_right_focus (x :: T) = peek x == peek (swapDown x)
|
||||||
|
|
||||||
-- swap is local
|
-- swap is local
|
||||||
prop_swap_master_local (x :: T) = hidden_spaces x == hidden_spaces (swapMaster x)
|
prop_swap_master_local (x :: T) = hidden_spaces x == hidden_spaces (swapMaster x)
|
||||||
@@ -39,9 +39,9 @@ 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)
|
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
|
-- 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
|
prop_swap_all_l (x :: T) = foldr (const swapUp) x [1..n] == x
|
||||||
where n = length (index x)
|
where n = length (index x)
|
||||||
prop_swap_all_r (x :: T) = (foldr (const swapDown) x [1..n]) == x
|
prop_swap_all_r (x :: T) = foldr (const swapDown) x [1..n] == x
|
||||||
where n = length (index x)
|
where n = length (index x)
|
||||||
|
|
||||||
prop_swap_master_idempotent (x :: T) = swapMaster (swapMaster x) == swapMaster x
|
prop_swap_master_idempotent (x :: T) = swapMaster (swapMaster x) == swapMaster x
|
||||||
|
@@ -37,7 +37,7 @@ prop_view_local (x :: T) = do
|
|||||||
-- view is idempotent
|
-- view is idempotent
|
||||||
prop_view_idem (x :: T) = do
|
prop_view_idem (x :: T) = do
|
||||||
n <- arbitraryTag x
|
n <- arbitraryTag x
|
||||||
return $ view n (view n x) == (view n x)
|
return $ view n (view n x) == view n x
|
||||||
|
|
||||||
-- view is reversible, though shuffles the order of hidden/visible
|
-- view is reversible, though shuffles the order of hidden/visible
|
||||||
prop_view_reversible (x :: T) = do
|
prop_view_reversible (x :: T) = do
|
||||||
|
@@ -12,8 +12,8 @@ hidden_spaces x = map workspace (visible x) ++ hidden x
|
|||||||
-- normalise workspace list
|
-- normalise workspace list
|
||||||
normal s = s { hidden = sortBy g (hidden s), visible = sortBy f (visible s) }
|
normal s = s { hidden = sortBy g (hidden s), visible = sortBy f (visible s) }
|
||||||
where
|
where
|
||||||
f = \a b -> tag (workspace a) `compare` tag (workspace b)
|
f a b = tag (workspace a) `compare` tag (workspace b)
|
||||||
g = \a b -> tag a `compare` tag b
|
g a b = tag a `compare` tag b
|
||||||
|
|
||||||
|
|
||||||
noOverlaps [] = True
|
noOverlaps [] = True
|
||||||
|
Reference in New Issue
Block a user