mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-03 05:31:54 -07:00
Compare commits
40 Commits
Author | SHA1 | Date | |
---|---|---|---|
|
8399e80327 | ||
|
3e3d516092 | ||
|
d2ae7310d6 | ||
|
ca3e277d2b | ||
|
bb2b6c7bf8 | ||
|
d74814af35 | ||
|
f9799422f9 | ||
|
be5e27038f | ||
|
1f4b8cb5f6 | ||
|
da7ca1c29d | ||
|
e095621ab9 | ||
|
93c55c948e | ||
|
9ff105340e | ||
|
5e61b137fb | ||
|
aeef36f74c | ||
|
673f303646 | ||
|
7f3c6823d4 | ||
|
79f23d6cec | ||
|
46f5e68cfa | ||
|
76d2bddaf0 | ||
|
f5e55f3a27 | ||
|
6c72a03fb1 | ||
|
31c7734f7b | ||
|
d1af7d986d | ||
|
da167bfc11 | ||
|
c46f3ad549 | ||
|
5b42a58d06 | ||
|
e8292e0e9d | ||
|
6cd46e12bb | ||
|
2441275122 | ||
|
f70ab7964e | ||
|
237fdbf037 | ||
|
5166ede96b | ||
|
56463b2391 | ||
|
f427c2b0e9 | ||
|
287d364e0d | ||
|
8c31768b79 | ||
|
9ceef229c3 | ||
|
40581c9bf8 | ||
|
161ade3593 |
27
Main.hs
27
Main.hs
@@ -1,6 +1,6 @@
|
||||
----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : Main.hs
|
||||
-- Module : Main
|
||||
-- Copyright : (c) Spencer Janssen 2007
|
||||
-- License : BSD3-style (see LICENSE)
|
||||
--
|
||||
@@ -14,21 +14,34 @@
|
||||
|
||||
module Main (main) where
|
||||
|
||||
import XMonad.Main
|
||||
import XMonad.Config
|
||||
import XMonad.Core (getXMonadDir, recompile)
|
||||
import XMonad
|
||||
|
||||
import Control.Exception (handle)
|
||||
import System.IO
|
||||
import System.Info
|
||||
import System.Environment
|
||||
import System.Posix.Process (executeFile)
|
||||
|
||||
#ifdef TESTING
|
||||
import qualified Properties
|
||||
#endif
|
||||
|
||||
-- | The entry point into xmonad. Attempts to compile any custom main
|
||||
-- for xmonad, and if it doesn't find one, just launches the default.
|
||||
main :: IO ()
|
||||
main = do
|
||||
handle (hPrint stderr) buildLaunch
|
||||
xmonad defaultConfig -- if buildLaunch returns, execute the trusted core
|
||||
args <- getArgs
|
||||
let launch = handle (hPrint stderr) buildLaunch >> xmonad defaultConfig
|
||||
case args of
|
||||
[] -> launch
|
||||
["--resume", _] -> launch
|
||||
["--recompile"] -> recompile False >> return ()
|
||||
["--recompile-force"] -> recompile True >> return ()
|
||||
["--version"] -> putStrLn "xmonad 0.5"
|
||||
#ifdef TESTING
|
||||
("--run-tests":_) -> Properties.main
|
||||
#endif
|
||||
_ -> fail "unrecognized flags"
|
||||
|
||||
-- | 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
|
||||
@@ -45,5 +58,5 @@ buildLaunch = do
|
||||
recompile False
|
||||
dir <- getXMonadDir
|
||||
args <- getArgs
|
||||
executeFile (dir ++ "/xmonad") False args Nothing
|
||||
executeFile (dir ++ "/xmonad-"++arch++"-"++os) False args Nothing
|
||||
return ()
|
||||
|
2
README
2
README
@@ -72,7 +72,7 @@ Building:
|
||||
|
||||
mtl http://hackage.haskell.org/cgi-bin/hackage-scripts/package/mtl-1.0
|
||||
unix http://hackage.haskell.org/cgi-bin/hackage-scripts/package/unix-2.0
|
||||
X11 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/X11-1.3.0
|
||||
X11 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/X11-1.4.1
|
||||
|
||||
* Build xmonad:
|
||||
|
||||
|
@@ -10,8 +10,12 @@
|
||||
-- Portability : portable
|
||||
--
|
||||
-- This module specifies the default configuration values for xmonad.
|
||||
-- Users should not modify this file. Rather, they should provide their
|
||||
-- own @~\/.xmonad\/xmonad.hs@ that overrides specific fields in defaultConfig.
|
||||
--
|
||||
-- DO NOT MODIFY THIS FILE! It won't work. You may configure xmonad
|
||||
-- by providing your own @~\/.xmonad\/xmonad.hs@ that overrides
|
||||
-- specific fields in 'defaultConfig'. For a starting point, you can
|
||||
-- copy the @xmonad.hs@ found in the @man@ directory, or look at
|
||||
-- examples on the xmonad wiki.
|
||||
--
|
||||
------------------------------------------------------------------------
|
||||
|
||||
@@ -22,10 +26,12 @@ module XMonad.Config (defaultConfig) where
|
||||
--
|
||||
import XMonad.Core as XMonad hiding
|
||||
(workspaces,manageHook,numlockMask,keys,logHook,borderWidth,mouseBindings
|
||||
,defaultGaps,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor)
|
||||
,defaultGaps,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor
|
||||
,focusFollowsMouse)
|
||||
import qualified XMonad.Core as XMonad
|
||||
(workspaces,manageHook,numlockMask,keys,logHook,borderWidth,mouseBindings
|
||||
,defaultGaps,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor)
|
||||
,defaultGaps,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor
|
||||
,focusFollowsMouse)
|
||||
|
||||
import XMonad.Layout
|
||||
import XMonad.Operations
|
||||
@@ -113,9 +119,7 @@ defaultGaps = [(0,0,0,0)] -- 15 for default dzen font
|
||||
manageHook :: ManageHook
|
||||
manageHook = composeAll
|
||||
[ className =? "MPlayer" --> doFloat
|
||||
, className =? "Gimp" --> doFloat
|
||||
, resource =? "desktop_window" --> doIgnore
|
||||
, resource =? "kdesktop" --> doIgnore ]
|
||||
, className =? "Gimp" --> doFloat ]
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- Logging
|
||||
@@ -163,6 +167,10 @@ layout = tiled ||| Mirror tiled ||| Full
|
||||
terminal :: String
|
||||
terminal = "xterm"
|
||||
|
||||
-- | Whether focus follows the mouse pointer.
|
||||
focusFollowsMouse :: Bool
|
||||
focusFollowsMouse = True
|
||||
|
||||
-- | The xmonad key bindings. Add, modify or remove key bindings here.
|
||||
--
|
||||
-- (The comment formatting character is used when generating the manpage)
|
||||
@@ -207,7 +215,7 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
||||
|
||||
-- quit, or restart
|
||||
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad
|
||||
, ((modMask , xK_q ), broadcastMessage ReleaseResources >> restart (Just "xmonad") True) -- %! Restart xmonad
|
||||
, ((modMask , xK_q ), restart "xmonad" True) -- %! Restart xmonad
|
||||
]
|
||||
++
|
||||
-- mod-[1..9] %! Switch to workspace N
|
||||
@@ -249,4 +257,5 @@ defaultConfig = XConfig
|
||||
, XMonad.keys = keys
|
||||
, XMonad.logHook = logHook
|
||||
, XMonad.mouseBindings = mouseBindings
|
||||
, XMonad.manageHook = manageHook }
|
||||
, XMonad.manageHook = manageHook
|
||||
, XMonad.focusFollowsMouse = focusFollowsMouse }
|
||||
|
@@ -5,7 +5,7 @@
|
||||
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : XMonad/Core.hs
|
||||
-- Module : XMonad.Core
|
||||
-- Copyright : (c) Spencer Janssen 2007
|
||||
-- License : BSD3-style (see LICENSE)
|
||||
--
|
||||
@@ -24,13 +24,13 @@ module XMonad.Core (
|
||||
XConf(..), XConfig(..), LayoutClass(..),
|
||||
Layout(..), readsLayout, Typeable, Message,
|
||||
SomeMessage(..), fromMessage, runLayout, LayoutMessages(..),
|
||||
runX, catchX, userCode, io, catchIO,
|
||||
withDisplay, withWindowSet, isRoot,
|
||||
runX, catchX, userCode, io, catchIO, doubleFork,
|
||||
withDisplay, withWindowSet, isRoot, runOnWorkspaces, broadcastMessage,
|
||||
getAtom, spawn, restart, getXMonadDir, recompile, trace, whenJust, whenX,
|
||||
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runManageHook
|
||||
) where
|
||||
|
||||
import XMonad.StackSet
|
||||
import XMonad.StackSet hiding (modify)
|
||||
|
||||
import Prelude hiding ( catch )
|
||||
import Control.Exception (catch, bracket, throw, Exception(ExitException))
|
||||
@@ -38,11 +38,11 @@ import Control.Applicative
|
||||
import Control.Monad.State
|
||||
import Control.Monad.Reader
|
||||
import System.IO
|
||||
import System.Info
|
||||
import System.Posix.Process (executeFile, forkProcess, getProcessStatus, createSession)
|
||||
import System.Process
|
||||
import System.Directory
|
||||
import System.Exit
|
||||
import System.Environment
|
||||
import Graphics.X11.Xlib
|
||||
import Graphics.X11.Xlib.Extras (Event)
|
||||
import Data.Typeable
|
||||
@@ -73,22 +73,22 @@ data XConf = XConf
|
||||
|
||||
-- todo, better name
|
||||
data XConfig l = XConfig
|
||||
{ normalBorderColor :: !String -- ^ Non focused windows border color. Default: \"#dddddd\"
|
||||
, focusedBorderColor :: !String -- ^ Focused windows border color. Default: \"#ff0000\"
|
||||
, terminal :: !String -- ^ The preferred terminal application. Default: \"xterm\"
|
||||
, layoutHook :: !(l Window) -- ^ The avaiable layouts
|
||||
, manageHook :: !ManageHook
|
||||
-- ^ The action to run when a new window is opened
|
||||
, workspaces :: [String] -- ^ The list of workspaces' names
|
||||
, defaultGaps :: [(Int,Int,Int,Int)] -- ^ The list of gaps, per screen
|
||||
, numlockMask :: !KeyMask -- ^ The numlock modifier
|
||||
, modMask :: !KeyMask -- ^ the mod modifier
|
||||
, keys :: XConfig Layout -> M.Map (ButtonMask,KeySym) (X ())
|
||||
-- ^ The key binding: a map from key presses and actions
|
||||
, mouseBindings :: XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ())
|
||||
-- ^ The mouse bindings
|
||||
, borderWidth :: !Dimension -- ^ The border width
|
||||
, logHook :: X () -- ^ The action to perform when the windows set is changed
|
||||
{ normalBorderColor :: !String -- ^ Non focused windows border color. Default: \"#dddddd\"
|
||||
, focusedBorderColor :: !String -- ^ Focused windows border color. Default: \"#ff0000\"
|
||||
, 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
|
||||
, workspaces :: ![String] -- ^ The list of workspaces' names
|
||||
, defaultGaps :: ![(Int,Int,Int,Int)] -- ^ The list of gaps, per screen
|
||||
, numlockMask :: !KeyMask -- ^ The numlock modifier
|
||||
, modMask :: !KeyMask -- ^ the mod modifier
|
||||
, keys :: !(XConfig Layout -> M.Map (ButtonMask,KeySym) (X ()))
|
||||
-- ^ The key binding: a map from key presses and actions
|
||||
, mouseBindings :: !(XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ()))
|
||||
-- ^ The mouse bindings
|
||||
, borderWidth :: !Dimension -- ^ The border width
|
||||
, logHook :: !(X ()) -- ^ The action to perform when the windows set is changed
|
||||
, focusFollowsMouse :: !Bool -- ^ Whether window entry events can change focus
|
||||
}
|
||||
|
||||
|
||||
@@ -303,17 +303,31 @@ doubleFork m = io $ do
|
||||
getProcessStatus True False pid
|
||||
return ()
|
||||
|
||||
-- | Restart xmonad via exec().
|
||||
-- | Send a message to all visible layouts, without necessarily refreshing.
|
||||
-- This is how we implement the hooks, such as UnDoLayout.
|
||||
broadcastMessage :: Message a => a -> X ()
|
||||
broadcastMessage a = runOnWorkspaces $ \w -> do
|
||||
ml' <- handleMessage (layout w) (SomeMessage a) `catchX` return Nothing
|
||||
return $ w { layout = maybe (layout w) id ml' }
|
||||
|
||||
-- | 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.
|
||||
runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X ()
|
||||
runOnWorkspaces job = do
|
||||
ws <- gets windowset
|
||||
h <- mapM job $ hidden ws
|
||||
c:v <- mapM (\s -> (\w -> s { workspace = w}) <$> job (workspace s))
|
||||
$ current ws : visible ws
|
||||
modify $ \s -> s { windowset = ws { current = c, visible = v, hidden = h } }
|
||||
|
||||
-- | @restart name resume@. Attempt to restart xmonad by executing the program
|
||||
-- @name@. If @resume@ is 'True', restart with the current window state.
|
||||
-- When executing another window manager, @resume@ should be 'False'.
|
||||
--
|
||||
-- If the first parameter is 'Just name', restart will attempt to execute the
|
||||
-- program corresponding to 'name'. Otherwise, xmonad will attempt to execute
|
||||
-- the name of the current program.
|
||||
--
|
||||
-- When the second parameter is 'True', xmonad will attempt to resume with the
|
||||
-- current window state.
|
||||
restart :: Maybe String -> Bool -> X ()
|
||||
restart mprog resume = do
|
||||
prog <- maybe (io getProgName) return mprog
|
||||
restart :: String -> Bool -> X ()
|
||||
restart prog resume = do
|
||||
broadcastMessage ReleaseResources
|
||||
io . flush =<< asks display
|
||||
args <- if resume then gets (("--resume":) . return . showWs . windowset) else return []
|
||||
catchIO (executeFile prog True args Nothing)
|
||||
where showWs = show . mapLayout show
|
||||
@@ -331,20 +345,25 @@ getXMonadDir = io $ getAppUserDataDirectory "xmonad"
|
||||
-- The -i flag is used to restrict recompilation to the xmonad.hs file only.
|
||||
--
|
||||
-- Compilation errors (if any) are logged to ~\/.xmonad\/xmonad.errors. If
|
||||
-- GHC indicates failure with a non-zero exit code, an xmessage containing
|
||||
-- GHC's is spawned.
|
||||
-- GHC indicates failure with a non-zero exit code, an xmessage displaying
|
||||
-- that file is spawned.
|
||||
--
|
||||
recompile :: MonadIO m => Bool -> m ()
|
||||
-- False is returned if there is compilation errors.
|
||||
--
|
||||
recompile :: MonadIO m => Bool -> m Bool
|
||||
recompile force = io $ do
|
||||
dir <- getXMonadDir
|
||||
let bin = dir ++ "/" ++ "xmonad"
|
||||
err = bin ++ ".errors"
|
||||
src = bin ++ ".hs"
|
||||
let binn = "xmonad-"++arch++"-"++os
|
||||
bin = dir ++ "/" ++ binn
|
||||
base = dir ++ "/" ++ "xmonad"
|
||||
err = base ++ ".errors"
|
||||
src = base ++ ".hs"
|
||||
srcT <- getModTime src
|
||||
binT <- getModTime bin
|
||||
when (force || srcT > binT) $ do
|
||||
if (force || srcT > binT)
|
||||
then do
|
||||
status <- bracket (openFile err WriteMode) hClose $ \h -> do
|
||||
waitForProcess =<< runProcess "ghc" ["--make", "xmonad.hs", "-i", "-no-recomp", "-v0"] (Just dir)
|
||||
waitForProcess =<< runProcess "ghc" ["--make", "xmonad.hs", "-i", "-no-recomp", "-v0", "-o",binn] (Just dir)
|
||||
Nothing Nothing Nothing (Just h)
|
||||
|
||||
-- now, if it fails, run xmessage to let the user know:
|
||||
@@ -354,6 +373,8 @@ recompile force = io $ do
|
||||
["Error detected while loading xmonad configuration file: " ++ src]
|
||||
++ lines ghcErr ++ ["","Please check the file for errors."]
|
||||
doubleFork $ executeFile "xmessage" True [msg] Nothing
|
||||
return (status == ExitSuccess)
|
||||
else return True
|
||||
where getModTime f = catch (Just <$> getModificationTime f) (const $ return Nothing)
|
||||
|
||||
-- | Run a side effecting action with the current workspace. Like 'when' but
|
||||
|
@@ -3,7 +3,7 @@
|
||||
|
||||
-- --------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : Layouts.hs
|
||||
-- Module : XMonad.Layout
|
||||
-- Copyright : (c) Spencer Janssen 2007
|
||||
-- License : BSD3-style (see LICENSE)
|
||||
--
|
||||
|
@@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE MultiParamTypeClasses, FlexibleContexts #-}
|
||||
----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : Core.hs
|
||||
-- Module : XMonad.Main
|
||||
-- Copyright : (c) Spencer Janssen 2007
|
||||
-- License : BSD3-style (see LICENSE)
|
||||
--
|
||||
@@ -26,7 +26,6 @@ import System.Environment (getArgs)
|
||||
|
||||
import Graphics.X11.Xlib hiding (refreshKeyboardMapping)
|
||||
import Graphics.X11.Xlib.Extras
|
||||
import Graphics.X11.Xinerama (getScreenInfo)
|
||||
|
||||
import XMonad.Core
|
||||
import XMonad.StackSet (new, floating, member)
|
||||
@@ -46,7 +45,7 @@ xmonad initxmc = do
|
||||
let dflt = defaultScreen dpy
|
||||
|
||||
rootw <- rootWindow dpy dflt
|
||||
xinesc <- getScreenInfo dpy
|
||||
xinesc <- getCleanedScreenInfo dpy
|
||||
nbc <- initColor dpy $ normalBorderColor xmc
|
||||
fbc <- initColor dpy $ focusedBorderColor xmc
|
||||
hSetBuffering stdout NoBuffering
|
||||
@@ -143,7 +142,10 @@ handle (MapRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
|
||||
|
||||
-- window destroyed, unmanage it
|
||||
-- window gone, unmanage it
|
||||
handle (DestroyWindowEvent {ev_window = w}) = whenX (isClient w) $ unmanage w
|
||||
handle (DestroyWindowEvent {ev_window = w}) = whenX (isClient w) $ do
|
||||
unmanage w
|
||||
modify (\s -> s { mapped = S.delete w (mapped s)
|
||||
, waitingUnmap = M.delete w (waitingUnmap s)})
|
||||
|
||||
-- We track expected unmap events in waitingUnmap. We ignore this event unless
|
||||
-- it is synthetic or we are not expecting an unmap notification from a window.
|
||||
@@ -151,7 +153,9 @@ handle (UnmapEvent {ev_window = w, ev_send_event = synthetic}) = whenX (isClient
|
||||
e <- gets (fromMaybe 0 . M.lookup w . waitingUnmap)
|
||||
if (synthetic || e == 0)
|
||||
then unmanage w
|
||||
else modify (\s -> s { waitingUnmap = M.adjust pred w (waitingUnmap s) })
|
||||
else modify (\s -> s { waitingUnmap = M.update mpred w (waitingUnmap s) })
|
||||
where mpred 1 = Nothing
|
||||
mpred n = Just $ pred n
|
||||
|
||||
-- set keyboard mapping
|
||||
handle e@(MappingNotifyEvent {}) = do
|
||||
@@ -184,12 +188,13 @@ handle e@(ButtonEvent {ev_window = w,ev_event_type = t,ev_button = b })
|
||||
ba <- asks buttonActions
|
||||
if isr then userCode $ whenJust (M.lookup (m, b) ba) ($ ev_subwindow e)
|
||||
else focus w
|
||||
sendMessage e -- Always send button events.
|
||||
broadcastMessage e -- Always send button events.
|
||||
|
||||
-- entered a normal window, makes this focused.
|
||||
handle e@(CrossingEvent {ev_window = w, ev_event_type = t})
|
||||
| t == enterNotify && ev_mode e == notifyNormal
|
||||
&& ev_detail e /= notifyInferior = focus w
|
||||
&& ev_detail e /= notifyInferior
|
||||
= whenX (asks $ focusFollowsMouse . config) (focus w)
|
||||
|
||||
-- left a window, check if we need to focus root
|
||||
handle e@(CrossingEvent {ev_event_type = t})
|
||||
|
@@ -2,7 +2,7 @@
|
||||
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : XMonad/ManageHook.hs
|
||||
-- Module : XMonad.ManageHook
|
||||
-- Copyright : (c) Spencer Janssen 2007
|
||||
-- License : BSD3-style (see LICENSE)
|
||||
--
|
||||
|
@@ -4,7 +4,7 @@
|
||||
|
||||
-- --------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : Operations.hs
|
||||
-- Module : XMonad.Operations
|
||||
-- Copyright : (c) Spencer Janssen 2007
|
||||
-- License : BSD3-style (see LICENSE)
|
||||
--
|
||||
@@ -71,13 +71,8 @@ manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do
|
||||
-- | unmanage. A window no longer exists, remove it from the window
|
||||
-- list, on whatever workspace it is.
|
||||
--
|
||||
-- should also unmap?
|
||||
--
|
||||
unmanage :: Window -> X ()
|
||||
unmanage w = do
|
||||
windows (W.delete w)
|
||||
setWMState w withdrawnState
|
||||
modify (\s -> s {mapped = S.delete w (mapped s), waitingUnmap = M.delete w (waitingUnmap s)})
|
||||
unmanage = windows . W.delete
|
||||
|
||||
-- | Modify the size of the status gap at the top of the current screen
|
||||
-- Taking a function giving the current screen, and current geometry.
|
||||
@@ -116,7 +111,9 @@ windows f = do
|
||||
let oldvisible = concatMap (W.integrate' . W.stack . W.workspace) $ W.current old : W.visible old
|
||||
ws = f old
|
||||
XConf { display = d , normalBorder = nbc, focusedBorder = fbc } <- ask
|
||||
|
||||
mapM_ setInitialProperties (W.allWindows ws \\ W.allWindows old)
|
||||
|
||||
whenJust (W.peek old) $ \otherw -> io $ setWindowBorder d otherw nbc
|
||||
modify (\s -> s { windowset = ws })
|
||||
|
||||
@@ -165,12 +162,16 @@ windows f = do
|
||||
whenJust (W.peek ws) $ \w -> io $ setWindowBorder d w fbc
|
||||
setTopFocus
|
||||
asks (logHook . config) >>= userCode
|
||||
-- io performGC -- really helps, but seems to trigger GC bugs?
|
||||
|
||||
-- hide every window that was potentially visible before, but is not
|
||||
-- given a position by a layout now.
|
||||
mapM_ hide (nub oldvisible \\ visible)
|
||||
|
||||
-- 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
|
||||
mapM_ (flip setWMState withdrawnState) (W.allWindows old \\ W.allWindows ws)
|
||||
|
||||
clearEvents enterWindowMask
|
||||
|
||||
-- | setWMState. set the WM_STATE property
|
||||
@@ -245,11 +246,31 @@ tileWindow w r = withDisplay $ \d -> do
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
|
||||
-- | Returns True if the first rectangle is contained within, but not equal
|
||||
-- to the second.
|
||||
containedIn :: Rectangle -> Rectangle -> Bool
|
||||
containedIn r1@(Rectangle x1 y1 w1 h1) r2@(Rectangle x2 y2 w2 h2)
|
||||
= and [ r1 /= r2
|
||||
, x1 >= x2
|
||||
, y1 >= y2
|
||||
, fromIntegral x1 + w1 <= fromIntegral x2 + w2
|
||||
, fromIntegral y1 + h1 <= fromIntegral y2 + h2 ]
|
||||
|
||||
-- | Given a list of screens, remove all duplicated screens and screens that
|
||||
-- are entirely contained within another.
|
||||
nubScreens :: [Rectangle] -> [Rectangle]
|
||||
nubScreens xs = nub . filter (\x -> not $ any (x `containedIn`) xs) $ xs
|
||||
|
||||
-- | Cleans the list of screens according to the rules documented for
|
||||
-- nubScreens.
|
||||
getCleanedScreenInfo :: MonadIO m => Display -> m [Rectangle]
|
||||
getCleanedScreenInfo = io . fmap nubScreens . getScreenInfo
|
||||
|
||||
-- | rescreen. The screen configuration may have changed (due to
|
||||
-- xrandr), update the state and refresh the screen, and reset the gap.
|
||||
rescreen :: X ()
|
||||
rescreen = do
|
||||
xinesc <- withDisplay (io . getScreenInfo)
|
||||
xinesc <- withDisplay getCleanedScreenInfo
|
||||
|
||||
windows $ \ws@(W.StackSet { W.current = v, W.visible = vs, W.hidden = hs }) ->
|
||||
let (xs, ys) = splitAt (length xinesc) $ map W.workspace (v:vs) ++ hs
|
||||
@@ -323,23 +344,6 @@ sendMessageToWorkspaces a l = runOnWorkspaces $ \w ->
|
||||
return $ w { W.layout = maybe (W.layout w) id ml' }
|
||||
else return w
|
||||
|
||||
-- | Send a message to all visible layouts, without necessarily refreshing.
|
||||
-- This is how we implement the hooks, such as UnDoLayout.
|
||||
broadcastMessage :: Message a => a -> X ()
|
||||
broadcastMessage a = runOnWorkspaces $ \w -> do
|
||||
ml' <- handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing
|
||||
return $ w { W.layout = maybe (W.layout w) id ml' }
|
||||
|
||||
-- | 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.
|
||||
runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X ()
|
||||
runOnWorkspaces job =do
|
||||
ws <- gets windowset
|
||||
h <- mapM job $ W.hidden ws
|
||||
c:v <- mapM (\s -> (\w -> s { W.workspace = w}) <$> job (W.workspace s))
|
||||
$ W.current ws : W.visible ws
|
||||
modify $ \s -> s { windowset = ws { W.current = c, W.visible = v, W.hidden = h } }
|
||||
|
||||
-- | Set the layout of the currently viewed workspace
|
||||
setLayout :: Layout Window -> X ()
|
||||
setLayout l = do
|
||||
|
@@ -2,7 +2,7 @@
|
||||
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : StackSet
|
||||
-- Module : XMonad.StackSet
|
||||
-- Copyright : (c) Don Stewart 2007
|
||||
-- License : BSD3-style (see LICENSE)
|
||||
--
|
||||
|
@@ -16,25 +16,19 @@ By utilising the expressivity of a modern functional language with a rich static
|
||||
.PP
|
||||
You can switch to workspace N with mod-N. For example, to switch to workspace 5, you would press mod-5. Similarly, you can move the current window to another workspace with mod-shift-N.
|
||||
.PP
|
||||
When running with multiple monitors (Xinerama), each screen has exactly 1 workspace visible. When \fBxmonad\fR starts, workspace 1 is on screen 1, workspace 2 is on screen 2, etc. If you switch to a workspace which is currently visible on another screen, \fBxmonad\fR simply switches focus to that screen. If you switch to a workspace which is *not* visible, \fBxmonad\fR replaces the workspace on the *current* screen with the workspace you selected.
|
||||
When running with multiple monitors (Xinerama), each screen has exactly 1 workspace visible. mod-{w,e,r} switch the focus between screens, while shift-mod-{w,e,r} move the current window to that screen. When \fBxmonad\fR starts, workspace 1 is on screen 1, workspace 2 is on screen 2, etc. When switching workspaces to one that is already visible, the current and visible workspaces are swapped.
|
||||
.PP
|
||||
For example, if you have the following configuration:
|
||||
.RS
|
||||
.PP
|
||||
Screen 1: Workspace 2
|
||||
.PP
|
||||
Screen 2: Workspace 5 (current workspace)
|
||||
.RE
|
||||
.PP
|
||||
and you wanted to view workspace 7 on screen 1, you would press:
|
||||
.RS
|
||||
.PP
|
||||
mod-2 (to select workspace 2, and make screen 1 the current screen)
|
||||
.PP
|
||||
mod-7 (to select workspace 7)
|
||||
.RE
|
||||
.PP
|
||||
Since switching to the workspace currently visible on a given screen is such a common operation, shortcuts are provided: mod-{w,e,r} switch to the workspace currently visible on screens 1, 2, and 3 respectively. Likewise, shift-mod-{w,e,r} moves the current window to the workspace on that screen. Using these keys, the above example would become mod-w mod-7.
|
||||
.SS Flags
|
||||
\fBxmonad\fR has several flags which you may pass to the executable. These flags are:
|
||||
.TP
|
||||
\fB--recompile
|
||||
Recompiles your configuration in ~/.xmonad/xmonad.hs if it is newer than your already existing ~/.xmonad/xmonad executable.
|
||||
.TP
|
||||
\fB--recompile-force
|
||||
Unconditionally recompiles your configuration in ~/.xmonad/xmonad.hs.
|
||||
.TP
|
||||
\fB--version
|
||||
Display version of \fBxmonad\fR.
|
||||
.SS Default keyboard bindings
|
||||
___KEYBINDINGS___
|
||||
.SH EXAMPLES
|
||||
@@ -44,6 +38,6 @@ xmonad
|
||||
.RE
|
||||
to your \fI~/.xinitrc\fR file
|
||||
.SH CUSTOMIZATION
|
||||
\fBxmonad\fR is customized by creating a custom Config.hs and (re)compiling the source code. After recompiling, 'restart' is used to fork the new version, with changes reflected immediately.
|
||||
\fBxmonad\fR is customized in ~/.xmonad/xmonad.hs, and then restarting with mod-q.
|
||||
.SH BUGS
|
||||
Probably. If you find any, please report them: http://code.google.com/p/xmonad/issues/list
|
||||
|
@@ -145,8 +145,7 @@ myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
||||
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
|
||||
|
||||
-- Restart xmonad
|
||||
, ((modMask , xK_q ),
|
||||
broadcastMessage ReleaseResources >> restart (Just "xmonad") True)
|
||||
, ((modMask , xK_q ), restart "xmonad" True)
|
||||
]
|
||||
++
|
||||
|
||||
@@ -222,12 +221,19 @@ myLayout = tiled ||| Mirror tiled ||| Full
|
||||
-- > xprop | grep WM_CLASS
|
||||
-- and click on the client you're interested in.
|
||||
--
|
||||
-- To match on the WM_NAME, you can use 'title' in the same way that
|
||||
-- 'className' and 'resource' are used below.
|
||||
--
|
||||
myManageHook = composeAll
|
||||
[ className =? "MPlayer" --> doFloat
|
||||
, className =? "Gimp" --> doFloat
|
||||
, resource =? "desktop_window" --> doIgnore
|
||||
, resource =? "kdesktop" --> doIgnore ]
|
||||
|
||||
-- Whether focus follows the mouse pointer.
|
||||
myFocusFollowsMouse :: Bool
|
||||
myFocusFollowsMouse = True
|
||||
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- Status bars and logging
|
||||
@@ -257,6 +263,7 @@ main = xmonad defaults
|
||||
defaults = defaultConfig {
|
||||
-- simple stuff
|
||||
terminal = myTerminal,
|
||||
focusFollowsMouse = myFocusFollowsMouse,
|
||||
borderWidth = myBorderWidth,
|
||||
modMask = myModMask,
|
||||
numlockMask = myNumlockMask,
|
||||
|
@@ -1,8 +0,0 @@
|
||||
module Main where
|
||||
|
||||
import qualified Properties
|
||||
|
||||
-- This will run all of the QC files for xmonad core. Currently, that's just
|
||||
-- Properties. If any more get added, sequence the main actions together.
|
||||
main = do
|
||||
Properties.main
|
@@ -1,4 +1,4 @@
|
||||
{-# OPTIONS -fglasgow-exts #-}
|
||||
{-# OPTIONS -fglasgow-exts -w #-}
|
||||
module Properties where
|
||||
|
||||
import XMonad.StackSet hiding (filter)
|
||||
@@ -52,7 +52,6 @@ instance (Integral i, Integral s, Eq a, Arbitrary a, Arbitrary l, Arbitrary sd)
|
||||
| s <- ls ]
|
||||
|
||||
return $ fromList (fromIntegral n, sds,fs,ls,lay)
|
||||
coarbitrary = error "no coarbitrary for StackSet"
|
||||
|
||||
|
||||
-- | fromList. Build a new StackSet from a list of list of elements,
|
||||
@@ -652,7 +651,7 @@ noOverlaps xs = and [ verts a `notOverlap` verts b
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
args <- getArgs
|
||||
args <- fmap (drop 1) getArgs
|
||||
let n = if null args then 100 else read (head args)
|
||||
(results, passed) <- liftM unzip $ mapM (\(s,a) -> printf "%-25s: " s >> a n) tests
|
||||
printf "Passed %d tests!\n" (sum passed)
|
||||
@@ -941,6 +940,7 @@ instance Arbitrary EmptyStackSet where
|
||||
l <- arbitrary
|
||||
-- there cannot be more screens than workspaces:
|
||||
return . EmptyStackSet . new l ns $ take (min (length ns) (length sds)) sds
|
||||
coarbitrary = error "coarbitrary EmptyStackSet"
|
||||
|
||||
-- | Generates a value that satisfies a predicate.
|
||||
suchThat :: Gen a -> (a -> Bool) -> Gen a
|
||||
|
35
xmonad.cabal
35
xmonad.cabal
@@ -1,5 +1,5 @@
|
||||
name: xmonad
|
||||
version: 0.5
|
||||
version: 0.6
|
||||
homepage: http://xmonad.org
|
||||
synopsis: A tiling window manager
|
||||
description:
|
||||
@@ -23,7 +23,11 @@ extra-source-files: README TODO CONFIG STYLE tests/loc.hs tests/Properties.hs
|
||||
cabal-version: >= 1.2
|
||||
|
||||
flag small_base
|
||||
description: Choose the new smaller, split-up base package.
|
||||
description: Choose the new smaller, split-up base package.
|
||||
|
||||
flag testing
|
||||
description: Testing mode, only build minimal components
|
||||
default: False
|
||||
|
||||
library
|
||||
exposed-modules: XMonad
|
||||
@@ -39,17 +43,34 @@ library
|
||||
build-depends: base >= 3, containers, directory, process
|
||||
else
|
||||
build-depends: base < 3
|
||||
build-depends: X11>=1.4.0, mtl, unix
|
||||
build-depends: X11>=1.4.1, mtl, unix
|
||||
|
||||
ghc-options: -funbox-strict-fields -Wall -Werror -optl-Wl,-s
|
||||
ghc-options: -funbox-strict-fields -Wall -optl-Wl,-s
|
||||
ghc-prof-options: -prof -auto-all
|
||||
extensions: CPP
|
||||
|
||||
if flag(testing)
|
||||
buildable: False
|
||||
|
||||
executable xmonad
|
||||
main-is: Main.hs
|
||||
other-modules: XMonad.Core XMonad.Main XMonad.Layout
|
||||
XMonad.Operations XMonad.StackSet XMonad
|
||||
other-modules: XMonad
|
||||
XMonad.Main
|
||||
XMonad.Core
|
||||
XMonad.Config
|
||||
XMonad.Layout
|
||||
XMonad.ManageHook
|
||||
XMonad.Operations
|
||||
XMonad.StackSet
|
||||
|
||||
ghc-options: -funbox-strict-fields -Wall -Werror -optl-Wl,-s
|
||||
ghc-options: -funbox-strict-fields -Wall -optl-Wl,-s
|
||||
ghc-prof-options: -prof -auto-all
|
||||
extensions: CPP
|
||||
|
||||
if flag(testing)
|
||||
cpp-options: -DTESTING
|
||||
hs-source-dirs: . tests/
|
||||
build-depends: QuickCheck < 2
|
||||
ghc-options: -Werror
|
||||
if flag(testing) && flag(small_base)
|
||||
build-depends: random
|
||||
|
Reference in New Issue
Block a user