mirror of
https://github.com/xmonad/xmonad.git
synced 2025-07-29 11:11:53 -07:00
Compare commits
82 Commits
Author | SHA1 | Date | |
---|---|---|---|
|
e87456ab77 | ||
|
cdc22f0849 | ||
|
70413b2e22 | ||
|
67ffde0dfb | ||
|
d904fb1cc4 | ||
|
4120be8ba0 | ||
|
e015155131 | ||
|
4c1536cd18 | ||
|
a34a5e979a | ||
|
38faddf9de | ||
|
3ab2b28711 | ||
|
934ff6a562 | ||
|
f8b07d8956 | ||
|
67d436a4e6 | ||
|
c6fef373dc | ||
|
2d4f304c0a | ||
|
1df8ea3d0e | ||
|
490719c035 | ||
|
3cd001e8df | ||
|
b0dda7b351 | ||
|
d8495adf0d | ||
|
06f35a650e | ||
|
56f5ecb320 | ||
|
ff674a27e2 | ||
|
6c51745122 | ||
|
108c2280ef | ||
|
e70b489936 | ||
|
450c3a34fe | ||
|
32f416a3c2 | ||
|
4be3b39cd2 | ||
|
75889ab62e | ||
|
792add376e | ||
|
87c50a911f | ||
|
d16aa9975e | ||
|
f34642cbac | ||
|
008c3638a5 | ||
|
f5c40e9e12 | ||
|
bd82cc9150 | ||
|
a025912ab7 | ||
|
19c1759b35 | ||
|
92acd1eb74 | ||
|
db9f39d6af | ||
|
ebcd67efac | ||
|
387a253f62 | ||
|
4c83e8e097 | ||
|
ae59a5184f | ||
|
fa8fe9aca4 | ||
|
673c3e9ed9 | ||
|
6ba45cdb38 | ||
|
b995b430bc | ||
|
ba482a4611 | ||
|
684907bc77 | ||
|
ad4136df26 | ||
|
defe0c282e | ||
|
c7bdac1a7e | ||
|
17799f131a | ||
|
8cd66aa380 | ||
|
32ba0d4a0d | ||
|
77b3f62610 | ||
|
f3b07eb5dc | ||
|
4372c256ed | ||
|
34239a79de | ||
|
5866db4f0f | ||
|
46d039cde5 | ||
|
dd22717961 | ||
|
0beeb4164b | ||
|
0b435028ff | ||
|
84a988da82 | ||
|
dbd739e41e | ||
|
d5d8d551e6 | ||
|
a2ba4d8a6c | ||
|
557d3edb7d | ||
|
262db2367f | ||
|
eddb445307 | ||
|
d5aadf2538 | ||
|
a16bb44934 | ||
|
2b854ee47c | ||
|
02ed1cabdc | ||
|
02693d307c | ||
|
37dc284460 | ||
|
73e406f4a6 | ||
|
44bc9558d9 |
15
Main.hs
15
Main.hs
@@ -17,7 +17,6 @@ module Main (main) where
|
||||
import XMonad
|
||||
|
||||
import Control.Monad (unless)
|
||||
import System.IO
|
||||
import System.Info
|
||||
import System.Environment
|
||||
import System.Posix.Process (executeFile)
|
||||
@@ -26,6 +25,8 @@ import System.Exit (exitFailure)
|
||||
import Paths_xmonad (version)
|
||||
import Data.Version (showVersion)
|
||||
|
||||
import Graphics.X11.Xinerama (compiledWithXinerama)
|
||||
|
||||
#ifdef TESTING
|
||||
import qualified Properties
|
||||
#endif
|
||||
@@ -39,15 +40,22 @@ main = do
|
||||
let launch = catchIO buildLaunch >> xmonad defaultConfig
|
||||
case args of
|
||||
[] -> launch
|
||||
["--resume", _] -> launch
|
||||
("--resume":_) -> launch
|
||||
["--help"] -> usage
|
||||
["--recompile"] -> recompile True >>= flip unless exitFailure
|
||||
["--replace"] -> launch
|
||||
["--restart"] -> sendRestart >> return ()
|
||||
["--version"] -> putStrLn ("xmonad " ++ showVersion version)
|
||||
["--version"] -> putStrLn $ unwords shortVersion
|
||||
["--verbose-version"] -> putStrLn . unwords $ shortVersion ++ longVersion
|
||||
#ifdef TESTING
|
||||
("--run-tests":_) -> Properties.main
|
||||
#endif
|
||||
_ -> fail "unrecognized flags"
|
||||
where
|
||||
shortVersion = ["xmonad", showVersion version]
|
||||
longVersion = [ "compiled by", compilerName, showVersion compilerVersion
|
||||
, "for", arch ++ "-" ++ os
|
||||
, "\nXinerama:", show compiledWithXinerama ]
|
||||
|
||||
usage :: IO ()
|
||||
usage = do
|
||||
@@ -58,6 +66,7 @@ usage = do
|
||||
" --help Print this message" :
|
||||
" --version Print the version number" :
|
||||
" --recompile Recompile your ~/.xmonad/xmonad.hs" :
|
||||
" --replace Replace the running window manager with xmonad" :
|
||||
" --restart Request a running xmonad process to restart" :
|
||||
#ifdef TESTING
|
||||
" --run-tests Run the test suite" :
|
||||
|
12
README
12
README
@@ -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:
|
||||
|
||||
|
2
TODO
2
TODO
@@ -16,6 +16,8 @@
|
||||
* test core with 6.6 and 6.8
|
||||
* bump xmonad.cabal version and X11 version
|
||||
* upload X11 and xmonad to Hackage
|
||||
* update links to hackage in download.html
|
||||
* update #xmonad topic
|
||||
* check examples/text in user-facing Config.hs
|
||||
* check tour.html and intro.html are up to date, and mention all core bindings
|
||||
* confirm template config is type correct
|
||||
|
111
XMonad/Config.hs
111
XMonad/Config.hs
@@ -25,13 +25,13 @@ module XMonad.Config (defaultConfig) where
|
||||
-- Useful imports
|
||||
--
|
||||
import XMonad.Core as XMonad hiding
|
||||
(workspaces,manageHook,numlockMask,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||
(workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
|
||||
,handleEventHook)
|
||||
,handleEventHook,clickJustFocuses)
|
||||
import qualified XMonad.Core as XMonad
|
||||
(workspaces,manageHook,numlockMask,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||
(workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
|
||||
,handleEventHook)
|
||||
,handleEventHook,clickJustFocuses)
|
||||
|
||||
import XMonad.Layout
|
||||
import XMonad.Operations
|
||||
@@ -64,22 +64,6 @@ workspaces = map show [1 .. 9 :: Int]
|
||||
defaultModMask :: KeyMask
|
||||
defaultModMask = mod1Mask
|
||||
|
||||
-- | The mask for the numlock key. Numlock status is "masked" from the
|
||||
-- current modifier status, so the keybindings will work with numlock on or
|
||||
-- off. You may need to change this on some systems.
|
||||
--
|
||||
-- You can find the numlock modifier by running "xmodmap" and looking for a
|
||||
-- modifier with Num_Lock bound to it:
|
||||
--
|
||||
-- > $ xmodmap | grep Num
|
||||
-- > mod2 Num_Lock (0x4d)
|
||||
--
|
||||
-- Set numlockMask = 0 if you don't have a numlock key, or want to treat
|
||||
-- numlock status separately.
|
||||
--
|
||||
numlockMask :: KeyMask
|
||||
numlockMask = mod2Mask
|
||||
|
||||
-- | Width of the window border in pixels.
|
||||
--
|
||||
borderWidth :: Dimension
|
||||
@@ -173,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)
|
||||
@@ -181,7 +170,7 @@ keys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
|
||||
keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
||||
-- launching and killing programs
|
||||
[ ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf) -- %! Launch terminal
|
||||
, ((modMask, xK_p ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"") -- %! Launch dmenu
|
||||
, ((modMask, xK_p ), spawn "dmenu_run") -- %! Launch dmenu
|
||||
, ((modMask .|. shiftMask, xK_p ), spawn "gmrun") -- %! Launch gmrun
|
||||
, ((modMask .|. shiftMask, xK_c ), kill) -- %! Close the focused window
|
||||
|
||||
@@ -213,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 "xmonad --recompile && xmonad --restart") -- %! Restart 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
|
||||
@@ -234,21 +224,20 @@ 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 $
|
||||
mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList
|
||||
-- mod-button1 %! Set the window to floating mode and move by dragging
|
||||
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w
|
||||
>> windows W.shiftMaster))
|
||||
[ ((modMask, button1), \w -> focus w >> mouseMoveWindow w
|
||||
>> windows W.shiftMaster)
|
||||
-- mod-button2 %! Raise the window to the top of the stack
|
||||
, ((modMask, button2), (\w -> focus w >> windows W.shiftMaster))
|
||||
, ((modMask, button2), windows . (W.shiftMaster .) . W.focusWindow)
|
||||
-- mod-button3 %! Set the window to floating mode and resize by dragging
|
||||
, ((modMask, button3), (\w -> focus w >> mouseResizeWindow w
|
||||
>> windows W.shiftMaster))
|
||||
, ((modMask, button3), \w -> focus w >> mouseResizeWindow w
|
||||
>> windows W.shiftMaster)
|
||||
-- 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
|
||||
@@ -256,7 +245,6 @@ defaultConfig = XConfig
|
||||
, XMonad.terminal = terminal
|
||||
, XMonad.normalBorderColor = normalBorderColor
|
||||
, XMonad.focusedBorderColor = focusedBorderColor
|
||||
, XMonad.numlockMask = numlockMask
|
||||
, XMonad.modMask = defaultModMask
|
||||
, XMonad.keys = keys
|
||||
, XMonad.logHook = logHook
|
||||
@@ -264,4 +252,57 @@ defaultConfig = XConfig
|
||||
, XMonad.mouseBindings = mouseBindings
|
||||
, XMonad.manageHook = manageHook
|
||||
, XMonad.handleEventHook = handleEventHook
|
||||
, XMonad.focusFollowsMouse = focusFollowsMouse }
|
||||
, 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"]
|
109
XMonad/Core.hs
109
XMonad/Core.hs
@@ -1,7 +1,5 @@
|
||||
{-# LANGUAGE ExistentialQuantification, FlexibleInstances, GeneralizedNewtypeDeriving,
|
||||
MultiParamTypeClasses, TypeSynonymInstances, CPP #-}
|
||||
-- required for deriving Typeable
|
||||
{-# OPTIONS_GHC -fglasgow-exts #-}
|
||||
MultiParamTypeClasses, TypeSynonymInstances, CPP, DeriveDataTypeable #-}
|
||||
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
@@ -24,16 +22,18 @@ module XMonad.Core (
|
||||
XConf(..), XConfig(..), LayoutClass(..),
|
||||
Layout(..), readsLayout, Typeable, Message,
|
||||
SomeMessage(..), fromMessage, LayoutMessages(..),
|
||||
StateExtension(..), ExtensionClass(..),
|
||||
runX, catchX, userCode, userCodeDef, io, catchIO, installSignalHandlers, uninstallSignalHandlers,
|
||||
withDisplay, withWindowSet, isRoot, runOnWorkspaces,
|
||||
getAtom, spawn, spawnPID, getXMonadDir, recompile, trace, whenJust, whenX,
|
||||
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runQuery
|
||||
getAtom, spawn, spawnPID, xfork, getXMonadDir, recompile, trace, whenJust, whenX,
|
||||
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, atom_WM_TAKE_FOCUS, ManageHook, Query(..), runQuery
|
||||
) where
|
||||
|
||||
import XMonad.StackSet hiding (modify)
|
||||
|
||||
import Prelude hiding ( catch )
|
||||
import Control.Exception (catch, try, bracket, throw, finally, Exception(ExitException))
|
||||
import Codec.Binary.UTF8.String (encodeString)
|
||||
import Control.Exception.Extensible (catch, fromException, try, bracket, throw, finally, SomeException(..))
|
||||
import Control.Applicative
|
||||
import Control.Monad.State
|
||||
import Control.Monad.Reader
|
||||
@@ -51,19 +51,25 @@ import Graphics.X11.Xlib
|
||||
import Graphics.X11.Xlib.Extras (Event)
|
||||
import Data.Typeable
|
||||
import Data.List ((\\))
|
||||
import Data.Maybe (isJust)
|
||||
import Data.Maybe (isJust,fromMaybe)
|
||||
import Data.Monoid
|
||||
import Data.Maybe (fromMaybe)
|
||||
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Set as S
|
||||
|
||||
-- | 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 ())) }
|
||||
{ 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 ()))
|
||||
, numberlockMask :: !KeyMask -- ^ The numlock modifier
|
||||
, extensibleState :: !(M.Map String (Either String StateExtension))
|
||||
-- ^ stores custom state information.
|
||||
--
|
||||
-- The module "XMonad.Utils.ExtensibleState" in xmonad-contrib
|
||||
-- provides additional information and a simple interface for using this.
|
||||
}
|
||||
|
||||
-- | XConf, the (read-only) window manager configuration.
|
||||
data XConf = XConf
|
||||
@@ -80,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
|
||||
@@ -93,7 +101,6 @@ data XConfig l = XConfig
|
||||
-- should also be run afterwards. mappend should be used for combining
|
||||
-- event hooks in most cases.
|
||||
, workspaces :: ![String] -- ^ The list of workspaces' names
|
||||
, numlockMask :: !KeyMask -- ^ The numlock modifier
|
||||
, modMask :: !KeyMask -- ^ the mod modifier
|
||||
, keys :: !(XConfig Layout -> M.Map (ButtonMask,KeySym) (X ()))
|
||||
-- ^ The key binding: a map from key presses and actions
|
||||
@@ -103,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
|
||||
}
|
||||
|
||||
|
||||
@@ -129,9 +137,7 @@ data ScreenDetail = SD { screenRect :: !Rectangle } deriving (Eq,Show, Read)
|
||||
-- instantiated on 'XConf' and 'XState' automatically.
|
||||
--
|
||||
newtype X a = X (ReaderT XConf (StateT XState IO) a)
|
||||
#ifndef __HADDOCK__
|
||||
deriving (Functor, Monad, MonadIO, MonadState XState, MonadReader XConf, Typeable)
|
||||
#endif
|
||||
|
||||
instance Applicative X where
|
||||
pure = return
|
||||
@@ -143,9 +149,7 @@ instance (Monoid a) => Monoid (X a) where
|
||||
|
||||
type ManageHook = Query (Endo WindowSet)
|
||||
newtype Query a = Query (ReaderT Window X a)
|
||||
#ifndef __HADDOCK__
|
||||
deriving (Functor, Monad, MonadReader Window, MonadIO)
|
||||
#endif
|
||||
|
||||
runQuery :: Query a -> Window -> X a
|
||||
runQuery (Query m) w = runReaderT m w
|
||||
@@ -165,9 +169,9 @@ catchX :: X a -> X a -> X a
|
||||
catchX job errcase = do
|
||||
st <- get
|
||||
c <- ask
|
||||
(a, s') <- io $ runX c st job `catch` \e -> case e of
|
||||
ExitException {} -> throw e
|
||||
_ -> do hPrint stderr e; runX c st errcase
|
||||
(a, s') <- io $ runX c st job `catch` \e -> case fromException e of
|
||||
Just x -> throw e `const` (x `asTypeOf` ExitSuccess)
|
||||
_ -> do hPrint stderr e; runX c st errcase
|
||||
put s'
|
||||
return a
|
||||
|
||||
@@ -201,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
|
||||
@@ -343,6 +348,33 @@ data LayoutMessages = Hide -- ^ sent when a layout becomes non-visi
|
||||
|
||||
instance Message LayoutMessages
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
-- Extensible state
|
||||
--
|
||||
|
||||
-- | Every module must make the data it wants to store
|
||||
-- an instance of this class.
|
||||
--
|
||||
-- Minimal complete definition: initialValue
|
||||
class Typeable a => ExtensionClass a where
|
||||
-- | Defines an initial value for the state extension
|
||||
initialValue :: a
|
||||
-- | Specifies whether the state extension should be
|
||||
-- persistent. Setting this method to 'PersistentExtension'
|
||||
-- will make the stored data survive restarts, but
|
||||
-- requires a to be an instance of Read and Show.
|
||||
--
|
||||
-- It defaults to 'StateExtension', i.e. no persistence.
|
||||
extensionType :: a -> StateExtension
|
||||
extensionType = StateExtension
|
||||
|
||||
-- | Existential type to store a state extension.
|
||||
data StateExtension =
|
||||
forall a. ExtensionClass a => StateExtension a
|
||||
-- ^ Non-persistent state extension
|
||||
| forall a. (Read a, Show a, ExtensionClass a) => PersistentExtension a
|
||||
-- ^ Persistent extension
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
-- | General utilities
|
||||
--
|
||||
@@ -353,19 +385,25 @@ io = liftIO
|
||||
-- | Lift an 'IO' action into the 'X' monad. If the action results in an 'IO'
|
||||
-- exception, log the exception to stderr and continue normal execution.
|
||||
catchIO :: MonadIO m => IO () -> m ()
|
||||
catchIO f = io (f `catch` \e -> hPrint stderr e >> hFlush stderr)
|
||||
catchIO f = io (f `catch` \(SomeException e) -> hPrint stderr e >> hFlush stderr)
|
||||
|
||||
-- | spawn. Launch an external application. Specifically, it double-forks and
|
||||
-- runs the 'String' you pass as a command to /bin/sh.
|
||||
-- runs the 'String' you pass as a command to \/bin\/sh.
|
||||
--
|
||||
-- Note this function assumes your locale uses utf8.
|
||||
spawn :: MonadIO m => String -> m ()
|
||||
spawn x = spawnPID x >> return ()
|
||||
|
||||
-- | Like 'spawn', but returns the 'ProcessID' of the launched application
|
||||
spawnPID :: MonadIO m => String -> m ProcessID
|
||||
spawnPID x = io . forkProcess . finally nullStdin $ do
|
||||
spawnPID x = xfork $ executeFile "/bin/sh" False ["-c", encodeString x] Nothing
|
||||
|
||||
-- | A replacement for 'forkProcess' which resets default signal handlers.
|
||||
xfork :: MonadIO m => IO () -> m ProcessID
|
||||
xfork x = io . forkProcess . finally nullStdin $ do
|
||||
uninstallSignalHandlers
|
||||
createSession
|
||||
executeFile "/bin/sh" False ["-c", x] Nothing
|
||||
x
|
||||
where
|
||||
nullStdin = do
|
||||
fd <- openFd "/dev/null" ReadOnly Nothing defaultFileFlags
|
||||
@@ -393,9 +431,11 @@ getXMonadDir = io $ getAppUserDataDirectory "xmonad"
|
||||
--
|
||||
-- * the xmonad executable does not exist
|
||||
--
|
||||
-- * the xmonad executable is older than xmonad.hs
|
||||
-- * the xmonad executable is older than xmonad.hs or any file in
|
||||
-- ~\/.xmonad\/lib
|
||||
--
|
||||
-- The -i flag is used to restrict recompilation to the xmonad.hs file only.
|
||||
-- The -i flag is used to restrict recompilation to the xmonad.hs file only,
|
||||
-- and any files in the ~\/.xmonad\/lib directory.
|
||||
--
|
||||
-- Compilation errors (if any) are logged to ~\/.xmonad\/xmonad.errors. If
|
||||
-- GHC indicates failure with a non-zero exit code, an xmessage displaying
|
||||
@@ -419,7 +459,7 @@ recompile force = io $ do
|
||||
then do
|
||||
-- temporarily disable SIGCHLD ignoring:
|
||||
uninstallSignalHandlers
|
||||
status <- bracket (openFile err WriteMode) hClose $ \h -> do
|
||||
status <- bracket (openFile err WriteMode) hClose $ \h ->
|
||||
waitForProcess =<< runProcess "ghc" ["--make", "xmonad.hs", "-i", "-ilib", "-fforce-recomp", "-v0", "-o",binn] (Just dir)
|
||||
Nothing Nothing Nothing (Just h)
|
||||
|
||||
@@ -431,7 +471,8 @@ recompile force = io $ do
|
||||
ghcErr <- readFile err
|
||||
let msg = unlines $
|
||||
["Error detected while loading xmonad configuration file: " ++ src]
|
||||
++ lines ghcErr ++ ["","Please check the file for errors."]
|
||||
++ lines (if null ghcErr then show status else ghcErr)
|
||||
++ ["","Please check the file for errors."]
|
||||
-- nb, the ordering of printing, then forking, is crucial due to
|
||||
-- lazy evaluation
|
||||
hPutStrLn stderr msg
|
||||
@@ -439,11 +480,11 @@ recompile force = io $ do
|
||||
return ()
|
||||
return (status == ExitSuccess)
|
||||
else return True
|
||||
where getModTime f = catch (Just <$> getModificationTime f) (const $ return Nothing)
|
||||
isSource = flip elem [".hs",".lhs",".hsc"]
|
||||
where getModTime f = catch (Just <$> getModificationTime f) (\(SomeException _) -> return Nothing)
|
||||
isSource = flip elem [".hs",".lhs",".hsc"] . takeExtension
|
||||
allFiles t = do
|
||||
let prep = map (t</>) . Prelude.filter (`notElem` [".",".."])
|
||||
cs <- prep <$> catch (getDirectoryContents t) (\_ -> return [])
|
||||
cs <- prep <$> catch (getDirectoryContents t) (\(SomeException _) -> return [])
|
||||
ds <- filterM doesDirectoryExist cs
|
||||
concat . ((cs \\ ds):) <$> mapM allFiles ds
|
||||
|
||||
@@ -466,12 +507,14 @@ installSignalHandlers :: MonadIO m => m ()
|
||||
installSignalHandlers = io $ do
|
||||
installHandler openEndedPipe Ignore Nothing
|
||||
installHandler sigCHLD Ignore Nothing
|
||||
try $ fix $ \more -> do
|
||||
(try :: IO a -> IO (Either SomeException a))
|
||||
$ fix $ \more -> do
|
||||
x <- getAnyProcessStatus False False
|
||||
when (isJust x) more
|
||||
return ()
|
||||
|
||||
uninstallSignalHandlers :: MonadIO m => m ()
|
||||
uninstallSignalHandlers = io $ do
|
||||
installHandler openEndedPipe Default Nothing
|
||||
installHandler sigCHLD Default Nothing
|
||||
return ()
|
||||
|
@@ -1,5 +1,4 @@
|
||||
{-# OPTIONS_GHC -fglasgow-exts #-} -- For deriving Data/Typeable
|
||||
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards, TypeSynonymInstances #-}
|
||||
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards, TypeSynonymInstances, DeriveDataTypeable #-}
|
||||
|
||||
-- --------------------------------------------------------------------------
|
||||
-- |
|
||||
@@ -53,7 +52,8 @@ instance LayoutClass Full a
|
||||
-- 'IncMasterN'.
|
||||
data Tall a = Tall { tallNMaster :: !Int -- ^ The default number of windows in the master pane (default: 1)
|
||||
, tallRatioIncrement :: !Rational -- ^ Percent of screen to increment by when resizing panes (default: 3/100)
|
||||
, tallRatio :: !Rational } -- ^ Default proportion of screen occupied by master pane (default: 1/2)
|
||||
, tallRatio :: !Rational -- ^ Default proportion of screen occupied by master pane (default: 1/2)
|
||||
}
|
||||
deriving (Show, Read)
|
||||
-- TODO should be capped [0..1] ..
|
||||
|
||||
@@ -125,7 +125,7 @@ instance LayoutClass l a => LayoutClass (Mirror l) a where
|
||||
|
||||
-- | Mirror a rectangle.
|
||||
mirrorRect :: Rectangle -> Rectangle
|
||||
mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
|
||||
mirrorRect (Rectangle rx ry rw rh) = Rectangle ry rx rh rw
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- LayoutClass selection manager
|
||||
@@ -173,7 +173,7 @@ choose (Choose d l r) d' ml mr = f lr
|
||||
|
||||
instance (LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a where
|
||||
runLayout (W.Workspace i (Choose L l r) ms) =
|
||||
fmap (second . fmap $ flip (Choose L) $ r) . runLayout (W.Workspace i l ms)
|
||||
fmap (second . fmap $ flip (Choose L) r) . runLayout (W.Workspace i l ms)
|
||||
runLayout (W.Workspace i (Choose R l r) ms) =
|
||||
fmap (second . fmap $ Choose R l) . runLayout (W.Workspace i r ms)
|
||||
|
||||
@@ -194,7 +194,7 @@ instance (LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a where
|
||||
|
||||
R -> choose c R Nothing =<< handle r NextNoWrap
|
||||
|
||||
handleMessage c@(Choose _ l _) m | Just FirstLayout <- fromMessage m = do
|
||||
handleMessage c@(Choose _ l _) m | Just FirstLayout <- fromMessage m =
|
||||
flip (choose c L) Nothing =<< handle l FirstLayout
|
||||
|
||||
handleMessage c@(Choose d l r) m | Just ReleaseResources <- fromMessage m =
|
||||
|
@@ -15,8 +15,10 @@
|
||||
|
||||
module XMonad.Main (xmonad) where
|
||||
|
||||
import Control.Arrow (second)
|
||||
import Data.Bits
|
||||
import Data.List ((\\))
|
||||
import Data.Function
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Set as S
|
||||
import Control.Monad.Reader
|
||||
@@ -66,6 +68,10 @@ xmonad initxmc = do
|
||||
|
||||
rootw <- rootWindow dpy dflt
|
||||
|
||||
args <- getArgs
|
||||
|
||||
when ("--replace" `elem` args) $ replace dpy dflt rootw
|
||||
|
||||
-- If another WM is running, a BadAccess error will be returned. The
|
||||
-- default error handler will write the exception to stderr and exit with
|
||||
-- an error.
|
||||
@@ -88,12 +94,10 @@ xmonad initxmc = do
|
||||
return (fromMaybe fbc_ v)
|
||||
|
||||
hSetBuffering stdout NoBuffering
|
||||
args <- getArgs
|
||||
|
||||
let layout = layoutHook xmc
|
||||
lreads = readsLayout layout
|
||||
initialWinset = new layout (workspaces xmc) $ map SD xinesc
|
||||
|
||||
maybeRead reads' s = case reads' s of
|
||||
[(x, "")] -> Just x
|
||||
_ -> Nothing
|
||||
@@ -103,6 +107,10 @@ xmonad initxmc = do
|
||||
ws <- maybeRead reads s
|
||||
return . W.ensureTags layout (workspaces xmc)
|
||||
$ W.mapLayout (fromMaybe layout . maybeRead lreads) ws
|
||||
extState = fromMaybe M.empty $ do
|
||||
("--resume" : _ : dyns : _) <- return args
|
||||
vals <- maybeRead reads dyns
|
||||
return . M.fromList . map (second Left) $ vals
|
||||
|
||||
cf = XConf
|
||||
{ display = dpy
|
||||
@@ -113,16 +121,21 @@ xmonad initxmc = do
|
||||
, keyActions = keys xmc xmc
|
||||
, buttonActions = mouseBindings xmc xmc
|
||||
, mouseFocused = False
|
||||
, mousePosition = Nothing }
|
||||
st = XState
|
||||
{ windowset = initialWinset
|
||||
, mapped = S.empty
|
||||
, waitingUnmap = M.empty
|
||||
, dragging = Nothing }
|
||||
, mousePosition = Nothing
|
||||
, currentEvent = Nothing }
|
||||
|
||||
st = XState
|
||||
{ windowset = initialWinset
|
||||
, numberlockMask = 0
|
||||
, mapped = S.empty
|
||||
, waitingUnmap = M.empty
|
||||
, dragging = Nothing
|
||||
, extensibleState = extState
|
||||
}
|
||||
allocaXEvent $ \e ->
|
||||
runX cf st $ do
|
||||
|
||||
setNumlockMask
|
||||
grabKeys
|
||||
grabButtons
|
||||
|
||||
@@ -143,17 +156,15 @@ xmonad initxmc = do
|
||||
userCode $ startupHook initxmc
|
||||
|
||||
-- main loop, for all you HOF/recursion fans out there.
|
||||
forever_ $ prehandle =<< io (nextEvent dpy e >> getEvent e)
|
||||
forever $ prehandle =<< io (nextEvent dpy e >> getEvent e)
|
||||
|
||||
return ()
|
||||
where
|
||||
forever_ a = a >> forever_ a
|
||||
|
||||
-- if the event gives us the position of the pointer, set mousePosition
|
||||
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]
|
||||
|
||||
@@ -212,7 +223,9 @@ handle (UnmapEvent {ev_window = w, ev_send_event = synthetic}) = whenX (isClient
|
||||
-- set keyboard mapping
|
||||
handle e@(MappingNotifyEvent {}) = do
|
||||
io $ refreshKeyboardMapping e
|
||||
when (ev_request e == mappingKeyboard) grabKeys
|
||||
when (ev_request e `elem` [mappingKeyboard, mappingModifier]) $ do
|
||||
setNumlockMask
|
||||
grabKeys
|
||||
|
||||
-- handle button release, which may finish dragging.
|
||||
handle e@(ButtonEvent {ev_event_type = t})
|
||||
@@ -235,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
|
||||
@@ -285,8 +302,9 @@ handle e@(ConfigureRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
|
||||
handle (ConfigureEvent {ev_window = w}) = whenX (isRoot w) rescreen
|
||||
|
||||
-- property notify
|
||||
handle PropertyEvent { ev_event_type = t, ev_atom = a }
|
||||
| t == propertyNotify && a == wM_NAME = userCodeDef () =<< asks (logHook . config)
|
||||
handle event@(PropertyEvent { ev_event_type = t, ev_atom = a })
|
||||
| t == propertyNotify && a == wM_NAME = asks (logHook . config) >>= userCodeDef () >>
|
||||
broadcastMessage event
|
||||
|
||||
handle e@ClientMessageEvent { ev_message_type = mt } = do
|
||||
a <- getAtom "XMONAD_RESTART"
|
||||
@@ -318,6 +336,18 @@ scan dpy rootw = do
|
||||
return $ not (wa_override_redirect wa)
|
||||
&& (wa_map_state wa == waIsViewable || ic)
|
||||
|
||||
setNumlockMask :: X ()
|
||||
setNumlockMask = do
|
||||
dpy <- asks display
|
||||
ms <- io $ getModifierMapping dpy
|
||||
xs <- sequence [ do
|
||||
ks <- io $ keycodeToKeysym dpy kc 0
|
||||
if ks == xK_Num_Lock
|
||||
then return (setBit 0 (fromIntegral m))
|
||||
else return (0 :: KeyMask)
|
||||
| (m, kcs) <- ms, kc <- kcs, kc /= 0]
|
||||
modify (\s -> s { numberlockMask = foldr (.|.) 0 xs })
|
||||
|
||||
-- | Grab the keys back
|
||||
grabKeys :: X ()
|
||||
grabKeys = do
|
||||
@@ -329,7 +359,7 @@ grabKeys = do
|
||||
kc <- io $ keysymToKeycode dpy sym
|
||||
-- "If the specified KeySym is not defined for any KeyCode,
|
||||
-- XKeysymToKeycode() returns zero."
|
||||
when (kc /= '\0') $ mapM_ (grab kc . (mask .|.)) =<< extraModifiers
|
||||
when (kc /= 0) $ mapM_ (grab kc . (mask .|.)) =<< extraModifiers
|
||||
|
||||
-- | XXX comment me
|
||||
grabButtons :: X ()
|
||||
@@ -341,3 +371,36 @@ grabButtons = do
|
||||
ems <- extraModifiers
|
||||
ba <- asks buttonActions
|
||||
mapM_ (\(m,b) -> mapM_ (grab b . (m .|.)) ems) (M.keys $ ba)
|
||||
|
||||
-- | @replace@ to signals compliant window managers to exit.
|
||||
replace :: Display -> ScreenNumber -> Window -> IO ()
|
||||
replace dpy dflt rootw = do
|
||||
-- check for other WM
|
||||
wmSnAtom <- internAtom dpy ("WM_S" ++ show dflt) False
|
||||
currentWmSnOwner <- xGetSelectionOwner dpy wmSnAtom
|
||||
when (currentWmSnOwner /= 0) $ do
|
||||
-- prepare to receive destroyNotify for old WM
|
||||
selectInput dpy currentWmSnOwner structureNotifyMask
|
||||
|
||||
-- create off-screen window
|
||||
netWmSnOwner <- allocaSetWindowAttributes $ \attributes -> do
|
||||
set_override_redirect attributes True
|
||||
set_event_mask attributes propertyChangeMask
|
||||
let screen = defaultScreenOfDisplay dpy
|
||||
visual = defaultVisualOfScreen screen
|
||||
attrmask = cWOverrideRedirect .|. cWEventMask
|
||||
createWindow dpy rootw (-100) (-100) 1 1 0 copyFromParent copyFromParent visual attrmask attributes
|
||||
|
||||
-- try to acquire wmSnAtom, this should signal the old WM to terminate
|
||||
xSetSelectionOwner dpy wmSnAtom netWmSnOwner currentTime
|
||||
|
||||
-- SKIPPED: check if we acquired the selection
|
||||
-- SKIPPED: send client message indicating that we are now the WM
|
||||
|
||||
-- wait for old WM to go away
|
||||
fix $ \again -> do
|
||||
evt <- allocaXEvent $ \event -> do
|
||||
windowEvent dpy currentWmSnOwner structureNotifyMask event
|
||||
get_EventType event
|
||||
|
||||
when (evt /= destroyNotify) again
|
||||
|
@@ -22,7 +22,7 @@ import Prelude hiding (catch)
|
||||
import XMonad.Core
|
||||
import Graphics.X11.Xlib.Extras
|
||||
import Graphics.X11.Xlib (Display, Window, internAtom, wM_NAME)
|
||||
import Control.Exception (bracket, catch)
|
||||
import Control.Exception.Extensible (bracket, catch, SomeException(..))
|
||||
import Control.Monad.Reader
|
||||
import Data.Maybe
|
||||
import Data.Monoid
|
||||
@@ -34,22 +34,24 @@ liftX :: X a -> Query a
|
||||
liftX = Query . lift
|
||||
|
||||
-- | The identity hook that returns the WindowSet unchanged.
|
||||
idHook :: ManageHook
|
||||
idHook = doF id
|
||||
idHook :: Monoid m => m
|
||||
idHook = mempty
|
||||
|
||||
-- | Compose two 'ManageHook's.
|
||||
(<+>) :: ManageHook -> ManageHook -> ManageHook
|
||||
-- | Infix 'mappend'. Compose two 'ManageHook' from right to left.
|
||||
(<+>) :: Monoid m => m -> m -> m
|
||||
(<+>) = mappend
|
||||
|
||||
-- | Compose the list of 'ManageHook's.
|
||||
composeAll :: [ManageHook] -> ManageHook
|
||||
composeAll :: Monoid m => [m] -> m
|
||||
composeAll = mconcat
|
||||
|
||||
infix 0 -->
|
||||
|
||||
-- | @p --> x@. If @p@ returns 'True', execute the 'ManageHook'.
|
||||
(-->) :: Query Bool -> ManageHook -> ManageHook
|
||||
p --> f = p >>= \b -> if b then f else mempty
|
||||
--
|
||||
-- > (-->) :: Monoid m => Query Bool -> Query m -> Query m -- a simpler type
|
||||
(-->) :: (Monad m, Monoid a) => m Bool -> m a -> m a
|
||||
p --> f = p >>= \b -> if b then f else return mempty
|
||||
|
||||
-- | @q =? x@. if the result of @q@ equals @x@, return 'True'.
|
||||
(=?) :: Eq a => Query a -> a -> Query Bool
|
||||
@@ -72,10 +74,10 @@ title = ask >>= \w -> liftX $ do
|
||||
let
|
||||
getProp =
|
||||
(internAtom d "_NET_WM_NAME" False >>= getTextProperty d w)
|
||||
`catch` \_ -> getTextProperty d w wM_NAME
|
||||
`catch` \(SomeException _) -> getTextProperty d w wM_NAME
|
||||
extract prop = do l <- wcTextPropertyToTextList d prop
|
||||
return $ if null l then "" else head l
|
||||
io $ bracket getProp (xFree . tp_value) extract `catch` \_ -> return ""
|
||||
io $ bracket getProp (xFree . tp_value) extract `catch` \(SomeException _) -> return ""
|
||||
|
||||
-- | Return the application name.
|
||||
appName :: Query String
|
||||
@@ -101,7 +103,7 @@ getStringProperty d w p = do
|
||||
return $ fmap (map (toEnum . fromIntegral)) md
|
||||
|
||||
-- | Modify the 'WindowSet' with a pure function.
|
||||
doF :: (WindowSet -> WindowSet) -> ManageHook
|
||||
doF :: (s -> s) -> Query (Endo s)
|
||||
doF = return . Endo
|
||||
|
||||
-- | Move the window to the floating layer.
|
||||
|
@@ -1,5 +1,4 @@
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||
{-# OPTIONS_GHC -fglasgow-exts #-} -- For deriving Data/Typeable
|
||||
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards, TypeSynonymInstances #-}
|
||||
|
||||
-- --------------------------------------------------------------------------
|
||||
@@ -25,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
|
||||
@@ -33,9 +32,8 @@ import qualified Data.Set as S
|
||||
import Control.Applicative
|
||||
import Control.Monad.Reader
|
||||
import Control.Monad.State
|
||||
import qualified Control.Exception as C
|
||||
import qualified Control.Exception.Extensible as C
|
||||
|
||||
import System.IO
|
||||
import System.Posix.Process (executeFile)
|
||||
import Graphics.X11.Xlib
|
||||
import Graphics.X11.Xinerama (getScreenInfo)
|
||||
@@ -68,7 +66,7 @@ manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do
|
||||
where i = W.tag $ W.workspace $ W.current ws
|
||||
|
||||
mh <- asks (manageHook . config)
|
||||
g <- fmap appEndo $ userCodeDef (Endo id) (runQuery mh w)
|
||||
g <- appEndo <$> userCodeDef (Endo id) (runQuery mh w)
|
||||
windows (g . f)
|
||||
|
||||
-- | unmanage. A window no longer exists, remove it from the window
|
||||
@@ -155,13 +153,13 @@ windows f = do
|
||||
|
||||
whenJust (W.peek ws) $ \w -> io $ setWindowBorder d w fbc
|
||||
|
||||
mapM_ reveal visible
|
||||
setTopFocus
|
||||
|
||||
-- hide every window that was potentially visible before, but is not
|
||||
-- given a position by a layout now.
|
||||
mapM_ hide (nub (oldvisible ++ newwindows) \\ visible)
|
||||
|
||||
mapM_ reveal visible
|
||||
setTopFocus
|
||||
|
||||
-- all windows that are no longer in the windowset are marked as
|
||||
-- withdrawn, it is important to do this after the above, otherwise 'hide'
|
||||
-- will overwrite withdrawnState with iconicState
|
||||
@@ -201,7 +199,7 @@ reveal :: Window -> X ()
|
||||
reveal w = withDisplay $ \d -> do
|
||||
setWMState w normalState
|
||||
io $ mapWindow d w
|
||||
modify (\s -> s { mapped = S.insert w (mapped s) })
|
||||
whenX (isClient w) $ modify (\s -> s { mapped = S.insert w (mapped s) })
|
||||
|
||||
-- | The client events that xmonad is interested in
|
||||
clientMask :: EventMask
|
||||
@@ -211,7 +209,7 @@ clientMask = structureNotifyMask .|. enterWindowMask .|. propertyChangeMask
|
||||
setInitialProperties :: Window -> X ()
|
||||
setInitialProperties w = asks normalBorder >>= \nb -> withDisplay $ \d -> do
|
||||
setWMState w iconicState
|
||||
io $ selectInput d w $ clientMask
|
||||
io $ selectInput d w clientMask
|
||||
bw <- asks (borderWidth . config)
|
||||
io $ setWindowBorderWidth d w bw
|
||||
-- we must initially set the color of new windows, to maintain invariants
|
||||
@@ -285,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
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
@@ -321,14 +322,33 @@ setFocusX w = withWindowSet $ \ws -> do
|
||||
dpy <- asks display
|
||||
|
||||
-- clear mouse button grab and border on other windows
|
||||
forM_ (W.current ws : W.visible ws) $ \wk -> do
|
||||
forM_ (W.index (W.view (W.tag (W.workspace wk)) ws)) $ \otherw -> do
|
||||
forM_ (W.current ws : W.visible ws) $ \wk ->
|
||||
forM_ (W.index (W.view (W.tag (W.workspace wk)) ws)) $ \otherw ->
|
||||
setButtonGrab True otherw
|
||||
|
||||
-- If we ungrab buttons on the root window, we lose our mouse bindings.
|
||||
whenX (not <$> isRoot w) $ setButtonGrab False w
|
||||
io $ do setInputFocus dpy w revertToPointerRoot 0
|
||||
-- raiseWindow dpy w
|
||||
|
||||
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
|
||||
@@ -339,7 +359,7 @@ sendMessage :: Message a => a -> X ()
|
||||
sendMessage a = do
|
||||
w <- W.workspace . W.current <$> gets windowset
|
||||
ml' <- handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing
|
||||
whenJust ml' $ \l' -> do
|
||||
whenJust ml' $ \l' ->
|
||||
windows $ \ws -> ws { W.current = (W.current ws)
|
||||
{ W.workspace = (W.workspace $ W.current ws)
|
||||
{ W.layout = l' }}}
|
||||
@@ -389,18 +409,18 @@ isClient w = withWindowSet $ return . W.member w
|
||||
-- (numlock and capslock)
|
||||
extraModifiers :: X [KeyMask]
|
||||
extraModifiers = do
|
||||
nlm <- asks (numlockMask . config)
|
||||
nlm <- gets numberlockMask
|
||||
return [0, nlm, lockMask, nlm .|. lockMask ]
|
||||
|
||||
-- | Strip numlock\/capslock from a mask
|
||||
cleanMask :: KeyMask -> X KeyMask
|
||||
cleanMask km = do
|
||||
nlm <- asks (numlockMask . config)
|
||||
nlm <- gets numberlockMask
|
||||
return (complement (nlm .|. lockMask) .&. km)
|
||||
|
||||
-- | Get the 'Pixel' value for a named color
|
||||
initColor :: Display -> String -> IO (Maybe Pixel)
|
||||
initColor dpy c = C.handle (\_ -> return Nothing) $
|
||||
initColor dpy c = C.handle (\(C.SomeException _) -> return Nothing) $
|
||||
(Just . color_pixel . fst) <$> allocNamedColor dpy colormap c
|
||||
where colormap = defaultColormap dpy (defaultScreen dpy)
|
||||
|
||||
@@ -413,9 +433,13 @@ restart :: String -> Bool -> X ()
|
||||
restart prog resume = do
|
||||
broadcastMessage ReleaseResources
|
||||
io . flush =<< asks display
|
||||
args <- if resume then gets (("--resume":) . return . showWs . windowset) else return []
|
||||
let wsData = show . W.mapLayout show . windowset
|
||||
maybeShow (t, Right (PersistentExtension ext)) = Just (t, show ext)
|
||||
maybeShow (t, Left str) = Just (t, str)
|
||||
maybeShow _ = Nothing
|
||||
extState = return . show . catMaybes . map maybeShow . M.toList . extensibleState
|
||||
args <- if resume then gets (\s -> "--resume":wsData s:extState s) else return []
|
||||
catchIO (executeFile prog True args Nothing)
|
||||
where showWs = show . W.mapLayout show
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- | Floating layer support
|
||||
@@ -435,7 +459,7 @@ floatLocation w = withDisplay $ \d -> do
|
||||
(fi (wa_width wa + bw*2) % fi (rect_width sr))
|
||||
(fi (wa_height wa + bw*2) % fi (rect_height sr))
|
||||
|
||||
return (W.screen $ sc, rr)
|
||||
return (W.screen sc, rr)
|
||||
where fi x = fromIntegral x
|
||||
|
||||
-- | Given a point, determine the screen (if any) that contains it.
|
||||
@@ -505,7 +529,7 @@ mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do
|
||||
wa <- io $ getWindowAttributes d w
|
||||
sh <- io $ getWMNormalHints d w
|
||||
io $ warpPointer d none w 0 0 0 0 (fromIntegral (wa_width wa)) (fromIntegral (wa_height wa))
|
||||
mouseDrag (\ex ey -> do
|
||||
mouseDrag (\ex ey ->
|
||||
io $ resizeWindow d w `uncurry`
|
||||
applySizeHintsContents sh (ex - fromIntegral (wa_x wa),
|
||||
ey - fromIntegral (wa_y wa)))
|
||||
|
@@ -52,7 +52,7 @@ module XMonad.StackSet (
|
||||
) where
|
||||
|
||||
import Prelude hiding (filter)
|
||||
import Data.Maybe (listToMaybe,isJust)
|
||||
import Data.Maybe (listToMaybe,isJust,fromMaybe)
|
||||
import qualified Data.List as L (deleteBy,find,splitAt,filter,nub)
|
||||
import Data.List ( (\\) )
|
||||
import qualified Data.Map as M (Map,insert,delete,empty)
|
||||
@@ -155,7 +155,7 @@ data RationalRect = RationalRect Rational Rational Rational Rational
|
||||
deriving (Show, Read, Eq)
|
||||
|
||||
-- |
|
||||
-- A stack is a cursor onto a (possibly empty) window list.
|
||||
-- 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
|
||||
@@ -369,7 +369,7 @@ reverseStack (Stack t ls rs) = Stack t rs ls
|
||||
--
|
||||
focusWindow :: (Eq s, Eq a, Eq i) => a -> StackSet i l a s sd -> StackSet i l a s sd
|
||||
focusWindow w s | Just w == peek s = s
|
||||
| otherwise = maybe s id $ do
|
||||
| otherwise = fromMaybe s $ do
|
||||
n <- findTag w s
|
||||
return $ until ((Just w ==) . peek) focusUp (view n s)
|
||||
|
||||
|
71
man/HCAR.tex
Normal file
71
man/HCAR.tex
Normal file
@@ -0,0 +1,71 @@
|
||||
% xmonad-Gx.tex
|
||||
\begin{hcarentry}{xmonad}
|
||||
\label{xmonad}
|
||||
\report{Gwern Branwen}%11/11
|
||||
\status{active development}
|
||||
\makeheader
|
||||
|
||||
XMonad is a tiling window manager for X. Windows are arranged
|
||||
automatically to tile the screen without gaps or overlap, maximizing
|
||||
screen use. Window manager features are accessible from the keyboard; a
|
||||
mouse is optional. XMonad is written, configured, and extensible in
|
||||
Haskell. Custom layout algorithms, key bindings, and other extensions may
|
||||
be written by the user in config files. Layouts are applied
|
||||
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; 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.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
|
||||
\item xmonad --replace CLI option
|
||||
\item XMonad.Prompt now has customizable keymaps
|
||||
\item Actions.GridSelect - a GUI menu for selecting windows or workspaces \& substring search on window names
|
||||
\item Actions.OnScreen
|
||||
\item Extensions now can have state
|
||||
\item Actions.SpawnOn - uses state to spawn applications on the workspace the user was originally on,
|
||||
and not where the user happens to be
|
||||
\item Markdown manpages and not man/troff
|
||||
\item XMonad.Layout.ImageButtonDecoration \&\\ XMonad.Util.Image
|
||||
\item XMonad.Layout.Groups
|
||||
\item XMonad.Layout.ZoomRow
|
||||
\item XMonad.Layout.Renamed
|
||||
\item XMonad.Layout.Drawer
|
||||
\item XMonad.Layout.FullScreen
|
||||
\item XMonad.Hooks.ScreenCorners
|
||||
\item XMonad.Actions.DynamicWorkspaceOrder
|
||||
\item XMonad.Actions.WorkspaceNames
|
||||
\item XMonad.Actions.DynamicWorkspaceGroups
|
||||
\end{compactitem}
|
||||
|
||||
Binary packages of XMonad and XMonadContrib are available for all major Linux distributions.
|
||||
|
||||
\FurtherReading
|
||||
\begin{compactitem}
|
||||
\item Homepage:
|
||||
\url{http://xmonad.org/}
|
||||
|
||||
\item Darcs source:
|
||||
|
||||
\texttt{darcs get} \url{http://code.haskell.org/xmonad}
|
||||
|
||||
\item IRC channel:
|
||||
\verb+#xmonad @@ irc.freenode.org+
|
||||
|
||||
\item Mailing list:
|
||||
\email{xmonad@@haskell.org}
|
||||
\end{compactitem}
|
||||
\end{hcarentry}
|
281
man/xmonad.1
Normal file
281
man/xmonad.1
Normal 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
181
man/xmonad.1.html
Normal 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 "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.</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">"function1: Not implemented yet!"</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>
|
@@ -1,57 +0,0 @@
|
||||
./" man page created by David Lazar on April 24, 2007
|
||||
./" uses ``tmac.an'' macro set
|
||||
.TH xmonad 1 "8 September 09"\
|
||||
___RELEASE___\
|
||||
"xmonad manual"
|
||||
.SH NAME
|
||||
xmonad \- a tiling window manager
|
||||
.SH DESCRIPTION
|
||||
.PP
|
||||
\fBxmonad\fR 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. \fBxmonad\fR is configured in Haskell, and custom layout algorithms may be implemented by the user in config files. A principle of \fBxmonad\fR is predictability: the user should know in advance precisely the window arrangement that will result from any action.
|
||||
.PP
|
||||
By default, \fBxmonad\fR 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, \fBxmonad\fR 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
|
||||
\fBxmonad\fR 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 \fBxmonad\fR 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.
|
||||
.PP
|
||||
.SS Flags
|
||||
\fBxmonad\fR has several flags which you may pass to the executable. These flags are:
|
||||
.TP
|
||||
\fB--recompile
|
||||
Recompiles your configuration in ~/.xmonad/xmonad.hs
|
||||
\fB--restart
|
||||
Causes the currently running xmonad process to restart
|
||||
.TP
|
||||
\fB--version
|
||||
Display version of \fBxmonad\fR.
|
||||
.SS Default keyboard bindings
|
||||
___KEYBINDINGS___
|
||||
.SH EXAMPLES
|
||||
To use \fBxmonad\fR as your window manager add:
|
||||
.RS
|
||||
exec xmonad
|
||||
.RE
|
||||
to your \fI~/.xinitrc\fR file
|
||||
.SH CUSTOMIZATION
|
||||
\fBxmonad\fR 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 http://xmonad.org/.
|
||||
.SS "Modular Configuration"
|
||||
As of \fBxmonad-0.9\fR, any additional Haskell modules may be placed in \fI~/.xmonad/lib/\fR are available in GHC's searchpath. Hierarchical modules are supported: for example, the file \fI~/.xmonad/lib/XMonad/Stack/MyAdditions.hs\fR could contain:
|
||||
.RS
|
||||
.nf
|
||||
|
||||
module XMonad.Stack.MyAdditions (function1) where
|
||||
function1 = error "function1: Not implemented yet!"
|
||||
.fi
|
||||
.RE
|
||||
.PP
|
||||
Your xmonad.hs may then \fBimport XMonad.Stack.MyAdditions\fR as if that module was contained within \fBxmonad\fR or \fBxmonad-contrib\fR.
|
||||
.SH BUGS
|
||||
Probably. If you find any, please report them: http://code.google.com/p/xmonad/issues/list
|
102
man/xmonad.1.markdown
Normal file
102
man/xmonad.1.markdown
Normal file
@@ -0,0 +1,102 @@
|
||||
#Name
|
||||
xmonad - a tiling window manager
|
||||
|
||||
#Description
|
||||
|
||||
_xmonad_ 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.
|
||||
_xmonad_ is configured in Haskell, and custom layout algorithms may be
|
||||
implemented by the user in config files. A principle of _xmonad_ is
|
||||
predictability: the user should know in advance precisely the window
|
||||
arrangement that will result from any action.
|
||||
|
||||
By default, _xmonad_ 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.
|
||||
|
||||
By utilizing the expressivity of a modern functional language with a rich
|
||||
static type system, _xmonad_ 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.
|
||||
|
||||
#Usage
|
||||
|
||||
_xmonad_ 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.
|
||||
|
||||
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.
|
||||
|
||||
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 _xmonad_
|
||||
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.
|
||||
|
||||
##Flags
|
||||
xmonad has several flags which you may pass to the executable.
|
||||
These flags are:
|
||||
|
||||
--recompile
|
||||
: Recompiles your configuration in _~/.xmonad/xmonad.hs_
|
||||
|
||||
--restart
|
||||
: Causes the currently running _xmonad_ process to restart
|
||||
|
||||
--replace
|
||||
: Replace the current window manager with xmonad
|
||||
|
||||
--version
|
||||
: Display version of _xmonad_
|
||||
|
||||
--verbose-version
|
||||
: Display detailed version of _xmonad_
|
||||
|
||||
##Default keyboard bindings
|
||||
|
||||
___KEYBINDINGS___
|
||||
|
||||
#Examples
|
||||
To use xmonad as your window manager add to your _~/.xinitrc_ file:
|
||||
|
||||
> exec xmonad
|
||||
|
||||
#Customization
|
||||
xmonad is customized in ~/.xmonad/xmonad.hs, and then restarting
|
||||
with mod-q.
|
||||
|
||||
You can find many extensions to the core feature set in the xmonad-
|
||||
contrib package, available through your package manager or from
|
||||
[xmonad.org].
|
||||
|
||||
##Modular Configuration
|
||||
As of _xmonad-0.9_, any additional Haskell modules may be placed in
|
||||
_~/.xmonad/lib/_ are available in GHC's searchpath. Hierarchical modules
|
||||
are supported: for example, the file
|
||||
_~/.xmonad/lib/XMonad/Stack/MyAdditions.hs_ could contain:
|
||||
|
||||
> module XMonad.Stack.MyAdditions (function1) where
|
||||
> function1 = error "function1: Not implemented yet!"
|
||||
|
||||
Your xmonad.hs may then import XMonad.Stack.MyAdditions as if that
|
||||
module was contained within xmonad or xmonad-contrib.
|
||||
|
||||
#Bugs
|
||||
Probably. If you find any, please report them to the [bugtracker]
|
||||
|
||||
[xmonad.org]: http://xmonad.org
|
||||
[bugtracker]: http://code.google.com/p/xmonad/issues/list
|
@@ -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
|
||||
@@ -34,21 +38,6 @@ myBorderWidth = 1
|
||||
--
|
||||
myModMask = mod1Mask
|
||||
|
||||
-- The mask for the numlock key. Numlock status is "masked" from the
|
||||
-- current modifier status, so the keybindings will work with numlock on or
|
||||
-- off. You may need to change this on some systems.
|
||||
--
|
||||
-- You can find the numlock modifier by running "xmodmap" and looking for a
|
||||
-- modifier with Num_Lock bound to it:
|
||||
--
|
||||
-- > $ xmodmap | grep Num
|
||||
-- > mod2 Num_Lock (0x4d)
|
||||
--
|
||||
-- Set numlockMask = 0 if you don't have a numlock key, or want to treat
|
||||
-- numlock status separately.
|
||||
--
|
||||
myNumlockMask = mod2Mask
|
||||
|
||||
-- The default number of workspaces (virtual screens) and their names.
|
||||
-- By default we use numeric strings, but any string may be used as a
|
||||
-- workspace name. The number of workspaces is determined by the length
|
||||
@@ -74,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")
|
||||
@@ -138,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 -"))
|
||||
]
|
||||
++
|
||||
|
||||
@@ -239,11 +231,7 @@ myEventHook = mempty
|
||||
-- Status bars and logging
|
||||
|
||||
-- Perform an arbitrary action on each internal state change or X event.
|
||||
-- See the 'DynamicLog' extension for examples.
|
||||
--
|
||||
-- To emulate dwm's status bar
|
||||
--
|
||||
-- > logHook = dynamicLogDzen
|
||||
-- See the 'XMonad.Hooks.DynamicLog' extension for examples.
|
||||
--
|
||||
myLogHook = return ()
|
||||
|
||||
@@ -274,9 +262,9 @@ defaults = defaultConfig {
|
||||
-- simple stuff
|
||||
terminal = myTerminal,
|
||||
focusFollowsMouse = myFocusFollowsMouse,
|
||||
clickJustFocuses = myClickJustFocuses,
|
||||
borderWidth = myBorderWidth,
|
||||
modMask = myModMask,
|
||||
numlockMask = myNumlockMask,
|
||||
workspaces = myWorkspaces,
|
||||
normalBorderColor = myNormalBorderColor,
|
||||
focusedBorderColor = myFocusedBorderColor,
|
||||
|
@@ -14,7 +14,7 @@ import Data.Ratio
|
||||
import Data.Maybe
|
||||
import System.Environment
|
||||
import Control.Exception (assert)
|
||||
import qualified Control.Exception as C
|
||||
import qualified Control.Exception.Extensible as C
|
||||
import Control.Monad
|
||||
import Test.QuickCheck hiding (promote)
|
||||
import System.IO.Unsafe
|
||||
@@ -613,13 +613,13 @@ prop_lookup_visible (x :: T) =
|
||||
|
||||
-- and help out hpc
|
||||
prop_abort x = unsafePerformIO $ C.catch (abort "fail")
|
||||
(\e -> return $ show e == "xmonad: StackSet: fail" )
|
||||
(\(C.SomeException e) -> return $ show e == "xmonad: StackSet: fail" )
|
||||
where
|
||||
_ = x :: Int
|
||||
|
||||
-- new should fail with an abort
|
||||
prop_new_abort x = unsafePerformIO $ C.catch f
|
||||
(\e -> return $ show e == "xmonad: StackSet: non-positive argument to StackSet.new" )
|
||||
(\(C.SomeException e) -> return $ show e == "xmonad: StackSet: non-positive argument to StackSet.new" )
|
||||
where
|
||||
f = new undefined{-layout-} [] [] `seq` return False
|
||||
|
||||
|
@@ -5,9 +5,9 @@ main = do foo <- getContents
|
||||
let actual_loc = filter (not.null) $ filter isntcomment $
|
||||
map (dropWhile (==' ')) $ lines foo
|
||||
loc = length actual_loc
|
||||
putStrLn $ show loc
|
||||
print loc
|
||||
-- uncomment the following to check for mistakes in isntcomment
|
||||
-- putStr $ unlines $ actual_loc
|
||||
-- print actual_loc
|
||||
|
||||
isntcomment ('-':'-':_) = False
|
||||
isntcomment ('{':'-':_) = False -- pragmas
|
||||
|
@@ -1,7 +1,14 @@
|
||||
-- Unlike the rest of xmonad, this file is copyright under the terms of the
|
||||
-- GPL.
|
||||
|
||||
--
|
||||
-- Generates man/xmonad.1 from man/xmonad.1.in by filling the list of
|
||||
-- keybindings with values scraped from Config.hs
|
||||
--
|
||||
-- Uses cabal to grab the xmonad version from xmonad.cabal
|
||||
--
|
||||
-- Uses pandoc to convert the "xmonad.1.markdown" to "xmonad.1"
|
||||
--
|
||||
-- Format for the docstrings in Config.hs takes the following form:
|
||||
--
|
||||
-- -- mod-x %! Frob the whatsit
|
||||
@@ -14,8 +21,8 @@
|
||||
-- [ ((modMask .|. shiftMask, xK_Return), spawn "xterm") -- %! Launch an xterm
|
||||
--
|
||||
-- Here, mod-shift-return will be used as the keybinding name.
|
||||
--
|
||||
import Control.Monad
|
||||
import Control.Applicative
|
||||
import Text.Regex.Posix
|
||||
import Data.Char
|
||||
import Data.List
|
||||
@@ -27,6 +34,10 @@ import Distribution.PackageDescription
|
||||
import Text.PrettyPrint.HughesPJ
|
||||
import Distribution.Text
|
||||
|
||||
import Text.Pandoc -- works with 1.6
|
||||
|
||||
releaseDate = "31 December 2012"
|
||||
|
||||
trim :: String -> String
|
||||
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
|
||||
|
||||
@@ -42,16 +53,47 @@ allBindings :: String -> [(String, String)]
|
||||
allBindings xs = map (binding . map trim) (xs =~ "(.*)--(.*)%!(.*)")
|
||||
|
||||
-- FIXME: What escaping should we be doing on these strings?
|
||||
troff :: (String, String) -> String
|
||||
troff (key, desc) = ".IP\n \\fB" ++ key ++ "\\fR\n" ++ desc ++ "\n"
|
||||
markdownDefn :: (String, String) -> String
|
||||
markdownDefn (key, desc) = key ++ "\n: " ++ desc
|
||||
|
||||
replace :: Eq a => a -> a -> [a] -> [a]
|
||||
replace x y = map (\a -> if a == x then y else a)
|
||||
|
||||
-- rawSystem "pandoc" ["--read=markdown","--write=man","man/xmonad.1.markdown"]
|
||||
|
||||
main = do
|
||||
releaseName <- ((' ':) . (++" \\") . show . disp . package . packageDescription) `liftM` readPackageDescription normal "xmonad.cabal"
|
||||
releaseName <- (show . disp . package . packageDescription)
|
||||
`liftM`readPackageDescription normal "xmonad.cabal"
|
||||
keybindings <- (intercalate "\n\n" . map markdownDefn . allBindings)
|
||||
`liftM` readFile "./XMonad/Config.hs"
|
||||
|
||||
troffBindings <- (concatMap troff . allBindings) `liftM` readFile "./XMonad/Config.hs"
|
||||
let manHeader = unwords [".TH xmonad 1","\""++releaseDate++"\"",releaseName,"\"xmonad manual\""]
|
||||
writeOpts = defaultWriterOptions -- { writerLiterateHaskell = True }
|
||||
|
||||
let sed = unlines . replace "___RELEASE___\\" releaseName . replace "___KEYBINDINGS___" troffBindings . lines
|
||||
readFile "./man/xmonad.1.in" >>= return . sed >>= writeFile "./man/xmonad.1"
|
||||
parsed <- readMarkdown defaultParserState { stateLiterateHaskell = True }
|
||||
. unlines
|
||||
. replace "___KEYBINDINGS___" keybindings
|
||||
. lines
|
||||
<$> readFile "./man/xmonad.1.markdown"
|
||||
|
||||
Right template <- getDefaultTemplate Nothing "man"
|
||||
writeFile "./man/xmonad.1"
|
||||
. (manHeader ++)
|
||||
. writeMan writeOpts{ writerStandalone = True, writerTemplate = template }
|
||||
$ parsed
|
||||
putStrLn "Documentation created: man/xmonad.1"
|
||||
|
||||
Right template <- getDefaultTemplate Nothing "html"
|
||||
writeFile "./man/xmonad.1.html"
|
||||
. writeHtmlString writeOpts
|
||||
{ writerVariables =
|
||||
[("include-before"
|
||||
,"<h1>"++releaseName++"</h1>"++
|
||||
"<p>Section: xmonad manual (1)<br/>"++
|
||||
"Updated: "++releaseDate++"</p>"++
|
||||
"<hr/>")]
|
||||
, writerStandalone = True
|
||||
, writerTemplate = template
|
||||
, writerTableOfContents = True }
|
||||
$ parsed
|
||||
putStrLn "Documentation created: man/xmonad.1.html"
|
||||
|
40
xmonad.cabal
40
xmonad.cabal
@@ -1,5 +1,5 @@
|
||||
name: xmonad
|
||||
version: 0.9
|
||||
version: 0.11
|
||||
homepage: http://xmonad.org
|
||||
synopsis: A tiling window manager
|
||||
description:
|
||||
@@ -18,12 +18,23 @@ license-file: LICENSE
|
||||
author: Spencer Janssen
|
||||
maintainer: xmonad@haskell.org
|
||||
extra-source-files: README TODO CONFIG STYLE tests/loc.hs tests/Properties.hs
|
||||
man/xmonad.1.in man/xmonad.1 man/xmonad.html
|
||||
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.
|
||||
@@ -43,12 +54,18 @@ library
|
||||
XMonad.StackSet
|
||||
|
||||
if flag(small_base)
|
||||
build-depends: base < 4 && >=3, containers, directory, process, filepath
|
||||
build-depends: base < 5 && >=3, containers, directory, process, filepath, extensible-exceptions
|
||||
else
|
||||
build-depends: base < 3
|
||||
build-depends: X11>=1.4.6.1, mtl, unix
|
||||
build-depends: X11>=1.5 && < 1.7, mtl, unix,
|
||||
utf8-string >= 0.3 && < 0.4
|
||||
|
||||
if true
|
||||
ghc-options: -funbox-strict-fields -Wall
|
||||
|
||||
if impl(ghc >= 6.12.1)
|
||||
ghc-options: -fno-warn-unused-do-bind
|
||||
|
||||
ghc-options: -funbox-strict-fields -Wall
|
||||
ghc-prof-options: -prof -auto-all
|
||||
extensions: CPP
|
||||
|
||||
@@ -66,7 +83,12 @@ executable xmonad
|
||||
XMonad.Operations
|
||||
XMonad.StackSet
|
||||
|
||||
ghc-options: -funbox-strict-fields -Wall
|
||||
if true
|
||||
ghc-options: -funbox-strict-fields -Wall
|
||||
|
||||
if impl(ghc >= 6.12.1)
|
||||
ghc-options: -fno-warn-unused-do-bind
|
||||
|
||||
ghc-prof-options: -prof -auto-all
|
||||
extensions: CPP
|
||||
|
||||
@@ -76,4 +98,4 @@ executable xmonad
|
||||
build-depends: QuickCheck < 2
|
||||
ghc-options: -Werror
|
||||
if flag(testing) && flag(small_base)
|
||||
build-depends: random
|
||||
build-depends: filepath, process, directory, mtl, unix, X11, base, containers, random, extensible-exceptions
|
||||
|
Reference in New Issue
Block a user