mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-22 06:53:47 -07:00
remove StackOrNot type synonymn.
This commit is contained in:
14
StackSet.hs
14
StackSet.hs
@@ -14,7 +14,7 @@
|
|||||||
module StackSet (
|
module StackSet (
|
||||||
-- * Introduction
|
-- * Introduction
|
||||||
-- $intro
|
-- $intro
|
||||||
StackSet(..), Workspace(..), Screen(..), StackOrNot, Stack(..), RationalRect(..),
|
StackSet(..), Workspace(..), Screen(..), Stack(..), RationalRect(..),
|
||||||
-- * Construction
|
-- * Construction
|
||||||
-- $construction
|
-- $construction
|
||||||
new, view, greedyView,
|
new, view, greedyView,
|
||||||
@@ -169,7 +169,7 @@ data Screen i l a sid sd = Screen { workspace :: !(Workspace i l a)
|
|||||||
-- |
|
-- |
|
||||||
-- A workspace is just a tag - its index - and a stack
|
-- A workspace is just a tag - its index - and a stack
|
||||||
--
|
--
|
||||||
data Workspace i l a = Workspace { tag :: !i, layout :: l, stack :: StackOrNot a }
|
data Workspace i l a = Workspace { tag :: !i, layout :: l, stack :: Maybe (Stack a) }
|
||||||
deriving (Show, Read, Eq)
|
deriving (Show, Read, Eq)
|
||||||
|
|
||||||
-- | A structure for window geometries
|
-- | A structure for window geometries
|
||||||
@@ -194,8 +194,6 @@ data RationalRect = RationalRect Rational Rational Rational Rational
|
|||||||
-- structures, it is the differentiation of a [a], and integrating it
|
-- structures, it is the differentiation of a [a], and integrating it
|
||||||
-- back has a natural implementation used in 'index'.
|
-- back has a natural implementation used in 'index'.
|
||||||
--
|
--
|
||||||
type StackOrNot a = Maybe (Stack a)
|
|
||||||
|
|
||||||
data Stack a = Stack { focus :: !a -- focused thing in this set
|
data Stack a = Stack { focus :: !a -- focused thing in this set
|
||||||
, up :: [a] -- clowns to the left
|
, up :: [a] -- clowns to the left
|
||||||
, down :: [a] } -- jokers to the right
|
, down :: [a] } -- jokers to the right
|
||||||
@@ -294,7 +292,7 @@ with dflt f = maybe dflt f . stack . workspace . current
|
|||||||
-- |
|
-- |
|
||||||
-- Apply a function, and a default value for Nothing, to modify the current stack.
|
-- Apply a function, and a default value for Nothing, to modify the current stack.
|
||||||
--
|
--
|
||||||
modify :: StackOrNot a -> (Stack a -> StackOrNot a) -> StackSet i l a s sd -> StackSet i l a s sd
|
modify :: Maybe (Stack a) -> (Stack a -> Maybe (Stack a)) -> StackSet i l a s sd -> StackSet i l a s sd
|
||||||
modify d f s = s { current = (current s)
|
modify d f s = s { current = (current s)
|
||||||
{ workspace = (workspace (current s)) { stack = with d f s }}}
|
{ workspace = (workspace (current s)) { stack = with d f s }}}
|
||||||
|
|
||||||
@@ -320,13 +318,13 @@ integrate (Stack x l r) = reverse l ++ x : r
|
|||||||
|
|
||||||
-- |
|
-- |
|
||||||
-- /O(n)/ Flatten a possibly empty stack into a list.
|
-- /O(n)/ Flatten a possibly empty stack into a list.
|
||||||
integrate' :: StackOrNot a -> [a]
|
integrate' :: Maybe (Stack a) -> [a]
|
||||||
integrate' = maybe [] integrate
|
integrate' = maybe [] integrate
|
||||||
|
|
||||||
-- |
|
-- |
|
||||||
-- /O(n)/. Texture a list.
|
-- /O(n)/. Texture a list.
|
||||||
--
|
--
|
||||||
differentiate :: [a] -> StackOrNot a
|
differentiate :: [a] -> Maybe (Stack a)
|
||||||
differentiate [] = Nothing
|
differentiate [] = Nothing
|
||||||
differentiate (x:xs) = Just $ Stack x [] xs
|
differentiate (x:xs) = Just $ Stack x [] xs
|
||||||
|
|
||||||
@@ -334,7 +332,7 @@ differentiate (x:xs) = Just $ Stack x [] xs
|
|||||||
-- /O(n)/. 'filter p s' returns the elements of 's' such that 'p' evaluates to
|
-- /O(n)/. 'filter p s' returns the elements of 's' such that 'p' evaluates to
|
||||||
-- True. Order is preserved, and focus moves as described for 'delete'.
|
-- True. Order is preserved, and focus moves as described for 'delete'.
|
||||||
--
|
--
|
||||||
filter :: (a -> Bool) -> Stack a -> StackOrNot a
|
filter :: (a -> Bool) -> Stack a -> Maybe (Stack a)
|
||||||
filter p (Stack f ls rs) = case L.filter p (f:rs) of
|
filter p (Stack f ls rs) = case L.filter p (f:rs) of
|
||||||
f':rs' -> Just $ Stack f' (L.filter p ls) rs' -- maybe move focus down
|
f':rs' -> Just $ Stack f' (L.filter p ls) rs' -- maybe move focus down
|
||||||
[] -> case L.filter p ls of -- filter back up
|
[] -> case L.filter p ls of -- filter back up
|
||||||
|
@@ -204,7 +204,7 @@ instance ReadableLayout a => LayoutClass Layout a where
|
|||||||
instance Show (Layout a) where show (Layout l) = show l
|
instance Show (Layout a) where show (Layout l) = show l
|
||||||
|
|
||||||
-- | This calls doLayout if there are any windows to be laid out.
|
-- | This calls doLayout if there are any windows to be laid out.
|
||||||
runLayout :: LayoutClass l a => l a -> Rectangle -> StackOrNot a -> X ([(a, Rectangle)], Maybe (l a))
|
runLayout :: LayoutClass l a => l a -> Rectangle -> Maybe (Stack a) -> X ([(a, Rectangle)], Maybe (l a))
|
||||||
runLayout l r = maybe (return ([], Nothing)) (doLayout l r)
|
runLayout l r = maybe (return ([], Nothing)) (doLayout l r)
|
||||||
|
|
||||||
-- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/,
|
-- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/,
|
||||||
|
Reference in New Issue
Block a user