xmonad-0.17.1.9: A tiling window manager
Copyright(c) Don Stewart 2007
LicenseBSD3-style (see LICENSE)
Maintainerdons@galois.com
Stabilityexperimental
Portabilityportable, Haskell 98
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.StackSet

Description

 
Synopsis

Introduction

The StackSet data type encodes a window manager abstraction. The window manager is a set of virtual workspaces. On each workspace is a stack of windows. A given workspace is always current, and a given window on each workspace has focus. The focused window on the current workspace is the one which will take user input. It can be visualised as follows:

Workspace  { 0*}   { 1 }   { 2 }   { 3 }   { 4 }

Windows    [1      []      [3*     [6*]    []
           ,2*]            ,4
                           ,5]

Note that workspaces are indexed from 0, windows are numbered uniquely. A * indicates the window on each workspace that has focus, and which workspace is current.

The Zipper

We encode all the focus tracking directly in the data structure, with a zipper:

A Zipper is essentially an updateable and yet pure functional cursor into a data structure. Zipper is also a delimited continuation reified as a data structure.

The Zipper lets us replace an item deep in a complex data structure, e.g., a tree or a term, without a mutation. The resulting data structure will share as much of its components with the old structure as possible.

Oleg Kiselyov, 27 Apr 2005, haskell@, "Zipper as a delimited continuation"

We use the zipper to keep track of the focused workspace and the focused window on each workspace, allowing us to have correct focus by construction. We closely follow Huet's original implementation:

G. Huet, Functional Pearl: The Zipper; 1997, J. Functional Programming 75(5):549–554

and

R. Hinze and J. Jeuring, Functional Pearl: Weaving a Web

and Conor McBride's zipper differentiation paper. Another good reference is: The Zipper, Haskell wikibook

Xinerama support

Xinerama in X11 lets us view multiple virtual workspaces simultaneously. While only one will ever be in focus (i.e. will receive keyboard events), other workspaces may be passively viewable. We thus need to track which virtual workspaces are associated (viewed) on which physical screens. To keep track of this, StackSet keeps separate lists of visible but non-focused workspaces, and non-visible workspaces.

Master and Focus

Each stack tracks a focused item, and for tiling purposes also tracks a master position. The connection between master and focus needs to be well defined, particularly in relation to insert and delete.

data StackSet i l a sid sd Source #

A cursor into a non-empty list of workspaces.

We puncture the workspace list, producing a hole in the structure used to track the currently focused workspace. The two other lists that are produced are used to track those workspaces visible as Xinerama screens, and those workspaces not visible anywhere.

Constructors

StackSet 

Fields

Instances

Instances details
(Read i, Read l, Read sid, Read sd, Read a, Ord a) => Read (StackSet i l a sid sd) Source # 
Instance details

Defined in XMonad.StackSet

Methods

readsPrec :: Int -> ReadS (StackSet i l a sid sd) #

readList :: ReadS [StackSet i l a sid sd] #

readPrec :: ReadPrec (StackSet i l a sid sd) #

readListPrec :: ReadPrec [StackSet i l a sid sd] #

(Show i, Show l, Show sid, Show sd, Show a) => Show (StackSet i l a sid sd) Source # 
Instance details

Defined in XMonad.StackSet

Methods

showsPrec :: Int -> StackSet i l a sid sd -> ShowS #

show :: StackSet i l a sid sd -> String #

showList :: [StackSet i l a sid sd] -> ShowS #

(Eq i, Eq l, Eq sid, Eq sd, Eq a) => Eq (StackSet i l a sid sd) Source # 
Instance details

Defined in XMonad.StackSet

Methods

(==) :: StackSet i l a sid sd -> StackSet i l a sid sd -> Bool #

(/=) :: StackSet i l a sid sd -> StackSet i l a sid sd -> Bool #

data Workspace i l a Source #

A workspace is just a tag, a layout, and a stack.

Constructors

Workspace 

Fields

Instances

Instances details
(Read i, Read l, Read a) => Read (Workspace i l a) Source # 
Instance details

Defined in XMonad.StackSet

(Show i, Show l, Show a) => Show (Workspace i l a) Source # 
Instance details

Defined in XMonad.StackSet

Methods

showsPrec :: Int -> Workspace i l a -> ShowS #

show :: Workspace i l a -> String #

showList :: [Workspace i l a] -> ShowS #

(Eq i, Eq l, Eq a) => Eq (Workspace i l a) Source # 
Instance details

Defined in XMonad.StackSet

Methods

(==) :: Workspace i l a -> Workspace i l a -> Bool #

(/=) :: Workspace i l a -> Workspace i l a -> Bool #

data Screen i l a sid sd Source #

Visible workspaces, and their Xinerama screens.

Constructors

Screen 

Fields

Instances

Instances details
(Read i, Read l, Read a, Read sid, Read sd) => Read (Screen i l a sid sd) Source # 
Instance details

Defined in XMonad.StackSet

Methods

readsPrec :: Int -> ReadS (Screen i l a sid sd) #

readList :: ReadS [Screen i l a sid sd] #

readPrec :: ReadPrec (Screen i l a sid sd) #

readListPrec :: ReadPrec [Screen i l a sid sd] #

(Show i, Show l, Show a, Show sid, Show sd) => Show (Screen i l a sid sd) Source # 
Instance details

Defined in XMonad.StackSet

Methods

showsPrec :: Int -> Screen i l a sid sd -> ShowS #

show :: Screen i l a sid sd -> String #

showList :: [Screen i l a sid sd] -> ShowS #

(Eq i, Eq l, Eq a, Eq sid, Eq sd) => Eq (Screen i l a sid sd) Source # 
Instance details

Defined in XMonad.StackSet

Methods

(==) :: Screen i l a sid sd -> Screen i l a sid sd -> Bool #

(/=) :: Screen i l a sid sd -> Screen i l a sid sd -> Bool #

data Stack a Source #

A stack is a cursor onto a window list. The data structure tracks focus by construction, and the master window is by convention the top-most item. Focus operations will not reorder the list that results from flattening the cursor. The structure can be envisaged as:

   +-- master:  < '7' >
up |            [ '2' ]
   +---------   [ '3' ]
focus:          < '4' >
dn +----------- [ '8' ]

A Stack can be viewed as a list with a hole punched in it to make the focused position. Under the zipper/calculus view of such structures, it is the differentiation of a [a], and integrating it back has a natural implementation used in index.

Constructors

Stack 

Fields

Instances

Instances details
Foldable Stack Source # 
Instance details

Defined in XMonad.StackSet

Methods

fold :: Monoid m => Stack m -> m #

foldMap :: Monoid m => (a -> m) -> Stack a -> m #

foldMap' :: Monoid m => (a -> m) -> Stack a -> m #

foldr :: (a -> b -> b) -> b -> Stack a -> b #

foldr' :: (a -> b -> b) -> b -> Stack a -> b #

foldl :: (b -> a -> b) -> b -> Stack a -> b #

foldl' :: (b -> a -> b) -> b -> Stack a -> b #

foldr1 :: (a -> a -> a) -> Stack a -> a #

foldl1 :: (a -> a -> a) -> Stack a -> a #

toList :: Stack a -> [a] #

null :: Stack a -> Bool #

length :: Stack a -> Int #

elem :: Eq a => a -> Stack a -> Bool #

maximum :: Ord a => Stack a -> a #

minimum :: Ord a => Stack a -> a #

sum :: Num a => Stack a -> a #

product :: Num a => Stack a -> a #

Traversable Stack Source # 
Instance details

Defined in XMonad.StackSet

Methods

traverse :: Applicative f => (a -> f b) -> Stack a -> f (Stack b) #

sequenceA :: Applicative f => Stack (f a) -> f (Stack a) #

mapM :: Monad m => (a -> m b) -> Stack a -> m (Stack b) #

sequence :: Monad m => Stack (m a) -> m (Stack a) #

Functor Stack Source # 
Instance details

Defined in XMonad.StackSet

Methods

fmap :: (a -> b) -> Stack a -> Stack b #

(<$) :: a -> Stack b -> Stack a #

Read a => Read (Stack a) Source # 
Instance details

Defined in XMonad.StackSet

Show a => Show (Stack a) Source # 
Instance details

Defined in XMonad.StackSet

Methods

showsPrec :: Int -> Stack a -> ShowS #

show :: Stack a -> String #

showList :: [Stack a] -> ShowS #

Eq a => Eq (Stack a) Source # 
Instance details

Defined in XMonad.StackSet

Methods

(==) :: Stack a -> Stack a -> Bool #

(/=) :: Stack a -> Stack a -> Bool #

data RationalRect Source #

A structure for window geometries

Construction

 

new :: Integral s => l -> [i] -> [sd] -> StackSet i l a s sd Source #

O(n). Create a new stackset, of empty stacks, with given tags, with physical screens whose descriptions are given by m. The number of physical screens (length m) should be less than or equal to the number of workspace tags. The first workspace in the list will be current.

Xinerama: Virtual workspaces are assigned to physical screens, starting at 0.

view :: (Eq s, Eq i) => i -> StackSet i l a s sd -> StackSet i l a s sd Source #

O(w). Set focus to the workspace with index 'i'. If the index is out of range, return the original StackSet.

Xinerama: If the workspace is not visible on any Xinerama screen, it becomes the current screen. If it is in the visible list, it becomes current.

greedyView :: (Eq s, Eq i) => i -> StackSet i l a s sd -> StackSet i l a s sd Source #

Set focus to the given workspace. If that workspace does not exist in the stackset, the original workspace is returned. If that workspace is hidden, then display that workspace on the current screen, and move the current workspace to hidden. If that workspace is visible on another screen, the workspaces of the current screen and the other screen are swapped.

Xinerama operations

Xinerama in X11 lets us view multiple virtual workspaces simultaneously. While only one will ever be in focus (i.e. will receive keyboard events), other workspaces may be passively viewable. We thus need to track which virtual workspaces are associated (viewed) on which physical screens. To keep track of this, StackSet keeps separate lists of visible but non-focused workspaces, and non-visible workspaces.

lookupWorkspace :: Eq s => s -> StackSet i l a s sd -> Maybe i Source #

Find the tag of the workspace visible on Xinerama screen sc. Nothing if screen is out of bounds.

screens :: StackSet i l a s sd -> [Screen i l a s sd] Source #

Get a list of all screens in the StackSet.

workspaces :: StackSet i l a s sd -> [Workspace i l a] Source #

Get a list of all workspaces in the StackSet.

allWindows :: Eq a => StackSet i l a s sd -> [a] Source #

Get a list of all windows in the StackSet in no particular order

currentTag :: StackSet i l a s sd -> i Source #

Get the tag of the currently focused workspace.

Operations on the current stack

 

peek :: StackSet i l a s sd -> Maybe a Source #

O(1). Extract the focused element of the current stack. Return Just that element, or Nothing for an empty stack.

index :: StackSet i l a s sd -> [a] Source #

O(s). Extract the stack on the current workspace, as a list. The order of the stack is determined by the master window -- it will be the head of the list. The implementation is given by the natural integration of a one-hole list cursor, back to a list.

integrate :: Stack a -> [a] Source #

O(n). Flatten a Stack into a list.

integrate' :: Maybe (Stack a) -> [a] Source #

O(n). Flatten a possibly empty stack into a list.

differentiate :: [a] -> Maybe (Stack a) Source #

O(n). Turn a list into a possibly empty stack (i.e., a zipper): the first element of the list is current, and the rest of the list is down.

focusUp :: StackSet i l a s sd -> StackSet i l a s sd Source #

O(1), O(w) on the wrapping case. Move the window focus up the stack, wrapping if we reach the end. The wrapping should model a cycle on the current stack. The master window and window order are unaffected by movement of focus.

focusDown :: StackSet i l a s sd -> StackSet i l a s sd Source #

O(1), O(w) on the wrapping case. Like focusUp, but move the window focus down the stack.

focusUp' :: Stack a -> Stack a Source #

A variant of focusUp with the same asymptotics that works on a Stack rather than an entire StackSet.

focusDown' :: Stack a -> Stack a Source #

A variant of focusDown with the same asymptotics that works on a Stack rather than an entire StackSet.

focusMaster :: StackSet i l a s sd -> StackSet i l a s sd Source #

O(s). Set focus to the master window.

focusWindow :: (Eq s, Eq a, Eq i) => a -> StackSet i l a s sd -> StackSet i l a s sd Source #

O(1) on current window, O(n) in general. Focus the window w, and set its workspace as current.

tagMember :: Eq i => i -> StackSet i l a s sd -> Bool Source #

Is the given tag present in the StackSet?

renameTag :: Eq i => i -> i -> StackSet i l a s sd -> StackSet i l a s sd Source #

Rename a given tag if present in the StackSet.

ensureTags :: Eq i => l -> [i] -> StackSet i l a s sd -> StackSet i l a s sd Source #

Ensure that a given set of workspace tags is present by renaming existing workspaces and/or creating new hidden workspaces as necessary.

member :: Eq a => a -> StackSet i l a s sd -> Bool Source #

O(n). Is a window in the StackSet?

findTag :: Eq a => a -> StackSet i l a s sd -> Maybe i Source #

O(1) on current window, O(n) in general. Return Just the workspace tag of the given window, or Nothing if the window is not in the StackSet.

mapWorkspace :: (Workspace i l a -> Workspace i l a) -> StackSet i l a s sd -> StackSet i l a s sd Source #

Map a function on all the workspaces in the StackSet.

mapLayout :: (l -> l') -> StackSet i l a s sd -> StackSet i l' a s sd Source #

Map a function on all the layouts in the StackSet.

Modifying the stackset

 

insertUp :: Eq a => a -> StackSet i l a s sd -> StackSet i l a s sd Source #

O(n). (Complexity due to duplicate check). Insert a new element into the stack, above the currently focused element. The new element is given focus; the previously focused element is moved down.

If the element is already in the stackset, the original stackset is returned unmodified.

Semantics in Huet's paper is that insert doesn't move the cursor. However, we choose to insert above, and move the focus.

delete :: Ord a => a -> StackSet i l a s sd -> StackSet i l a s sd Source #

O(1) on current window, O(n) in general. Delete window w if it exists. There are 4 cases to consider:

  • delete on an Nothing workspace leaves it Nothing
  • otherwise, try to move focus to the down
  • otherwise, try to move focus to the up
  • otherwise, you've got an empty workspace, becomes Nothing

Behaviour with respect to the master:

  • deleting the master window resets it to the newly focused window
  • otherwise, delete doesn't affect the master.

delete' :: Eq a => a -> StackSet i l a s sd -> StackSet i l a s sd Source #

Only temporarily remove the window from the stack, thereby not destroying special information saved in the Stackset

filter :: (a -> Bool) -> Stack a -> Maybe (Stack a) Source #

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.

Setting the master window

 

swapUp :: StackSet i l a s sd -> StackSet i l a s sd Source #

O(1), O(w) on the wrapping case. Swap the upwards (left) neighbour in the stack ordering, wrapping if we reach the end. Much like for focusUp and focusDown, the wrapping model should cycle on the current stack.

swapDown :: StackSet i l a s sd -> StackSet i l a s sd Source #

O(1), O(w) on the wrapping case. Like swapUp, but for swapping the downwards (right) neighbour.

swapMaster :: StackSet i l a s sd -> StackSet i l a s sd Source #

O(s). Set the master window to the focused window. The old master window is swapped in the tiling order with the focused window. Focus stays with the item moved.

shiftMaster :: StackSet i l a s sd -> StackSet i l a s sd Source #

O(s). Set the master window to the focused window. The other windows are kept in order and shifted down on the stack, as if you just hit mod-shift-k a bunch of times. Focus stays with the item moved.

modify :: Maybe (Stack a) -> (Stack a -> Maybe (Stack a)) -> StackSet i l a s sd -> StackSet i l a s sd Source #

Apply a function, and a default value for Nothing, to modify the current stack.

modify' :: (Stack a -> Stack a) -> StackSet i l a s sd -> StackSet i l a s sd Source #

Apply a function to modify the current stack if it isn't empty, and we don't want to empty it.

float :: Ord a => a -> RationalRect -> StackSet i l a s sd -> StackSet i l a s sd Source #

Given a window, and its preferred rectangle, set it as floating A floating window should already be managed by the StackSet.

sink :: Ord a => a -> StackSet i l a s sd -> StackSet i l a s sd Source #

Clear the floating status of a window

Composite operations

 

shift :: (Ord a, Eq s, Eq i) => i -> StackSet i l a s sd -> StackSet i l a s sd Source #

O(w). shift. Move the focused element of the current stack to stack n, leaving it as the focused element on that stack. The item is inserted above the currently focused element on that workspace. The actual focused workspace doesn't change. If there is no element on the current stack, the original stackSet is returned.

shiftWin :: (Ord a, Eq s, Eq i) => i -> a -> StackSet i l a s sd -> StackSet i l a s sd Source #

O(n). shiftWin. Searches for the specified window w on all workspaces of the stackSet and moves it to stack n, leaving it as the focused element on that stack. The item is inserted above the currently focused element on that workspace. The actual focused workspace doesn't change. If the window is not found in the stackSet, the original stackSet is returned.

abort :: String -> a Source #

this function indicates to catch that an error is expected