mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-05 06:31:54 -07:00
Remove toList
This commit is contained in:
11
StackSet.hs
11
StackSet.hs
@@ -25,7 +25,7 @@ module StackSet (
|
|||||||
|
|
||||||
screen, peekStack, index, empty, peek, push, delete, member,
|
screen, peekStack, index, empty, peek, push, delete, member,
|
||||||
raiseFocus, rotate, promote, shift, view, workspace, fromList,
|
raiseFocus, rotate, promote, shift, view, workspace, fromList,
|
||||||
toList, size, visibleWorkspaces, swap {- helper -}
|
size, visibleWorkspaces, swap {- helper -}
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
@@ -44,10 +44,7 @@ data StackSet i j a =
|
|||||||
, stacks :: !(M.Map i [a]) -- ^ the separate stacks
|
, stacks :: !(M.Map i [a]) -- ^ the separate stacks
|
||||||
, focus :: !(M.Map i a) -- ^ the window focused in each stack
|
, focus :: !(M.Map i a) -- ^ the window focused in each stack
|
||||||
, cache :: !(M.Map a i) -- ^ a cache of windows back to their stacks
|
, cache :: !(M.Map a i) -- ^ a cache of windows back to their stacks
|
||||||
} deriving Eq
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
instance (Show i, Show a) => Show (StackSet i j a) where
|
|
||||||
showsPrec p s r = showsPrec p (show . toList $ s) r
|
|
||||||
|
|
||||||
-- The cache is used to check on insertion that we don't already have
|
-- The cache is used to check on insertion that we don't already have
|
||||||
-- this window managed on another stack
|
-- this window managed on another stack
|
||||||
@@ -99,10 +96,6 @@ fromList (o,m,xs) = view o $ foldr (\(i,ys) s ->
|
|||||||
(empty (length xs) m) (zip [0..] xs)
|
(empty (length xs) m) (zip [0..] xs)
|
||||||
|
|
||||||
|
|
||||||
-- | toList. Flatten a stackset to a list of lists
|
|
||||||
toList :: StackSet i j a -> (i,Int,[[a]])
|
|
||||||
toList x = (current x, M.size $ screen2ws x, map snd $ M.toList (stacks x))
|
|
||||||
|
|
||||||
-- | Push. Insert an element onto the top of the current stack.
|
-- | Push. Insert an element onto the top of the current stack.
|
||||||
-- If the element is already in the current stack, it is moved to the top.
|
-- If the element is already in the current stack, it is moved to the top.
|
||||||
-- If the element is managed on another stack, it is removed from that
|
-- If the element is managed on another stack, it is removed from that
|
||||||
|
@@ -35,9 +35,6 @@ instance (Integral i, Integral j, Ord a, Arbitrary a) => Arbitrary (StackSet i j
|
|||||||
return $ fromList (fromIntegral n,sc,ls)
|
return $ fromList (fromIntegral n,sc,ls)
|
||||||
coarbitrary = error "no coarbitrary for StackSet"
|
coarbitrary = error "no coarbitrary for StackSet"
|
||||||
|
|
||||||
prop_id x = fromList (toList x) == x
|
|
||||||
where _ = x :: T
|
|
||||||
|
|
||||||
prop_member1 i n m = member i (push i x)
|
prop_member1 i n m = member i (push i x)
|
||||||
where x = empty n m :: T
|
where x = empty n m :: T
|
||||||
|
|
||||||
@@ -243,9 +240,7 @@ main = do
|
|||||||
n = 100
|
n = 100
|
||||||
|
|
||||||
tests =
|
tests =
|
||||||
[("read.show ", mytest prop_id)
|
[("member/push ", mytest prop_member1)
|
||||||
|
|
||||||
,("member/push ", mytest prop_member1)
|
|
||||||
,("member/peek ", mytest prop_peekmember)
|
,("member/peek ", mytest prop_peekmember)
|
||||||
,("member/delete ", mytest prop_member2)
|
,("member/delete ", mytest prop_member2)
|
||||||
,("member/empty ", mytest prop_member3)
|
,("member/empty ", mytest prop_member3)
|
||||||
|
Reference in New Issue
Block a user