mirror of
https://github.com/xmonad/xmonad.git
synced 2025-07-29 19:21:52 -07:00
Compare commits
58 Commits
Author | SHA1 | Date | |
---|---|---|---|
|
0eb84e4866 | ||
|
b4bf8de874 | ||
|
17c89e327e | ||
|
da71b6c8ac | ||
|
2621f3f6a8 | ||
|
8ec0bf3290 | ||
|
7e20d0d308 | ||
|
24d8de93d7 | ||
|
2dd6eeba7d | ||
|
72997cf982 | ||
|
7365d7bc11 | ||
|
36e20f689c | ||
|
cde261ed56 | ||
|
8d8cc8bcd8 | ||
|
ccb6ff92f2 | ||
|
e944a6c8d3 | ||
|
eb1e29c8bb | ||
|
66e7715ea6 | ||
|
d9d3e40112 | ||
|
7385793c65 | ||
|
72885e7e24 | ||
|
a931776e54 | ||
|
61568318d6 | ||
|
3caa989e20 | ||
|
09fd11d13b | ||
|
f33681de49 | ||
|
bf8bfc66a5 | ||
|
4075e2d9d3 | ||
|
78856e1a6f | ||
|
4222dd9ad3 | ||
|
34a547ce57 | ||
|
353e7cd681 | ||
|
72dece0769 | ||
|
6e1c5e9b49 | ||
|
bf8ba79090 | ||
|
5edfb1d262 | ||
|
0fecae0abc | ||
|
26f4f734f9 | ||
|
5e7df396b9 | ||
|
314ba78335 | ||
|
7aa78ecc75 | ||
|
ba8e26458e | ||
|
c627e8cc4d | ||
|
04f894275d | ||
|
edb752136f | ||
|
2b463a632f | ||
|
ca122dd2cb | ||
|
77657b65f9 | ||
|
28c57a837a | ||
|
afda20b56d | ||
|
0cc7b12fd0 | ||
|
15a78ae715 | ||
|
18444799e0 | ||
|
cc60fa73ad | ||
|
8881e2ac78 | ||
|
533031e3d6 | ||
|
76d4af15e4 | ||
|
74c6dd2721 |
4
CONFIG
4
CONFIG
@@ -51,9 +51,9 @@ Ok, looks good.
|
||||
|
||||
To have xmonad start using your settings, type 'mod-q'. xmonad will
|
||||
then load this new file, and run it. If it is unable to, the defaults
|
||||
are used.
|
||||
are used.
|
||||
|
||||
To load succesfully, both 'xmonad' and 'ghc' must be in your $PATH
|
||||
To load successfully, both 'xmonad' and 'ghc' must be in your $PATH
|
||||
environment variable. If GHC isn't in your path, for some reason, you
|
||||
can compile the xmonad.hs file yourself:
|
||||
|
||||
|
24
Main.hs
24
Main.hs
@@ -16,10 +16,12 @@ module Main (main) where
|
||||
|
||||
import XMonad
|
||||
|
||||
import Control.Monad (unless)
|
||||
import System.IO
|
||||
import System.Info
|
||||
import System.Environment
|
||||
import System.Posix.Process (executeFile)
|
||||
import System.Exit (exitFailure)
|
||||
|
||||
import Paths_xmonad (version)
|
||||
import Data.Version (showVersion)
|
||||
@@ -32,13 +34,15 @@ import qualified Properties
|
||||
-- for xmonad, and if it doesn't find one, just launches the default.
|
||||
main :: IO ()
|
||||
main = do
|
||||
installSignalHandlers -- important to ignore SIGCHLD to avoid zombies
|
||||
args <- getArgs
|
||||
let launch = catchIO buildLaunch >> xmonad defaultConfig
|
||||
case args of
|
||||
[] -> launch
|
||||
["--resume", _] -> launch
|
||||
["--help"] -> usage
|
||||
["--recompile"] -> recompile True >> return ()
|
||||
["--recompile"] -> recompile True >>= flip unless exitFailure
|
||||
["--restart"] -> sendRestart >> return ()
|
||||
["--version"] -> putStrLn ("xmonad " ++ showVersion version)
|
||||
#ifdef TESTING
|
||||
("--run-tests":_) -> Properties.main
|
||||
@@ -54,18 +58,19 @@ usage = do
|
||||
" --help Print this message" :
|
||||
" --version Print the version number" :
|
||||
" --recompile Recompile your ~/.xmonad/xmonad.hs" :
|
||||
" --restart Request a running xmonad process to restart" :
|
||||
#ifdef TESTING
|
||||
" --run-tests Run the test suite" :
|
||||
#endif
|
||||
[]
|
||||
|
||||
-- | Build "~/.xmonad/xmonad.hs" with ghc, then execute it. If there are no
|
||||
-- | Build "~\/.xmonad\/xmonad.hs" with ghc, then execute it. If there are no
|
||||
-- errors, this function does not return. An exception is raised in any of
|
||||
-- these cases:
|
||||
--
|
||||
-- * ghc missing
|
||||
--
|
||||
-- * ~/.xmonad/xmonad.hs missing
|
||||
-- * both "~\/.xmonad\/xmonad.hs" and "~\/.xmonad\/xmonad-$arch-$os" missing
|
||||
--
|
||||
-- * xmonad.hs fails to compile
|
||||
--
|
||||
@@ -73,7 +78,7 @@ usage = do
|
||||
--
|
||||
-- ** type error, syntax error, ..
|
||||
--
|
||||
-- * Missing xmonad/XMonadContrib modules due to ghc upgrade
|
||||
-- * Missing XMonad\/XMonadContrib modules due to ghc upgrade
|
||||
--
|
||||
buildLaunch :: IO ()
|
||||
buildLaunch = do
|
||||
@@ -82,3 +87,14 @@ buildLaunch = do
|
||||
args <- getArgs
|
||||
executeFile (dir ++ "/xmonad-"++arch++"-"++os) False args Nothing
|
||||
return ()
|
||||
|
||||
sendRestart :: IO ()
|
||||
sendRestart = do
|
||||
dpy <- openDisplay ""
|
||||
rw <- rootWindow dpy $ defaultScreen dpy
|
||||
xmonad_restart <- internAtom dpy "XMONAD_RESTART" False
|
||||
allocaXEvent $ \e -> do
|
||||
setEventType e clientMessage
|
||||
setClientMessageEvent e rw xmonad_restart 32 0 currentTime
|
||||
sendEvent dpy rw False structureNotifyMask e
|
||||
sync dpy False
|
||||
|
16
README
16
README
@@ -26,16 +26,16 @@ Building:
|
||||
|
||||
Building is quite straightforward, and requires a basic Haskell toolchain.
|
||||
On many systems xmonad is available as a binary package in your
|
||||
package system (e.g. on debian or gentoo). If at all possible, use this
|
||||
package system (e.g. on Debian or Gentoo). If at all possible, use this
|
||||
in preference to a source build, as the dependency resolution will be
|
||||
simpler.
|
||||
|
||||
We'll now walk through the complete list of toolchain dependencies.
|
||||
|
||||
* GHC: the Glasgow Haskell Compiler
|
||||
|
||||
|
||||
You first need a Haskell compiler. Your distribution's package
|
||||
system will have binaries of GHC (the Glasgow Haskell Compiler), the
|
||||
system will have binaries of GHC (the Glasgow Haskell Compiler), the
|
||||
compiler we use, so install that first. If your operating system's
|
||||
package system doesn't provide a binary version of GHC, you can find
|
||||
them here:
|
||||
@@ -46,7 +46,7 @@ Building:
|
||||
|
||||
apt-get install ghc6
|
||||
|
||||
It shouldn't be necessary to compile GHC from source -- every common
|
||||
It shouldn't be necessary to compile GHC from source -- every common
|
||||
system has a pre-build binary version.
|
||||
|
||||
* X11 libraries:
|
||||
@@ -60,7 +60,7 @@ Building:
|
||||
Typically you need: libXinerama libXext libX11
|
||||
|
||||
* Cabal
|
||||
|
||||
|
||||
xmonad requires a recent version of Cabal, >= 1.2.0. If you're using
|
||||
GHC 6.8, then it comes bundled with the right version. If you're
|
||||
using GHC 6.6.x, you'll need to build and install Cabal from hackage
|
||||
@@ -84,7 +84,7 @@ Building:
|
||||
unix http://hackage.haskell.org/cgi-bin/hackage-scripts/package/unix
|
||||
X11 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/X11
|
||||
|
||||
* Build xmonad:
|
||||
* Build xmonad:
|
||||
|
||||
Once you've got all the dependencies in place (which should be
|
||||
straightforward), build xmonad:
|
||||
@@ -128,14 +128,14 @@ XMonadContrib
|
||||
|
||||
Other useful programs:
|
||||
|
||||
A nicer xterm replacment, that supports resizing better:
|
||||
A nicer xterm replacement, that supports resizing better:
|
||||
|
||||
urxvt http://software.schmorp.de/pkg/rxvt-unicode.html
|
||||
|
||||
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/cgi-bin/hackage-scripts/package/xmobar
|
||||
|
||||
For a program dispatch menu:
|
||||
|
||||
|
4
STYLE
4
STYLE
@@ -2,7 +2,7 @@
|
||||
== Coding guidelines for contributing to
|
||||
== xmonad and the xmonad contributed extensions
|
||||
|
||||
* Comment every top level function (particularly exported funtions), and
|
||||
* Comment every top level function (particularly exported functions), and
|
||||
provide a type signature; use Haddock syntax in the comments.
|
||||
|
||||
* Follow the coding style of the other modules.
|
||||
@@ -15,7 +15,7 @@
|
||||
* Tabs are illegal. Use 4 spaces for indenting.
|
||||
|
||||
* Any pure function added to the core should have QuickCheck properties
|
||||
precisely defining its behaviour.
|
||||
precisely defining its behavior.
|
||||
|
||||
* New modules should identify the author, and be submitted under
|
||||
the same license as xmonad (BSD3 license or freer).
|
||||
|
4
TODO
4
TODO
@@ -1,7 +1,7 @@
|
||||
- Write down invariants for the window life cycle, especially:
|
||||
- When are borders set? Prove that the current handling is sufficient.
|
||||
|
||||
- current floating layer handling is unoptimal. FocusUp should raise,
|
||||
- current floating layer handling is nonoptimal. FocusUp should raise,
|
||||
for example
|
||||
|
||||
- Issues still with stacking order.
|
||||
@@ -15,7 +15,7 @@
|
||||
* double check README build instructions
|
||||
* test core with 6.6 and 6.8
|
||||
* bump xmonad.cabal version and X11 version
|
||||
* upload X11 and xmonad to hackage
|
||||
* upload X11 and xmonad to Hackage
|
||||
* 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
|
||||
|
@@ -26,19 +26,23 @@ module XMonad.Config (defaultConfig) where
|
||||
--
|
||||
import XMonad.Core as XMonad hiding
|
||||
(workspaces,manageHook,numlockMask,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse)
|
||||
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
|
||||
,handleEventHook)
|
||||
import qualified XMonad.Core as XMonad
|
||||
(workspaces,manageHook,numlockMask,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse)
|
||||
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
|
||||
,handleEventHook)
|
||||
|
||||
import XMonad.Layout
|
||||
import XMonad.Operations
|
||||
import XMonad.ManageHook
|
||||
import qualified XMonad.StackSet as W
|
||||
import Data.Bits ((.|.))
|
||||
import Data.Monoid
|
||||
import qualified Data.Map as M
|
||||
import System.Exit
|
||||
import Graphics.X11.Xlib
|
||||
import Graphics.X11.Xlib.Extras
|
||||
|
||||
-- | The default number of workspaces (virtual screens) and their names.
|
||||
-- By default we use numeric strings, but any string may be used as a
|
||||
@@ -119,6 +123,15 @@ manageHook = composeAll
|
||||
logHook :: X ()
|
||||
logHook = return ()
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- Event handling
|
||||
|
||||
-- | Defines a custom handler function for X Events. The function should
|
||||
-- return (All True) if the default handler is to be run afterwards.
|
||||
-- To combine event hooks, use mappend or mconcat from Data.Monoid.
|
||||
handleEventHook :: Event -> X All
|
||||
handleEventHook _ = return (All True)
|
||||
|
||||
-- | Perform an arbitrary action at xmonad startup.
|
||||
startupHook :: X ()
|
||||
startupHook = return ()
|
||||
@@ -205,7 +218,7 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
||||
|
||||
-- quit, or restart
|
||||
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad
|
||||
, ((modMask , xK_q ), restart "xmonad" True) -- %! Restart xmonad
|
||||
, ((modMask , xK_q ), spawn "xmonad --recompile && xmonad --restart") -- %! Restart xmonad
|
||||
]
|
||||
++
|
||||
-- mod-[1..9] %! Switch to workspace N
|
||||
@@ -226,12 +239,12 @@ 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
|
||||
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w
|
||||
>> windows W.swapMaster))
|
||||
>> windows W.shiftMaster))
|
||||
-- mod-button2 %! Raise the window to the top of the stack
|
||||
, ((modMask, button2), (\w -> focus w >> windows W.swapMaster))
|
||||
, ((modMask, button2), (\w -> focus w >> windows W.shiftMaster))
|
||||
-- mod-button3 %! Set the window to floating mode and resize by dragging
|
||||
, ((modMask, button3), (\w -> focus w >> mouseResizeWindow w
|
||||
>> windows W.swapMaster))
|
||||
>> windows W.shiftMaster))
|
||||
-- you may also bind events to the mouse scroll wheel (button4 and button5)
|
||||
]
|
||||
|
||||
@@ -250,4 +263,5 @@ defaultConfig = XConfig
|
||||
, XMonad.startupHook = startupHook
|
||||
, XMonad.mouseBindings = mouseBindings
|
||||
, XMonad.manageHook = manageHook
|
||||
, XMonad.handleEventHook = handleEventHook
|
||||
, XMonad.focusFollowsMouse = focusFollowsMouse }
|
||||
|
@@ -24,29 +24,36 @@ module XMonad.Core (
|
||||
XConf(..), XConfig(..), LayoutClass(..),
|
||||
Layout(..), readsLayout, Typeable, Message,
|
||||
SomeMessage(..), fromMessage, LayoutMessages(..),
|
||||
runX, catchX, userCode, io, catchIO, doubleFork,
|
||||
runX, catchX, userCode, userCodeDef, io, catchIO, installSignalHandlers, uninstallSignalHandlers,
|
||||
withDisplay, withWindowSet, isRoot, runOnWorkspaces,
|
||||
getAtom, spawn, getXMonadDir, recompile, trace, whenJust, whenX,
|
||||
getAtom, spawn, spawnPID, getXMonadDir, recompile, trace, whenJust, whenX,
|
||||
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runQuery
|
||||
) where
|
||||
|
||||
import XMonad.StackSet hiding (modify)
|
||||
|
||||
import Prelude hiding ( catch )
|
||||
import Control.Exception (catch, bracket, throw, Exception(ExitException))
|
||||
import Control.Exception (catch, try, bracket, throw, finally, Exception(ExitException))
|
||||
import Control.Applicative
|
||||
import Control.Monad.State
|
||||
import Control.Monad.Reader
|
||||
import System.FilePath
|
||||
import System.IO
|
||||
import System.Info
|
||||
import System.Posix.Process (executeFile, forkProcess, getProcessStatus, createSession)
|
||||
import System.Posix.Process (executeFile, forkProcess, getAnyProcessStatus, createSession)
|
||||
import System.Posix.Signals
|
||||
import System.Posix.IO
|
||||
import System.Posix.Types (ProcessID)
|
||||
import System.Process
|
||||
import System.Directory
|
||||
import System.Exit
|
||||
import Graphics.X11.Xlib
|
||||
import Graphics.X11.Xlib.Extras (Event)
|
||||
import Data.Typeable
|
||||
import Data.List ((\\))
|
||||
import Data.Maybe (isJust)
|
||||
import Data.Monoid
|
||||
import Data.Maybe (fromMaybe)
|
||||
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Set as S
|
||||
@@ -70,6 +77,9 @@ data XConf = XConf
|
||||
, buttonActions :: !(M.Map (KeyMask, Button) (Window -> X ()))
|
||||
-- ^ a mapping of button presses to actions
|
||||
, mouseFocused :: !Bool -- ^ was refocus caused by mouse action?
|
||||
, mousePosition :: !(Maybe (Position, Position))
|
||||
-- ^ position of the mouse according to
|
||||
-- the event currently being processed
|
||||
}
|
||||
|
||||
-- todo, better name
|
||||
@@ -79,6 +89,9 @@ data XConfig l = XConfig
|
||||
, terminal :: !String -- ^ The preferred terminal application. Default: \"xterm\"
|
||||
, layoutHook :: !(l Window) -- ^ The available layouts
|
||||
, manageHook :: !ManageHook -- ^ The action to run when a new window is opened
|
||||
, handleEventHook :: !(Event -> X All) -- ^ Handle an X event, returns (All True) if the default handler
|
||||
-- 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
|
||||
@@ -117,7 +130,7 @@ data ScreenDetail = SD { screenRect :: !Rectangle } deriving (Eq,Show, Read)
|
||||
--
|
||||
newtype X a = X (ReaderT XConf (StateT XState IO) a)
|
||||
#ifndef __HADDOCK__
|
||||
deriving (Functor, Monad, MonadIO, MonadState XState, MonadReader XConf)
|
||||
deriving (Functor, Monad, MonadIO, MonadState XState, MonadReader XConf, Typeable)
|
||||
#endif
|
||||
|
||||
instance Applicative X where
|
||||
@@ -160,8 +173,13 @@ catchX job errcase = do
|
||||
|
||||
-- | Execute the argument, catching all exceptions. Either this function or
|
||||
-- 'catchX' should be used at all callsites of user customized code.
|
||||
userCode :: X () -> X ()
|
||||
userCode a = catchX (a >> return ()) (return ())
|
||||
userCode :: X a -> X (Maybe a)
|
||||
userCode a = catchX (Just `liftM` a) (return Nothing)
|
||||
|
||||
-- | Same as userCode but with a default argument to return instead of using
|
||||
-- Maybe, provided for convenience.
|
||||
userCodeDef :: a -> X a -> X a
|
||||
userCodeDef def a = fromMaybe def `liftM` userCode a
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
-- Convenient wrappers to state
|
||||
@@ -337,19 +355,22 @@ io = liftIO
|
||||
catchIO :: MonadIO m => IO () -> m ()
|
||||
catchIO f = io (f `catch` \e -> hPrint stderr e >> hFlush stderr)
|
||||
|
||||
-- | spawn. Launch an external application
|
||||
-- | spawn. Launch an external application. Specifically, it double-forks and
|
||||
-- runs the 'String' you pass as a command to /bin/sh.
|
||||
spawn :: MonadIO m => String -> m ()
|
||||
spawn x = doubleFork $ executeFile "/bin/sh" False ["-c", x] Nothing
|
||||
spawn x = spawnPID x >> return ()
|
||||
|
||||
-- | Double fork and execute an 'IO' action (usually one of the exec family of
|
||||
-- functions)
|
||||
doubleFork :: MonadIO m => IO () -> m ()
|
||||
doubleFork m = io $ do
|
||||
pid <- forkProcess $ do
|
||||
forkProcess (createSession >> m)
|
||||
exitWith ExitSuccess
|
||||
getProcessStatus True False pid
|
||||
return ()
|
||||
-- | Like 'spawn', but returns the 'ProcessID' of the launched application
|
||||
spawnPID :: MonadIO m => String -> m ProcessID
|
||||
spawnPID x = io . forkProcess . finally nullStdin $ do
|
||||
uninstallSignalHandlers
|
||||
createSession
|
||||
executeFile "/bin/sh" False ["-c", x] Nothing
|
||||
where
|
||||
nullStdin = do
|
||||
fd <- openFd "/dev/null" ReadOnly Nothing defaultFileFlags
|
||||
dupTo fd stdInput
|
||||
closeFd fd
|
||||
|
||||
-- | This is basically a map function, running a function in the 'X' monad on
|
||||
-- each workspace with the output of that function being the modified workspace.
|
||||
@@ -386,18 +407,25 @@ recompile :: MonadIO m => Bool -> m Bool
|
||||
recompile force = io $ do
|
||||
dir <- getXMonadDir
|
||||
let binn = "xmonad-"++arch++"-"++os
|
||||
bin = dir ++ "/" ++ binn
|
||||
base = dir ++ "/" ++ "xmonad"
|
||||
bin = dir </> binn
|
||||
base = dir </> "xmonad"
|
||||
err = base ++ ".errors"
|
||||
src = base ++ ".hs"
|
||||
lib = dir </> "lib"
|
||||
libTs <- mapM getModTime . Prelude.filter isSource =<< allFiles lib
|
||||
srcT <- getModTime src
|
||||
binT <- getModTime bin
|
||||
if (force || srcT > binT)
|
||||
if force || any (binT <) (srcT : libTs)
|
||||
then do
|
||||
-- temporarily disable SIGCHLD ignoring:
|
||||
uninstallSignalHandlers
|
||||
status <- bracket (openFile err WriteMode) hClose $ \h -> do
|
||||
waitForProcess =<< runProcess "ghc" ["--make", "xmonad.hs", "-i", "-no-recomp", "-v0", "-o",binn] (Just dir)
|
||||
waitForProcess =<< runProcess "ghc" ["--make", "xmonad.hs", "-i", "-ilib", "-fforce-recomp", "-v0", "-o",binn] (Just dir)
|
||||
Nothing Nothing Nothing (Just h)
|
||||
|
||||
-- re-enable SIGCHLD:
|
||||
installSignalHandlers
|
||||
|
||||
-- now, if it fails, run xmessage to let the user know:
|
||||
when (status /= ExitSuccess) $ do
|
||||
ghcErr <- readFile err
|
||||
@@ -407,10 +435,17 @@ recompile force = io $ do
|
||||
-- nb, the ordering of printing, then forking, is crucial due to
|
||||
-- lazy evaluation
|
||||
hPutStrLn stderr msg
|
||||
doubleFork $ executeFile "xmessage" True ["-default", "okay", msg] Nothing
|
||||
forkProcess $ executeFile "xmessage" True ["-default", "okay", msg] Nothing
|
||||
return ()
|
||||
return (status == ExitSuccess)
|
||||
else return True
|
||||
where getModTime f = catch (Just <$> getModificationTime f) (const $ return Nothing)
|
||||
isSource = flip elem [".hs",".lhs",".hsc"]
|
||||
allFiles t = do
|
||||
let prep = map (t</>) . Prelude.filter (`notElem` [".",".."])
|
||||
cs <- prep <$> catch (getDirectoryContents t) (\_ -> return [])
|
||||
ds <- filterM doesDirectoryExist cs
|
||||
concat . ((cs \\ ds):) <$> mapM allFiles ds
|
||||
|
||||
-- | Conditionally run an action, using a @Maybe a@ to decide.
|
||||
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
|
||||
@@ -424,3 +459,19 @@ whenX a f = a >>= \b -> when b f
|
||||
-- be found in your .xsession-errors file
|
||||
trace :: MonadIO m => String -> m ()
|
||||
trace = io . hPutStrLn stderr
|
||||
|
||||
-- | Ignore SIGPIPE to avoid termination when a pipe is full, and SIGCHLD to
|
||||
-- avoid zombie processes, and clean up any extant zombie processes.
|
||||
installSignalHandlers :: MonadIO m => m ()
|
||||
installSignalHandlers = io $ do
|
||||
installHandler openEndedPipe Ignore Nothing
|
||||
installHandler sigCHLD Ignore Nothing
|
||||
try $ fix $ \more -> do
|
||||
x <- getAnyProcessStatus False False
|
||||
when (isJust x) more
|
||||
return ()
|
||||
|
||||
uninstallSignalHandlers :: MonadIO m => m ()
|
||||
uninstallSignalHandlers = io $ do
|
||||
installHandler sigCHLD Default Nothing
|
||||
return ()
|
||||
|
@@ -51,7 +51,10 @@ instance LayoutClass Full a
|
||||
|
||||
-- | The builtin tiling mode of xmonad. Supports 'Shrink', 'Expand' and
|
||||
-- 'IncMasterN'.
|
||||
data Tall a = Tall !Int !Rational !Rational deriving (Show, Read)
|
||||
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)
|
||||
deriving (Show, Read)
|
||||
-- TODO should be capped [0..1] ..
|
||||
|
||||
-- a nice pure layout, lots of properties for the layout, and its messages, in Properties.hs
|
||||
|
@@ -22,12 +22,12 @@ import qualified Data.Set as S
|
||||
import Control.Monad.Reader
|
||||
import Control.Monad.State
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Monoid (getAll)
|
||||
|
||||
import Foreign.C
|
||||
import Foreign.Ptr
|
||||
|
||||
import System.Environment (getArgs)
|
||||
import System.Posix.Signals
|
||||
|
||||
import Graphics.X11.Xlib hiding (refreshKeyboardMapping)
|
||||
import Graphics.X11.Xlib.Extras
|
||||
@@ -57,14 +57,27 @@ xmonad :: (LayoutClass l Window, Read (l Window)) => XConfig l -> IO ()
|
||||
xmonad initxmc = do
|
||||
-- setup locale information from environment
|
||||
withCString "" $ c_setlocale (#const LC_ALL)
|
||||
-- ignore SIGPIPE
|
||||
installHandler openEndedPipe Ignore Nothing
|
||||
-- ignore SIGPIPE and SIGCHLD
|
||||
installSignalHandlers
|
||||
-- First, wrap the layout in an existential, to keep things pretty:
|
||||
let xmc = initxmc { layoutHook = Layout $ layoutHook initxmc }
|
||||
dpy <- openDisplay ""
|
||||
let dflt = defaultScreen dpy
|
||||
|
||||
rootw <- rootWindow dpy dflt
|
||||
|
||||
-- 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.
|
||||
selectInput dpy rootw $ substructureRedirectMask .|. substructureNotifyMask
|
||||
.|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask
|
||||
.|. buttonPressMask
|
||||
sync dpy False -- sync to ensure all outstanding errors are delivered
|
||||
|
||||
-- turn off the default handler in favor of one that ignores all errors
|
||||
-- (ugly, I know)
|
||||
xSetErrorHandler -- in C, I'm too lazy to write the binding: dons
|
||||
|
||||
xinesc <- getCleanedScreenInfo dpy
|
||||
nbc <- do v <- initColor dpy $ normalBorderColor xmc
|
||||
~(Just nbc_) <- initColor dpy $ normalBorderColor Default.defaultConfig
|
||||
@@ -99,20 +112,14 @@ xmonad initxmc = do
|
||||
, focusedBorder = fbc
|
||||
, keyActions = keys xmc xmc
|
||||
, buttonActions = mouseBindings xmc xmc
|
||||
, mouseFocused = False }
|
||||
, mouseFocused = False
|
||||
, mousePosition = Nothing }
|
||||
st = XState
|
||||
{ windowset = initialWinset
|
||||
, mapped = S.empty
|
||||
, waitingUnmap = M.empty
|
||||
, dragging = Nothing }
|
||||
|
||||
xSetErrorHandler -- in C, I'm too lazy to write the binding: dons
|
||||
|
||||
-- setup initial X environment
|
||||
sync dpy False
|
||||
selectInput dpy rootw $ substructureRedirectMask .|. substructureNotifyMask
|
||||
.|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask
|
||||
|
||||
allocaXEvent $ \e ->
|
||||
runX cf st $ do
|
||||
|
||||
@@ -136,11 +143,27 @@ xmonad initxmc = do
|
||||
userCode $ startupHook initxmc
|
||||
|
||||
-- main loop, for all you HOF/recursion fans out there.
|
||||
forever_ $ handle =<< io (nextEvent dpy e >> getEvent e)
|
||||
forever_ $ prehandle =<< io (nextEvent dpy e >> getEvent e)
|
||||
|
||||
return ()
|
||||
where forever_ a = a >> forever_ a
|
||||
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)
|
||||
evs = [ keyPress, keyRelease, enterNotify, leaveNotify
|
||||
, buttonPress, buttonRelease]
|
||||
|
||||
|
||||
-- | Runs handleEventHook from the configuration and runs the default handler
|
||||
-- function if it returned True.
|
||||
handleWithHook :: Event -> X ()
|
||||
handleWithHook e = do
|
||||
evHook <- asks (handleEventHook . config)
|
||||
whenX (userCodeDef True $ getAll `fmap` evHook e) (handle e)
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
-- | Event handler. Map X events onto calls into Operations.hs, which
|
||||
@@ -160,7 +183,7 @@ handle (KeyEvent {ev_event_type = t, ev_state = m, ev_keycode = code})
|
||||
s <- io $ keycodeToKeysym dpy code 0
|
||||
mClean <- cleanMask m
|
||||
ks <- asks keyActions
|
||||
userCode $ whenJust (M.lookup (mClean, s) ks) id
|
||||
userCodeDef () $ whenJust (M.lookup (mClean, s) ks) id
|
||||
|
||||
-- manage a new window
|
||||
handle (MapRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
|
||||
@@ -214,16 +237,16 @@ handle e@(ButtonEvent {ev_window = w,ev_event_type = t,ev_button = b })
|
||||
-- grabbed in grabButtons. Otherwise, it's click-to-focus.
|
||||
isr <- isRoot w
|
||||
m <- cleanMask $ ev_state e
|
||||
ba <- asks buttonActions
|
||||
if isr then userCode $ whenJust (M.lookup (m, b) ba) ($ ev_subwindow e)
|
||||
else focus w
|
||||
mact <- asks (M.lookup (m, b) . buttonActions)
|
||||
case mact of
|
||||
(Just act) | isr -> act $ ev_subwindow e
|
||||
_ -> focus w
|
||||
broadcastMessage e -- Always send button events.
|
||||
|
||||
-- entered a normal window: focus it if focusFollowsMouse is set to
|
||||
-- True in the user's config.
|
||||
handle e@(CrossingEvent {ev_window = w, ev_event_type = t})
|
||||
| t == enterNotify && ev_mode e == notifyNormal
|
||||
&& ev_detail e /= notifyInferior
|
||||
= whenX (asks $ focusFollowsMouse . config) (focus w)
|
||||
|
||||
-- left a window, check if we need to focus root
|
||||
@@ -263,7 +286,13 @@ 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 = userCode =<< asks (logHook . config)
|
||||
| t == propertyNotify && a == wM_NAME = userCodeDef () =<< asks (logHook . config)
|
||||
|
||||
handle e@ClientMessageEvent { ev_message_type = mt } = do
|
||||
a <- getAtom "XMONAD_RESTART"
|
||||
if (mt == a)
|
||||
then restart "xmonad" True
|
||||
else broadcastMessage e
|
||||
|
||||
handle e = broadcastMessage e -- trace (eventName e) -- ignoring
|
||||
|
||||
|
@@ -45,6 +45,8 @@ idHook = doF id
|
||||
composeAll :: [ManageHook] -> ManageHook
|
||||
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
|
||||
@@ -71,7 +73,8 @@ title = ask >>= \w -> liftX $ do
|
||||
getProp =
|
||||
(internAtom d "_NET_WM_NAME" False >>= getTextProperty d w)
|
||||
`catch` \_ -> getTextProperty d w wM_NAME
|
||||
extract = fmap head . wcTextPropertyToTextList d
|
||||
extract prop = do l <- wcTextPropertyToTextList d prop
|
||||
return $ if null l then "" else head l
|
||||
io $ bracket getProp (xFree . tp_value) extract `catch` \_ -> return ""
|
||||
|
||||
-- | Return the application name.
|
||||
@@ -111,4 +114,4 @@ doIgnore = ask >>= \w -> liftX (reveal w) >> doF (W.delete w)
|
||||
|
||||
-- | Move the window to a given workspace
|
||||
doShift :: WorkspaceId -> ManageHook
|
||||
doShift = doF . W.shift
|
||||
doShift i = doF . W.shiftWin i =<< ask
|
||||
|
@@ -23,7 +23,7 @@ import XMonad.Layout (Full(..))
|
||||
import qualified XMonad.StackSet as W
|
||||
|
||||
import Data.Maybe
|
||||
import Data.Monoid (appEndo)
|
||||
import Data.Monoid (Endo(..))
|
||||
import Data.List (nub, (\\), find)
|
||||
import Data.Bits ((.|.), (.&.), complement)
|
||||
import Data.Ratio
|
||||
@@ -68,7 +68,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 (runQuery mh w) `catchX` return id
|
||||
g <- fmap appEndo $ userCodeDef (Endo id) (runQuery mh w)
|
||||
windows (g . f)
|
||||
|
||||
-- | unmanage. A window no longer exists, remove it from the window
|
||||
@@ -77,14 +77,14 @@ manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do
|
||||
unmanage :: Window -> X ()
|
||||
unmanage = windows . W.delete
|
||||
|
||||
-- | Kill the currently focused client. If we do kill it, we'll get a
|
||||
-- | Kill the specified window. If we do kill it, we'll get a
|
||||
-- delete notify back from X.
|
||||
--
|
||||
-- There are two ways to delete a window. Either just kill it, or if it
|
||||
-- supports the delete protocol, send a delete event (e.g. firefox)
|
||||
--
|
||||
kill :: X ()
|
||||
kill = withDisplay $ \d -> withFocused $ \w -> do
|
||||
killWindow :: Window -> X ()
|
||||
killWindow w = withDisplay $ \d -> do
|
||||
wmdelt <- atom_WM_DELETE_WINDOW ; wmprot <- atom_WM_PROTOCOLS
|
||||
|
||||
protocols <- io $ getWMProtocols d w
|
||||
@@ -95,6 +95,10 @@ kill = withDisplay $ \d -> withFocused $ \w -> do
|
||||
sendEvent d w False noEventMask ev
|
||||
else killClient d w >> return ()
|
||||
|
||||
-- | Kill the currently focused client.
|
||||
kill :: X ()
|
||||
kill = withFocused killWindow
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
-- Managing windows
|
||||
|
||||
@@ -120,46 +124,44 @@ windows f = do
|
||||
-- for each workspace, layout the currently visible workspaces
|
||||
let allscreens = W.screens ws
|
||||
summed_visible = scanl (++) [] $ map (W.integrate' . W.stack . W.workspace) allscreens
|
||||
visible <- fmap concat $ forM (zip allscreens summed_visible) $ \ (w, vis) -> do
|
||||
rects <- fmap concat $ forM (zip allscreens summed_visible) $ \ (w, vis) -> do
|
||||
let wsp = W.workspace w
|
||||
this = W.view n ws
|
||||
n = W.tag wsp
|
||||
flt = filter (flip M.member (W.floating ws)) (W.index this)
|
||||
tiled = (W.stack . W.workspace . W.current $ this)
|
||||
>>= W.filter (`M.notMember` W.floating ws)
|
||||
>>= W.filter (`notElem` vis)
|
||||
viewrect@(Rectangle sx sy sw sh) = screenRect $ W.screenDetail w
|
||||
viewrect = screenRect $ W.screenDetail w
|
||||
|
||||
-- just the tiled windows:
|
||||
-- now tile the windows on this workspace, modified by the gap
|
||||
(rs, ml') <- runLayout wsp { W.stack = tiled } viewrect `catchX`
|
||||
runLayout wsp { W.stack = tiled, W.layout = Layout Full } viewrect
|
||||
mapM_ (uncurry tileWindow) rs
|
||||
updateLayout n ml'
|
||||
|
||||
-- now the floating windows:
|
||||
-- move/resize the floating windows, if there are any
|
||||
forM_ flt $ \fw -> whenJust (M.lookup fw (W.floating ws)) $
|
||||
\(W.RationalRect rx ry rw rh) -> do
|
||||
tileWindow fw $ Rectangle
|
||||
(sx + floor (toRational sw*rx)) (sy + floor (toRational sh*ry))
|
||||
(floor (toRational sw*rw)) (floor (toRational sh*rh))
|
||||
let m = W.floating ws
|
||||
flt = [(fw, scaleRationalRect viewrect r)
|
||||
| fw <- filter (flip M.member m) (W.index this)
|
||||
, Just r <- [M.lookup fw m]]
|
||||
vs = flt ++ rs
|
||||
|
||||
let vs = flt ++ map fst rs
|
||||
io $ restackWindows d vs
|
||||
io $ restackWindows d (map fst vs)
|
||||
-- return the visible windows for this workspace:
|
||||
return vs
|
||||
|
||||
whenJust (W.peek ws) $ \w -> io $ setWindowBorder d w fbc
|
||||
asks (logHook . config) >>= userCode
|
||||
let visible = map fst rects
|
||||
|
||||
mapM_ reveal visible
|
||||
setTopFocus
|
||||
mapM_ (uncurry tileWindow) rects
|
||||
|
||||
whenJust (W.peek ws) $ \w -> io $ setWindowBorder d w fbc
|
||||
|
||||
-- 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
|
||||
@@ -167,6 +169,13 @@ windows f = do
|
||||
|
||||
isMouseFocused <- asks mouseFocused
|
||||
unless isMouseFocused $ clearEvents enterWindowMask
|
||||
asks (logHook . config) >>= userCodeDef ()
|
||||
|
||||
-- | Produce the actual rectangle from a screen and a ratio on that screen.
|
||||
scaleRationalRect :: Rectangle -> W.RationalRect -> Rectangle
|
||||
scaleRationalRect (Rectangle sx sy sw sh) (W.RationalRect rx ry rw rh)
|
||||
= Rectangle (sx + scale sw rx) (sy + scale sh ry) (scale sw rw) (scale sh rh)
|
||||
where scale s r = floor (toRational s * r)
|
||||
|
||||
-- | setWMState. set the WM_STATE property
|
||||
setWMState :: Window -> Int -> X ()
|
||||
@@ -294,11 +303,17 @@ setTopFocus = withWindowSet $ maybe (setFocusX =<< asks theRoot) setFocusX . W.p
|
||||
-- This happens if X notices we've moved the mouse (and perhaps moved
|
||||
-- the mouse to a new screen).
|
||||
focus :: Window -> X ()
|
||||
focus w = withWindowSet $ \s -> do
|
||||
if W.member w s then when (W.peek s /= Just w) $ do
|
||||
local (\c -> c { mouseFocused = True }) $ do
|
||||
windows (W.focusWindow w)
|
||||
else whenX (isRoot w) $ setFocusX w
|
||||
focus w = local (\c -> c { mouseFocused = True }) $ withWindowSet $ \s -> do
|
||||
let stag = W.tag . W.workspace
|
||||
curr = stag $ W.current s
|
||||
mnew <- maybe (return Nothing) (fmap (fmap stag) . uncurry pointScreen)
|
||||
=<< asks mousePosition
|
||||
root <- asks theRoot
|
||||
case () of
|
||||
_ | W.member w s && W.peek s /= Just w -> windows (W.focusWindow w)
|
||||
| Just new <- mnew, w == root && curr /= new
|
||||
-> windows (W.view new)
|
||||
| otherwise -> return ()
|
||||
|
||||
-- | Call X to set the keyboard focus details.
|
||||
setFocusX :: Window -> X ()
|
||||
@@ -412,10 +427,9 @@ floatLocation w = withDisplay $ \d -> do
|
||||
ws <- gets windowset
|
||||
wa <- io $ getWindowAttributes d w
|
||||
bw <- fi <$> asks (borderWidth . config)
|
||||
sc <- fromMaybe (W.current ws) <$> pointScreen (fi $ wa_x wa) (fi $ wa_y wa)
|
||||
|
||||
-- XXX horrible
|
||||
let sc = fromMaybe (W.current ws) $ find (pointWithin (fi $ wa_x wa) (fi $ wa_y wa) . screenRect . W.screenDetail) $ W.screens ws
|
||||
sr = screenRect . W.screenDetail $ sc
|
||||
let sr = screenRect . W.screenDetail $ sc
|
||||
rr = W.RationalRect ((fi (wa_x wa) - fi (rect_x sr)) % fi (rect_width sr))
|
||||
((fi (wa_y wa) - fi (rect_y sr)) % fi (rect_height sr))
|
||||
(fi (wa_width wa + bw*2) % fi (rect_width sr))
|
||||
@@ -423,11 +437,20 @@ floatLocation w = withDisplay $ \d -> do
|
||||
|
||||
return (W.screen $ sc, rr)
|
||||
where fi x = fromIntegral x
|
||||
pointWithin :: Integer -> Integer -> Rectangle -> Bool
|
||||
pointWithin x y r = x >= fi (rect_x r) &&
|
||||
x < fi (rect_x r) + fi (rect_width r) &&
|
||||
y >= fi (rect_y r) &&
|
||||
y < fi (rect_y r) + fi (rect_height r)
|
||||
|
||||
-- | Given a point, determine the screen (if any) that contains it.
|
||||
pointScreen :: Position -> Position
|
||||
-> X (Maybe (W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail))
|
||||
pointScreen x y = withWindowSet $ return . find p . W.screens
|
||||
where p = pointWithin x y . screenRect . W.screenDetail
|
||||
|
||||
-- | @pointWithin x y r@ returns 'True' if the @(x, y)@ co-ordinate is within
|
||||
-- @r@.
|
||||
pointWithin :: Position -> Position -> Rectangle -> Bool
|
||||
pointWithin x y r = x >= rect_x r &&
|
||||
x < rect_x r + fromIntegral (rect_width r) &&
|
||||
y >= rect_y r &&
|
||||
y < rect_y r + fromIntegral (rect_height r)
|
||||
|
||||
-- | Make a tiled window floating, using its suggested rectangle
|
||||
float :: Window -> X ()
|
||||
|
@@ -35,14 +35,14 @@ module XMonad.StackSet (
|
||||
-- * Operations on the current stack
|
||||
-- $stackOperations
|
||||
peek, index, integrate, integrate', differentiate,
|
||||
focusUp, focusDown, focusMaster, focusWindow,
|
||||
focusUp, focusDown, focusUp', focusDown', focusMaster, focusWindow,
|
||||
tagMember, renameTag, ensureTags, member, findTag, mapWorkspace, mapLayout,
|
||||
-- * Modifying the stackset
|
||||
-- $modifyStackset
|
||||
insertUp, delete, delete', filter,
|
||||
-- * Setting the master window
|
||||
-- $settingMW
|
||||
swapUp, swapDown, swapMaster, modify, modify', float, sink, -- needed by users
|
||||
swapUp, swapDown, swapMaster, shiftMaster, modify, modify', float, sink, -- needed by users
|
||||
-- * Composite operations
|
||||
-- $composite
|
||||
shift, shiftWin,
|
||||
@@ -52,7 +52,7 @@ module XMonad.StackSet (
|
||||
) where
|
||||
|
||||
import Prelude hiding (filter)
|
||||
import Data.Maybe (listToMaybe,fromJust,isJust)
|
||||
import Data.Maybe (listToMaybe,isJust)
|
||||
import qualified Data.List as L (deleteBy,find,splitAt,filter,nub)
|
||||
import Data.List ( (\\) )
|
||||
import qualified Data.Map as M (Map,insert,delete,empty)
|
||||
@@ -194,7 +194,8 @@ abort x = error $ "xmonad: StackSet: " ++ x
|
||||
-- Xinerama: Virtual workspaces are assigned to physical screens, starting at 0.
|
||||
--
|
||||
new :: (Integral s) => l -> [i] -> [sd] -> StackSet i l a s sd
|
||||
new l wids m | not (null wids) && length m <= length wids = StackSet cur visi unseen M.empty
|
||||
new l wids m | not (null wids) && length m <= length wids && not (null m)
|
||||
= StackSet cur visi unseen M.empty
|
||||
where (seen,unseen) = L.splitAt (length m) $ map (\i -> Workspace i l Nothing) wids
|
||||
(cur:visi) = [ Screen i s sd | (i, s, sd) <- zip3 seen [0..] m ]
|
||||
-- now zip up visibles with their screen id
|
||||
@@ -342,15 +343,19 @@ index = with [] integrate
|
||||
--
|
||||
focusUp, focusDown, swapUp, swapDown :: StackSet i l a s sd -> StackSet i l a s sd
|
||||
focusUp = modify' focusUp'
|
||||
focusDown = modify' (reverseStack . focusUp' . reverseStack)
|
||||
focusDown = modify' focusDown'
|
||||
|
||||
swapUp = modify' swapUp'
|
||||
swapDown = modify' (reverseStack . swapUp' . reverseStack)
|
||||
|
||||
focusUp', swapUp' :: Stack a -> Stack a
|
||||
-- | Variants of 'focusUp' and 'focusDown' that work on a
|
||||
-- 'Stack' rather than an entire 'StackSet'.
|
||||
focusUp', focusDown' :: Stack a -> Stack a
|
||||
focusUp' (Stack t (l:ls) rs) = Stack l ls (t:rs)
|
||||
focusUp' (Stack t [] rs) = Stack x xs [] where (x:xs) = reverse (t:rs)
|
||||
focusDown' = reverseStack . focusUp' . reverseStack
|
||||
|
||||
swapUp' :: Stack a -> Stack a
|
||||
swapUp' (Stack t (l:ls) rs) = Stack t ls (l:rs)
|
||||
swapUp' (Stack t [] rs) = Stack t (reverse rs) []
|
||||
|
||||
@@ -508,6 +513,15 @@ swapMaster = modify' $ \c -> case c of
|
||||
|
||||
-- natural! keep focus, move current to the top, move top to current.
|
||||
|
||||
-- | /O(s)/. Set the master window to the focused window.
|
||||
-- The other windows are kept in order and shifted down on the stack, as if you
|
||||
-- just hit mod-shift-k a bunch of times.
|
||||
-- Focus stays with the item moved.
|
||||
shiftMaster :: StackSet i l a s sd -> StackSet i l a s sd
|
||||
shiftMaster = modify' $ \c -> case c of
|
||||
Stack _ [] _ -> c -- already master.
|
||||
Stack t ls rs -> Stack t [] (reverse ls ++ rs)
|
||||
|
||||
-- | /O(s)/. Set focus to the master window.
|
||||
focusMaster :: StackSet i l a s sd -> StackSet i l a s sd
|
||||
focusMaster = modify' $ \c -> case c of
|
||||
@@ -525,10 +539,7 @@ focusMaster = modify' $ \c -> case c of
|
||||
-- element on the current stack, the original stackSet is returned.
|
||||
--
|
||||
shift :: (Ord a, Eq s, Eq i) => i -> StackSet i l a s sd -> StackSet i l a s sd
|
||||
shift n s | n `tagMember` s && n /= curtag = maybe s go (peek s)
|
||||
| otherwise = s
|
||||
where go w = view curtag . insertUp w . view n . delete' w $ s
|
||||
curtag = currentTag s
|
||||
shift n s = maybe s (\w -> shiftWin n w s) (peek s)
|
||||
|
||||
-- | /O(n)/. shiftWin. Searches for the specified window 'w' on all workspaces
|
||||
-- of the stackSet and moves it to stack 'n', leaving it as the focused
|
||||
@@ -536,13 +547,12 @@ shift n s | n `tagMember` s && n /= curtag = maybe s go (peek s)
|
||||
-- focused element on that workspace.
|
||||
-- The actual focused workspace doesn't change. If the window is not
|
||||
-- found in the stackSet, the original stackSet is returned.
|
||||
-- TODO how does this duplicate 'shift's behaviour?
|
||||
shiftWin :: (Ord a, Eq a, Eq s, Eq i) => i -> a -> StackSet i l a s sd -> StackSet i l a s sd
|
||||
shiftWin n w s | from == Nothing = s -- not found
|
||||
| n `tagMember` s && (Just n) /= from = go
|
||||
| otherwise = s
|
||||
where from = findTag w s
|
||||
|
||||
go = on n (insertUp w) . on (fromJust from) (delete' w) $ s
|
||||
on i f = view (currentTag s) . f . view i
|
||||
shiftWin n w s = case findTag w s of
|
||||
Just from | n `tagMember` s && n /= from -> go from s
|
||||
_ -> s
|
||||
where go from = onWorkspace n (insertUp w) . onWorkspace from (delete' w)
|
||||
|
||||
onWorkspace :: (Eq i, Eq s) => i -> (StackSet i l a s sd -> StackSet i l a s sd)
|
||||
-> (StackSet i l a s sd -> StackSet i l a s sd)
|
||||
onWorkspace n f s = view (currentTag s) . f . view n $ s
|
||||
|
@@ -1,15 +1,17 @@
|
||||
./" man page created by David Lazar on April 24, 2007
|
||||
./" uses ``tmac.an'' macro set
|
||||
.TH xmonad 1 "18 April 07" xmonad\-1.0 "xmonad manual"
|
||||
.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 maximise 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.
|
||||
\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 maximise 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 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 utilising 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.
|
||||
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.
|
||||
@@ -23,6 +25,8 @@ When running with multiple monitors (Xinerama), each screen has exactly 1 worksp
|
||||
.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.
|
||||
@@ -31,10 +35,23 @@ ___KEYBINDINGS___
|
||||
.SH EXAMPLES
|
||||
To use \fBxmonad\fR as your window manager add:
|
||||
.RS
|
||||
xmonad
|
||||
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
|
||||
|
@@ -8,6 +8,7 @@
|
||||
--
|
||||
|
||||
import XMonad
|
||||
import Data.Monoid
|
||||
import System.Exit
|
||||
|
||||
import qualified XMonad.StackSet as W
|
||||
@@ -18,6 +19,10 @@ import qualified Data.Map as M
|
||||
--
|
||||
myTerminal = "xterm"
|
||||
|
||||
-- Whether focus follows the mouse pointer.
|
||||
myFocusFollowsMouse :: Bool
|
||||
myFocusFollowsMouse = True
|
||||
|
||||
-- Width of the window border in pixels.
|
||||
--
|
||||
myBorderWidth = 1
|
||||
@@ -63,73 +68,76 @@ myFocusedBorderColor = "#ff0000"
|
||||
------------------------------------------------------------------------
|
||||
-- Key bindings. Add, modify or remove key bindings here.
|
||||
--
|
||||
myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
||||
myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $
|
||||
|
||||
-- launch a terminal
|
||||
[ ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
|
||||
[ ((modm .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
|
||||
|
||||
-- launch dmenu
|
||||
, ((modMask, xK_p ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"")
|
||||
, ((modm, xK_p ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"")
|
||||
|
||||
-- launch gmrun
|
||||
, ((modMask .|. shiftMask, xK_p ), spawn "gmrun")
|
||||
, ((modm .|. shiftMask, xK_p ), spawn "gmrun")
|
||||
|
||||
-- close focused window
|
||||
, ((modMask .|. shiftMask, xK_c ), kill)
|
||||
-- close focused window
|
||||
, ((modm .|. shiftMask, xK_c ), kill)
|
||||
|
||||
-- Rotate through the available layout algorithms
|
||||
, ((modMask, xK_space ), sendMessage NextLayout)
|
||||
, ((modm, xK_space ), sendMessage NextLayout)
|
||||
|
||||
-- Reset the layouts on the current workspace to default
|
||||
, ((modMask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf)
|
||||
, ((modm .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf)
|
||||
|
||||
-- Resize viewed windows to the correct size
|
||||
, ((modMask, xK_n ), refresh)
|
||||
, ((modm, xK_n ), refresh)
|
||||
|
||||
-- Move focus to the next window
|
||||
, ((modMask, xK_Tab ), windows W.focusDown)
|
||||
, ((modm, xK_Tab ), windows W.focusDown)
|
||||
|
||||
-- Move focus to the next window
|
||||
, ((modMask, xK_j ), windows W.focusDown)
|
||||
, ((modm, xK_j ), windows W.focusDown)
|
||||
|
||||
-- Move focus to the previous window
|
||||
, ((modMask, xK_k ), windows W.focusUp )
|
||||
, ((modm, xK_k ), windows W.focusUp )
|
||||
|
||||
-- Move focus to the master window
|
||||
, ((modMask, xK_m ), windows W.focusMaster )
|
||||
, ((modm, xK_m ), windows W.focusMaster )
|
||||
|
||||
-- Swap the focused window and the master window
|
||||
, ((modMask, xK_Return), windows W.swapMaster)
|
||||
, ((modm, xK_Return), windows W.swapMaster)
|
||||
|
||||
-- Swap the focused window with the next window
|
||||
, ((modMask .|. shiftMask, xK_j ), windows W.swapDown )
|
||||
, ((modm .|. shiftMask, xK_j ), windows W.swapDown )
|
||||
|
||||
-- Swap the focused window with the previous window
|
||||
, ((modMask .|. shiftMask, xK_k ), windows W.swapUp )
|
||||
, ((modm .|. shiftMask, xK_k ), windows W.swapUp )
|
||||
|
||||
-- Shrink the master area
|
||||
, ((modMask, xK_h ), sendMessage Shrink)
|
||||
, ((modm, xK_h ), sendMessage Shrink)
|
||||
|
||||
-- Expand the master area
|
||||
, ((modMask, xK_l ), sendMessage Expand)
|
||||
, ((modm, xK_l ), sendMessage Expand)
|
||||
|
||||
-- Push window back into tiling
|
||||
, ((modMask, xK_t ), withFocused $ windows . W.sink)
|
||||
, ((modm, xK_t ), withFocused $ windows . W.sink)
|
||||
|
||||
-- Increment the number of windows in the master area
|
||||
, ((modMask , xK_comma ), sendMessage (IncMasterN 1))
|
||||
, ((modm , xK_comma ), sendMessage (IncMasterN 1))
|
||||
|
||||
-- Deincrement the number of windows in the master area
|
||||
, ((modMask , xK_period), sendMessage (IncMasterN (-1)))
|
||||
, ((modm , xK_period), sendMessage (IncMasterN (-1)))
|
||||
|
||||
-- toggle the status bar gap
|
||||
-- TODO, update this binding with avoidStruts , ((modMask , xK_b ),
|
||||
-- Toggle the status bar gap
|
||||
-- Use this binding with avoidStruts from Hooks.ManageDocks.
|
||||
-- See also the statusBar function from Hooks.DynamicLog.
|
||||
--
|
||||
-- , ((modm , xK_b ), sendMessage ToggleStruts)
|
||||
|
||||
-- Quit xmonad
|
||||
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
|
||||
, ((modm .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
|
||||
|
||||
-- Restart xmonad
|
||||
, ((modMask , xK_q ), restart "xmonad" True)
|
||||
, ((modm , xK_q ), spawn "xmonad --recompile; xmonad --restart")
|
||||
]
|
||||
++
|
||||
|
||||
@@ -137,7 +145,7 @@ myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
||||
-- mod-[1..9], Switch to workspace N
|
||||
-- mod-shift-[1..9], Move client to workspace N
|
||||
--
|
||||
[((m .|. modMask, k), windows $ f i)
|
||||
[((m .|. modm, k), windows $ f i)
|
||||
| (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
|
||||
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
|
||||
++
|
||||
@@ -146,7 +154,7 @@ myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
||||
-- 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
|
||||
--
|
||||
[((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
|
||||
[((m .|. modm, key), screenWorkspace sc >>= flip whenJust (windows . f))
|
||||
| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
|
||||
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
|
||||
|
||||
@@ -154,16 +162,18 @@ myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
||||
------------------------------------------------------------------------
|
||||
-- Mouse bindings: default actions bound to mouse events
|
||||
--
|
||||
myMouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
|
||||
myMouseBindings (XConfig {XMonad.modMask = modm}) = M.fromList $
|
||||
|
||||
-- mod-button1, Set the window to floating mode and move by dragging
|
||||
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
|
||||
[ ((modm, 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.swapMaster))
|
||||
, ((modm, button2), (\w -> focus w >> windows W.shiftMaster))
|
||||
|
||||
-- mod-button3, Set the window to floating mode and resize by dragging
|
||||
, ((modMask, button3), (\w -> focus w >> mouseResizeWindow w))
|
||||
, ((modm, button3), (\w -> focus w >> mouseResizeWindow w
|
||||
>> windows W.shiftMaster))
|
||||
|
||||
-- you may also bind events to the mouse scroll wheel (button4 and button5)
|
||||
]
|
||||
@@ -214,10 +224,16 @@ myManageHook = composeAll
|
||||
, resource =? "desktop_window" --> doIgnore
|
||||
, resource =? "kdesktop" --> doIgnore ]
|
||||
|
||||
-- Whether focus follows the mouse pointer.
|
||||
myFocusFollowsMouse :: Bool
|
||||
myFocusFollowsMouse = True
|
||||
------------------------------------------------------------------------
|
||||
-- Event handling
|
||||
|
||||
-- * EwmhDesktops users should change this to ewmhDesktopsEventHook
|
||||
--
|
||||
-- Defines a custom handler function for X Events. The function should
|
||||
-- return (All True) if the default handler is to be run afterwards. To
|
||||
-- combine event hooks use mappend or mconcat from Data.Monoid.
|
||||
--
|
||||
myEventHook = mempty
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- Status bars and logging
|
||||
@@ -249,9 +265,9 @@ myStartupHook = return ()
|
||||
main = xmonad defaults
|
||||
|
||||
-- A structure containing your configuration settings, overriding
|
||||
-- fields in the default config. Any you don't override, will
|
||||
-- fields in the default config. Any you don't override, will
|
||||
-- use the defaults defined in xmonad/XMonad/Config.hs
|
||||
--
|
||||
--
|
||||
-- No need to modify this.
|
||||
--
|
||||
defaults = defaultConfig {
|
||||
@@ -272,6 +288,7 @@ defaults = defaultConfig {
|
||||
-- hooks, layouts
|
||||
layoutHook = myLayout,
|
||||
manageHook = myManageHook,
|
||||
handleEventHook = myEventHook,
|
||||
logHook = myLogHook,
|
||||
startupHook = myStartupHook
|
||||
}
|
||||
|
@@ -528,6 +528,18 @@ prop_shift_reversible i (x :: T) =
|
||||
y = swapMaster x
|
||||
n = tag (workspace $ current y)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- shiftMaster
|
||||
|
||||
-- focus/local/idempotent same as swapMaster:
|
||||
prop_shift_master_focus (x :: T) = peek x == (peek $ shiftMaster x)
|
||||
prop_shift_master_local (x :: T) = hidden_spaces x == hidden_spaces (shiftMaster x)
|
||||
prop_shift_master_idempotent (x :: T) = shiftMaster (shiftMaster x) == shiftMaster x
|
||||
-- ordering is constant modulo the focused window:
|
||||
prop_shift_master_ordering (x :: T) = case peek x of
|
||||
Nothing -> True
|
||||
Just m -> L.delete m (index x) == L.delete m (index $ shiftMaster x)
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
-- shiftWin
|
||||
|
||||
@@ -933,6 +945,11 @@ main = do
|
||||
,("swapUp is local" , mytest prop_swap_left_local)
|
||||
,("swapDown is local" , mytest prop_swap_right_local)
|
||||
|
||||
,("shiftMaster id on focus", mytest prop_shift_master_focus)
|
||||
,("shiftMaster is local", mytest prop_shift_master_local)
|
||||
,("shiftMaster is idempotent", mytest prop_shift_master_idempotent)
|
||||
,("shiftMaster preserves ordering", mytest prop_shift_master_ordering)
|
||||
|
||||
,("shift: invariant" , mytest prop_shift_I)
|
||||
,("shift is reversible" , mytest prop_shift_reversible)
|
||||
,("shiftWin: invariant" , mytest prop_shift_win_I)
|
||||
|
@@ -20,6 +20,13 @@ import Text.Regex.Posix
|
||||
import Data.Char
|
||||
import Data.List
|
||||
|
||||
import Distribution.PackageDescription.Parse
|
||||
import Distribution.Verbosity
|
||||
import Distribution.Package
|
||||
import Distribution.PackageDescription
|
||||
import Text.PrettyPrint.HughesPJ
|
||||
import Distribution.Text
|
||||
|
||||
trim :: String -> String
|
||||
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
|
||||
|
||||
@@ -42,6 +49,9 @@ replace :: Eq a => a -> a -> [a] -> [a]
|
||||
replace x y = map (\a -> if a == x then y else a)
|
||||
|
||||
main = do
|
||||
releaseName <- ((' ':) . (++" \\") . show . disp . package . packageDescription) `liftM` readPackageDescription normal "xmonad.cabal"
|
||||
|
||||
troffBindings <- (concatMap troff . allBindings) `liftM` readFile "./XMonad/Config.hs"
|
||||
let sed = unlines . replace "___KEYBINDINGS___" troffBindings . lines
|
||||
|
||||
let sed = unlines . replace "___RELEASE___\\" releaseName . replace "___KEYBINDINGS___" troffBindings . lines
|
||||
readFile "./man/xmonad.1.in" >>= return . sed >>= writeFile "./man/xmonad.1"
|
||||
|
10
xmonad.cabal
10
xmonad.cabal
@@ -1,5 +1,5 @@
|
||||
name: xmonad
|
||||
version: 0.8
|
||||
version: 0.9
|
||||
homepage: http://xmonad.org
|
||||
synopsis: A tiling window manager
|
||||
description:
|
||||
@@ -18,11 +18,13 @@ 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.hs
|
||||
man/xmonad.1.in man/xmonad.1 man/xmonad.html
|
||||
util/GenerateManpage.hs
|
||||
cabal-version: >= 1.2
|
||||
build-type: Simple
|
||||
|
||||
data-files: man/xmonad.hs
|
||||
|
||||
flag small_base
|
||||
description: Choose the new smaller, split-up base package.
|
||||
|
||||
@@ -41,10 +43,10 @@ library
|
||||
XMonad.StackSet
|
||||
|
||||
if flag(small_base)
|
||||
build-depends: base >= 3, containers, directory, process
|
||||
build-depends: base < 4 && >=3, containers, directory, process, filepath
|
||||
else
|
||||
build-depends: base < 3
|
||||
build-depends: X11>=1.4.1, mtl, unix
|
||||
build-depends: X11>=1.4.6.1, mtl, unix
|
||||
|
||||
ghc-options: -funbox-strict-fields -Wall
|
||||
ghc-prof-options: -prof -auto-all
|
||||
|
Reference in New Issue
Block a user