mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
haddock compatibility
This commit is contained in:
parent
6365601c77
commit
e1885f27e1
24
Config.hs
24
Config.hs
@ -7,13 +7,13 @@
|
|||||||
-- Maintainer : dons@cse.unsw.edu.au
|
-- Maintainer : dons@cse.unsw.edu.au
|
||||||
-- Stability : stable
|
-- Stability : stable
|
||||||
-- Portability : portable
|
-- Portability : portable
|
||||||
--
|
--
|
||||||
------------------------------------------------------------------------
|
|
||||||
--
|
--
|
||||||
-- This module specifies configurable defaults for xmonad. If you change
|
-- This module specifies configurable defaults for xmonad. If you change
|
||||||
-- values here, be sure to recompile and restart (mod-q) xmonad,
|
-- values here, be sure to recompile and restart (mod-q) xmonad,
|
||||||
-- for the changes to take effect.
|
-- for the changes to take effect.
|
||||||
--
|
--
|
||||||
|
------------------------------------------------------------------------
|
||||||
|
|
||||||
module Config where
|
module Config where
|
||||||
|
|
||||||
@ -34,7 +34,7 @@ import Graphics.X11.Xlib
|
|||||||
workspaces :: Int
|
workspaces :: Int
|
||||||
workspaces = 9
|
workspaces = 9
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- modMask lets you specify which modkey you want to use. The default is
|
-- modMask lets you specify which modkey you want to use. The default is
|
||||||
-- mod1Mask ("left alt"). You may also consider using mod3Mask ("right
|
-- mod1Mask ("left alt"). You may also consider using mod3Mask ("right
|
||||||
-- alt"), which does not conflict with emacs keybindings. The "windows
|
-- alt"), which does not conflict with emacs keybindings. The "windows
|
||||||
@ -43,7 +43,7 @@ workspaces = 9
|
|||||||
modMask :: KeyMask
|
modMask :: KeyMask
|
||||||
modMask = mod1Mask
|
modMask = mod1Mask
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- Default offset of drawable screen boundaries from each physical screen.
|
-- Default offset of drawable screen boundaries from each physical screen.
|
||||||
-- Anything non-zero here will leave a gap of that many pixels on the
|
-- Anything non-zero here will leave a gap of that many pixels on the
|
||||||
-- given edge, on the that screen. A useful gap at top of screen for a
|
-- given edge, on the that screen. A useful gap at top of screen for a
|
||||||
@ -54,7 +54,7 @@ modMask = mod1Mask
|
|||||||
defaultGaps :: [(Int,Int,Int,Int)]
|
defaultGaps :: [(Int,Int,Int,Int)]
|
||||||
defaultGaps = [(0,0,0,0)] -- 15 for default dzen
|
defaultGaps = [(0,0,0,0)] -- 15 for default dzen
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- numlock handling:
|
-- numlock handling:
|
||||||
--
|
--
|
||||||
-- The mask for the numlock key. You may need to change this on some systems.
|
-- The mask for the numlock key. You may need to change this on some systems.
|
||||||
@ -68,20 +68,20 @@ defaultGaps = [(0,0,0,0)] -- 15 for default dzen
|
|||||||
numlockMask :: KeyMask
|
numlockMask :: KeyMask
|
||||||
numlockMask = mod2Mask
|
numlockMask = mod2Mask
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- Border colors for unfocused and focused windows, respectively.
|
-- Border colors for unfocused and focused windows, respectively.
|
||||||
--
|
--
|
||||||
normalBorderColor, focusedBorderColor :: String
|
normalBorderColor, focusedBorderColor :: String
|
||||||
normalBorderColor = "#dddddd"
|
normalBorderColor = "#dddddd"
|
||||||
focusedBorderColor = "#ff0000"
|
focusedBorderColor = "#ff0000"
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- Width of the window border in pixels
|
-- Width of the window border in pixels
|
||||||
--
|
--
|
||||||
borderWidth :: Dimension
|
borderWidth :: Dimension
|
||||||
borderWidth = 1
|
borderWidth = 1
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- The default set of tiling algorithms
|
-- The default set of tiling algorithms
|
||||||
--
|
--
|
||||||
defaultLayouts :: [Layout]
|
defaultLayouts :: [Layout]
|
||||||
@ -99,7 +99,7 @@ defaultLayouts = [ tiled , mirror tiled , full ]
|
|||||||
-- Percent of screen to increment by when resizing panes
|
-- Percent of screen to increment by when resizing panes
|
||||||
delta = 3%100
|
delta = 3%100
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- Perform an arbitrary action on each state change.
|
-- Perform an arbitrary action on each state change.
|
||||||
-- Examples include:
|
-- Examples include:
|
||||||
-- * do nothing
|
-- * do nothing
|
||||||
@ -108,7 +108,7 @@ defaultLayouts = [ tiled , mirror tiled , full ]
|
|||||||
logHook :: X ()
|
logHook :: X ()
|
||||||
logHook = return ()
|
logHook = return ()
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- The key bindings list.
|
-- The key bindings list.
|
||||||
--
|
--
|
||||||
-- The unusual comment format is used to generate the documentation
|
-- The unusual comment format is used to generate the documentation
|
||||||
@ -167,7 +167,7 @@ keys = M.fromList $
|
|||||||
| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
|
| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
|
||||||
, (f, m) <- [(view, 0), (shift, shiftMask)]]
|
, (f, m) <- [(view, 0), (shift, shiftMask)]]
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- default actions bound to mouse events
|
-- default actions bound to mouse events
|
||||||
--
|
--
|
||||||
mouseBindings :: M.Map (KeyMask, Button) (Window -> X ())
|
mouseBindings :: M.Map (KeyMask, Button) (Window -> X ())
|
||||||
|
9
Main.hs
9
Main.hs
@ -8,10 +8,11 @@
|
|||||||
-- Stability : unstable
|
-- Stability : unstable
|
||||||
-- Portability : not portable, uses mtl, X11, posix
|
-- Portability : not portable, uses mtl, X11, posix
|
||||||
--
|
--
|
||||||
-----------------------------------------------------------------------------
|
|
||||||
--
|
|
||||||
-- xmonad, a minimalist, tiling window manager for X11
|
-- xmonad, a minimalist, tiling window manager for X11
|
||||||
--
|
--
|
||||||
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
|
module Main where
|
||||||
|
|
||||||
import Data.Bits
|
import Data.Bits
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
@ -34,7 +35,7 @@ import Operations
|
|||||||
|
|
||||||
import System.IO
|
import System.IO
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- The main entry point
|
-- The main entry point
|
||||||
--
|
--
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
|
@ -1,5 +1,5 @@
|
|||||||
{-# OPTIONS -fglasgow-exts #-}
|
{-# OPTIONS -fglasgow-exts #-}
|
||||||
-- ^^ deriving Typeable
|
-- \^^ deriving Typeable
|
||||||
-- --------------------------------------------------------------------------
|
-- --------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : Operations.hs
|
-- Module : Operations.hs
|
||||||
@ -10,6 +10,8 @@
|
|||||||
-- Stability : unstable
|
-- Stability : unstable
|
||||||
-- Portability : not portable, Typeable deriving, mtl, posix
|
-- Portability : not portable, Typeable deriving, mtl, posix
|
||||||
--
|
--
|
||||||
|
-- Operations.
|
||||||
|
--
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
module Operations where
|
module Operations where
|
||||||
@ -35,9 +37,9 @@ import Graphics.X11.Xinerama (getScreenInfo)
|
|||||||
import Graphics.X11.Xlib.Extras
|
import Graphics.X11.Xlib.Extras
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
|
-- |
|
||||||
-- Window manager operations
|
-- Window manager operations
|
||||||
|
-- manage. Add a new window to be managed in the current workspace.
|
||||||
-- | manage. Add a new window to be managed in the current workspace.
|
|
||||||
-- Bring it into focus.
|
-- Bring it into focus.
|
||||||
--
|
--
|
||||||
-- Whether the window is already managed, or not, it is mapped, has its
|
-- Whether the window is already managed, or not, it is mapped, has its
|
||||||
@ -54,7 +56,7 @@ manage w = withDisplay $ \d -> do
|
|||||||
isTransient <- isJust `liftM` io (getTransientForHint d w)
|
isTransient <- isJust `liftM` io (getTransientForHint d w)
|
||||||
if isTransient
|
if isTransient
|
||||||
then do modify $ \s -> s { windowset = W.insertUp w (windowset s) }
|
then do modify $ \s -> s { windowset = W.insertUp w (windowset s) }
|
||||||
float w -- ^^ now go the refresh.
|
float w -- \^^ now go the refresh.
|
||||||
else windows $ W.insertUp w
|
else windows $ W.insertUp w
|
||||||
|
|
||||||
-- | unmanage. A window no longer exists, remove it from the window
|
-- | unmanage. A window no longer exists, remove it from the window
|
||||||
@ -447,12 +449,12 @@ withFocused f = withWindowSet $ \w -> whenJust (W.peek w) f
|
|||||||
isClient :: Window -> X Bool
|
isClient :: Window -> X Bool
|
||||||
isClient w = withWindowSet $ return . W.member w
|
isClient w = withWindowSet $ return . W.member w
|
||||||
|
|
||||||
-- | Combinations of extra modifier masks we need to grab keys/buttons for.
|
-- | Combinations of extra modifier masks we need to grab keys\/buttons for.
|
||||||
-- (numlock and capslock)
|
-- (numlock and capslock)
|
||||||
extraModifiers :: [KeyMask]
|
extraModifiers :: [KeyMask]
|
||||||
extraModifiers = [0, numlockMask, lockMask, numlockMask .|. lockMask ]
|
extraModifiers = [0, numlockMask, lockMask, numlockMask .|. lockMask ]
|
||||||
|
|
||||||
-- | Strip numlock/capslock from a mask
|
-- | Strip numlock\/capslock from a mask
|
||||||
cleanMask :: KeyMask -> KeyMask
|
cleanMask :: KeyMask -> KeyMask
|
||||||
cleanMask = (complement (numlockMask .|. lockMask) .&.)
|
cleanMask = (complement (numlockMask .|. lockMask) .&.)
|
||||||
|
|
||||||
|
149
StackSet.hs
149
StackSet.hs
@ -8,9 +8,7 @@
|
|||||||
-- Stability : experimental
|
-- Stability : experimental
|
||||||
-- Portability : portable, Haskell 98
|
-- Portability : portable, Haskell 98
|
||||||
--
|
--
|
||||||
-----------------------------------------------------------------------------
|
-- Introduction
|
||||||
--
|
|
||||||
-- ** Introduction
|
|
||||||
--
|
--
|
||||||
-- The 'StackSet' data type encodes a window manager abstraction. The
|
-- The 'StackSet' data type encodes a window manager abstraction. The
|
||||||
-- window manager is a set of virtual workspaces. On each workspace is a
|
-- window manager is a set of virtual workspaces. On each workspace is a
|
||||||
@ -18,18 +16,18 @@
|
|||||||
-- window on each workspace has focus. The focused window on the current
|
-- 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
|
-- workspace is the one which will take user input. It can be visualised
|
||||||
-- as follows:
|
-- as follows:
|
||||||
--
|
--
|
||||||
-- Workspace { 0*} { 1 } { 2 } { 3 } { 4 }
|
-- > Workspace { 0*} { 1 } { 2 } { 3 } { 4 }
|
||||||
--
|
-- >
|
||||||
-- Windows [1 [] [3* [6*] []
|
-- > Windows [1 [] [3* [6*] []
|
||||||
-- ,2*] ,4
|
-- > ,2*] ,4
|
||||||
-- ,5]
|
-- > ,5]
|
||||||
--
|
--
|
||||||
-- Note that workspaces are indexed from 0, windows are numbered
|
-- Note that workspaces are indexed from 0, windows are numbered
|
||||||
-- uniquely. A '*' indicates the window on each workspace that has
|
-- uniquely. A '*' indicates the window on each workspace that has
|
||||||
-- focus, and which workspace is current.
|
-- focus, and which workspace is current.
|
||||||
--
|
--
|
||||||
-- ** Zipper
|
-- Zipper
|
||||||
--
|
--
|
||||||
-- We encode all the focus tracking directly in the data structure, with a 'zipper':
|
-- We encode all the focus tracking directly in the data structure, with a 'zipper':
|
||||||
--
|
--
|
||||||
@ -42,7 +40,7 @@
|
|||||||
-- resulting data structure will share as much of its components with
|
-- resulting data structure will share as much of its components with
|
||||||
-- the old structure as possible.
|
-- the old structure as possible.
|
||||||
--
|
--
|
||||||
-- Oleg Kiselyov, 27 Apr 2005, haskell@, "Zipper as a delimited continuation"
|
-- Oleg Kiselyov, 27 Apr 2005, haskell\@, "Zipper as a delimited continuation"
|
||||||
--
|
--
|
||||||
-- We use the zipper to keep track of the focused workspace and the
|
-- We use the zipper to keep track of the focused workspace and the
|
||||||
-- focused window on each workspace, allowing us to have correct focus
|
-- focused window on each workspace, allowing us to have correct focus
|
||||||
@ -58,7 +56,7 @@
|
|||||||
--
|
--
|
||||||
-- The Zipper, Haskell wikibook
|
-- The Zipper, Haskell wikibook
|
||||||
--
|
--
|
||||||
-- ** Xinerama support:
|
-- Xinerama support:
|
||||||
--
|
--
|
||||||
-- Xinerama in X11 lets us view multiple virtual workspaces
|
-- Xinerama in X11 lets us view multiple virtual workspaces
|
||||||
-- simultaneously. While only one will ever be in focus (i.e. will
|
-- simultaneously. While only one will ever be in focus (i.e. will
|
||||||
@ -67,13 +65,14 @@
|
|||||||
-- (viewed) on which physical screens. We use a simple Map Workspace
|
-- (viewed) on which physical screens. We use a simple Map Workspace
|
||||||
-- Screen for this.
|
-- Screen for this.
|
||||||
--
|
--
|
||||||
-- ** Master and Focus
|
-- Master and Focus
|
||||||
--
|
--
|
||||||
-- Each stack tracks a focused item, and for tiling purposes also tracks
|
-- Each stack tracks a focused item, and for tiling purposes also tracks
|
||||||
-- a 'master' position. The connection between 'master' and 'focus'
|
-- a 'master' position. The connection between 'master' and 'focus'
|
||||||
-- needs to be well defined. Particular in relation to 'insert' and
|
-- needs to be well defined. Particular in relation to 'insert' and
|
||||||
-- 'delete'.
|
-- 'delete'.
|
||||||
--
|
--
|
||||||
|
|
||||||
module StackSet (
|
module StackSet (
|
||||||
StackSet(..), Workspace(..), Screen(..), Stack(..), RationalRect(..),
|
StackSet(..), Workspace(..), Screen(..), Stack(..), RationalRect(..),
|
||||||
new, view, lookupWorkspace, peek, index, integrate, focusUp, focusDown,
|
new, view, lookupWorkspace, peek, index, integrate, focusUp, focusDown,
|
||||||
@ -85,45 +84,60 @@ import Data.Maybe (listToMaybe)
|
|||||||
import qualified Data.List as L (delete,find,genericSplitAt)
|
import qualified Data.List as L (delete,find,genericSplitAt)
|
||||||
import qualified Data.Map as M (Map,insert,delete,empty)
|
import qualified Data.Map as M (Map,insert,delete,empty)
|
||||||
|
|
||||||
|
-- |
|
||||||
-- API changes from xmonad 0.1:
|
-- API changes from xmonad 0.1:
|
||||||
-- StackSet constructor arguments changed. StackSet workspace window screen
|
-- StackSet constructor arguments changed. StackSet workspace window screen
|
||||||
-- new, -- was: empty
|
--
|
||||||
-- view,
|
-- * new, -- was: empty
|
||||||
-- index,
|
--
|
||||||
-- peek, -- was: peek/peekStack
|
-- * view,
|
||||||
-- focusUp, focusDown, -- was: rotate
|
--
|
||||||
-- swapUp, swapDown
|
-- * index,
|
||||||
-- focus -- was: raiseFocus
|
--
|
||||||
-- insertUp, -- was: insert/push
|
-- * peek, -- was: peek\/peekStack
|
||||||
-- delete,
|
--
|
||||||
-- swapMaster, -- was: promote/swap
|
-- * focusUp, focusDown, -- was: rotate
|
||||||
-- member,
|
--
|
||||||
-- shift,
|
-- * swapUp, swapDown
|
||||||
-- lookupWorkspace, -- was: workspace
|
--
|
||||||
-- visibleWorkspaces -- gone.
|
-- * focus -- was: raiseFocus
|
||||||
|
--
|
||||||
|
-- * insertUp, -- was: insert\/push
|
||||||
|
--
|
||||||
|
-- * delete,
|
||||||
|
--
|
||||||
|
-- * swapMaster, -- was: promote\/swap
|
||||||
|
--
|
||||||
|
-- * member,
|
||||||
|
--
|
||||||
|
-- * shift,
|
||||||
|
--
|
||||||
|
-- * lookupWorkspace, -- was: workspace
|
||||||
|
--
|
||||||
|
-- * visibleWorkspaces -- gone.
|
||||||
--
|
--
|
||||||
------------------------------------------------------------------------
|
------------------------------------------------------------------------
|
||||||
|
-- |
|
||||||
--
|
|
||||||
-- A cursor into a non-empty list of workspaces.
|
-- A cursor into a non-empty list of workspaces.
|
||||||
|
--
|
||||||
-- We puncture the workspace list, producing a hole in the structure
|
-- We puncture the workspace list, producing a hole in the structure
|
||||||
-- used to track the currently focused workspace. The two other lists
|
-- used to track the currently focused workspace. The two other lists
|
||||||
-- that are produced are used to track those workspaces visible as
|
-- that are produced are used to track those workspaces visible as
|
||||||
-- Xinerama screens, and those workspaces not visible anywhere.
|
-- Xinerama screens, and those workspaces not visible anywhere.
|
||||||
--
|
|
||||||
data StackSet i a sid =
|
data StackSet i a sid =
|
||||||
StackSet { size :: !i -- number of workspaces
|
StackSet { size :: !i -- ^ number of workspaces
|
||||||
, current :: !(Screen i a sid) -- currently focused workspace
|
, current :: !(Screen i a sid) -- ^ currently focused workspace
|
||||||
, visible :: [Screen i a sid] -- non-focused workspaces, visible in xinerama
|
, visible :: [Screen i a sid] -- ^ non-focused workspaces, visible in xinerama
|
||||||
, hidden :: [Workspace i a] -- workspaces not visible anywhere
|
, hidden :: [Workspace i a] -- ^ workspaces not visible anywhere
|
||||||
, floating :: M.Map a RationalRect -- floating windows
|
, floating :: M.Map a RationalRect -- ^ floating windows
|
||||||
} deriving (Show, Read, Eq)
|
} deriving (Show, Read, Eq)
|
||||||
|
|
||||||
-- Visible workspaces, and their Xinerama screens.
|
-- | Visible workspaces, and their Xinerama screens.
|
||||||
data Screen i a sid = Screen { workspace :: !(Workspace i a), screen :: !sid }
|
data Screen i a sid = Screen { workspace :: !(Workspace i a), screen :: !sid }
|
||||||
deriving (Show, Read, Eq)
|
deriving (Show, Read, Eq)
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- 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 a = Workspace { tag :: !i, stack :: Stack a }
|
data Workspace i a = Workspace { tag :: !i, stack :: Stack a }
|
||||||
@ -132,21 +146,21 @@ data Workspace i a = Workspace { tag :: !i, stack :: Stack a }
|
|||||||
data RationalRect = RationalRect Rational Rational Rational Rational
|
data RationalRect = RationalRect Rational Rational Rational Rational
|
||||||
deriving (Show, Read, Eq)
|
deriving (Show, Read, Eq)
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- A stack is a cursor onto a (possibly empty) window list.
|
-- A stack is a cursor onto a (possibly empty) window list.
|
||||||
-- The data structure tracks focus by construction, and
|
-- The data structure tracks focus by construction, and
|
||||||
-- the master window is by convention the top-most item.
|
-- the master window is by convention the top-most item.
|
||||||
-- Focus operations will not reorder the list that results from
|
-- Focus operations will not reorder the list that results from
|
||||||
-- flattening the cursor. The structure can be envisaged as:
|
-- flattening the cursor. The structure can be envisaged as:
|
||||||
--
|
--
|
||||||
-- +-- master: < '7' >
|
-- > +-- master: < '7' >
|
||||||
-- up | [ '2' ]
|
-- > up | [ '2' ]
|
||||||
-- +--------- [ '3' ]
|
-- > +--------- [ '3' ]
|
||||||
-- focus: < '4' >
|
-- > focus: < '4' >
|
||||||
-- dn +----------- [ '8' ]
|
-- > dn +----------- [ '8' ]
|
||||||
--
|
--
|
||||||
-- A 'Stack' can be viewed as a list with a hole punched in it to make
|
-- 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
|
-- the focused position. Under the zipper\/calculus view of such
|
||||||
-- 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'.
|
||||||
--
|
--
|
||||||
@ -162,7 +176,7 @@ abort :: String -> a
|
|||||||
abort x = error $ "xmonad: StackSet: " ++ x
|
abort x = error $ "xmonad: StackSet: " ++ x
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Construction
|
-- | Construction
|
||||||
|
|
||||||
-- | /O(n)/. Create a new stackset, of empty stacks, of size 'n', with
|
-- | /O(n)/. Create a new stackset, of empty stacks, of size 'n', with
|
||||||
-- 'm' physical screens. 'm' should be less than or equal to 'n'.
|
-- 'm' physical screens. 'm' should be less than or equal to 'n'.
|
||||||
@ -178,14 +192,14 @@ new n m | n > 0 && m > 0 = StackSet n cur visi unseen M.empty
|
|||||||
(cur:visi) = [ Screen i s | (i,s) <- zip seen [0..] ]
|
(cur:visi) = [ Screen i s | (i,s) <- zip seen [0..] ]
|
||||||
-- now zip up visibles with their screen id
|
-- now zip up visibles with their screen id
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- /O(w)/. Set focus to the workspace with index 'i'.
|
-- /O(w)/. Set focus to the workspace with index \'i\'.
|
||||||
-- If the index is out of range, return the original StackSet.
|
-- If the index is out of range, return the original StackSet.
|
||||||
--
|
--
|
||||||
-- Xinerama: If the workspace is not visible on any Xinerama screen, it
|
-- 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
|
-- becomes the current screen. If it is in the visible list, it becomes
|
||||||
-- current.
|
-- current.
|
||||||
--
|
|
||||||
view :: (Eq a, Eq s, Integral i) => i -> StackSet i a s -> StackSet i a s
|
view :: (Eq a, Eq s, Integral i) => i -> StackSet i a s -> StackSet i a s
|
||||||
view i s
|
view i s
|
||||||
| i < 0 && i >= size s || i == tag (workspace (current s)) = s -- out of bounds or current
|
| i < 0 && i >= size s || i == tag (workspace (current s)) = s -- out of bounds or current
|
||||||
@ -205,7 +219,7 @@ view i s
|
|||||||
-- workspace tags defined in 'new'
|
-- workspace tags defined in 'new'
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Xinerama operations
|
-- | Xinerama operations
|
||||||
|
|
||||||
-- | Find the tag of the workspace visible on Xinerama screen 'sc'.
|
-- | Find the tag of the workspace visible on Xinerama screen 'sc'.
|
||||||
-- Nothing if screen is out of bounds.
|
-- Nothing if screen is out of bounds.
|
||||||
@ -215,7 +229,7 @@ lookupWorkspace sc w = listToMaybe [ tag i | Screen i s <- current w : visible w
|
|||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Operations on the current stack
|
-- Operations on the current stack
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- The 'with' function takes a default value, a function, and a
|
-- The 'with' function takes a default value, a function, and a
|
||||||
-- StackSet. If the current stack is Empty, 'with' returns the
|
-- StackSet. If the current stack is Empty, 'with' returns the
|
||||||
-- default value. Otherwise, it applies the function to the stack,
|
-- default value. Otherwise, it applies the function to the stack,
|
||||||
@ -226,28 +240,28 @@ with dflt f s = case stack (workspace (current s)) of Empty -> dflt; v -> f v
|
|||||||
-- TODO: ndm: a 'catch' proof here that 'f' only gets Node
|
-- TODO: ndm: a 'catch' proof here that 'f' only gets Node
|
||||||
-- constructors, hence all 'f's are safe below?
|
-- constructors, hence all 'f's are safe below?
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- Apply a function, and a default value for Empty, to modify the current stack.
|
-- Apply a function, and a default value for Empty, to modify the current stack.
|
||||||
--
|
--
|
||||||
modify :: Stack a -> (Stack a -> Stack a) -> StackSet i a s -> StackSet i a s
|
modify :: Stack a -> (Stack a -> Stack a) -> StackSet i a s -> StackSet i a s
|
||||||
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 }}}
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- /O(1)/. Extract the focused element of the current stack.
|
-- /O(1)/. Extract the focused element of the current stack.
|
||||||
-- Return Just that element, or Nothing for an empty stack.
|
-- Return Just that element, or Nothing for an empty stack.
|
||||||
--
|
--
|
||||||
peek :: StackSet i a s -> Maybe a
|
peek :: StackSet i a s -> Maybe a
|
||||||
peek = with Nothing (return . focus)
|
peek = with Nothing (return . focus)
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- /O(n)/. Flatten a Stack into a list.
|
-- /O(n)/. Flatten a Stack into a list.
|
||||||
--
|
--
|
||||||
integrate :: Stack a -> [a]
|
integrate :: Stack a -> [a]
|
||||||
integrate Empty = []
|
integrate Empty = []
|
||||||
integrate (Node x l r) = reverse l ++ x : r
|
integrate (Node x l r) = reverse l ++ x : r
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- /O(s)/. Extract the stack on the current workspace, as a list.
|
-- /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 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
|
-- the head of the list. The implementation is given by the natural
|
||||||
@ -258,7 +272,7 @@ index = with [] integrate
|
|||||||
|
|
||||||
-- let is = t : r ++ reverse l in take (length is) (dropWhile (/= m) (cycle is))
|
-- let is = t : r ++ reverse l in take (length is) (dropWhile (/= m) (cycle is))
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- /O(1), O(w) on the wrapping case/.
|
-- /O(1), O(w) on the wrapping case/.
|
||||||
--
|
--
|
||||||
-- focusUp, focusDown. Move the window focus up or down the stack,
|
-- focusUp, focusDown. Move the window focus up or down the stack,
|
||||||
@ -284,7 +298,7 @@ focusUp' (Node t [] rs) = Node x xs [] where (x:xs) = reverse (t:rs)
|
|||||||
swapUp' (Node t (l:ls) rs) = Node t ls (l:rs)
|
swapUp' (Node t (l:ls) rs) = Node t ls (l:rs)
|
||||||
swapUp' (Node t [] rs) = Node t (reverse rs) []
|
swapUp' (Node t [] rs) = Node t (reverse rs) []
|
||||||
|
|
||||||
-- reverse a stack: up becomes down and down becomes up.
|
-- | reverse a stack: up becomes down and down becomes up.
|
||||||
reverseStack :: Stack a -> Stack a
|
reverseStack :: Stack a -> Stack a
|
||||||
reverseStack (Node t ls rs) = Node t rs ls
|
reverseStack (Node t ls rs) = Node t rs ls
|
||||||
reverseStack x = x
|
reverseStack x = x
|
||||||
@ -299,7 +313,7 @@ focusWindow w s | Just w == peek s = s
|
|||||||
n <- findIndex w s
|
n <- findIndex w s
|
||||||
return $ until ((Just w ==) . peek) focusUp (view n s)
|
return $ until ((Just w ==) . peek) focusUp (view n s)
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- Finding if a window is in the stackset is a little tedious. We could
|
-- Finding if a window is in the stackset is a little tedious. We could
|
||||||
-- keep a cache :: Map a i, but with more bookkeeping.
|
-- keep a cache :: Map a i, but with more bookkeeping.
|
||||||
--
|
--
|
||||||
@ -318,9 +332,9 @@ findIndex a s = listToMaybe
|
|||||||
has x (Node t l r) = x `elem` (t : l ++ r)
|
has x (Node t l r) = x `elem` (t : l ++ r)
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Modifying the stackset
|
-- | Modifying the stackset
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- /O(n)/. (Complexity due to duplicate check). Insert a new element into
|
-- /O(n)/. (Complexity due to duplicate check). Insert a new element into
|
||||||
-- the stack, above the currently focused element.
|
-- the stack, above the currently focused element.
|
||||||
--
|
--
|
||||||
@ -343,7 +357,7 @@ insertUp a s = if member a s then s else insert
|
|||||||
-- Old semantics, from Huet.
|
-- Old semantics, from Huet.
|
||||||
-- > w { down = a : down w }
|
-- > w { down = a : down w }
|
||||||
|
|
||||||
--
|
-- |
|
||||||
-- /O(1) on current window, O(n) in general/. Delete window 'w' if it exists.
|
-- /O(1) on current window, O(n) in general/. Delete window 'w' if it exists.
|
||||||
-- There are 4 cases to consider:
|
-- There are 4 cases to consider:
|
||||||
--
|
--
|
||||||
@ -385,8 +399,8 @@ sink :: Ord a => a -> StackSet i a s -> StackSet i a s
|
|||||||
sink w s = s { floating = M.delete w (floating s) }
|
sink w s = s { floating = M.delete w (floating s) }
|
||||||
|
|
||||||
------------------------------------------------------------------------
|
------------------------------------------------------------------------
|
||||||
-- Setting the master window
|
-- | Setting the master window
|
||||||
|
--
|
||||||
-- /O(s)/. Set the master window to the focused window.
|
-- /O(s)/. Set the master window to the focused window.
|
||||||
-- The old master window is swapped in the tiling order with the focused window.
|
-- The old master window is swapped in the tiling order with the focused window.
|
||||||
-- Focus stays with the item moved.
|
-- Focus stays with the item moved.
|
||||||
@ -395,12 +409,11 @@ swapMaster = modify Empty $ \c -> case c of
|
|||||||
Node _ [] _ -> c -- already master.
|
Node _ [] _ -> c -- already master.
|
||||||
Node t ls rs -> Node t [] (ys ++ x : rs) where (x:ys) = reverse ls
|
Node t ls rs -> Node t [] (ys ++ x : rs) where (x:ys) = reverse ls
|
||||||
|
|
||||||
-- natural! keep focus, move current to the top, move top to current.
|
-- natural! keep focus, move current to the top, move top to current.
|
||||||
|
--
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Composite operations
|
-- | Composite operations
|
||||||
--
|
--
|
||||||
|
|
||||||
-- /O(w)/. shift. Move the focused element of the current stack to stack
|
-- /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
|
-- 'n', leaving it as the focused element on that stack. The item is
|
||||||
-- inserted above the currently focused element on that workspace. --
|
-- inserted above the currently focused element on that workspace. --
|
||||||
@ -411,4 +424,4 @@ shift :: (Ord a, Eq s, Integral i) => i -> StackSet i a s -> StackSet i a s
|
|||||||
shift n s = if and [n >= 0,n < size s,n /= tag (workspace (current s))]
|
shift n s = if and [n >= 0,n < size s,n /= tag (workspace (current s))]
|
||||||
then maybe s go (peek s) else s
|
then maybe s go (peek s) else s
|
||||||
where go w = foldr ($) s [view (tag (workspace (current s))),insertUp w,view n,delete w]
|
where go w = foldr ($) s [view (tag (workspace (current s))),insertUp w,view n,delete w]
|
||||||
-- ^^ poor man's state monad :-)
|
-- ^^ poor man's state monad :-)
|
||||||
|
@ -9,11 +9,10 @@
|
|||||||
-- Stability : unstable
|
-- Stability : unstable
|
||||||
-- Portability : not portable, uses cunning newtype deriving
|
-- Portability : not portable, uses cunning newtype deriving
|
||||||
--
|
--
|
||||||
-----------------------------------------------------------------------------
|
|
||||||
--
|
|
||||||
-- The X monad, a state monad transformer over IO, for the window
|
-- The X monad, a state monad transformer over IO, for the window
|
||||||
-- manager state, and support routines.
|
-- manager state, and support routines.
|
||||||
--
|
--
|
||||||
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
module XMonad (
|
module XMonad (
|
||||||
X, WindowSet, WorkspaceId(..), ScreenId(..), XState(..), XConf(..), Layout(..),
|
X, WindowSet, WorkspaceId(..), ScreenId(..), XState(..), XConf(..), Layout(..),
|
||||||
|
Loading…
x
Reference in New Issue
Block a user