summaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorBrent Yorgey <byorgey@gmail.com>2008-02-01 20:06:53 +0100
committerBrent Yorgey <byorgey@gmail.com>2008-02-01 20:06:53 +0100
commitedc466856bf8723c5439f12663230b5b78320b9f (patch)
tree0f2151eccfde34478ed243f108fe0bb35fa1fafd /XMonad
parent8f65f8773459f30a03857be213beb21368198322 (diff)
downloadmetatile-edc466856bf8723c5439f12663230b5b78320b9f.tar
metatile-edc466856bf8723c5439f12663230b5b78320b9f.zip
Core.hs, StackSet.hs: some documentation updates
darcs-hash:20080201190653-bd4d7-767473ef51a27bfdbadead306a1c3250dcaafaab
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Core.hs41
-rw-r--r--XMonad/StackSet.hs8
2 files changed, 25 insertions, 24 deletions
diff --git a/XMonad/Core.hs b/XMonad/Core.hs
index 8dfa91f..dbcee94 100644
--- a/XMonad/Core.hs
+++ b/XMonad/Core.hs
@@ -51,14 +51,14 @@ import Data.Monoid
import qualified Data.Map as M
import qualified Data.Set as S
--- | XState, the window manager state.
--- Just the display, width, height and a window list
+-- | XState, the (mutable) window manager state.
data XState = XState
{ windowset :: !WindowSet -- ^ workspace list
, mapped :: !(S.Set Window) -- ^ the Set of mapped windows
, waitingUnmap :: !(M.Map Window Int) -- ^ the number of expected UnmapEvents
, dragging :: !(Maybe (Position -> Position -> X (), X ())) }
+-- | XConf, the (read-only) window manager configuration.
data XConf = XConf
{ display :: Display -- ^ the X11 display
, config :: !(XConfig Layout) -- ^ initial user configuration
@@ -95,21 +95,22 @@ data XConfig l = XConfig
type WindowSet = StackSet WorkspaceId (Layout Window) Window ScreenId ScreenDetail
type WindowSpace = Workspace WorkspaceId (Layout Window) Window
--- | Virtual workspace indicies
+-- | Virtual workspace indices
type WorkspaceId = String
--- | Physical screen indicies
+-- | Physical screen indices
newtype ScreenId = S Int deriving (Eq,Ord,Show,Read,Enum,Num,Integral,Real)
-- | The 'Rectangle' with screen dimensions and the list of gaps
data ScreenDetail = SD { screenRect :: !Rectangle
- , statusGap :: !(Int,Int,Int,Int) -- ^ width of status bar on the screen
+ , statusGap :: !(Int,Int,Int,Int) -- ^ gaps on the sides of the screen that shouldn't be tiled, usually for status bars
} deriving (Eq,Show, Read)
------------------------------------------------------------------------
--- | The X monad, a StateT transformer over IO encapsulating the window
--- manager state
+-- | The X monad, ReaderT and StateT transformers over IO
+-- encapsulating the window manager configuration and state,
+-- respectively.
--
-- Dynamic components may be retrieved with 'get', static components
-- with 'ask'. With newtype deriving we get readers and state monads
@@ -195,18 +196,17 @@ data Layout a = forall l. (LayoutClass l a, Read (l a)) => Layout (l a)
readsLayout :: Layout a -> String -> [(Layout a, String)]
readsLayout (Layout l) s = [(Layout (asTypeOf x l), rs) | (x, rs) <- reads s]
--- | The different layout modes
---
--- 'doLayout': given a Rectangle and a Stack, layout the stack elements
--- inside the given Rectangle. If an element is not given a Rectangle
--- by 'doLayout', then it is not shown on screen. Windows are restacked
--- according to the order they are returned by 'doLayout'.
+-- | Every layout must be an instance of LayoutClass, which defines
+-- the basic layout operations along with a sensible default for each.
--
class Show (layout a) => LayoutClass layout a where
- -- | Given a Rectangle in which to place the windows, and a Stack of
- -- windows, return a list of windows and their corresponding Rectangles.
- -- The order of windows in this list should be the desired stacking order.
+ -- | Given a Rectangle in which to place the windows, and a Stack
+ -- of windows, return a list of windows and their corresponding
+ -- Rectangles. If an element is not given a Rectangle by
+ -- 'doLayout', then it is not shown on screen. The order of
+ -- windows in this list should be the desired stacking order.
+ --
-- Also return a modified layout, if this layout needs to be modified
-- (e.g. if we keep track of the windows we have displayed).
doLayout :: layout a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (layout a))
@@ -248,7 +248,8 @@ instance LayoutClass Layout Window where
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, and
+-- emptyLayout otherwise.
runLayout :: LayoutClass l a => l a -> Rectangle -> Maybe (Stack a) -> X ([(a, Rectangle)], Maybe (l a))
runLayout l r = maybe (emptyLayout l r) (doLayout l r)
@@ -341,7 +342,7 @@ restart prog resume = do
getXMonadDir :: MonadIO m => m String
getXMonadDir = io $ getAppUserDataDirectory "xmonad"
--- | 'recompile force', recompile ~\/.xmonad\/xmonad.hs when any of the
+-- | 'recompile force', recompile @~\/.xmonad\/xmonad.hs@ when any of the
-- following apply:
-- * force is True
-- * the xmonad executable does not exist
@@ -353,7 +354,7 @@ getXMonadDir = io $ getAppUserDataDirectory "xmonad"
-- GHC indicates failure with a non-zero exit code, an xmessage displaying
-- that file is spawned.
--
--- False is returned if there is compilation errors.
+-- False is returned if there are compilation errors.
--
recompile :: MonadIO m => Bool -> m Bool
recompile force = io $ do
@@ -382,7 +383,7 @@ recompile force = io $ do
else return True
where getModTime f = catch (Just <$> getModificationTime f) (const $ return Nothing)
--- | Run a side effecting action with the current workspace. Like 'when' but
+-- | Conditionally run an action, using a @Maybe a@ to decide.
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust mg f = maybe (return ()) f mg
diff --git a/XMonad/StackSet.hs b/XMonad/StackSet.hs
index aa3e53a..d9e7e6b 100644
--- a/XMonad/StackSet.hs
+++ b/XMonad/StackSet.hs
@@ -112,7 +112,7 @@ import qualified Data.Map as M (Map,insert,delete,empty)
-- 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.
+-- workspaces, and non-visible workspaces.
-- $focus
--
@@ -145,7 +145,7 @@ data Screen i l a sid sd = Screen { workspace :: !(Workspace i l a)
deriving (Show, Read, Eq)
-- |
--- A workspace is just a tag - its index - and a stack
+-- A workspace is just a tag, a layout, and a stack.
--
data Workspace i l a = Workspace { tag :: !i, layout :: l, stack :: Maybe (Stack a) }
deriving (Show, Read, Eq)
@@ -301,7 +301,7 @@ integrate (Stack x l r) = reverse l ++ x : r
integrate' :: Maybe (Stack a) -> [a]
integrate' = maybe [] integrate
--- |
+-- |
-- /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.
@@ -414,7 +414,7 @@ mapLayout f (StackSet v vs hs m) = StackSet (fScreen v) (map fScreen vs) (map fW
fScreen (Screen ws s sd) = Screen (fWorkspace ws) s sd
fWorkspace (Workspace t l s) = Workspace t (f l) s
--- | /O(n)/. Is a window in the StackSet.
+-- | /O(n)/. Is a window in the StackSet?
member :: Eq a => a -> StackSet i l a s sd -> Bool
member a s = isJust (findTag a s)