29 Commits
v0.10 ... v0.11

Author SHA1 Message Date
Adam Vogt
e87456ab77 bump cabal-version to satisfy hackage 2013-01-01 01:40:56 +00:00
Adam Vogt
cdc22f0849 TAG 0.11 2013-01-01 01:30:31 +00:00
Adam Vogt
70413b2e22 Bump version to 0.11 2012-12-31 18:48:10 +00:00
Adam Vogt
67ffde0dfb Add more metadata to cabal file 2012-12-31 18:46:52 +00:00
Adam Vogt
d904fb1cc4 Update generated manpage (and releaseDate in util/GenerateManpage.hs) 2012-12-31 16:34:03 +00:00
Adam Vogt
4120be8ba0 Copy help binding from XMonad.Config to man/xmonad.hs 2012-12-31 16:33:05 +00:00
Adam Vogt
e015155131 Shorter hyperlinks to hackage in README. 2012-12-31 10:53:58 +00:00
Adam Vogt
4c1536cd18 Add clickJustFocuses option to template configuration. 2012-12-31 10:44:20 +00:00
Adam Vogt
a34a5e979a Add configuration option clickToFocus (issue 225)
To summarize this allows clicks which change the focus to also be passed on to
that window.
2012-01-03 01:39:16 +00:00
conrad.irwin
38faddf9de pass mouse clicks on to focused windows (experimental)
Originally: http://www.haskell.org/pipermail/xmonad/2008-June/005807.html
2011-05-25 04:34:13 +00:00
Adam Vogt
3ab2b28711 HCAR.tex convert line endings. 2012-11-18 19:40:06 +00:00
gwern0
934ff6a562 HCAR.tex: update to Janis's master version per his instructions 2012-11-18 01:03:10 +00:00
Adam Vogt
f8b07d8956 Add generated manpage and html manpage to the repo.
The intention of adding these files to the data-files
is so that they get included in the upload to hackage:
people might like manpage but not have to install pandoc.

It's not really clear that this is the best solution.
2012-11-08 23:11:39 +00:00
Adam Vogt
67d436a4e6 Resolve conflicts Geoff Reedy's window focus hack. 2010-02-22 14:45:12 +00:00
Geoff Reedy
c6fef373dc Give focus to windows that don't set the input hint 2009-10-10 23:19:07 +00:00
Geoff Reedy
2d4f304c0a implement the ICCCM WM_TAKE_FOCUS protocol 2009-06-22 05:19:11 +00:00
Geoff Reedy
1df8ea3d0e track currently processing event 2009-06-22 03:56:49 +00:00
Adam Vogt
490719c035 resolve HCar.tex conflict 2012-11-08 22:35:14 +00:00
gwern0
3cd001e8df HCAR.tex: update with Janis's master version 2012-10-03 19:04:25 +00:00
gwern0
b0dda7b351 HCAR.tex: update per Janis 2012-05-16 21:13:52 +00:00
gwern0
d8495adf0d HCAR.tex: update per Janis 2012-05-13 21:15:22 +00:00
gwern0
06f35a650e Config.hs: implement mod-shift-/ newbie keybinding guide per http://code.google.com/p/xmonad/issues/detail?id=182 2012-01-13 01:04:10 +00:00
gwern0
56f5ecb320 Config.hs: rm commented out keybinding (dead for years) 2012-01-13 00:01:15 +00:00
Adam Vogt
ff674a27e2 Include manual pages in data-files. 2011-12-04 00:11:37 +00:00
Adam Vogt
6c51745122 Correctly identify source files in ~/.lib (David McLean) 2012-04-30 15:42:22 +00:00
Adam Vogt
108c2280ef Address versioning problems related to X11 1.6 release.
Bump version to 0.10.1 since cabal uses hackage dependencies even when the
locally installed package differs.

Allow X11-1.6 dependency.
2012-03-20 00:49:24 +00:00
Adam Vogt
e70b489936 Drop PlainConfig from HCAR.tex: it doesn't exist in contrib.
The code for that moved out to a separate project:
http://braincrater.wordpress.com/2008/08/28/announcing-xmonad-light/
2011-12-11 00:44:05 +00:00
gwern0
450c3a34fe HCAR: update module count, date, versions, maintainer 2011-12-04 02:59:31 +00:00
Adam Vogt
32f416a3c2 Minor updates to supporting files (for 0.10 release). 2011-11-18 23:13:24 +00:00
11 changed files with 610 additions and 37 deletions

12
README
View File

@@ -66,7 +66,7 @@ Building:
using GHC 6.6.x, you'll need to build and install Cabal from hackage
first:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Cabal
http://hackage.haskell.org/package/Cabal
You can check which version you have with the command:
@@ -80,9 +80,9 @@ Building:
provided. To check whether you've got a package run 'ghc-pkg list
some_package_name'. You will need the following packages:
mtl http://hackage.haskell.org/cgi-bin/hackage-scripts/package/mtl
unix http://hackage.haskell.org/cgi-bin/hackage-scripts/package/unix
X11 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/X11
mtl http://hackage.haskell.org/package/mtl
unix http://hackage.haskell.org/package/unix
X11 http://hackage.haskell.org/package/X11
* Build xmonad:
@@ -120,7 +120,7 @@ XMonadContrib
prompt/program launcher, and various other useful modules.
XMonadContrib is available at:
latest release: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/xmonad-contrib
latest release: http://hackage.haskell.org/package/xmonad-contrib
darcs version: darcs get http://code.haskell.org/XMonadContrib
@@ -135,7 +135,7 @@ Other useful programs:
For custom status bars:
dzen http://gotmor.googlepages.com/dzen
xmobar http://hackage.haskell.org/cgi-bin/hackage-scripts/package/xmobar
xmobar http://hackage.haskell.org/package/xmobar
For a program dispatch menu:

View File

@@ -27,11 +27,11 @@ module XMonad.Config (defaultConfig) where
import XMonad.Core as XMonad hiding
(workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
,handleEventHook)
,handleEventHook,clickJustFocuses)
import qualified XMonad.Core as XMonad
(workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
,handleEventHook)
,handleEventHook,clickJustFocuses)
import XMonad.Layout
import XMonad.Operations
@@ -157,6 +157,11 @@ terminal = "xterm"
focusFollowsMouse :: Bool
focusFollowsMouse = True
-- | Whether a mouse click select the focus or is just passed to the window
clickJustFocuses :: Bool
clickJustFocuses = True
-- | The xmonad key bindings. Add, modify or remove key bindings here.
--
-- (The comment formatting character is used when generating the manpage)
@@ -197,12 +202,13 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
, ((modMask , xK_comma ), sendMessage (IncMasterN 1)) -- %! Increment the number of windows in the master area
, ((modMask , xK_period), sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area
-- toggle the status bar gap
--, ((modMask , xK_b ), modifyGap (\i n -> let x = (XMonad.defaultGaps conf ++ repeat (0,0,0,0)) !! i in if n == x then (0,0,0,0) else x)) -- %! Toggle the status bar gap
-- quit, or restart
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad
, ((modMask , xK_q ), spawn "if type xmonad; then xmonad --recompile && xmonad --restart; else xmessage xmonad not in \\$PATH: \"$PATH\"; fi") -- %! Restart xmonad
, ((modMask .|. shiftMask, xK_slash ), spawn ("echo \"" ++ help ++ "\" | xmessage -file -")) -- %! Run xmessage with a summary of the default keybindings (useful for beginners)
-- repeat the binding for non-American layout keyboards
, ((modMask , xK_question), spawn ("echo \"" ++ help ++ "\" | xmessage -file -"))
]
++
-- mod-[1..9] %! Switch to workspace N
@@ -218,7 +224,6 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
-- | Mouse bindings: default actions bound to mouse events
--
mouseBindings :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ())
mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList
-- mod-button1 %! Set the window to floating mode and move by dragging
@@ -232,7 +237,7 @@ mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList
-- you may also bind events to the mouse scroll wheel (button4 and button5)
]
-- | And, finally, the default set of configuration values itself
-- | The default set of configuration values itself
defaultConfig = XConfig
{ XMonad.borderWidth = borderWidth
, XMonad.workspaces = workspaces
@@ -248,4 +253,56 @@ defaultConfig = XConfig
, XMonad.manageHook = manageHook
, XMonad.handleEventHook = handleEventHook
, XMonad.focusFollowsMouse = focusFollowsMouse
, XMonad.clickJustFocuses = clickJustFocuses
}
-- | Finally, a copy of the default bindings in simple textual tabular format.
help :: String
help = unlines ["The default modifier key is 'alt'. Default keybindings:",
"",
"-- launching and killing programs",
"mod-Shift-Enter Launch xterminal",
"mod-p Launch dmenu",
"mod-Shift-p Launch gmrun",
"mod-Shift-c Close/kill the focused window",
"mod-Space Rotate through the available layout algorithms",
"mod-Shift-Space Reset the layouts on the current workSpace to default",
"mod-n Resize/refresh viewed windows to the correct size",
"",
"-- move focus up or down the window stack",
"mod-Tab Move focus to the next window",
"mod-Shift-Tab Move focus to the previous window",
"mod-j Move focus to the next window",
"mod-k Move focus to the previous window",
"mod-m Move focus to the master window",
"",
"-- modifying the window order",
"mod-Return Swap the focused window and the master window",
"mod-Shift-j Swap the focused window with the next window",
"mod-Shift-k Swap the focused window with the previous window",
"",
"-- resizing the master/slave ratio",
"mod-h Shrink the master area",
"mod-l Expand the master area",
"",
"-- floating layer support",
"mod-t Push window back into tiling; unfloat and re-tile it",
"",
"-- increase or decrease number of windows in the master area",
"mod-comma (mod-,) Increment the number of windows in the master area",
"mod-period (mod-.) Deincrement the number of windows in the master area",
"",
"-- quit, or restart",
"mod-Shift-q Quit xmonad",
"mod-q Restart xmonad",
"mod-[1..9] Switch to workSpace N",
"",
"-- Workspaces & screens",
"mod-Shift-[1..9] Move client to workspace N",
"mod-{w,e,r} Switch to physical/Xinerama screens 1, 2, or 3",
"mod-Shift-{w,e,r} Move client to screen 1, 2, or 3",
"",
"-- Mouse bindings: default actions bound to mouse events",
"mod-button1 Set the window to floating mode and move by dragging",
"mod-button2 Raise the window to the top of the stack",
"mod-button3 Set the window to floating mode and resize by dragging"]

View File

@@ -26,7 +26,7 @@ module XMonad.Core (
runX, catchX, userCode, userCodeDef, io, catchIO, installSignalHandlers, uninstallSignalHandlers,
withDisplay, withWindowSet, isRoot, runOnWorkspaces,
getAtom, spawn, spawnPID, xfork, getXMonadDir, recompile, trace, whenJust, whenX,
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runQuery
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, atom_WM_TAKE_FOCUS, ManageHook, Query(..), runQuery
) where
import XMonad.StackSet hiding (modify)
@@ -86,6 +86,8 @@ data XConf = XConf
, mousePosition :: !(Maybe (Position, Position))
-- ^ position of the mouse according to
-- the event currently being processed
, currentEvent :: !(Maybe Event)
-- ^ event currently being processed
}
-- todo, better name
@@ -108,6 +110,7 @@ data XConfig l = XConfig
, logHook :: !(X ()) -- ^ The action to perform when the windows set is changed
, startupHook :: !(X ()) -- ^ The action to perform on startup
, focusFollowsMouse :: !Bool -- ^ Whether window entry events can change focus
, clickJustFocuses :: !Bool -- ^ False to make a click which changes focus to be additionally passed to the window
}
@@ -202,10 +205,11 @@ getAtom :: String -> X Atom
getAtom str = withDisplay $ \dpy -> io $ internAtom dpy str False
-- | Common non-predefined atoms
atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, atom_WM_STATE :: X Atom
atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, atom_WM_STATE, atom_WM_TAKE_FOCUS :: X Atom
atom_WM_PROTOCOLS = getAtom "WM_PROTOCOLS"
atom_WM_DELETE_WINDOW = getAtom "WM_DELETE_WINDOW"
atom_WM_STATE = getAtom "WM_STATE"
atom_WM_TAKE_FOCUS = getAtom "WM_TAKE_FOCUS"
------------------------------------------------------------------------
-- LayoutClass handling. See particular instances in Operations.hs
@@ -477,7 +481,7 @@ recompile force = io $ do
return (status == ExitSuccess)
else return True
where getModTime f = catch (Just <$> getModificationTime f) (\(SomeException _) -> return Nothing)
isSource = flip elem [".hs",".lhs",".hsc"]
isSource = flip elem [".hs",".lhs",".hsc"] . takeExtension
allFiles t = do
let prep = map (t</>) . Prelude.filter (`notElem` [".",".."])
cs <- prep <$> catch (getDirectoryContents t) (\(SomeException _) -> return [])

View File

@@ -121,7 +121,8 @@ xmonad initxmc = do
, keyActions = keys xmc xmc
, buttonActions = mouseBindings xmc xmc
, mouseFocused = False
, mousePosition = Nothing }
, mousePosition = Nothing
, currentEvent = Nothing }
st = XState
{ windowset = initialWinset
@@ -163,7 +164,7 @@ xmonad initxmc = do
prehandle e = let mouse = do guard (ev_event_type e `elem` evs)
return (fromIntegral (ev_x_root e)
,fromIntegral (ev_y_root e))
in local (\c -> c { mousePosition = mouse }) (handleWithHook e)
in local (\c -> c { mousePosition = mouse, currentEvent = Just e }) (handleWithHook e)
evs = [ keyPress, keyRelease, enterNotify, leaveNotify
, buttonPress, buttonRelease]
@@ -247,12 +248,16 @@ handle e@(ButtonEvent {ev_window = w,ev_event_type = t,ev_button = b })
| t == buttonPress = do
-- If it's the root window, then it's something we
-- grabbed in grabButtons. Otherwise, it's click-to-focus.
dpy <- asks display
isr <- isRoot w
m <- cleanMask $ ev_state e
mact <- asks (M.lookup (m, b) . buttonActions)
case mact of
(Just act) | isr -> act $ ev_subwindow e
_ -> focus w
Just act | isr -> act $ ev_subwindow e
_ -> do
focus w
ctf <- asks (clickJustFocuses . config)
unless ctf $ io (allowEvents dpy replayPointer currentTime)
broadcastMessage e -- Always send button events.
-- entered a normal window: focus it if focusFollowsMouse is set to

View File

@@ -24,7 +24,7 @@ import qualified XMonad.StackSet as W
import Data.Maybe
import Data.Monoid (Endo(..))
import Data.List (nub, (\\), find)
import Data.Bits ((.|.), (.&.), complement)
import Data.Bits ((.|.), (.&.), complement, testBit)
import Data.Ratio
import qualified Data.Map as M
import qualified Data.Set as S
@@ -283,11 +283,14 @@ rescreen = do
-- | setButtonGrab. Tell whether or not to intercept clicks on a given window
setButtonGrab :: Bool -> Window -> X ()
setButtonGrab grab w = withDisplay $ \d -> io $
if grab
setButtonGrab grab w = do
pointerMode <- asks $ \c -> if clickJustFocuses (config c)
then grabModeAsync
else grabModeSync
withDisplay $ \d -> io $ if grab
then forM_ [button1, button2, button3] $ \b ->
grabButton d b anyModifier w False buttonPressMask
grabModeAsync grabModeSync none none
pointerMode grabModeSync none none
else ungrabButton d anyButton anyModifier w
-- ---------------------------------------------------------------------
@@ -325,7 +328,27 @@ setFocusX w = withWindowSet $ \ws -> do
-- If we ungrab buttons on the root window, we lose our mouse bindings.
whenX (not <$> isRoot w) $ setButtonGrab False w
io $ setInputFocus dpy w revertToPointerRoot 0
hints <- io $ getWMHints dpy w
protocols <- io $ getWMProtocols dpy w
wmprot <- atom_WM_PROTOCOLS
wmtf <- atom_WM_TAKE_FOCUS
currevt <- asks currentEvent
let inputHintSet = wmh_flags hints `testBit` inputHintBit
when ((inputHintSet && wmh_input hints) || (not inputHintSet)) $
io $ do setInputFocus dpy w revertToPointerRoot 0
when (wmtf `elem` protocols) $
io $ allocaXEvent $ \ev -> do
setEventType ev clientMessage
setClientMessageEvent ev w wmprot 32 wmtf $ maybe currentTime event_time currevt
sendEvent dpy w False noEventMask ev
where event_time ev =
if (ev_event_type ev) `elem` timedEvents then
ev_time ev
else
currentTime
timedEvents = [ keyPress, keyRelease, buttonPress, buttonRelease, enterNotify, leaveNotify, selectionRequest ]
------------------------------------------------------------------------
-- Message handling

View File

@@ -1,7 +1,7 @@
% xmonad-Gx.tex
\begin{hcarentry}{xmonad}
\label{xmonad}
\report{Gwern Branwen}%05/10
\report{Gwern Branwen}%11/11
\status{active development}
\makeheader
@@ -15,16 +15,19 @@ dynamically, and different layouts may be used on each workspace.
Xinerama is fully supported, allowing windows to be tiled on several
physical screens.
Development since the last report has continued apace, with versions
0.8, 0.8.1, 0.9 and 0.9.1 released, with simultaneous releases of the
XMonadContrib library of customizations and extensions, which has now
grown to no less than 205 modules encompassing a dizzying array of features.
Development since the last report has continued; XMonad founder Don Stewart
has stepped down and Adam Vogt is the new maintainer.
After gestating for 2 years, version 0.10 has been released, with simultaneous
releases of the XMonadContrib library of customizations (which has now grown to
no less than 216 modules encompassing a dizzying array of features) and the
xmonad-extras package of extensions,
Details of changes between releases can be found in the release notes:
\begin{compactitem}
\item \url{http://haskell.org/haskellwiki/Xmonad/Notable_changes_since_0.7}
\item \url{http://haskell.org/haskellwiki/Xmonad/Notable_changes_since_0.8}
\item \url{http://haskell.org/haskellwiki/Xmonad/Notable_changes_since_0.9}
% \item \url{http://haskell.org/haskellwiki/Xmonad/Notable_changes_since_0.10}
\item the Darcs repositories have been upgraded to the hashed format
\item XMonad.Config.PlainConfig allows writing configs in a more 'normal' style, and not raw Haskell
\item Supports using local modules in xmonad.hs; for example: to use definitions from \~/.xmonad/lib/XMonad/Stack/MyAdditions.hs
\item xmonad --restart CLI option

281
man/xmonad.1 Normal file
View File

@@ -0,0 +1,281 @@
.TH xmonad 1 "31 December 2012" xmonad-0.11 "xmonad manual".TH "" ""
.SH Name
.PP
xmonad - a tiling window manager
.SH Description
.PP
\f[I]xmonad\f[] is a minimalist tiling window manager for X, written in
Haskell.
Windows are managed using automatic layout algorithms, which can be
dynamically reconfigured.
At any time windows are arranged so as to maximize the use of screen
real estate.
All features of the window manager are accessible purely from the
keyboard: a mouse is entirely optional.
\f[I]xmonad\f[] is configured in Haskell, and custom layout algorithms
may be implemented by the user in config files.
A principle of \f[I]xmonad\f[] is predictability: the user should know
in advance precisely the window arrangement that will result from any
action.
.PP
By default, \f[I]xmonad\f[] provides three layout algorithms: tall, wide
and fullscreen.
In tall or wide mode, windows are tiled and arranged to prevent overlap
and maximize screen use.
Sets of windows are grouped together on virtual screens, and each screen
retains its own layout, which may be reconfigured dynamically.
Multiple physical monitors are supported via Xinerama, allowing
simultaneous display of a number of screens.
.PP
By utilizing the expressivity of a modern functional language with a
rich static type system, \f[I]xmonad\f[] provides a complete, featureful
window manager in less than 1200 lines of code, with an emphasis on
correctness and robustness.
Internal properties of the window manager are checked using a
combination of static guarantees provided by the type system, and
type-based automated testing.
A benefit of this is that the code is simple to understand, and easy to
modify.
.SH Usage
.PP
\f[I]xmonad\f[] places each window into a "workspace".
Each workspace can have any number of windows, which you can cycle
though with mod-j and mod-k.
Windows are either displayed full screen, tiled horizontally, or tiled
vertically.
You can toggle the layout mode with mod-space, which will cycle through
the available modes.
.PP
You can switch to workspace N with mod-N.
For example, to switch to workspace 5, you would press mod-5.
Similarly, you can move the current window to another workspace with
mod-shift-N.
.PP
When running with multiple monitors (Xinerama), each screen has exactly
1 workspace visible.
mod-{w,e,r} switch the focus between screens, while shift-mod-{w,e,r}
move the current window to that screen.
When \f[I]xmonad\f[] starts, workspace 1 is on screen 1, workspace 2 is
on screen 2, etc.
When switching workspaces to one that is already visible, the current
and visible workspaces are swapped.
.SS Flags
.PP
xmonad has several flags which you may pass to the executable.
These flags are:
.TP
.B --recompile
Recompiles your configuration in \f[I]~/.xmonad/xmonad.hs\f[]
.RS
.RE
.TP
.B --restart
Causes the currently running \f[I]xmonad\f[] process to restart
.RS
.RE
.TP
.B --replace
Replace the current window manager with xmonad
.RS
.RE
.TP
.B --version
Display version of \f[I]xmonad\f[]
.RS
.RE
.TP
.B --verbose-version
Display detailed version of \f[I]xmonad\f[]
.RS
.RE
.SS Default keyboard bindings
.TP
.B mod-shift-return
Launch terminal
.RS
.RE
.TP
.B mod-p
Launch dmenu
.RS
.RE
.TP
.B mod-shift-p
Launch gmrun
.RS
.RE
.TP
.B mod-shift-c
Close the focused window
.RS
.RE
.TP
.B mod-space
Rotate through the available layout algorithms
.RS
.RE
.TP
.B mod-shift-space
Reset the layouts on the current workspace to default
.RS
.RE
.TP
.B mod-n
Resize viewed windows to the correct size
.RS
.RE
.TP
.B mod-tab
Move focus to the next window
.RS
.RE
.TP
.B mod-shift-tab
Move focus to the previous window
.RS
.RE
.TP
.B mod-j
Move focus to the next window
.RS
.RE
.TP
.B mod-k
Move focus to the previous window
.RS
.RE
.TP
.B mod-m
Move focus to the master window
.RS
.RE
.TP
.B mod-return
Swap the focused window and the master window
.RS
.RE
.TP
.B mod-shift-j
Swap the focused window with the next window
.RS
.RE
.TP
.B mod-shift-k
Swap the focused window with the previous window
.RS
.RE
.TP
.B mod-h
Shrink the master area
.RS
.RE
.TP
.B mod-l
Expand the master area
.RS
.RE
.TP
.B mod-t
Push window back into tiling
.RS
.RE
.TP
.B mod-comma
Increment the number of windows in the master area
.RS
.RE
.TP
.B mod-period
Deincrement the number of windows in the master area
.RS
.RE
.TP
.B mod-shift-q
Quit xmonad
.RS
.RE
.TP
.B mod-q
Restart xmonad
.RS
.RE
.TP
.B mod-shift-slash
Run xmessage with a summary of the default keybindings (useful for
beginners)
.RS
.RE
.TP
.B mod-[1..9]
Switch to workspace N
.RS
.RE
.TP
.B mod-shift-[1..9]
Move client to workspace N
.RS
.RE
.TP
.B mod-{w,e,r}
Switch to physical/Xinerama screens 1, 2, or 3
.RS
.RE
.TP
.B mod-shift-{w,e,r}
Move client to screen 1, 2, or 3
.RS
.RE
.TP
.B mod-button1
Set the window to floating mode and move by dragging
.RS
.RE
.TP
.B mod-button2
Raise the window to the top of the stack
.RS
.RE
.TP
.B mod-button3
Set the window to floating mode and resize by dragging
.RS
.RE
.SH Examples
.PP
To use xmonad as your window manager add to your \f[I]~/.xinitrc\f[]
file:
.IP
.nf
\f[C]
exec\ xmonad
\f[]
.fi
.SH Customization
.PP
xmonad is customized in ~/.xmonad/xmonad.hs, and then restarting with
mod-q.
.PP
You can find many extensions to the core feature set in the xmonad-
contrib package, available through your package manager or from
xmonad.org (http://xmonad.org).
.SS Modular Configuration
.PP
As of \f[I]xmonad-0.9\f[], any additional Haskell modules may be placed
in \f[I]~/.xmonad/lib/\f[] are available in GHC\[aq]s searchpath.
Hierarchical modules are supported: for example, the file
\f[I]~/.xmonad/lib/XMonad/Stack/MyAdditions.hs\f[] could contain:
.IP
.nf
\f[C]
module\ XMonad.Stack.MyAdditions\ (function1)\ where
\ \ \ \ function1\ =\ error\ "function1:\ Not\ implemented\ yet!"
\f[]
.fi
.PP
Your xmonad.hs may then import XMonad.Stack.MyAdditions as if that
module was contained within xmonad or xmonad-contrib.
.SH Bugs
.PP
Probably.
If you find any, please report them to the
bugtracker (http://code.google.com/p/xmonad/issues/list)

181
man/xmonad.1.html Normal file
View File

@@ -0,0 +1,181 @@
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
<html xmlns="http://www.w3.org/1999/xhtml">
<head>
<meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
<meta http-equiv="Content-Style-Type" content="text/css" />
<meta name="generator" content="pandoc" />
<title></title>
<style type="text/css">
table.sourceCode, tr.sourceCode, td.lineNumbers, td.sourceCode {
margin: 0; padding: 0; vertical-align: baseline; border: none; }
table.sourceCode { width: 100%; }
td.lineNumbers { text-align: right; padding-right: 4px; padding-left: 4px; color: #aaaaaa; border-right: 1px solid #aaaaaa; }
td.sourceCode { padding-left: 5px; }
code > span.kw { color: #007020; font-weight: bold; }
code > span.dt { color: #902000; }
code > span.dv { color: #40a070; }
code > span.bn { color: #40a070; }
code > span.fl { color: #40a070; }
code > span.ch { color: #4070a0; }
code > span.st { color: #4070a0; }
code > span.co { color: #60a0b0; font-style: italic; }
code > span.ot { color: #007020; }
code > span.al { color: #ff0000; font-weight: bold; }
code > span.fu { color: #06287e; }
code > span.er { color: #ff0000; font-weight: bold; }
</style>
</head>
<body>
<h1>xmonad-0.11</h1><p>Section: xmonad manual (1)<br/>Updated: 31 December 2012</p><hr/>
<div id="TOC">
<ul>
<li><a href="#name">Name</a></li>
<li><a href="#description">Description</a></li>
<li><a href="#usage">Usage</a><ul>
<li><a href="#flags">Flags</a></li>
<li><a href="#default-keyboard-bindings">Default keyboard bindings</a></li>
</ul></li>
<li><a href="#examples">Examples</a></li>
<li><a href="#customization">Customization</a><ul>
<li><a href="#modular-configuration">Modular Configuration</a></li>
</ul></li>
<li><a href="#bugs">Bugs</a></li>
</ul>
</div>
<h1 id="name"><a href="#TOC">Name</a></h1>
<p>xmonad - a tiling window manager</p>
<h1 id="description"><a href="#TOC">Description</a></h1>
<p><em>xmonad</em> is a minimalist tiling window manager for X, written in Haskell. Windows are managed using automatic layout algorithms, which can be dynamically reconfigured. At any time windows are arranged so as to maximize the use of screen real estate. All features of the window manager are accessible purely from the keyboard: a mouse is entirely optional. <em>xmonad</em> is configured in Haskell, and custom layout algorithms may be implemented by the user in config files. A principle of <em>xmonad</em> is predictability: the user should know in advance precisely the window arrangement that will result from any action.</p>
<p>By default, <em>xmonad</em> provides three layout algorithms: tall, wide and fullscreen. In tall or wide mode, windows are tiled and arranged to prevent overlap and maximize screen use. Sets of windows are grouped together on virtual screens, and each screen retains its own layout, which may be reconfigured dynamically. Multiple physical monitors are supported via Xinerama, allowing simultaneous display of a number of screens.</p>
<p>By utilizing the expressivity of a modern functional language with a rich static type system, <em>xmonad</em> provides a complete, featureful window manager in less than 1200 lines of code, with an emphasis on correctness and robustness. Internal properties of the window manager are checked using a combination of static guarantees provided by the type system, and type-based automated testing. A benefit of this is that the code is simple to understand, and easy to modify.</p>
<h1 id="usage"><a href="#TOC">Usage</a></h1>
<p><em>xmonad</em> places each window into a &quot;workspace&quot;. Each workspace can have any number of windows, which you can cycle though with mod-j and mod-k. Windows are either displayed full screen, tiled horizontally, or tiled vertically. You can toggle the layout mode with mod-space, which will cycle through the available modes.</p>
<p>You can switch to workspace N with mod-N. For example, to switch to workspace 5, you would press mod-5. Similarly, you can move the current window to another workspace with mod-shift-N.</p>
<p>When running with multiple monitors (Xinerama), each screen has exactly 1 workspace visible. mod-{w,e,r} switch the focus between screens, while shift-mod-{w,e,r} move the current window to that screen. When <em>xmonad</em> starts, workspace 1 is on screen 1, workspace 2 is on screen 2, etc. When switching workspaces to one that is already visible, the current and visible workspaces are swapped.</p>
<h2 id="flags"><a href="#TOC">Flags</a></h2>
<p>xmonad has several flags which you may pass to the executable. These flags are:</p>
<dl>
<dt>--recompile</dt>
<dd><p>Recompiles your configuration in <em>~/.xmonad/xmonad.hs</em></p>
</dd>
<dt>--restart</dt>
<dd><p>Causes the currently running <em>xmonad</em> process to restart</p>
</dd>
<dt>--replace</dt>
<dd><p>Replace the current window manager with xmonad</p>
</dd>
<dt>--version</dt>
<dd><p>Display version of <em>xmonad</em></p>
</dd>
<dt>--verbose-version</dt>
<dd><p>Display detailed version of <em>xmonad</em></p>
</dd>
</dl>
<h2 id="default-keyboard-bindings"><a href="#TOC">Default keyboard bindings</a></h2>
<dl>
<dt>mod-shift-return</dt>
<dd><p>Launch terminal</p>
</dd>
<dt>mod-p</dt>
<dd><p>Launch dmenu</p>
</dd>
<dt>mod-shift-p</dt>
<dd><p>Launch gmrun</p>
</dd>
<dt>mod-shift-c</dt>
<dd><p>Close the focused window</p>
</dd>
<dt>mod-space</dt>
<dd><p>Rotate through the available layout algorithms</p>
</dd>
<dt>mod-shift-space</dt>
<dd><p>Reset the layouts on the current workspace to default</p>
</dd>
<dt>mod-n</dt>
<dd><p>Resize viewed windows to the correct size</p>
</dd>
<dt>mod-tab</dt>
<dd><p>Move focus to the next window</p>
</dd>
<dt>mod-shift-tab</dt>
<dd><p>Move focus to the previous window</p>
</dd>
<dt>mod-j</dt>
<dd><p>Move focus to the next window</p>
</dd>
<dt>mod-k</dt>
<dd><p>Move focus to the previous window</p>
</dd>
<dt>mod-m</dt>
<dd><p>Move focus to the master window</p>
</dd>
<dt>mod-return</dt>
<dd><p>Swap the focused window and the master window</p>
</dd>
<dt>mod-shift-j</dt>
<dd><p>Swap the focused window with the next window</p>
</dd>
<dt>mod-shift-k</dt>
<dd><p>Swap the focused window with the previous window</p>
</dd>
<dt>mod-h</dt>
<dd><p>Shrink the master area</p>
</dd>
<dt>mod-l</dt>
<dd><p>Expand the master area</p>
</dd>
<dt>mod-t</dt>
<dd><p>Push window back into tiling</p>
</dd>
<dt>mod-comma</dt>
<dd><p>Increment the number of windows in the master area</p>
</dd>
<dt>mod-period</dt>
<dd><p>Deincrement the number of windows in the master area</p>
</dd>
<dt>mod-shift-q</dt>
<dd><p>Quit xmonad</p>
</dd>
<dt>mod-q</dt>
<dd><p>Restart xmonad</p>
</dd>
<dt>mod-shift-slash</dt>
<dd><p>Run xmessage with a summary of the default keybindings (useful for beginners)</p>
</dd>
<dt>mod-[1..9]</dt>
<dd><p>Switch to workspace N</p>
</dd>
<dt>mod-shift-[1..9]</dt>
<dd><p>Move client to workspace N</p>
</dd>
<dt>mod-{w,e,r}</dt>
<dd><p>Switch to physical/Xinerama screens 1, 2, or 3</p>
</dd>
<dt>mod-shift-{w,e,r}</dt>
<dd><p>Move client to screen 1, 2, or 3</p>
</dd>
<dt>mod-button1</dt>
<dd><p>Set the window to floating mode and move by dragging</p>
</dd>
<dt>mod-button2</dt>
<dd><p>Raise the window to the top of the stack</p>
</dd>
<dt>mod-button3</dt>
<dd><p>Set the window to floating mode and resize by dragging</p>
</dd>
</dl>
<h1 id="examples"><a href="#TOC">Examples</a></h1>
<p>To use xmonad as your window manager add to your <em>~/.xinitrc</em> file:</p>
<pre class="sourceCode literate haskell"><code class="sourceCode haskell">exec xmonad</code></pre>
<h1 id="customization"><a href="#TOC">Customization</a></h1>
<p>xmonad is customized in ~/.xmonad/xmonad.hs, and then restarting with mod-q.</p>
<p>You can find many extensions to the core feature set in the xmonad- contrib package, available through your package manager or from <a href="http://xmonad.org">xmonad.org</a>.</p>
<h2 id="modular-configuration"><a href="#TOC">Modular Configuration</a></h2>
<p>As of <em>xmonad-0.9</em>, any additional Haskell modules may be placed in <em>~/.xmonad/lib/</em> are available in GHC's searchpath. Hierarchical modules are supported: for example, the file <em>~/.xmonad/lib/XMonad/Stack/MyAdditions.hs</em> could contain:</p>
<pre class="sourceCode literate haskell"><code class="sourceCode haskell"><span class="kw">module</span> <span class="dt">XMonad.Stack.MyAdditions</span> (function1) <span class="kw">where</span>
function1 <span class="fu">=</span> <span class="fu">error</span> <span class="st">&quot;function1: Not implemented yet!&quot;</span></code></pre>
<p>Your xmonad.hs may then import XMonad.Stack.MyAdditions as if that module was contained within xmonad or xmonad-contrib.</p>
<h1 id="bugs"><a href="#TOC">Bugs</a></h1>
<p>Probably. If you find any, please report them to the <a href="http://code.google.com/p/xmonad/issues/list">bugtracker</a></p>
</body>
</html>

View File

@@ -23,6 +23,10 @@ myTerminal = "xterm"
myFocusFollowsMouse :: Bool
myFocusFollowsMouse = True
-- Whether clicking on a window to focus also passes the click to the window
myClickJustFocuses :: Bool
myClickJustFocuses = False
-- Width of the window border in pixels.
--
myBorderWidth = 1
@@ -59,7 +63,7 @@ myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $
[ ((modm .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
-- launch dmenu
, ((modm, xK_p ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"")
, ((modm, xK_p ), spawn "dmenu_run")
-- launch gmrun
, ((modm .|. shiftMask, xK_p ), spawn "gmrun")
@@ -123,6 +127,9 @@ myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $
-- Restart xmonad
, ((modm , xK_q ), spawn "xmonad --recompile; xmonad --restart")
-- Run xmessage with a summary of the default keybindings (useful for beginners)
, ((modMask .|. shiftMask, xK_slash ), spawn ("echo \"" ++ help ++ "\" | xmessage -file -"))
]
++
@@ -255,6 +262,7 @@ defaults = defaultConfig {
-- simple stuff
terminal = myTerminal,
focusFollowsMouse = myFocusFollowsMouse,
clickJustFocuses = myClickJustFocuses,
borderWidth = myBorderWidth,
modMask = myModMask,
workspaces = myWorkspaces,

View File

@@ -36,7 +36,7 @@ import Distribution.Text
import Text.Pandoc -- works with 1.6
releaseDate = "25 October 09"
releaseDate = "31 December 2012"
trim :: String -> String
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace

View File

@@ -1,5 +1,5 @@
name: xmonad
version: 0.10
version: 0.11
homepage: http://xmonad.org
synopsis: A tiling window manager
description:
@@ -20,10 +20,21 @@ maintainer: xmonad@haskell.org
extra-source-files: README TODO CONFIG STYLE tests/loc.hs tests/Properties.hs
man/xmonad.1.markdown man/xmonad.1 man/xmonad.1.html
util/GenerateManpage.hs
cabal-version: >= 1.2
cabal-version: >= 1.6
bug-reports: http://code.google.com/p/xmonad/issues/list
build-type: Simple
data-files: man/xmonad.hs
tested-with: GHC==7.6.1,
GHC==7.4.1,
GHC==7.2.1,
GHC==6.12.3,
GHC==6.10.4
data-files: man/xmonad.hs, man/xmonad.1, man/xmonad.1.html
source-repository head
type: darcs
location: http://code.haskell.org/xmonad
flag small_base
description: Choose the new smaller, split-up base package.
@@ -46,7 +57,7 @@ library
build-depends: base < 5 && >=3, containers, directory, process, filepath, extensible-exceptions
else
build-depends: base < 3
build-depends: X11>=1.5.0.0 && < 1.6, mtl, unix,
build-depends: X11>=1.5 && < 1.7, mtl, unix,
utf8-string >= 0.3 && < 0.4
if true