mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-03 13:41:54 -07:00
Compare commits
35 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 |
19
Main.hs
19
Main.hs
@@ -16,10 +16,12 @@ module Main (main) where
|
|||||||
|
|
||||||
import XMonad
|
import XMonad
|
||||||
|
|
||||||
|
import Control.Monad (unless)
|
||||||
import System.IO
|
import System.IO
|
||||||
import System.Info
|
import System.Info
|
||||||
import System.Environment
|
import System.Environment
|
||||||
import System.Posix.Process (executeFile)
|
import System.Posix.Process (executeFile)
|
||||||
|
import System.Exit (exitFailure)
|
||||||
|
|
||||||
import Paths_xmonad (version)
|
import Paths_xmonad (version)
|
||||||
import Data.Version (showVersion)
|
import Data.Version (showVersion)
|
||||||
@@ -39,7 +41,8 @@ main = do
|
|||||||
[] -> launch
|
[] -> launch
|
||||||
["--resume", _] -> launch
|
["--resume", _] -> launch
|
||||||
["--help"] -> usage
|
["--help"] -> usage
|
||||||
["--recompile"] -> recompile True >> return ()
|
["--recompile"] -> recompile True >>= flip unless exitFailure
|
||||||
|
["--restart"] -> sendRestart >> return ()
|
||||||
["--version"] -> putStrLn ("xmonad " ++ showVersion version)
|
["--version"] -> putStrLn ("xmonad " ++ showVersion version)
|
||||||
#ifdef TESTING
|
#ifdef TESTING
|
||||||
("--run-tests":_) -> Properties.main
|
("--run-tests":_) -> Properties.main
|
||||||
@@ -55,6 +58,7 @@ usage = do
|
|||||||
" --help Print this message" :
|
" --help Print this message" :
|
||||||
" --version Print the version number" :
|
" --version Print the version number" :
|
||||||
" --recompile Recompile your ~/.xmonad/xmonad.hs" :
|
" --recompile Recompile your ~/.xmonad/xmonad.hs" :
|
||||||
|
" --restart Request a running xmonad process to restart" :
|
||||||
#ifdef TESTING
|
#ifdef TESTING
|
||||||
" --run-tests Run the test suite" :
|
" --run-tests Run the test suite" :
|
||||||
#endif
|
#endif
|
||||||
@@ -66,7 +70,7 @@ usage = do
|
|||||||
--
|
--
|
||||||
-- * ghc missing
|
-- * ghc missing
|
||||||
--
|
--
|
||||||
-- * "~\/.xmonad\/xmonad.hs" missing
|
-- * both "~\/.xmonad\/xmonad.hs" and "~\/.xmonad\/xmonad-$arch-$os" missing
|
||||||
--
|
--
|
||||||
-- * xmonad.hs fails to compile
|
-- * xmonad.hs fails to compile
|
||||||
--
|
--
|
||||||
@@ -83,3 +87,14 @@ buildLaunch = do
|
|||||||
args <- getArgs
|
args <- getArgs
|
||||||
executeFile (dir ++ "/xmonad-"++arch++"-"++os) False args Nothing
|
executeFile (dir ++ "/xmonad-"++arch++"-"++os) False args Nothing
|
||||||
return ()
|
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
|
||||||
|
@@ -26,19 +26,23 @@ module XMonad.Config (defaultConfig) where
|
|||||||
--
|
--
|
||||||
import XMonad.Core as XMonad hiding
|
import XMonad.Core as XMonad hiding
|
||||||
(workspaces,manageHook,numlockMask,keys,logHook,startupHook,borderWidth,mouseBindings
|
(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
|
import qualified XMonad.Core as XMonad
|
||||||
(workspaces,manageHook,numlockMask,keys,logHook,startupHook,borderWidth,mouseBindings
|
(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.Layout
|
||||||
import XMonad.Operations
|
import XMonad.Operations
|
||||||
import XMonad.ManageHook
|
import XMonad.ManageHook
|
||||||
import qualified XMonad.StackSet as W
|
import qualified XMonad.StackSet as W
|
||||||
import Data.Bits ((.|.))
|
import Data.Bits ((.|.))
|
||||||
|
import Data.Monoid
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import System.Exit
|
import System.Exit
|
||||||
import Graphics.X11.Xlib
|
import Graphics.X11.Xlib
|
||||||
|
import Graphics.X11.Xlib.Extras
|
||||||
|
|
||||||
-- | The default number of workspaces (virtual screens) and their names.
|
-- | The default number of workspaces (virtual screens) and their names.
|
||||||
-- By default we use numeric strings, but any string may be used as a
|
-- By default we use numeric strings, but any string may be used as a
|
||||||
@@ -119,6 +123,15 @@ manageHook = composeAll
|
|||||||
logHook :: X ()
|
logHook :: X ()
|
||||||
logHook = return ()
|
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.
|
-- | Perform an arbitrary action at xmonad startup.
|
||||||
startupHook :: X ()
|
startupHook :: X ()
|
||||||
startupHook = return ()
|
startupHook = return ()
|
||||||
@@ -205,7 +218,7 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
|||||||
|
|
||||||
-- quit, or restart
|
-- quit, or restart
|
||||||
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad
|
, ((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
|
-- mod-[1..9] %! Switch to workspace N
|
||||||
@@ -250,4 +263,5 @@ defaultConfig = XConfig
|
|||||||
, XMonad.startupHook = startupHook
|
, XMonad.startupHook = startupHook
|
||||||
, XMonad.mouseBindings = mouseBindings
|
, XMonad.mouseBindings = mouseBindings
|
||||||
, XMonad.manageHook = manageHook
|
, XMonad.manageHook = manageHook
|
||||||
|
, XMonad.handleEventHook = handleEventHook
|
||||||
, XMonad.focusFollowsMouse = focusFollowsMouse }
|
, XMonad.focusFollowsMouse = focusFollowsMouse }
|
||||||
|
@@ -24,7 +24,7 @@ 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, userCodeDef, io, catchIO, installSignalHandlers,
|
runX, catchX, userCode, userCodeDef, io, catchIO, installSignalHandlers, uninstallSignalHandlers,
|
||||||
withDisplay, withWindowSet, isRoot, runOnWorkspaces,
|
withDisplay, withWindowSet, isRoot, runOnWorkspaces,
|
||||||
getAtom, spawn, spawnPID, 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
|
||||||
@@ -33,14 +33,16 @@ module XMonad.Core (
|
|||||||
import XMonad.StackSet hiding (modify)
|
import XMonad.StackSet hiding (modify)
|
||||||
|
|
||||||
import Prelude hiding ( catch )
|
import Prelude hiding ( catch )
|
||||||
import Control.Exception (catch, try, bracket, throw, Exception(ExitException))
|
import Control.Exception (catch, try, bracket, throw, finally, 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.FilePath
|
||||||
import System.IO
|
import System.IO
|
||||||
import System.Info
|
import System.Info
|
||||||
import System.Posix.Process (executeFile, forkProcess, getAnyProcessStatus)
|
import System.Posix.Process (executeFile, forkProcess, getAnyProcessStatus, createSession)
|
||||||
import System.Posix.Signals
|
import System.Posix.Signals
|
||||||
|
import System.Posix.IO
|
||||||
import System.Posix.Types (ProcessID)
|
import System.Posix.Types (ProcessID)
|
||||||
import System.Process
|
import System.Process
|
||||||
import System.Directory
|
import System.Directory
|
||||||
@@ -48,6 +50,7 @@ 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.List ((\\))
|
||||||
import Data.Maybe (isJust)
|
import Data.Maybe (isJust)
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
@@ -86,6 +89,9 @@ data XConfig l = XConfig
|
|||||||
, terminal :: !String -- ^ The preferred terminal application. Default: \"xterm\"
|
, terminal :: !String -- ^ The preferred terminal application. Default: \"xterm\"
|
||||||
, layoutHook :: !(l Window) -- ^ The available layouts
|
, layoutHook :: !(l Window) -- ^ The available layouts
|
||||||
, manageHook :: !ManageHook -- ^ The action to run when a new window is opened
|
, 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
|
, workspaces :: ![String] -- ^ The list of workspaces' names
|
||||||
, numlockMask :: !KeyMask -- ^ The numlock modifier
|
, numlockMask :: !KeyMask -- ^ The numlock modifier
|
||||||
, modMask :: !KeyMask -- ^ the mod modifier
|
, modMask :: !KeyMask -- ^ the mod modifier
|
||||||
@@ -124,7 +130,7 @@ data ScreenDetail = SD { screenRect :: !Rectangle } deriving (Eq,Show, Read)
|
|||||||
--
|
--
|
||||||
newtype X a = X (ReaderT XConf (StateT XState IO) a)
|
newtype X a = X (ReaderT XConf (StateT XState IO) a)
|
||||||
#ifndef __HADDOCK__
|
#ifndef __HADDOCK__
|
||||||
deriving (Functor, Monad, MonadIO, MonadState XState, MonadReader XConf)
|
deriving (Functor, Monad, MonadIO, MonadState XState, MonadReader XConf, Typeable)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
instance Applicative X where
|
instance Applicative X where
|
||||||
@@ -354,8 +360,17 @@ catchIO f = io (f `catch` \e -> hPrint stderr e >> hFlush stderr)
|
|||||||
spawn :: MonadIO m => String -> m ()
|
spawn :: MonadIO m => String -> m ()
|
||||||
spawn x = spawnPID x >> return ()
|
spawn x = spawnPID x >> return ()
|
||||||
|
|
||||||
|
-- | Like 'spawn', but returns the 'ProcessID' of the launched application
|
||||||
spawnPID :: MonadIO m => String -> m ProcessID
|
spawnPID :: MonadIO m => String -> m ProcessID
|
||||||
spawnPID x = io $ forkProcess $ executeFile "/bin/sh" False ["-c", x] Nothing
|
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
|
-- | 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.
|
||||||
@@ -392,18 +407,20 @@ recompile :: MonadIO m => Bool -> m Bool
|
|||||||
recompile force = io $ do
|
recompile force = io $ do
|
||||||
dir <- getXMonadDir
|
dir <- getXMonadDir
|
||||||
let binn = "xmonad-"++arch++"-"++os
|
let binn = "xmonad-"++arch++"-"++os
|
||||||
bin = dir ++ "/" ++ binn
|
bin = dir </> binn
|
||||||
base = dir ++ "/" ++ "xmonad"
|
base = dir </> "xmonad"
|
||||||
err = base ++ ".errors"
|
err = base ++ ".errors"
|
||||||
src = base ++ ".hs"
|
src = base ++ ".hs"
|
||||||
|
lib = dir </> "lib"
|
||||||
|
libTs <- mapM getModTime . Prelude.filter isSource =<< allFiles lib
|
||||||
srcT <- getModTime src
|
srcT <- getModTime src
|
||||||
binT <- getModTime bin
|
binT <- getModTime bin
|
||||||
if (force || srcT > binT)
|
if force || any (binT <) (srcT : libTs)
|
||||||
then do
|
then do
|
||||||
-- temporarily disable SIGCHLD ignoring:
|
-- temporarily disable SIGCHLD ignoring:
|
||||||
installHandler sigCHLD Default Nothing
|
uninstallSignalHandlers
|
||||||
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", "-ilib", "-fforce-recomp", "-v0", "-o",binn] (Just dir)
|
||||||
Nothing Nothing Nothing (Just h)
|
Nothing Nothing Nothing (Just h)
|
||||||
|
|
||||||
-- re-enable SIGCHLD:
|
-- re-enable SIGCHLD:
|
||||||
@@ -423,6 +440,12 @@ recompile force = io $ do
|
|||||||
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)
|
||||||
|
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.
|
-- | Conditionally run an action, using a @Maybe a@ to decide.
|
||||||
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
|
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
|
||||||
@@ -447,3 +470,8 @@ installSignalHandlers = io $ do
|
|||||||
x <- getAnyProcessStatus False False
|
x <- getAnyProcessStatus False False
|
||||||
when (isJust x) more
|
when (isJust x) more
|
||||||
return ()
|
return ()
|
||||||
|
|
||||||
|
uninstallSignalHandlers :: MonadIO m => m ()
|
||||||
|
uninstallSignalHandlers = io $ do
|
||||||
|
installHandler sigCHLD Default Nothing
|
||||||
|
return ()
|
||||||
|
@@ -51,9 +51,9 @@ 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 -- ^ The default number of windows in the master pane (default: 1)
|
data Tall a = Tall { tallNMaster :: !Int -- ^ The default number of windows in the master pane (default: 1)
|
||||||
!Rational -- ^ Default proportion of screen occupied by master pane (default: 1/2)
|
, tallRatioIncrement :: !Rational -- ^ Percent of screen to increment by when resizing panes (default: 3/100)
|
||||||
!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)
|
deriving (Show, Read)
|
||||||
-- TODO should be capped [0..1] ..
|
-- TODO should be capped [0..1] ..
|
||||||
|
|
||||||
|
@@ -22,6 +22,7 @@ import qualified Data.Set as S
|
|||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
|
import Data.Monoid (getAll)
|
||||||
|
|
||||||
import Foreign.C
|
import Foreign.C
|
||||||
import Foreign.Ptr
|
import Foreign.Ptr
|
||||||
@@ -152,11 +153,18 @@ xmonad initxmc = do
|
|||||||
prehandle e = let mouse = do guard (ev_event_type e `elem` evs)
|
prehandle e = let mouse = do guard (ev_event_type e `elem` evs)
|
||||||
return (fromIntegral (ev_x_root e)
|
return (fromIntegral (ev_x_root e)
|
||||||
,fromIntegral (ev_y_root e))
|
,fromIntegral (ev_y_root e))
|
||||||
in local (\c -> c { mousePosition = mouse }) (handle e)
|
in local (\c -> c { mousePosition = mouse }) (handleWithHook e)
|
||||||
evs = [ keyPress, keyRelease, enterNotify, leaveNotify
|
evs = [ keyPress, keyRelease, enterNotify, leaveNotify
|
||||||
, buttonPress, buttonRelease]
|
, 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
|
-- | Event handler. Map X events onto calls into Operations.hs, which
|
||||||
-- modify our internal model of the window manager state.
|
-- modify our internal model of the window manager state.
|
||||||
@@ -280,6 +288,12 @@ handle (ConfigureEvent {ev_window = w}) = whenX (isRoot w) rescreen
|
|||||||
handle PropertyEvent { ev_event_type = t, ev_atom = a }
|
handle PropertyEvent { ev_event_type = t, ev_atom = a }
|
||||||
| t == propertyNotify && a == wM_NAME = userCodeDef () =<< 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
|
handle e = broadcastMessage e -- trace (eventName e) -- ignoring
|
||||||
|
|
||||||
|
|
||||||
|
@@ -45,6 +45,8 @@ idHook = doF id
|
|||||||
composeAll :: [ManageHook] -> ManageHook
|
composeAll :: [ManageHook] -> ManageHook
|
||||||
composeAll = mconcat
|
composeAll = mconcat
|
||||||
|
|
||||||
|
infix 0 -->
|
||||||
|
|
||||||
-- | @p --> x@. If @p@ returns 'True', execute the 'ManageHook'.
|
-- | @p --> x@. If @p@ returns 'True', execute the 'ManageHook'.
|
||||||
(-->) :: Query Bool -> ManageHook -> ManageHook
|
(-->) :: Query Bool -> ManageHook -> ManageHook
|
||||||
p --> f = p >>= \b -> if b then f else mempty
|
p --> f = p >>= \b -> if b then f else mempty
|
||||||
@@ -71,7 +73,8 @@ title = ask >>= \w -> liftX $ do
|
|||||||
getProp =
|
getProp =
|
||||||
(internAtom d "_NET_WM_NAME" False >>= getTextProperty d w)
|
(internAtom d "_NET_WM_NAME" False >>= getTextProperty d w)
|
||||||
`catch` \_ -> getTextProperty d w wM_NAME
|
`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 ""
|
io $ bracket getProp (xFree . tp_value) extract `catch` \_ -> return ""
|
||||||
|
|
||||||
-- | Return the application name.
|
-- | 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
|
-- | Move the window to a given workspace
|
||||||
doShift :: WorkspaceId -> ManageHook
|
doShift :: WorkspaceId -> ManageHook
|
||||||
doShift = doF . W.shift
|
doShift i = doF . W.shiftWin i =<< ask
|
||||||
|
@@ -52,7 +52,7 @@ module XMonad.StackSet (
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import Prelude hiding (filter)
|
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 qualified Data.List as L (deleteBy,find,splitAt,filter,nub)
|
||||||
import Data.List ( (\\) )
|
import Data.List ( (\\) )
|
||||||
import qualified Data.Map as M (Map,insert,delete,empty)
|
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.
|
-- Xinerama: Virtual workspaces are assigned to physical screens, starting at 0.
|
||||||
--
|
--
|
||||||
new :: (Integral s) => l -> [i] -> [sd] -> StackSet i l a s sd
|
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
|
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 ]
|
(cur:visi) = [ Screen i s sd | (i, s, sd) <- zip3 seen [0..] m ]
|
||||||
-- now zip up visibles with their screen id
|
-- now zip up visibles with their screen id
|
||||||
@@ -538,10 +539,7 @@ focusMaster = modify' $ \c -> case c of
|
|||||||
-- element on the current stack, the original stackSet is returned.
|
-- 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 :: (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)
|
shift n s = maybe s (\w -> shiftWin n w s) (peek s)
|
||||||
| otherwise = s
|
|
||||||
where go w = view curtag . insertUp w . view n . delete' w $ s
|
|
||||||
curtag = currentTag s
|
|
||||||
|
|
||||||
-- | /O(n)/. shiftWin. Searches for the specified window 'w' on all workspaces
|
-- | /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
|
-- of the stackSet and moves it to stack 'n', leaving it as the focused
|
||||||
@@ -549,13 +547,12 @@ shift n s | n `tagMember` s && n /= curtag = maybe s go (peek s)
|
|||||||
-- focused element on that workspace.
|
-- focused element on that workspace.
|
||||||
-- The actual focused workspace doesn't change. If the window is not
|
-- The actual focused workspace doesn't change. If the window is not
|
||||||
-- found in the stackSet, the original stackSet is returned.
|
-- 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 :: (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
|
shiftWin n w s = case findTag w s of
|
||||||
| n `tagMember` s && (Just n) /= from = go
|
Just from | n `tagMember` s && n /= from -> go from s
|
||||||
| otherwise = s
|
_ -> s
|
||||||
where from = findTag w s
|
where go from = onWorkspace n (insertUp w) . onWorkspace from (delete' w)
|
||||||
|
|
||||||
go = on n (insertUp w) . on (fromJust from) (delete' w) $ s
|
|
||||||
on i f = view (currentTag s) . f . view i
|
|
||||||
|
|
||||||
|
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
|
./" man page created by David Lazar on April 24, 2007
|
||||||
./" uses ``tmac.an'' macro set
|
./" 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
|
.SH NAME
|
||||||
xmonad \- a tiling window manager
|
xmonad \- a tiling window manager
|
||||||
.SH DESCRIPTION
|
.SH DESCRIPTION
|
||||||
.PP
|
.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
|
.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
|
.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
|
.SH USAGE
|
||||||
.PP
|
.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.
|
\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
|
.TP
|
||||||
\fB--recompile
|
\fB--recompile
|
||||||
Recompiles your configuration in ~/.xmonad/xmonad.hs
|
Recompiles your configuration in ~/.xmonad/xmonad.hs
|
||||||
|
\fB--restart
|
||||||
|
Causes the currently running xmonad process to restart
|
||||||
.TP
|
.TP
|
||||||
\fB--version
|
\fB--version
|
||||||
Display version of \fBxmonad\fR.
|
Display version of \fBxmonad\fR.
|
||||||
@@ -31,12 +35,23 @@ ___KEYBINDINGS___
|
|||||||
.SH EXAMPLES
|
.SH EXAMPLES
|
||||||
To use \fBxmonad\fR as your window manager add:
|
To use \fBxmonad\fR as your window manager add:
|
||||||
.RS
|
.RS
|
||||||
xmonad
|
exec xmonad
|
||||||
.RE
|
.RE
|
||||||
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
|
.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/.
|
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
|
.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
|
||||||
|
@@ -8,6 +8,7 @@
|
|||||||
--
|
--
|
||||||
|
|
||||||
import XMonad
|
import XMonad
|
||||||
|
import Data.Monoid
|
||||||
import System.Exit
|
import System.Exit
|
||||||
|
|
||||||
import qualified XMonad.StackSet as W
|
import qualified XMonad.StackSet as W
|
||||||
@@ -18,6 +19,10 @@ import qualified Data.Map as M
|
|||||||
--
|
--
|
||||||
myTerminal = "xterm"
|
myTerminal = "xterm"
|
||||||
|
|
||||||
|
-- Whether focus follows the mouse pointer.
|
||||||
|
myFocusFollowsMouse :: Bool
|
||||||
|
myFocusFollowsMouse = True
|
||||||
|
|
||||||
-- Width of the window border in pixels.
|
-- Width of the window border in pixels.
|
||||||
--
|
--
|
||||||
myBorderWidth = 1
|
myBorderWidth = 1
|
||||||
@@ -63,73 +68,76 @@ myFocusedBorderColor = "#ff0000"
|
|||||||
------------------------------------------------------------------------
|
------------------------------------------------------------------------
|
||||||
-- Key bindings. Add, modify or remove key bindings here.
|
-- 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
|
-- launch a terminal
|
||||||
[ ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
|
[ ((modm .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
|
||||||
|
|
||||||
-- launch dmenu
|
-- 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
|
-- launch gmrun
|
||||||
, ((modMask .|. shiftMask, xK_p ), spawn "gmrun")
|
, ((modm .|. shiftMask, xK_p ), spawn "gmrun")
|
||||||
|
|
||||||
-- close focused window
|
-- close focused window
|
||||||
, ((modMask .|. shiftMask, xK_c ), kill)
|
, ((modm .|. shiftMask, xK_c ), kill)
|
||||||
|
|
||||||
-- Rotate through the available layout algorithms
|
-- 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
|
-- 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
|
-- Resize viewed windows to the correct size
|
||||||
, ((modMask, xK_n ), refresh)
|
, ((modm, xK_n ), refresh)
|
||||||
|
|
||||||
-- Move focus to the next window
|
-- Move focus to the next window
|
||||||
, ((modMask, xK_Tab ), windows W.focusDown)
|
, ((modm, xK_Tab ), windows W.focusDown)
|
||||||
|
|
||||||
-- Move focus to the next window
|
-- Move focus to the next window
|
||||||
, ((modMask, xK_j ), windows W.focusDown)
|
, ((modm, xK_j ), windows W.focusDown)
|
||||||
|
|
||||||
-- Move focus to the previous window
|
-- Move focus to the previous window
|
||||||
, ((modMask, xK_k ), windows W.focusUp )
|
, ((modm, xK_k ), windows W.focusUp )
|
||||||
|
|
||||||
-- Move focus to the master window
|
-- 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
|
-- 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
|
-- 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
|
-- 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
|
-- Shrink the master area
|
||||||
, ((modMask, xK_h ), sendMessage Shrink)
|
, ((modm, xK_h ), sendMessage Shrink)
|
||||||
|
|
||||||
-- Expand the master area
|
-- Expand the master area
|
||||||
, ((modMask, xK_l ), sendMessage Expand)
|
, ((modm, xK_l ), sendMessage Expand)
|
||||||
|
|
||||||
-- Push window back into tiling
|
-- 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
|
-- 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
|
-- 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
|
-- Toggle the status bar gap
|
||||||
-- TODO, update this binding with avoidStruts , ((modMask , xK_b ),
|
-- Use this binding with avoidStruts from Hooks.ManageDocks.
|
||||||
|
-- See also the statusBar function from Hooks.DynamicLog.
|
||||||
|
--
|
||||||
|
-- , ((modm , xK_b ), sendMessage ToggleStruts)
|
||||||
|
|
||||||
-- Quit xmonad
|
-- Quit xmonad
|
||||||
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
|
, ((modm .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
|
||||||
|
|
||||||
-- Restart xmonad
|
-- 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-[1..9], Switch to workspace N
|
||||||
-- mod-shift-[1..9], Move client 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]
|
| (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
|
||||||
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
|
, (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-{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
|
-- 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..]
|
| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
|
||||||
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
|
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
|
||||||
|
|
||||||
@@ -154,18 +162,18 @@ myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
|||||||
------------------------------------------------------------------------
|
------------------------------------------------------------------------
|
||||||
-- Mouse bindings: default actions bound to mouse events
|
-- 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
|
-- 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))
|
>> 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.shiftMaster))
|
, ((modm, 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
|
, ((modm, button3), (\w -> focus w >> mouseResizeWindow w
|
||||||
>> windows W.shiftMaster))
|
>> 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)
|
||||||
]
|
]
|
||||||
@@ -216,10 +224,16 @@ myManageHook = composeAll
|
|||||||
, resource =? "desktop_window" --> doIgnore
|
, resource =? "desktop_window" --> doIgnore
|
||||||
, resource =? "kdesktop" --> doIgnore ]
|
, resource =? "kdesktop" --> doIgnore ]
|
||||||
|
|
||||||
-- Whether focus follows the mouse pointer.
|
------------------------------------------------------------------------
|
||||||
myFocusFollowsMouse :: Bool
|
-- Event handling
|
||||||
myFocusFollowsMouse = True
|
|
||||||
|
|
||||||
|
-- * 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
|
-- Status bars and logging
|
||||||
@@ -251,9 +265,9 @@ myStartupHook = return ()
|
|||||||
main = xmonad defaults
|
main = xmonad defaults
|
||||||
|
|
||||||
-- A structure containing your configuration settings, overriding
|
-- 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
|
-- use the defaults defined in xmonad/XMonad/Config.hs
|
||||||
--
|
--
|
||||||
-- No need to modify this.
|
-- No need to modify this.
|
||||||
--
|
--
|
||||||
defaults = defaultConfig {
|
defaults = defaultConfig {
|
||||||
@@ -274,6 +288,7 @@ defaults = defaultConfig {
|
|||||||
-- hooks, layouts
|
-- hooks, layouts
|
||||||
layoutHook = myLayout,
|
layoutHook = myLayout,
|
||||||
manageHook = myManageHook,
|
manageHook = myManageHook,
|
||||||
|
handleEventHook = myEventHook,
|
||||||
logHook = myLogHook,
|
logHook = myLogHook,
|
||||||
startupHook = myStartupHook
|
startupHook = myStartupHook
|
||||||
}
|
}
|
||||||
|
@@ -20,6 +20,13 @@ import Text.Regex.Posix
|
|||||||
import Data.Char
|
import Data.Char
|
||||||
import Data.List
|
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 :: String -> String
|
||||||
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
|
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)
|
replace x y = map (\a -> if a == x then y else a)
|
||||||
|
|
||||||
main = do
|
main = do
|
||||||
|
releaseName <- ((' ':) . (++" \\") . show . disp . package . packageDescription) `liftM` readPackageDescription normal "xmonad.cabal"
|
||||||
|
|
||||||
troffBindings <- (concatMap troff . allBindings) `liftM` readFile "./XMonad/Config.hs"
|
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"
|
readFile "./man/xmonad.1.in" >>= return . sed >>= writeFile "./man/xmonad.1"
|
||||||
|
10
xmonad.cabal
10
xmonad.cabal
@@ -1,5 +1,5 @@
|
|||||||
name: xmonad
|
name: xmonad
|
||||||
version: 0.8.1
|
version: 0.9
|
||||||
homepage: http://xmonad.org
|
homepage: http://xmonad.org
|
||||||
synopsis: A tiling window manager
|
synopsis: A tiling window manager
|
||||||
description:
|
description:
|
||||||
@@ -18,11 +18,13 @@ license-file: LICENSE
|
|||||||
author: Spencer Janssen
|
author: Spencer Janssen
|
||||||
maintainer: xmonad@haskell.org
|
maintainer: xmonad@haskell.org
|
||||||
extra-source-files: README TODO CONFIG STYLE tests/loc.hs tests/Properties.hs
|
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
|
util/GenerateManpage.hs
|
||||||
cabal-version: >= 1.2
|
cabal-version: >= 1.2
|
||||||
build-type: Simple
|
build-type: Simple
|
||||||
|
|
||||||
|
data-files: man/xmonad.hs
|
||||||
|
|
||||||
flag small_base
|
flag small_base
|
||||||
description: Choose the new smaller, split-up base package.
|
description: Choose the new smaller, split-up base package.
|
||||||
|
|
||||||
@@ -41,10 +43,10 @@ library
|
|||||||
XMonad.StackSet
|
XMonad.StackSet
|
||||||
|
|
||||||
if flag(small_base)
|
if flag(small_base)
|
||||||
build-depends: base < 4 && >=3, containers, directory, process
|
build-depends: base < 4 && >=3, containers, directory, process, filepath
|
||||||
else
|
else
|
||||||
build-depends: base < 3
|
build-depends: base < 3
|
||||||
build-depends: X11>=1.4.3, mtl, unix
|
build-depends: X11>=1.4.6.1, 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