mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-02 13:11:53 -07:00
Compare commits
23 Commits
Author | SHA1 | Date | |
---|---|---|---|
|
5edfb1d262 | ||
|
0fecae0abc | ||
|
26f4f734f9 | ||
|
5e7df396b9 | ||
|
314ba78335 | ||
|
7aa78ecc75 | ||
|
ba8e26458e | ||
|
c627e8cc4d | ||
|
04f894275d | ||
|
edb752136f | ||
|
2b463a632f | ||
|
ca122dd2cb | ||
|
77657b65f9 | ||
|
28c57a837a | ||
|
afda20b56d | ||
|
0cc7b12fd0 | ||
|
15a78ae715 | ||
|
18444799e0 | ||
|
cc60fa73ad | ||
|
8881e2ac78 | ||
|
533031e3d6 | ||
|
76d4af15e4 | ||
|
74c6dd2721 |
2
CONFIG
2
CONFIG
@@ -53,7 +53,7 @@ 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
|
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
|
environment variable. If GHC isn't in your path, for some reason, you
|
||||||
can compile the xmonad.hs file yourself:
|
can compile the xmonad.hs file yourself:
|
||||||
|
|
||||||
|
7
Main.hs
7
Main.hs
@@ -32,6 +32,7 @@ import qualified Properties
|
|||||||
-- for xmonad, and if it doesn't find one, just launches the default.
|
-- for xmonad, and if it doesn't find one, just launches the default.
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
|
installSignalHandlers -- important to ignore SIGCHLD to avoid zombies
|
||||||
args <- getArgs
|
args <- getArgs
|
||||||
let launch = catchIO buildLaunch >> xmonad defaultConfig
|
let launch = catchIO buildLaunch >> xmonad defaultConfig
|
||||||
case args of
|
case args of
|
||||||
@@ -59,13 +60,13 @@ usage = do
|
|||||||
#endif
|
#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
|
-- errors, this function does not return. An exception is raised in any of
|
||||||
-- these cases:
|
-- these cases:
|
||||||
--
|
--
|
||||||
-- * ghc missing
|
-- * ghc missing
|
||||||
--
|
--
|
||||||
-- * ~/.xmonad/xmonad.hs missing
|
-- * "~\/.xmonad\/xmonad.hs" missing
|
||||||
--
|
--
|
||||||
-- * xmonad.hs fails to compile
|
-- * xmonad.hs fails to compile
|
||||||
--
|
--
|
||||||
@@ -73,7 +74,7 @@ usage = do
|
|||||||
--
|
--
|
||||||
-- ** type error, syntax error, ..
|
-- ** type error, syntax error, ..
|
||||||
--
|
--
|
||||||
-- * Missing xmonad/XMonadContrib modules due to ghc upgrade
|
-- * Missing XMonad\/XMonadContrib modules due to ghc upgrade
|
||||||
--
|
--
|
||||||
buildLaunch :: IO ()
|
buildLaunch :: IO ()
|
||||||
buildLaunch = do
|
buildLaunch = do
|
||||||
|
4
README
4
README
@@ -26,7 +26,7 @@ Building:
|
|||||||
|
|
||||||
Building is quite straightforward, and requires a basic Haskell toolchain.
|
Building is quite straightforward, and requires a basic Haskell toolchain.
|
||||||
On many systems xmonad is available as a binary package in your
|
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
|
in preference to a source build, as the dependency resolution will be
|
||||||
simpler.
|
simpler.
|
||||||
|
|
||||||
@@ -128,7 +128,7 @@ XMonadContrib
|
|||||||
|
|
||||||
Other useful programs:
|
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
|
urxvt http://software.schmorp.de/pkg/rxvt-unicode.html
|
||||||
|
|
||||||
|
4
STYLE
4
STYLE
@@ -2,7 +2,7 @@
|
|||||||
== Coding guidelines for contributing to
|
== Coding guidelines for contributing to
|
||||||
== xmonad and the xmonad contributed extensions
|
== 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.
|
provide a type signature; use Haddock syntax in the comments.
|
||||||
|
|
||||||
* Follow the coding style of the other modules.
|
* Follow the coding style of the other modules.
|
||||||
@@ -15,7 +15,7 @@
|
|||||||
* Tabs are illegal. Use 4 spaces for indenting.
|
* Tabs are illegal. Use 4 spaces for indenting.
|
||||||
|
|
||||||
* Any pure function added to the core should have QuickCheck properties
|
* 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
|
* New modules should identify the author, and be submitted under
|
||||||
the same license as xmonad (BSD3 license or freer).
|
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:
|
- Write down invariants for the window life cycle, especially:
|
||||||
- When are borders set? Prove that the current handling is sufficient.
|
- 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
|
for example
|
||||||
|
|
||||||
- Issues still with stacking order.
|
- Issues still with stacking order.
|
||||||
@@ -15,7 +15,7 @@
|
|||||||
* double check README build instructions
|
* double check README build instructions
|
||||||
* test core with 6.6 and 6.8
|
* test core with 6.6 and 6.8
|
||||||
* bump xmonad.cabal version and X11 version
|
* 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 examples/text in user-facing Config.hs
|
||||||
* check tour.html and intro.html are up to date, and mention all core bindings
|
* check tour.html and intro.html are up to date, and mention all core bindings
|
||||||
* confirm template config is type correct
|
* confirm template config is type correct
|
||||||
|
@@ -226,12 +226,12 @@ 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
|
-- mod-button1 %! Set the window to floating mode and move by dragging
|
||||||
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w
|
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w
|
||||||
>> windows W.swapMaster))
|
>> windows W.shiftMaster))
|
||||||
-- mod-button2 %! Raise the window to the top of the stack
|
-- 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
|
-- mod-button3 %! Set the window to floating mode and resize by dragging
|
||||||
, ((modMask, button3), (\w -> focus w >> mouseResizeWindow w
|
, ((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)
|
-- you may also bind events to the mouse scroll wheel (button4 and button5)
|
||||||
]
|
]
|
||||||
|
|
||||||
|
@@ -24,29 +24,33 @@ module XMonad.Core (
|
|||||||
XConf(..), XConfig(..), LayoutClass(..),
|
XConf(..), XConfig(..), LayoutClass(..),
|
||||||
Layout(..), readsLayout, Typeable, Message,
|
Layout(..), readsLayout, Typeable, Message,
|
||||||
SomeMessage(..), fromMessage, LayoutMessages(..),
|
SomeMessage(..), fromMessage, LayoutMessages(..),
|
||||||
runX, catchX, userCode, io, catchIO, doubleFork,
|
runX, catchX, userCode, userCodeDef, io, catchIO, installSignalHandlers,
|
||||||
withDisplay, withWindowSet, isRoot, runOnWorkspaces,
|
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
|
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runQuery
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import XMonad.StackSet hiding (modify)
|
import XMonad.StackSet hiding (modify)
|
||||||
|
|
||||||
import Prelude hiding ( catch )
|
import Prelude hiding ( catch )
|
||||||
import Control.Exception (catch, bracket, throw, Exception(ExitException))
|
import Control.Exception (catch, try, bracket, throw, Exception(ExitException))
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import System.IO
|
import System.IO
|
||||||
import System.Info
|
import System.Info
|
||||||
import System.Posix.Process (executeFile, forkProcess, getProcessStatus, createSession)
|
import System.Posix.Process (executeFile, forkProcess, getAnyProcessStatus)
|
||||||
|
import System.Posix.Signals
|
||||||
|
import System.Posix.Types (ProcessID)
|
||||||
import System.Process
|
import System.Process
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import System.Exit
|
import System.Exit
|
||||||
import Graphics.X11.Xlib
|
import Graphics.X11.Xlib
|
||||||
import Graphics.X11.Xlib.Extras (Event)
|
import Graphics.X11.Xlib.Extras (Event)
|
||||||
import Data.Typeable
|
import Data.Typeable
|
||||||
|
import Data.Maybe (isJust)
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
|
import Data.Maybe (fromMaybe)
|
||||||
|
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
@@ -70,6 +74,9 @@ data XConf = XConf
|
|||||||
, buttonActions :: !(M.Map (KeyMask, Button) (Window -> X ()))
|
, buttonActions :: !(M.Map (KeyMask, Button) (Window -> X ()))
|
||||||
-- ^ a mapping of button presses to actions
|
-- ^ a mapping of button presses to actions
|
||||||
, mouseFocused :: !Bool -- ^ was refocus caused by mouse action?
|
, 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
|
-- todo, better name
|
||||||
@@ -160,8 +167,13 @@ catchX job errcase = do
|
|||||||
|
|
||||||
-- | Execute the argument, catching all exceptions. Either this function or
|
-- | Execute the argument, catching all exceptions. Either this function or
|
||||||
-- 'catchX' should be used at all callsites of user customized code.
|
-- 'catchX' should be used at all callsites of user customized code.
|
||||||
userCode :: X () -> X ()
|
userCode :: X a -> X (Maybe a)
|
||||||
userCode a = catchX (a >> return ()) (return ())
|
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
|
-- Convenient wrappers to state
|
||||||
@@ -337,19 +349,13 @@ io = liftIO
|
|||||||
catchIO :: MonadIO m => IO () -> m ()
|
catchIO :: MonadIO m => IO () -> m ()
|
||||||
catchIO f = io (f `catch` \e -> hPrint stderr e >> hFlush stderr)
|
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 :: 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
|
spawnPID :: MonadIO m => String -> m ProcessID
|
||||||
-- functions)
|
spawnPID x = io $ forkProcess $ executeFile "/bin/sh" False ["-c", x] Nothing
|
||||||
doubleFork :: MonadIO m => IO () -> m ()
|
|
||||||
doubleFork m = io $ do
|
|
||||||
pid <- forkProcess $ do
|
|
||||||
forkProcess (createSession >> m)
|
|
||||||
exitWith ExitSuccess
|
|
||||||
getProcessStatus True False pid
|
|
||||||
return ()
|
|
||||||
|
|
||||||
-- | This is basically a map function, running a function in the 'X' monad on
|
-- | 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.
|
-- each workspace with the output of that function being the modified workspace.
|
||||||
@@ -394,10 +400,15 @@ recompile force = io $ do
|
|||||||
binT <- getModTime bin
|
binT <- getModTime bin
|
||||||
if (force || srcT > binT)
|
if (force || srcT > binT)
|
||||||
then do
|
then do
|
||||||
|
-- temporarily disable SIGCHLD ignoring:
|
||||||
|
installHandler sigCHLD Default Nothing
|
||||||
status <- bracket (openFile err WriteMode) hClose $ \h -> do
|
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", "-no-recomp", "-v0", "-o",binn] (Just dir)
|
||||||
Nothing Nothing Nothing (Just h)
|
Nothing Nothing Nothing (Just h)
|
||||||
|
|
||||||
|
-- re-enable SIGCHLD:
|
||||||
|
installSignalHandlers
|
||||||
|
|
||||||
-- now, if it fails, run xmessage to let the user know:
|
-- now, if it fails, run xmessage to let the user know:
|
||||||
when (status /= ExitSuccess) $ do
|
when (status /= ExitSuccess) $ do
|
||||||
ghcErr <- readFile err
|
ghcErr <- readFile err
|
||||||
@@ -407,7 +418,8 @@ recompile force = io $ do
|
|||||||
-- nb, the ordering of printing, then forking, is crucial due to
|
-- nb, the ordering of printing, then forking, is crucial due to
|
||||||
-- lazy evaluation
|
-- lazy evaluation
|
||||||
hPutStrLn stderr msg
|
hPutStrLn stderr msg
|
||||||
doubleFork $ executeFile "xmessage" True ["-default", "okay", msg] Nothing
|
forkProcess $ executeFile "xmessage" True ["-default", "okay", msg] Nothing
|
||||||
|
return ()
|
||||||
return (status == ExitSuccess)
|
return (status == ExitSuccess)
|
||||||
else return True
|
else return True
|
||||||
where getModTime f = catch (Just <$> getModificationTime f) (const $ return Nothing)
|
where getModTime f = catch (Just <$> getModificationTime f) (const $ return Nothing)
|
||||||
@@ -424,3 +436,14 @@ whenX a f = a >>= \b -> when b f
|
|||||||
-- be found in your .xsession-errors file
|
-- be found in your .xsession-errors file
|
||||||
trace :: MonadIO m => String -> m ()
|
trace :: MonadIO m => String -> m ()
|
||||||
trace = io . hPutStrLn stderr
|
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 ()
|
||||||
|
@@ -51,7 +51,10 @@ instance LayoutClass Full a
|
|||||||
|
|
||||||
-- | The builtin tiling mode of xmonad. Supports 'Shrink', 'Expand' and
|
-- | The builtin tiling mode of xmonad. Supports 'Shrink', 'Expand' and
|
||||||
-- 'IncMasterN'.
|
-- 'IncMasterN'.
|
||||||
data Tall a = Tall !Int !Rational !Rational deriving (Show, Read)
|
data Tall a = Tall !Int -- ^ The default number of windows in the master pane (default: 1)
|
||||||
|
!Rational -- ^ Default proportion of screen occupied by master pane (default: 1/2)
|
||||||
|
!Rational -- ^ Percent of screen to increment by when resizing panes (default: 3/100)
|
||||||
|
deriving (Show, Read)
|
||||||
-- TODO should be capped [0..1] ..
|
-- TODO should be capped [0..1] ..
|
||||||
|
|
||||||
-- a nice pure layout, lots of properties for the layout, and its messages, in Properties.hs
|
-- a nice pure layout, lots of properties for the layout, and its messages, in Properties.hs
|
||||||
|
@@ -27,7 +27,6 @@ import Foreign.C
|
|||||||
import Foreign.Ptr
|
import Foreign.Ptr
|
||||||
|
|
||||||
import System.Environment (getArgs)
|
import System.Environment (getArgs)
|
||||||
import System.Posix.Signals
|
|
||||||
|
|
||||||
import Graphics.X11.Xlib hiding (refreshKeyboardMapping)
|
import Graphics.X11.Xlib hiding (refreshKeyboardMapping)
|
||||||
import Graphics.X11.Xlib.Extras
|
import Graphics.X11.Xlib.Extras
|
||||||
@@ -57,14 +56,27 @@ xmonad :: (LayoutClass l Window, Read (l Window)) => XConfig l -> IO ()
|
|||||||
xmonad initxmc = do
|
xmonad initxmc = do
|
||||||
-- setup locale information from environment
|
-- setup locale information from environment
|
||||||
withCString "" $ c_setlocale (#const LC_ALL)
|
withCString "" $ c_setlocale (#const LC_ALL)
|
||||||
-- ignore SIGPIPE
|
-- ignore SIGPIPE and SIGCHLD
|
||||||
installHandler openEndedPipe Ignore Nothing
|
installSignalHandlers
|
||||||
-- First, wrap the layout in an existential, to keep things pretty:
|
-- First, wrap the layout in an existential, to keep things pretty:
|
||||||
let xmc = initxmc { layoutHook = Layout $ layoutHook initxmc }
|
let xmc = initxmc { layoutHook = Layout $ layoutHook initxmc }
|
||||||
dpy <- openDisplay ""
|
dpy <- openDisplay ""
|
||||||
let dflt = defaultScreen dpy
|
let dflt = defaultScreen dpy
|
||||||
|
|
||||||
rootw <- rootWindow dpy dflt
|
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
|
xinesc <- getCleanedScreenInfo dpy
|
||||||
nbc <- do v <- initColor dpy $ normalBorderColor xmc
|
nbc <- do v <- initColor dpy $ normalBorderColor xmc
|
||||||
~(Just nbc_) <- initColor dpy $ normalBorderColor Default.defaultConfig
|
~(Just nbc_) <- initColor dpy $ normalBorderColor Default.defaultConfig
|
||||||
@@ -99,20 +111,14 @@ xmonad initxmc = do
|
|||||||
, focusedBorder = fbc
|
, focusedBorder = fbc
|
||||||
, keyActions = keys xmc xmc
|
, keyActions = keys xmc xmc
|
||||||
, buttonActions = mouseBindings xmc xmc
|
, buttonActions = mouseBindings xmc xmc
|
||||||
, mouseFocused = False }
|
, mouseFocused = False
|
||||||
|
, mousePosition = Nothing }
|
||||||
st = XState
|
st = XState
|
||||||
{ windowset = initialWinset
|
{ windowset = initialWinset
|
||||||
, mapped = S.empty
|
, mapped = S.empty
|
||||||
, waitingUnmap = M.empty
|
, waitingUnmap = M.empty
|
||||||
, dragging = Nothing }
|
, 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 ->
|
allocaXEvent $ \e ->
|
||||||
runX cf st $ do
|
runX cf st $ do
|
||||||
|
|
||||||
@@ -136,10 +142,19 @@ xmonad initxmc = do
|
|||||||
userCode $ startupHook initxmc
|
userCode $ startupHook initxmc
|
||||||
|
|
||||||
-- main loop, for all you HOF/recursion fans out there.
|
-- 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 ()
|
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 }) (handle e)
|
||||||
|
evs = [ keyPress, keyRelease, enterNotify, leaveNotify
|
||||||
|
, buttonPress, buttonRelease]
|
||||||
|
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
@@ -160,7 +175,7 @@ handle (KeyEvent {ev_event_type = t, ev_state = m, ev_keycode = code})
|
|||||||
s <- io $ keycodeToKeysym dpy code 0
|
s <- io $ keycodeToKeysym dpy code 0
|
||||||
mClean <- cleanMask m
|
mClean <- cleanMask m
|
||||||
ks <- asks keyActions
|
ks <- asks keyActions
|
||||||
userCode $ whenJust (M.lookup (mClean, s) ks) id
|
userCodeDef () $ whenJust (M.lookup (mClean, s) ks) id
|
||||||
|
|
||||||
-- manage a new window
|
-- manage a new window
|
||||||
handle (MapRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
|
handle (MapRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
|
||||||
@@ -214,16 +229,16 @@ handle e@(ButtonEvent {ev_window = w,ev_event_type = t,ev_button = b })
|
|||||||
-- grabbed in grabButtons. Otherwise, it's click-to-focus.
|
-- grabbed in grabButtons. Otherwise, it's click-to-focus.
|
||||||
isr <- isRoot w
|
isr <- isRoot w
|
||||||
m <- cleanMask $ ev_state e
|
m <- cleanMask $ ev_state e
|
||||||
ba <- asks buttonActions
|
mact <- asks (M.lookup (m, b) . buttonActions)
|
||||||
if isr then userCode $ whenJust (M.lookup (m, b) ba) ($ ev_subwindow e)
|
case mact of
|
||||||
else focus w
|
(Just act) | isr -> act $ ev_subwindow e
|
||||||
|
_ -> focus w
|
||||||
broadcastMessage e -- Always send button events.
|
broadcastMessage e -- Always send button events.
|
||||||
|
|
||||||
-- entered a normal window: focus it if focusFollowsMouse is set to
|
-- entered a normal window: focus it if focusFollowsMouse is set to
|
||||||
-- True in the user's config.
|
-- True in the user's config.
|
||||||
handle e@(CrossingEvent {ev_window = w, ev_event_type = t})
|
handle e@(CrossingEvent {ev_window = w, ev_event_type = t})
|
||||||
| t == enterNotify && ev_mode e == notifyNormal
|
| t == enterNotify && ev_mode e == notifyNormal
|
||||||
&& ev_detail e /= notifyInferior
|
|
||||||
= whenX (asks $ focusFollowsMouse . config) (focus w)
|
= whenX (asks $ focusFollowsMouse . config) (focus w)
|
||||||
|
|
||||||
-- left a window, check if we need to focus root
|
-- left a window, check if we need to focus root
|
||||||
@@ -263,7 +278,7 @@ handle (ConfigureEvent {ev_window = w}) = whenX (isRoot w) rescreen
|
|||||||
|
|
||||||
-- property notify
|
-- property notify
|
||||||
handle PropertyEvent { ev_event_type = t, ev_atom = a }
|
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 = broadcastMessage e -- trace (eventName e) -- ignoring
|
handle e = broadcastMessage e -- trace (eventName e) -- ignoring
|
||||||
|
|
||||||
|
@@ -23,7 +23,7 @@ import XMonad.Layout (Full(..))
|
|||||||
import qualified XMonad.StackSet as W
|
import qualified XMonad.StackSet as W
|
||||||
|
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Monoid (appEndo)
|
import Data.Monoid (Endo(..))
|
||||||
import Data.List (nub, (\\), find)
|
import Data.List (nub, (\\), find)
|
||||||
import Data.Bits ((.|.), (.&.), complement)
|
import Data.Bits ((.|.), (.&.), complement)
|
||||||
import Data.Ratio
|
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
|
where i = W.tag $ W.workspace $ W.current ws
|
||||||
|
|
||||||
mh <- asks (manageHook . config)
|
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)
|
windows (g . f)
|
||||||
|
|
||||||
-- | unmanage. A window no longer exists, remove it from the window
|
-- | 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 :: Window -> X ()
|
||||||
unmanage = windows . W.delete
|
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.
|
-- delete notify back from X.
|
||||||
--
|
--
|
||||||
-- There are two ways to delete a window. Either just kill it, or if it
|
-- 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)
|
-- supports the delete protocol, send a delete event (e.g. firefox)
|
||||||
--
|
--
|
||||||
kill :: X ()
|
killWindow :: Window -> X ()
|
||||||
kill = withDisplay $ \d -> withFocused $ \w -> do
|
killWindow w = withDisplay $ \d -> do
|
||||||
wmdelt <- atom_WM_DELETE_WINDOW ; wmprot <- atom_WM_PROTOCOLS
|
wmdelt <- atom_WM_DELETE_WINDOW ; wmprot <- atom_WM_PROTOCOLS
|
||||||
|
|
||||||
protocols <- io $ getWMProtocols d w
|
protocols <- io $ getWMProtocols d w
|
||||||
@@ -95,6 +95,10 @@ kill = withDisplay $ \d -> withFocused $ \w -> do
|
|||||||
sendEvent d w False noEventMask ev
|
sendEvent d w False noEventMask ev
|
||||||
else killClient d w >> return ()
|
else killClient d w >> return ()
|
||||||
|
|
||||||
|
-- | Kill the currently focused client.
|
||||||
|
kill :: X ()
|
||||||
|
kill = withFocused killWindow
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Managing windows
|
-- Managing windows
|
||||||
|
|
||||||
@@ -120,46 +124,44 @@ windows f = do
|
|||||||
-- for each workspace, layout the currently visible workspaces
|
-- for each workspace, layout the currently visible workspaces
|
||||||
let allscreens = W.screens ws
|
let allscreens = W.screens ws
|
||||||
summed_visible = scanl (++) [] $ map (W.integrate' . W.stack . W.workspace) allscreens
|
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
|
let wsp = W.workspace w
|
||||||
this = W.view n ws
|
this = W.view n ws
|
||||||
n = W.tag wsp
|
n = W.tag wsp
|
||||||
flt = filter (flip M.member (W.floating ws)) (W.index this)
|
|
||||||
tiled = (W.stack . W.workspace . W.current $ this)
|
tiled = (W.stack . W.workspace . W.current $ this)
|
||||||
>>= W.filter (`M.notMember` W.floating ws)
|
>>= W.filter (`M.notMember` W.floating ws)
|
||||||
>>= W.filter (`notElem` vis)
|
>>= W.filter (`notElem` vis)
|
||||||
viewrect@(Rectangle sx sy sw sh) = screenRect $ W.screenDetail w
|
viewrect = screenRect $ W.screenDetail w
|
||||||
|
|
||||||
-- just the tiled windows:
|
-- just the tiled windows:
|
||||||
-- now tile the windows on this workspace, modified by the gap
|
-- now tile the windows on this workspace, modified by the gap
|
||||||
(rs, ml') <- runLayout wsp { W.stack = tiled } viewrect `catchX`
|
(rs, ml') <- runLayout wsp { W.stack = tiled } viewrect `catchX`
|
||||||
runLayout wsp { W.stack = tiled, W.layout = Layout Full } viewrect
|
runLayout wsp { W.stack = tiled, W.layout = Layout Full } viewrect
|
||||||
mapM_ (uncurry tileWindow) rs
|
|
||||||
updateLayout n ml'
|
updateLayout n ml'
|
||||||
|
|
||||||
-- now the floating windows:
|
let m = W.floating ws
|
||||||
-- move/resize the floating windows, if there are any
|
flt = [(fw, scaleRationalRect viewrect r)
|
||||||
forM_ flt $ \fw -> whenJust (M.lookup fw (W.floating ws)) $
|
| fw <- filter (flip M.member m) (W.index this)
|
||||||
\(W.RationalRect rx ry rw rh) -> do
|
, Just r <- [M.lookup fw m]]
|
||||||
tileWindow fw $ Rectangle
|
vs = flt ++ rs
|
||||||
(sx + floor (toRational sw*rx)) (sy + floor (toRational sh*ry))
|
|
||||||
(floor (toRational sw*rw)) (floor (toRational sh*rh))
|
|
||||||
|
|
||||||
let vs = flt ++ map fst rs
|
io $ restackWindows d (map fst vs)
|
||||||
io $ restackWindows d vs
|
|
||||||
-- return the visible windows for this workspace:
|
-- return the visible windows for this workspace:
|
||||||
return vs
|
return vs
|
||||||
|
|
||||||
whenJust (W.peek ws) $ \w -> io $ setWindowBorder d w fbc
|
let visible = map fst rects
|
||||||
asks (logHook . config) >>= userCode
|
|
||||||
|
|
||||||
mapM_ reveal visible
|
mapM_ (uncurry tileWindow) rects
|
||||||
setTopFocus
|
|
||||||
|
whenJust (W.peek ws) $ \w -> io $ setWindowBorder d w fbc
|
||||||
|
|
||||||
-- hide every window that was potentially visible before, but is not
|
-- hide every window that was potentially visible before, but is not
|
||||||
-- given a position by a layout now.
|
-- given a position by a layout now.
|
||||||
mapM_ hide (nub (oldvisible ++ newwindows) \\ visible)
|
mapM_ hide (nub (oldvisible ++ newwindows) \\ visible)
|
||||||
|
|
||||||
|
mapM_ reveal visible
|
||||||
|
setTopFocus
|
||||||
|
|
||||||
-- all windows that are no longer in the windowset are marked as
|
-- all windows that are no longer in the windowset are marked as
|
||||||
-- withdrawn, it is important to do this after the above, otherwise 'hide'
|
-- withdrawn, it is important to do this after the above, otherwise 'hide'
|
||||||
-- will overwrite withdrawnState with iconicState
|
-- will overwrite withdrawnState with iconicState
|
||||||
@@ -167,6 +169,13 @@ windows f = do
|
|||||||
|
|
||||||
isMouseFocused <- asks mouseFocused
|
isMouseFocused <- asks mouseFocused
|
||||||
unless isMouseFocused $ clearEvents enterWindowMask
|
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. set the WM_STATE property
|
||||||
setWMState :: Window -> Int -> X ()
|
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
|
-- This happens if X notices we've moved the mouse (and perhaps moved
|
||||||
-- the mouse to a new screen).
|
-- the mouse to a new screen).
|
||||||
focus :: Window -> X ()
|
focus :: Window -> X ()
|
||||||
focus w = withWindowSet $ \s -> do
|
focus w = local (\c -> c { mouseFocused = True }) $ withWindowSet $ \s -> do
|
||||||
if W.member w s then when (W.peek s /= Just w) $ do
|
let stag = W.tag . W.workspace
|
||||||
local (\c -> c { mouseFocused = True }) $ do
|
curr = stag $ W.current s
|
||||||
windows (W.focusWindow w)
|
mnew <- maybe (return Nothing) (fmap (fmap stag) . uncurry pointScreen)
|
||||||
else whenX (isRoot w) $ setFocusX w
|
=<< 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.
|
-- | Call X to set the keyboard focus details.
|
||||||
setFocusX :: Window -> X ()
|
setFocusX :: Window -> X ()
|
||||||
@@ -412,10 +427,9 @@ floatLocation w = withDisplay $ \d -> do
|
|||||||
ws <- gets windowset
|
ws <- gets windowset
|
||||||
wa <- io $ getWindowAttributes d w
|
wa <- io $ getWindowAttributes d w
|
||||||
bw <- fi <$> asks (borderWidth . config)
|
bw <- fi <$> asks (borderWidth . config)
|
||||||
|
sc <- fromMaybe (W.current ws) <$> pointScreen (fi $ wa_x wa) (fi $ wa_y wa)
|
||||||
|
|
||||||
-- XXX horrible
|
let sr = screenRect . W.screenDetail $ sc
|
||||||
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
|
|
||||||
rr = W.RationalRect ((fi (wa_x wa) - fi (rect_x sr)) % fi (rect_width sr))
|
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_y wa) - fi (rect_y sr)) % fi (rect_height sr))
|
||||||
(fi (wa_width wa + bw*2) % fi (rect_width 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)
|
return (W.screen $ sc, rr)
|
||||||
where fi x = fromIntegral x
|
where fi x = fromIntegral x
|
||||||
pointWithin :: Integer -> Integer -> Rectangle -> Bool
|
|
||||||
pointWithin x y r = x >= fi (rect_x r) &&
|
-- | Given a point, determine the screen (if any) that contains it.
|
||||||
x < fi (rect_x r) + fi (rect_width r) &&
|
pointScreen :: Position -> Position
|
||||||
y >= fi (rect_y r) &&
|
-> X (Maybe (W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail))
|
||||||
y < fi (rect_y r) + fi (rect_height r)
|
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
|
-- | Make a tiled window floating, using its suggested rectangle
|
||||||
float :: Window -> X ()
|
float :: Window -> X ()
|
||||||
|
@@ -35,14 +35,14 @@ module XMonad.StackSet (
|
|||||||
-- * Operations on the current stack
|
-- * Operations on the current stack
|
||||||
-- $stackOperations
|
-- $stackOperations
|
||||||
peek, index, integrate, integrate', differentiate,
|
peek, index, integrate, integrate', differentiate,
|
||||||
focusUp, focusDown, focusMaster, focusWindow,
|
focusUp, focusDown, focusUp', focusDown', focusMaster, focusWindow,
|
||||||
tagMember, renameTag, ensureTags, member, findTag, mapWorkspace, mapLayout,
|
tagMember, renameTag, ensureTags, member, findTag, mapWorkspace, mapLayout,
|
||||||
-- * Modifying the stackset
|
-- * Modifying the stackset
|
||||||
-- $modifyStackset
|
-- $modifyStackset
|
||||||
insertUp, delete, delete', filter,
|
insertUp, delete, delete', filter,
|
||||||
-- * Setting the master window
|
-- * Setting the master window
|
||||||
-- $settingMW
|
-- $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 operations
|
||||||
-- $composite
|
-- $composite
|
||||||
shift, shiftWin,
|
shift, shiftWin,
|
||||||
@@ -342,15 +342,19 @@ index = with [] integrate
|
|||||||
--
|
--
|
||||||
focusUp, focusDown, swapUp, swapDown :: StackSet i l a s sd -> StackSet i l a s sd
|
focusUp, focusDown, swapUp, swapDown :: StackSet i l a s sd -> StackSet i l a s sd
|
||||||
focusUp = modify' focusUp'
|
focusUp = modify' focusUp'
|
||||||
focusDown = modify' (reverseStack . focusUp' . reverseStack)
|
focusDown = modify' focusDown'
|
||||||
|
|
||||||
swapUp = modify' swapUp'
|
swapUp = modify' swapUp'
|
||||||
swapDown = modify' (reverseStack . swapUp' . reverseStack)
|
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 (l:ls) rs) = Stack l ls (t:rs)
|
||||||
focusUp' (Stack t [] rs) = Stack x xs [] where (x:xs) = reverse (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 (l:ls) rs) = Stack t ls (l:rs)
|
||||||
swapUp' (Stack t [] rs) = Stack t (reverse rs) []
|
swapUp' (Stack t [] rs) = Stack t (reverse rs) []
|
||||||
|
|
||||||
@@ -508,6 +512,15 @@ swapMaster = modify' $ \c -> case c of
|
|||||||
|
|
||||||
-- natural! keep focus, move current to the top, move top to current.
|
-- 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.
|
-- | /O(s)/. Set focus to the master window.
|
||||||
focusMaster :: StackSet i l a s sd -> StackSet i l a s sd
|
focusMaster :: StackSet i l a s sd -> StackSet i l a s sd
|
||||||
focusMaster = modify' $ \c -> case c of
|
focusMaster = modify' $ \c -> case c of
|
||||||
|
@@ -36,5 +36,7 @@ xmonad
|
|||||||
to your \fI~/.xinitrc\fR file
|
to your \fI~/.xinitrc\fR file
|
||||||
.SH CUSTOMIZATION
|
.SH CUSTOMIZATION
|
||||||
\fBxmonad\fR is customized in ~/.xmonad/xmonad.hs, and then restarting with mod-q.
|
\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/.
|
||||||
.SH BUGS
|
.SH BUGS
|
||||||
Probably. If you find any, please report them: http://code.google.com/p/xmonad/issues/list
|
Probably. If you find any, please report them: http://code.google.com/p/xmonad/issues/list
|
||||||
|
@@ -157,13 +157,15 @@ myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
|||||||
myMouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
|
myMouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
|
||||||
|
|
||||||
-- mod-button1, Set the window to floating mode and move by dragging
|
-- mod-button1, Set the window to floating mode and move by dragging
|
||||||
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
|
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w
|
||||||
|
>> windows W.shiftMaster))
|
||||||
|
|
||||||
-- mod-button2, Raise the window to the top of the stack
|
-- 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
|
-- mod-button3, Set the window to floating mode and resize by dragging
|
||||||
, ((modMask, button3), (\w -> focus w >> mouseResizeWindow w))
|
, ((modMask, button3), (\w -> focus w >> mouseResizeWindow w
|
||||||
|
>> windows W.shiftMaster))
|
||||||
|
|
||||||
-- you may also bind events to the mouse scroll wheel (button4 and button5)
|
-- you may also bind events to the mouse scroll wheel (button4 and button5)
|
||||||
]
|
]
|
||||||
|
@@ -528,6 +528,18 @@ prop_shift_reversible i (x :: T) =
|
|||||||
y = swapMaster x
|
y = swapMaster x
|
||||||
n = tag (workspace $ current y)
|
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
|
-- shiftWin
|
||||||
|
|
||||||
@@ -933,6 +945,11 @@ main = do
|
|||||||
,("swapUp is local" , mytest prop_swap_left_local)
|
,("swapUp is local" , mytest prop_swap_left_local)
|
||||||
,("swapDown is local" , mytest prop_swap_right_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: invariant" , mytest prop_shift_I)
|
||||||
,("shift is reversible" , mytest prop_shift_reversible)
|
,("shift is reversible" , mytest prop_shift_reversible)
|
||||||
,("shiftWin: invariant" , mytest prop_shift_win_I)
|
,("shiftWin: invariant" , mytest prop_shift_win_I)
|
||||||
|
@@ -1,5 +1,5 @@
|
|||||||
name: xmonad
|
name: xmonad
|
||||||
version: 0.8
|
version: 0.8.1
|
||||||
homepage: http://xmonad.org
|
homepage: http://xmonad.org
|
||||||
synopsis: A tiling window manager
|
synopsis: A tiling window manager
|
||||||
description:
|
description:
|
||||||
@@ -41,10 +41,10 @@ library
|
|||||||
XMonad.StackSet
|
XMonad.StackSet
|
||||||
|
|
||||||
if flag(small_base)
|
if flag(small_base)
|
||||||
build-depends: base >= 3, containers, directory, process
|
build-depends: base < 4 && >=3, containers, directory, process
|
||||||
else
|
else
|
||||||
build-depends: base < 3
|
build-depends: base < 3
|
||||||
build-depends: X11>=1.4.1, mtl, unix
|
build-depends: X11>=1.4.3, mtl, unix
|
||||||
|
|
||||||
ghc-options: -funbox-strict-fields -Wall
|
ghc-options: -funbox-strict-fields -Wall
|
||||||
ghc-prof-options: -prof -auto-all
|
ghc-prof-options: -prof -auto-all
|
||||||
|
Reference in New Issue
Block a user