mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-02 05:01:53 -07:00
Compare commits
66 Commits
Author | SHA1 | Date | |
---|---|---|---|
|
ef516142b9 | ||
|
cb51875da6 | ||
|
167a6e155b | ||
|
2b2774f81d | ||
|
16725dfe0d | ||
|
15db3c6f0a | ||
|
6db444eb1a | ||
|
46bc3bbd17 | ||
|
d948210935 | ||
|
db08970071 | ||
|
4c69a85b3f | ||
|
ac103b8472 | ||
|
029965e4d4 | ||
|
9fd1d4f9d0 | ||
|
dbbd934b0b | ||
|
750544fda9 | ||
|
90eae3fd63 | ||
|
d6233d0463 | ||
|
5f088f4e99 | ||
|
f8a7d8d381 | ||
|
f7686746c6 | ||
|
04ee55c3ca | ||
|
50ce362626 | ||
|
209b88f821 | ||
|
c5cca485df | ||
|
0593a282ca | ||
|
351de8d2b6 | ||
|
4bd9073937 | ||
|
79754fd5d3 | ||
|
b14de19e8b | ||
|
e97c326ff0 | ||
|
bc13b4ba07 | ||
|
5bea59a823 | ||
|
669a162cfc | ||
|
310c22694e | ||
|
1c930ba955 | ||
|
797204fe6c | ||
|
a3ecf5d304 | ||
|
1a4a4a5000 | ||
|
a8d3564653 | ||
|
d5955b023c | ||
|
4d9a6c2681 | ||
|
87193ff61e | ||
|
3303c6e05d | ||
|
9d9acba45f | ||
|
cc2754d82a | ||
|
cea3492d28 | ||
|
14d9a194ff | ||
|
e8d1d028ba | ||
|
695860f1fd | ||
|
261f742404 | ||
|
1de1bcded2 | ||
|
0c697ebbb4 | ||
|
a626083721 | ||
|
481e42ab72 | ||
|
e751c4b62f | ||
|
730984fd60 | ||
|
ad85e11a4a | ||
|
2da09787da | ||
|
162a54d992 | ||
|
d00d4ca046 | ||
|
0dd54885eb | ||
|
f80d593d57 | ||
|
10be8aaae0 | ||
|
66f623b656 | ||
|
b86351f3c3 |
24
LICENSE
24
LICENSE
@@ -1,27 +1,31 @@
|
||||
Copyright (c) Spencer Janssen
|
||||
Copyright (c) 2007,2008 Spencer Janssen
|
||||
Copyright (c) 2007,2008 Don Stewart
|
||||
|
||||
All rights reserved.
|
||||
|
||||
Redistribution and use in source and binary forms, with or without
|
||||
modification, are permitted provided that the following conditions
|
||||
are met:
|
||||
|
||||
1. Redistributions of source code must retain the above copyright
|
||||
notice, this list of conditions and the following disclaimer.
|
||||
|
||||
2. Redistributions in binary form must reproduce the above copyright
|
||||
notice, this list of conditions and the following disclaimer in the
|
||||
documentation and/or other materials provided with the distribution.
|
||||
|
||||
3. Neither the name of the author nor the names of his contributors
|
||||
may be used to endorse or promote products derived from this software
|
||||
without specific prior written permission.
|
||||
|
||||
THIS SOFTWARE IS PROVIDED BY THE AUTHORS ``AS IS'' AND
|
||||
ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
|
||||
IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
|
||||
ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHORS OR CONTRIBUTORS BE LIABLE
|
||||
FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
|
||||
THIS SOFTWARE IS PROVIDED BY THE AUTHORS ``AS IS'' AND ANY EXPRESS OR
|
||||
IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
|
||||
WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
|
||||
DISCLAIMED. IN NO EVENT SHALL THE AUTHORS OR CONTRIBUTORS BE LIABLE FOR
|
||||
ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
|
||||
DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
|
||||
OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
|
||||
HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
|
||||
LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
|
||||
OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
|
||||
SUCH DAMAGE.
|
||||
HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
|
||||
STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
|
||||
ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
|
||||
POSSIBILITY OF SUCH DAMAGE.
|
||||
|
26
Main.hs
26
Main.hs
@@ -16,12 +16,14 @@ module Main (main) where
|
||||
|
||||
import XMonad
|
||||
|
||||
import Control.Exception (handle)
|
||||
import System.IO
|
||||
import System.Info
|
||||
import System.Environment
|
||||
import System.Posix.Process (executeFile)
|
||||
|
||||
import Paths_xmonad (version)
|
||||
import Data.Version (showVersion)
|
||||
|
||||
#ifdef TESTING
|
||||
import qualified Properties
|
||||
#endif
|
||||
@@ -31,18 +33,32 @@ import qualified Properties
|
||||
main :: IO ()
|
||||
main = do
|
||||
args <- getArgs
|
||||
let launch = handle (hPrint stderr) buildLaunch >> xmonad defaultConfig
|
||||
let launch = catchIO buildLaunch >> xmonad defaultConfig
|
||||
case args of
|
||||
[] -> launch
|
||||
["--resume", _] -> launch
|
||||
["--recompile"] -> recompile False >> return ()
|
||||
["--recompile-force"] -> recompile True >> return ()
|
||||
["--version"] -> putStrLn "xmonad 0.5"
|
||||
["--help"] -> usage
|
||||
["--recompile"] -> recompile True >> return ()
|
||||
["--version"] -> putStrLn ("xmonad " ++ showVersion version)
|
||||
#ifdef TESTING
|
||||
("--run-tests":_) -> Properties.main
|
||||
#endif
|
||||
_ -> fail "unrecognized flags"
|
||||
|
||||
usage :: IO ()
|
||||
usage = do
|
||||
self <- getProgName
|
||||
putStr . unlines $
|
||||
concat ["Usage: ", self, " [OPTION]"] :
|
||||
"Options:" :
|
||||
" --help Print this message" :
|
||||
" --version Print the version number" :
|
||||
" --recompile Recompile your ~/.xmonad/xmonad.hs" :
|
||||
#ifdef TESTING
|
||||
" --run-tests Run the test suite" :
|
||||
#endif
|
||||
[]
|
||||
|
||||
-- | Build "~/.xmonad/xmonad.hs" with ghc, then execute it. If there are no
|
||||
-- errors, this function does not return. An exception is raised in any of
|
||||
-- these cases:
|
||||
|
14
README
14
README
@@ -12,6 +12,16 @@
|
||||
workspace. Xinerama is fully supported, allowing windows to be tiled
|
||||
on several physical screens.
|
||||
|
||||
Quick start:
|
||||
|
||||
Obtain the dependent libraries, then build with:
|
||||
|
||||
runhaskell Setup.lhs configure --user --prefix=$HOME
|
||||
runhaskell Setup.lhs build
|
||||
runhaskell Setup.lhs install --user
|
||||
|
||||
For the full story, read on.
|
||||
|
||||
Building:
|
||||
|
||||
Building is quite straightforward, and requries a basic Haskell toolchain.
|
||||
@@ -123,9 +133,9 @@ XMonadContrib
|
||||
prompt/program launcher, and various other useful modules.
|
||||
XMonadContrib is available at:
|
||||
|
||||
0.5 release: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/xmonad-contrib-0.5
|
||||
latest release: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/xmonad-contrib
|
||||
|
||||
darcs version: darcs get http://code.haskell.org/XMonadContrib
|
||||
darcs version: darcs get http://code.haskell.org/XMonadContrib
|
||||
|
||||
------------------------------------------------------------------------
|
||||
|
||||
|
1
TODO
1
TODO
@@ -18,3 +18,4 @@
|
||||
* upload X11 and xmonad to hackage
|
||||
* check examples/text in user-facing Config.hs
|
||||
* check tour.html and intro.html are up to date, and mention all core bindings
|
||||
* confirm template config is type correct
|
||||
|
@@ -25,11 +25,11 @@ module XMonad.Config (defaultConfig) where
|
||||
-- Useful imports
|
||||
--
|
||||
import XMonad.Core as XMonad hiding
|
||||
(workspaces,manageHook,numlockMask,keys,logHook,borderWidth,mouseBindings
|
||||
(workspaces,manageHook,numlockMask,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||
,defaultGaps,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor
|
||||
,focusFollowsMouse)
|
||||
import qualified XMonad.Core as XMonad
|
||||
(workspaces,manageHook,numlockMask,keys,logHook,borderWidth,mouseBindings
|
||||
(workspaces,manageHook,numlockMask,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||
,defaultGaps,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor
|
||||
,focusFollowsMouse)
|
||||
|
||||
@@ -134,6 +134,10 @@ manageHook = composeAll
|
||||
logHook :: X ()
|
||||
logHook = return ()
|
||||
|
||||
-- | Perform an arbitrary action at xmonad startup.
|
||||
startupHook :: X ()
|
||||
startupHook = return ()
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- Extensible layouts
|
||||
--
|
||||
@@ -190,6 +194,7 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
||||
|
||||
-- move focus up or down the window stack
|
||||
, ((modMask, xK_Tab ), windows W.focusDown) -- %! Move focus to the next window
|
||||
, ((modMask .|. shiftMask, xK_Tab ), windows W.focusUp ) -- %! Move focus to the previous window
|
||||
, ((modMask, xK_j ), windows W.focusDown) -- %! Move focus to the next window
|
||||
, ((modMask, xK_k ), windows W.focusUp ) -- %! Move focus to the previous window
|
||||
, ((modMask, xK_m ), windows W.focusMaster ) -- %! Move focus to the master window
|
||||
@@ -256,6 +261,7 @@ defaultConfig = XConfig
|
||||
, XMonad.modMask = defaultModMask
|
||||
, XMonad.keys = keys
|
||||
, XMonad.logHook = logHook
|
||||
, XMonad.startupHook = startupHook
|
||||
, XMonad.mouseBindings = mouseBindings
|
||||
, XMonad.manageHook = manageHook
|
||||
, XMonad.focusFollowsMouse = focusFollowsMouse }
|
||||
|
180
XMonad/Core.hs
180
XMonad/Core.hs
@@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE ExistentialQuantification, FlexibleInstances, GeneralizedNewtypeDeriving,
|
||||
MultiParamTypeClasses, TypeSynonymInstances #-}
|
||||
MultiParamTypeClasses, TypeSynonymInstances, CPP #-}
|
||||
-- required for deriving Typeable
|
||||
{-# OPTIONS_GHC -fglasgow-exts #-}
|
||||
|
||||
@@ -23,11 +23,11 @@ module XMonad.Core (
|
||||
ScreenId(..), ScreenDetail(..), XState(..),
|
||||
XConf(..), XConfig(..), LayoutClass(..),
|
||||
Layout(..), readsLayout, Typeable, Message,
|
||||
SomeMessage(..), fromMessage, runLayout, LayoutMessages(..),
|
||||
SomeMessage(..), fromMessage, LayoutMessages(..),
|
||||
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
|
||||
withDisplay, withWindowSet, isRoot, runOnWorkspaces,
|
||||
getAtom, spawn, getXMonadDir, recompile, trace, whenJust, whenX,
|
||||
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runQuery
|
||||
) where
|
||||
|
||||
import XMonad.StackSet hiding (modify)
|
||||
@@ -51,14 +51,14 @@ import Data.Monoid
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Set as S
|
||||
|
||||
-- | XState, the window manager state.
|
||||
-- Just the display, width, height and a window list
|
||||
-- | XState, the (mutable) window manager state.
|
||||
data XState = XState
|
||||
{ windowset :: !WindowSet -- ^ workspace list
|
||||
, mapped :: !(S.Set Window) -- ^ the Set of mapped windows
|
||||
, waitingUnmap :: !(M.Map Window Int) -- ^ the number of expected UnmapEvents
|
||||
, dragging :: !(Maybe (Position -> Position -> X (), X ())) }
|
||||
|
||||
-- | XConf, the (read-only) window manager configuration.
|
||||
data XConf = XConf
|
||||
{ display :: Display -- ^ the X11 display
|
||||
, config :: !(XConfig Layout) -- ^ initial user configuration
|
||||
@@ -88,6 +88,7 @@ data XConfig l = XConfig
|
||||
-- ^ The mouse bindings
|
||||
, borderWidth :: !Dimension -- ^ The border width
|
||||
, logHook :: !(X ()) -- ^ The action to perform when the windows set is changed
|
||||
, startupHook :: !(X ()) -- ^ The action to perform on startup
|
||||
, focusFollowsMouse :: !Bool -- ^ Whether window entry events can change focus
|
||||
}
|
||||
|
||||
@@ -95,21 +96,22 @@ data XConfig l = XConfig
|
||||
type WindowSet = StackSet WorkspaceId (Layout Window) Window ScreenId ScreenDetail
|
||||
type WindowSpace = Workspace WorkspaceId (Layout Window) Window
|
||||
|
||||
-- | Virtual workspace indicies
|
||||
-- | Virtual workspace indices
|
||||
type WorkspaceId = String
|
||||
|
||||
-- | Physical screen indicies
|
||||
-- | Physical screen indices
|
||||
newtype ScreenId = S Int deriving (Eq,Ord,Show,Read,Enum,Num,Integral,Real)
|
||||
|
||||
-- | The 'Rectangle' with screen dimensions and the list of gaps
|
||||
data ScreenDetail = SD { screenRect :: !Rectangle
|
||||
, statusGap :: !(Int,Int,Int,Int) -- ^ width of status bar on the screen
|
||||
, statusGap :: !(Int,Int,Int,Int) -- ^ gaps on the sides of the screen that shouldn't be tiled, usually for status bars
|
||||
} deriving (Eq,Show, Read)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
|
||||
-- | The X monad, a StateT transformer over IO encapsulating the window
|
||||
-- manager state
|
||||
-- | The X monad, ReaderT and StateT transformers over IO
|
||||
-- encapsulating the window manager configuration and state,
|
||||
-- respectively.
|
||||
--
|
||||
-- Dynamic components may be retrieved with 'get', static components
|
||||
-- with 'ask'. With newtype deriving we get readers and state monads
|
||||
@@ -120,6 +122,10 @@ newtype X a = X (ReaderT XConf (StateT XState IO) a)
|
||||
deriving (Functor, Monad, MonadIO, MonadState XState, MonadReader XConf)
|
||||
#endif
|
||||
|
||||
instance Applicative X where
|
||||
pure = return
|
||||
(<*>) = ap
|
||||
|
||||
instance (Monoid a) => Monoid (X a) where
|
||||
mempty = return mempty
|
||||
mappend = liftM2 mappend
|
||||
@@ -130,8 +136,8 @@ newtype Query a = Query (ReaderT Window X a)
|
||||
deriving (Functor, Monad, MonadReader Window, MonadIO)
|
||||
#endif
|
||||
|
||||
runManageHook :: ManageHook -> Window -> X (WindowSet -> WindowSet)
|
||||
runManageHook (Query m) w = appEndo <$> runReaderT m w
|
||||
runQuery :: Query a -> Window -> X a
|
||||
runQuery (Query m) w = runReaderT m w
|
||||
|
||||
instance Monoid a => Monoid (Query a) where
|
||||
mempty = return mempty
|
||||
@@ -185,91 +191,135 @@ atom_WM_DELETE_WINDOW = getAtom "WM_DELETE_WINDOW"
|
||||
atom_WM_STATE = getAtom "WM_STATE"
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- | LayoutClass handling. See particular instances in Operations.hs
|
||||
-- LayoutClass handling. See particular instances in Operations.hs
|
||||
|
||||
-- | An existential type that can hold any object that is in Read and LayoutClass.
|
||||
-- | An existential type that can hold any object that is in 'Read'
|
||||
-- and 'LayoutClass'.
|
||||
data Layout a = forall l. (LayoutClass l a, Read (l a)) => Layout (l a)
|
||||
|
||||
-- | Using the 'Layout' as a witness, parse existentially wrapped windows
|
||||
-- from a 'String'
|
||||
-- from a 'String'.
|
||||
readsLayout :: Layout a -> String -> [(Layout a, String)]
|
||||
readsLayout (Layout l) s = [(Layout (asTypeOf x l), rs) | (x, rs) <- reads s]
|
||||
|
||||
-- | The different layout modes
|
||||
-- | Every layout must be an instance of 'LayoutClass', which defines
|
||||
-- the basic layout operations along with a sensible default for each.
|
||||
--
|
||||
-- 'doLayout': given a Rectangle and a Stack, layout the stack elements
|
||||
-- inside the given Rectangle. If an element is not given a Rectangle
|
||||
-- by 'doLayout', then it is not shown on screen. Windows are restacked
|
||||
-- according to the order they are returned by 'doLayout'.
|
||||
-- Minimal complete definition:
|
||||
--
|
||||
-- * 'runLayout' || (('doLayout' || 'pureLayout') && 'emptyLayout'), and
|
||||
--
|
||||
-- * 'handleMessage' || 'pureMessage'
|
||||
--
|
||||
-- You should also strongly consider implementing 'description',
|
||||
-- although it is not required.
|
||||
--
|
||||
-- Note that any code which /uses/ 'LayoutClass' methods should only
|
||||
-- ever call 'runLayout', 'handleMessage', and 'description'! In
|
||||
-- other words, the only calls to 'doLayout', 'pureMessage', and other
|
||||
-- such methods should be from the default implementations of
|
||||
-- 'runLayout', 'handleMessage', and so on. This ensures that the
|
||||
-- proper methods will be used, regardless of the particular methods
|
||||
-- that any 'LayoutClass' instance chooses to define.
|
||||
class Show (layout a) => LayoutClass layout a where
|
||||
|
||||
-- | Given a Rectangle in which to place the windows, and a Stack of
|
||||
-- windows, return a list of windows and their corresponding Rectangles.
|
||||
-- The order of windows in this list should be the desired stacking order.
|
||||
-- Also return a modified layout, if this layout needs to be modified
|
||||
-- (e.g. if we keep track of the windows we have displayed).
|
||||
doLayout :: layout a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (layout a))
|
||||
-- | By default, 'runLayout' calls 'doLayout' if there are any
|
||||
-- windows to be laid out, and 'emptyLayout' otherwise. Most
|
||||
-- instances of 'LayoutClass' probably do not need to implement
|
||||
-- 'runLayout'; it is only useful for layouts which wish to make
|
||||
-- use of more of the 'Workspace' information (for example,
|
||||
-- "XMonad.Layout.PerWorkspace").
|
||||
runLayout :: Workspace WorkspaceId (layout a) a
|
||||
-> Rectangle
|
||||
-> X ([(a, Rectangle)], Maybe (layout a))
|
||||
runLayout (Workspace _ l ms) r = maybe (emptyLayout l r) (doLayout l r) ms
|
||||
|
||||
-- | Given a 'Rectangle' in which to place the windows, and a 'Stack'
|
||||
-- of windows, return a list of windows and their corresponding
|
||||
-- Rectangles. If an element is not given a Rectangle by
|
||||
-- 'doLayout', then it is not shown on screen. The order of
|
||||
-- windows in this list should be the desired stacking order.
|
||||
--
|
||||
-- Also possibly return a modified layout (by returning @Just
|
||||
-- newLayout@), if this layout needs to be modified (e.g. if it
|
||||
-- keeps track of some sort of state). Return @Nothing@ if the
|
||||
-- layout does not need to be modified.
|
||||
--
|
||||
-- Layouts which do not need access to the 'X' monad ('IO', window
|
||||
-- manager state, or configuration) and do not keep track of their
|
||||
-- own state should implement 'pureLayout' instead of 'doLayout'.
|
||||
doLayout :: layout a -> Rectangle -> Stack a
|
||||
-> X ([(a, Rectangle)], Maybe (layout a))
|
||||
doLayout l r s = return (pureLayout l r s, Nothing)
|
||||
|
||||
-- | This is a pure version of doLayout, for cases where we don't need
|
||||
-- access to the X monad to determine how to layout the windows, and
|
||||
-- we don't need to modify our layout itself.
|
||||
-- | This is a pure version of 'doLayout', for cases where we
|
||||
-- don't need access to the 'X' monad to determine how to lay out
|
||||
-- the windows, and we don't need to modify the layout itself.
|
||||
pureLayout :: layout a -> Rectangle -> Stack a -> [(a, Rectangle)]
|
||||
pureLayout _ r s = [(focus s, r)]
|
||||
|
||||
-- | 'handleMessage' performs message handling for that layout. If
|
||||
-- 'handleMessage' returns Nothing, then the layout did not respond to
|
||||
-- that message and the screen is not refreshed. Otherwise, 'handleMessage'
|
||||
-- returns an updated 'Layout' and the screen is refreshed.
|
||||
-- | 'emptyLayout' is called when there are no windows.
|
||||
emptyLayout :: layout a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
|
||||
emptyLayout _ _ = return ([], Nothing)
|
||||
|
||||
-- | 'handleMessage' performs message handling. If
|
||||
-- 'handleMessage' returns @Nothing@, then the layout did not
|
||||
-- respond to the message and the screen is not refreshed.
|
||||
-- Otherwise, 'handleMessage' returns an updated layout and the
|
||||
-- screen is refreshed.
|
||||
--
|
||||
-- Layouts which do not need access to the 'X' monad to decide how
|
||||
-- to handle messages should implement 'pureMessage' instead of
|
||||
-- 'handleMessage' (this restricts the risk of error, and makes
|
||||
-- testing much easier).
|
||||
handleMessage :: layout a -> SomeMessage -> X (Maybe (layout a))
|
||||
handleMessage l = return . pureMessage l
|
||||
|
||||
-- | Respond to a message by (possibly) changing our layout, but taking
|
||||
-- no other action. If the layout changes, the screen will be refreshed.
|
||||
-- | Respond to a message by (possibly) changing our layout, but
|
||||
-- taking no other action. If the layout changes, the screen will
|
||||
-- be refreshed.
|
||||
pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
|
||||
pureMessage _ _ = Nothing
|
||||
|
||||
-- | This should be a human-readable string that is used when selecting
|
||||
-- layouts by name.
|
||||
-- | This should be a human-readable string that is used when
|
||||
-- selecting layouts by name. The default implementation is
|
||||
-- 'show', which is in some cases a poor default.
|
||||
description :: layout a -> String
|
||||
description = show
|
||||
|
||||
instance LayoutClass Layout Window where
|
||||
runLayout (Workspace i (Layout l) ms) r = fmap (fmap Layout) `fmap` runLayout (Workspace i l ms) r
|
||||
doLayout (Layout l) r s = fmap (fmap Layout) `fmap` doLayout l r s
|
||||
emptyLayout (Layout l) r = fmap (fmap Layout) `fmap` emptyLayout l r
|
||||
handleMessage (Layout l) = fmap (fmap Layout) . handleMessage l
|
||||
description (Layout l) = description l
|
||||
|
||||
instance Show (Layout a) where show (Layout l) = show l
|
||||
|
||||
-- | This calls doLayout if there are any windows to be laid out.
|
||||
runLayout :: LayoutClass l a => l a -> Rectangle -> Maybe (Stack a) -> X ([(a, Rectangle)], Maybe (l a))
|
||||
runLayout l r = maybe (return ([], Nothing)) (doLayout l r)
|
||||
|
||||
-- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/,
|
||||
-- Simon Marlow, 2006. Use extensible messages to the handleMessage handler.
|
||||
-- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of
|
||||
-- Exceptions/, Simon Marlow, 2006. Use extensible messages to the
|
||||
-- 'handleMessage' handler.
|
||||
--
|
||||
-- User-extensible messages must be a member of this class.
|
||||
--
|
||||
class Typeable a => Message a
|
||||
|
||||
-- |
|
||||
-- A wrapped value of some type in the Message class.
|
||||
-- A wrapped value of some type in the 'Message' class.
|
||||
--
|
||||
data SomeMessage = forall a. Message a => SomeMessage a
|
||||
|
||||
-- |
|
||||
-- And now, unwrap a given, unknown Message type, performing a (dynamic)
|
||||
-- And now, unwrap a given, unknown 'Message' type, performing a (dynamic)
|
||||
-- type check on the result.
|
||||
--
|
||||
fromMessage :: Message m => SomeMessage -> Maybe m
|
||||
fromMessage (SomeMessage m) = cast m
|
||||
|
||||
-- | X Events are valid Messages
|
||||
-- X Events are valid Messages.
|
||||
instance Message Event
|
||||
|
||||
-- | LayoutMessages are core messages that all layouts (especially stateful
|
||||
-- | 'LayoutMessages' are core messages that all layouts (especially stateful
|
||||
-- layouts) should consider handling.
|
||||
data LayoutMessages = Hide -- ^ sent when a layout becomes non-visible
|
||||
| ReleaseResources -- ^ sent when xmonad is exiting or restarting
|
||||
@@ -286,7 +336,7 @@ io = liftIO
|
||||
|
||||
-- | Lift an IO action into the X monad. If the action results in an IO
|
||||
-- exception, log the exception to stderr and continue normal execution.
|
||||
catchIO :: IO () -> X ()
|
||||
catchIO :: MonadIO m => IO () -> m ()
|
||||
catchIO f = io (f `catch` \e -> hPrint stderr e >> hFlush stderr)
|
||||
|
||||
-- | spawn. Launch an external application
|
||||
@@ -303,13 +353,6 @@ doubleFork m = io $ do
|
||||
getProcessStatus True False pid
|
||||
return ()
|
||||
|
||||
-- | 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 ()
|
||||
@@ -320,23 +363,11 @@ runOnWorkspaces job = do
|
||||
$ 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'.
|
||||
--
|
||||
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
|
||||
|
||||
-- | Return the path to @~\/.xmonad@.
|
||||
getXMonadDir :: MonadIO m => m String
|
||||
getXMonadDir = io $ getAppUserDataDirectory "xmonad"
|
||||
|
||||
-- | 'recompile force', recompile ~\/.xmonad\/xmonad.hs when any of the
|
||||
-- | 'recompile force', recompile @~\/.xmonad\/xmonad.hs@ when any of the
|
||||
-- following apply:
|
||||
-- * force is True
|
||||
-- * the xmonad executable does not exist
|
||||
@@ -348,7 +379,7 @@ getXMonadDir = io $ getAppUserDataDirectory "xmonad"
|
||||
-- GHC indicates failure with a non-zero exit code, an xmessage displaying
|
||||
-- that file is spawned.
|
||||
--
|
||||
-- False is returned if there is compilation errors.
|
||||
-- False is returned if there are compilation errors.
|
||||
--
|
||||
recompile :: MonadIO m => Bool -> m Bool
|
||||
recompile force = io $ do
|
||||
@@ -372,12 +403,15 @@ recompile force = io $ do
|
||||
let msg = unlines $
|
||||
["Error detected while loading xmonad configuration file: " ++ src]
|
||||
++ lines ghcErr ++ ["","Please check the file for errors."]
|
||||
doubleFork $ executeFile "xmessage" True [msg] Nothing
|
||||
-- nb, the ordering of printing, then forking, is crucial due to
|
||||
-- lazy evaluation
|
||||
hPutStrLn stderr msg
|
||||
doubleFork $ executeFile "xmessage" True ["-default", "okay", 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
|
||||
-- | Conditionally run an action, using a @Maybe a@ to decide.
|
||||
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
|
||||
whenJust mg f = maybe (return ()) f mg
|
||||
|
||||
|
179
XMonad/Layout.hs
179
XMonad/Layout.hs
@@ -15,9 +15,14 @@
|
||||
--
|
||||
-----------------------------------------------------------------------------
|
||||
|
||||
module XMonad.Layout (ChangeLayout(..), Choose, (|||), Resize(..), IncMasterN(..),
|
||||
Full(..), Tall(..), Mirror(..), mirrorRect, splitVertically,
|
||||
splitHorizontally, splitHorizontallyBy, splitVerticallyBy) where
|
||||
module XMonad.Layout (
|
||||
ChangeLayout(..), Choose, (|||), Resize(..), IncMasterN(..),
|
||||
Full(..), Tall(..), Mirror(..), mirrorRect, splitVertically,
|
||||
splitHorizontally, splitHorizontallyBy, splitVerticallyBy,
|
||||
|
||||
tile
|
||||
|
||||
) where
|
||||
|
||||
import XMonad.Core
|
||||
|
||||
@@ -27,64 +32,8 @@ import Control.Arrow ((***), second)
|
||||
import Control.Monad
|
||||
import Data.Maybe (fromMaybe)
|
||||
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- LayoutClass selection manager
|
||||
|
||||
-- | A layout that allows users to switch between various layout options.
|
||||
|
||||
-- | Messages to change the current layout.
|
||||
data ChangeLayout = FirstLayout | NextLayout deriving (Eq, Show, Typeable)
|
||||
|
||||
instance Message ChangeLayout
|
||||
|
||||
-- | The layout choice combinator
|
||||
(|||) :: (LayoutClass l a, LayoutClass r a) => l a -> r a -> Choose l r a
|
||||
(|||) = flip SLeft
|
||||
infixr 5 |||
|
||||
|
||||
data Choose l r a = SLeft (r a) (l a)
|
||||
| SRight (l a) (r a) deriving (Read, Show)
|
||||
|
||||
data NextNoWrap = NextNoWrap deriving (Eq, Show, Typeable)
|
||||
instance Message NextNoWrap
|
||||
|
||||
-- This has lots of pseudo duplicated code, we must find a better way
|
||||
instance (LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a where
|
||||
doLayout (SLeft r l) = (fmap (second . fmap $ SLeft r) .) . doLayout l
|
||||
doLayout (SRight l r) = (fmap (second . fmap $ SRight l) .) . doLayout r
|
||||
|
||||
description (SLeft _ l) = description l
|
||||
description (SRight _ r) = description r
|
||||
|
||||
handleMessage lr m | Just FirstLayout <- fromMessage m = case lr of
|
||||
SLeft {} -> return Nothing
|
||||
SRight l r -> fmap (Just . flip SLeft l . fromMaybe r)
|
||||
$ handleMessage r (SomeMessage Hide)
|
||||
|
||||
handleMessage lr m | Just NextLayout <- fromMessage m = do
|
||||
mlr <- handleMessage lr $ SomeMessage NextNoWrap
|
||||
maybe (handleMessage lr $ SomeMessage FirstLayout) (return . Just) mlr
|
||||
|
||||
handleMessage (SLeft r l) m | Just NextNoWrap <- fromMessage m = do
|
||||
handleMessage l (SomeMessage Hide)
|
||||
mr <- handleMessage r (SomeMessage FirstLayout)
|
||||
return . Just . SRight l $ fromMaybe r mr
|
||||
|
||||
handleMessage lr m | Just ReleaseResources <- fromMessage m =
|
||||
liftM2 ((Just .) . cons)
|
||||
(fmap (fromMaybe l) $ handleMessage l m)
|
||||
(fmap (fromMaybe r) $ handleMessage r m)
|
||||
where (cons, l, r) = case lr of
|
||||
(SLeft r' l') -> (flip SLeft, l', r')
|
||||
(SRight l' r') -> (SRight, l', r')
|
||||
|
||||
-- The default cases for left and right:
|
||||
handleMessage (SLeft r l) m = fmap (fmap $ SLeft r) $ handleMessage l m
|
||||
handleMessage (SRight l r) m = fmap (fmap $ SRight l) $ handleMessage r m
|
||||
|
||||
--
|
||||
-- | Builtin layout algorithms:
|
||||
-- | Builtin basic layout algorithms:
|
||||
--
|
||||
-- > fullscreen mode
|
||||
-- > tall mode
|
||||
@@ -97,7 +46,7 @@ instance (LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a where
|
||||
data Resize = Shrink | Expand deriving Typeable
|
||||
|
||||
-- | You can also increase the number of clients in the master pane
|
||||
data IncMasterN = IncMasterN Int deriving Typeable
|
||||
data IncMasterN = IncMasterN !Int deriving Typeable
|
||||
|
||||
instance Message Resize
|
||||
instance Message IncMasterN
|
||||
@@ -107,34 +56,26 @@ data Full a = Full deriving (Show, Read)
|
||||
|
||||
instance LayoutClass Full a
|
||||
|
||||
-- | The inbuilt tiling mode of xmonad, and its operations.
|
||||
data Tall a = Tall Int Rational Rational deriving (Show, Read)
|
||||
-- | The builtin tiling mode of xmonad, and its operations.
|
||||
data Tall a = Tall !Int !Rational !Rational deriving (Show, Read)
|
||||
-- TODO should be capped [0..1] ..
|
||||
|
||||
-- a nice pure layout, lots of properties for the layout, and its messages, in Properties.hs
|
||||
instance LayoutClass Tall a where
|
||||
pureLayout (Tall nmaster _ frac) r s = zip ws rs
|
||||
where ws = W.integrate s
|
||||
rs = tile frac r nmaster (length ws)
|
||||
|
||||
pureMessage (Tall nmaster delta frac) m = msum [fmap resize (fromMessage m)
|
||||
,fmap incmastern (fromMessage m)]
|
||||
where resize Shrink = Tall nmaster delta (max 0 $ frac-delta)
|
||||
resize Expand = Tall nmaster delta (min 1 $ frac+delta)
|
||||
incmastern (IncMasterN d) = Tall (max 0 (nmaster+d)) delta frac
|
||||
pureMessage (Tall nmaster delta frac) m =
|
||||
msum [fmap resize (fromMessage m)
|
||||
,fmap incmastern (fromMessage m)]
|
||||
|
||||
where resize Shrink = Tall nmaster delta (max 0 $ frac-delta)
|
||||
resize Expand = Tall nmaster delta (min 1 $ frac+delta)
|
||||
incmastern (IncMasterN d) = Tall (max 0 (nmaster+d)) delta frac
|
||||
|
||||
description _ = "Tall"
|
||||
|
||||
-- | Mirror a rectangle
|
||||
mirrorRect :: Rectangle -> Rectangle
|
||||
mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
|
||||
|
||||
-- | Mirror a layout, compute its 90 degree rotated form.
|
||||
data Mirror l a = Mirror (l a) deriving (Show, Read)
|
||||
|
||||
instance LayoutClass l a => LayoutClass (Mirror l) a where
|
||||
doLayout (Mirror l) r s = (map (second mirrorRect) *** fmap Mirror)
|
||||
`fmap` doLayout l (mirrorRect r) s
|
||||
handleMessage (Mirror l) = fmap (fmap Mirror) . handleMessage l
|
||||
description (Mirror l) = "Mirror "++ description l
|
||||
|
||||
-- | tile. Compute the positions for windows using the default 2 pane tiling algorithm.
|
||||
--
|
||||
-- The screen is divided (currently) into two panes. all clients are
|
||||
@@ -163,6 +104,7 @@ splitVertically n (Rectangle sx sy sw sh) = Rectangle sx sy sw smallh :
|
||||
splitVertically (n-1) (Rectangle sx (sy+fromIntegral smallh) sw (sh-smallh))
|
||||
where smallh = sh `div` fromIntegral n --hmm, this is a fold or map.
|
||||
|
||||
-- Not used in the core, but exported
|
||||
splitHorizontally n = map mirrorRect . splitVertically n . mirrorRect
|
||||
|
||||
-- Divide the screen into two rectangles, using a rational to specify the ratio
|
||||
@@ -172,4 +114,79 @@ splitHorizontallyBy f (Rectangle sx sy sw sh) =
|
||||
, Rectangle (sx + fromIntegral leftw) sy (sw-fromIntegral leftw) sh)
|
||||
where leftw = floor $ fromIntegral sw * f
|
||||
|
||||
-- Not used in the core, but exported
|
||||
splitVerticallyBy f = (mirrorRect *** mirrorRect) . splitHorizontallyBy f . mirrorRect
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- | Mirror a layout, compute its 90 degree rotated form.
|
||||
|
||||
-- | Mirror a layout, compute its 90 degree rotated form.
|
||||
data Mirror l a = Mirror (l a) deriving (Show, Read)
|
||||
|
||||
instance LayoutClass l a => LayoutClass (Mirror l) a where
|
||||
runLayout (W.Workspace i (Mirror l) ms) r = (map (second mirrorRect) *** fmap Mirror)
|
||||
`fmap` runLayout (W.Workspace i l ms) (mirrorRect r)
|
||||
handleMessage (Mirror l) = fmap (fmap Mirror) . handleMessage l
|
||||
description (Mirror l) = "Mirror "++ description l
|
||||
|
||||
-- | Mirror a rectangle
|
||||
mirrorRect :: Rectangle -> Rectangle
|
||||
mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- LayoutClass selection manager
|
||||
-- Layouts that transition between other layouts
|
||||
|
||||
-- | A layout that allows users to switch between various layout options.
|
||||
|
||||
-- | Messages to change the current layout.
|
||||
data ChangeLayout = FirstLayout | NextLayout deriving (Eq, Show, Typeable)
|
||||
|
||||
instance Message ChangeLayout
|
||||
|
||||
-- | The layout choice combinator
|
||||
(|||) :: (LayoutClass l a, LayoutClass r a) => l a -> r a -> Choose l r a
|
||||
(|||) = flip SLeft
|
||||
infixr 5 |||
|
||||
|
||||
data Choose l r a = SLeft (r a) (l a)
|
||||
| SRight (l a) (r a) deriving (Read, Show)
|
||||
|
||||
data NextNoWrap = NextNoWrap deriving (Eq, Show, Typeable)
|
||||
instance Message NextNoWrap
|
||||
|
||||
-- This has lots of pseudo duplicated code, we must find a better way
|
||||
instance (LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a where
|
||||
runLayout (W.Workspace i (SLeft r l) ms) =
|
||||
fmap (second . fmap $ SLeft r) . runLayout (W.Workspace i l ms)
|
||||
runLayout (W.Workspace i (SRight l r) ms) =
|
||||
fmap (second . fmap $ SRight l) . runLayout (W.Workspace i r ms)
|
||||
|
||||
description (SLeft _ l) = description l
|
||||
description (SRight _ r) = description r
|
||||
|
||||
handleMessage lr m | Just FirstLayout <- fromMessage m = case lr of
|
||||
SLeft {} -> return Nothing
|
||||
SRight l r -> fmap (Just . flip SLeft l . fromMaybe r)
|
||||
$ handleMessage r (SomeMessage Hide)
|
||||
|
||||
handleMessage lr m | Just NextLayout <- fromMessage m = do
|
||||
mlr <- handleMessage lr $ SomeMessage NextNoWrap
|
||||
maybe (handleMessage lr $ SomeMessage FirstLayout) (return . Just) mlr
|
||||
|
||||
handleMessage (SLeft r l) m | Just NextNoWrap <- fromMessage m = do
|
||||
handleMessage l (SomeMessage Hide)
|
||||
mr <- handleMessage r (SomeMessage FirstLayout)
|
||||
return . Just . SRight l $ fromMaybe r mr
|
||||
|
||||
handleMessage lr m | Just ReleaseResources <- fromMessage m =
|
||||
liftM2 ((Just .) . cons)
|
||||
(fmap (fromMaybe l) $ handleMessage l m)
|
||||
(fmap (fromMaybe r) $ handleMessage r m)
|
||||
where (cons, l, r) = case lr of
|
||||
(SLeft r' l') -> (flip SLeft, l', r')
|
||||
(SRight l' r') -> (SRight, l', r')
|
||||
|
||||
-- The default cases for left and right:
|
||||
handleMessage (SLeft r l) m = fmap (fmap $ SLeft r) $ handleMessage l m
|
||||
handleMessage (SRight l r) m = fmap (fmap $ SRight l) $ handleMessage r m
|
||||
|
@@ -16,6 +16,7 @@
|
||||
module XMonad.Main (xmonad) where
|
||||
|
||||
import Data.Bits
|
||||
import Data.List ((\\))
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Set as S
|
||||
import Control.Monad.Reader
|
||||
@@ -23,11 +24,13 @@ import Control.Monad.State
|
||||
import Data.Maybe (fromMaybe)
|
||||
|
||||
import System.Environment (getArgs)
|
||||
import System.Posix.Signals
|
||||
|
||||
import Graphics.X11.Xlib hiding (refreshKeyboardMapping)
|
||||
import Graphics.X11.Xlib.Extras
|
||||
|
||||
import XMonad.Core
|
||||
import qualified XMonad.Config as Default
|
||||
import XMonad.StackSet (new, floating, member)
|
||||
import qualified XMonad.StackSet as W
|
||||
import XMonad.Operations
|
||||
@@ -39,6 +42,8 @@ import System.IO
|
||||
--
|
||||
xmonad :: (LayoutClass l Window, Read (l Window)) => XConfig l -> IO ()
|
||||
xmonad initxmc = do
|
||||
-- ignore SIGPIPE
|
||||
installHandler openEndedPipe Ignore Nothing
|
||||
-- First, wrap the layout in an existential, to keep things pretty:
|
||||
let xmc = initxmc { layoutHook = Layout $ layoutHook initxmc }
|
||||
dpy <- openDisplay ""
|
||||
@@ -46,8 +51,14 @@ xmonad initxmc = do
|
||||
|
||||
rootw <- rootWindow dpy dflt
|
||||
xinesc <- getCleanedScreenInfo dpy
|
||||
nbc <- initColor dpy $ normalBorderColor xmc
|
||||
fbc <- initColor dpy $ focusedBorderColor xmc
|
||||
nbc <- do v <- initColor dpy $ normalBorderColor xmc
|
||||
~(Just nbc_) <- initColor dpy $ normalBorderColor Default.defaultConfig
|
||||
return (fromMaybe nbc_ v)
|
||||
|
||||
fbc <- do v <- initColor dpy $ focusedBorderColor xmc
|
||||
~(Just fbc_) <- initColor dpy $ focusedBorderColor Default.defaultConfig
|
||||
return (fromMaybe fbc_ v)
|
||||
|
||||
hSetBuffering stdout NoBuffering
|
||||
args <- getArgs
|
||||
|
||||
@@ -96,15 +107,19 @@ xmonad initxmc = do
|
||||
|
||||
io $ sync dpy False
|
||||
|
||||
ws <- io $ scan dpy rootw
|
||||
|
||||
-- bootstrap the windowset, Operations.windows will identify all
|
||||
-- the windows in winset as new and set initial properties for
|
||||
-- those windows
|
||||
windows (const winset)
|
||||
-- those windows. Remove all windows that are no longer top-level
|
||||
-- children of the root, they may have disappeared since
|
||||
-- restarting.
|
||||
windows . const . foldr W.delete winset $ W.allWindows winset \\ ws
|
||||
|
||||
-- scan for all top-level windows, add the unmanaged ones to the
|
||||
-- windowset
|
||||
ws <- io $ scan dpy rootw
|
||||
mapM_ manage ws
|
||||
-- manage the as-yet-unmanaged windows
|
||||
mapM_ manage (ws \\ W.allWindows winset)
|
||||
|
||||
userCode $ startupHook initxmc
|
||||
|
||||
-- main loop, for all you HOF/recursion fans out there.
|
||||
forever_ $ handle =<< io (nextEvent dpy e >> getEvent e)
|
||||
@@ -190,7 +205,8 @@ handle e@(ButtonEvent {ev_window = w,ev_event_type = t,ev_button = b })
|
||||
else focus w
|
||||
broadcastMessage e -- Always send button events.
|
||||
|
||||
-- entered a normal window, makes this focused.
|
||||
-- entered a normal window: focus it if focusFollowsMouse is set to
|
||||
-- True in the user's config.
|
||||
handle e@(CrossingEvent {ev_window = w, ev_event_type = t})
|
||||
| t == enterNotify && ev_mode e == notifyNormal
|
||||
&& ev_detail e /= notifyInferior
|
||||
|
@@ -20,6 +20,7 @@ module XMonad.ManageHook where
|
||||
|
||||
import XMonad.Core
|
||||
import Graphics.X11.Xlib.Extras
|
||||
import Graphics.X11.Xlib (Display,Window)
|
||||
import Control.Monad.Reader
|
||||
import Data.Maybe
|
||||
import Data.Monoid
|
||||
@@ -65,6 +66,17 @@ title = ask >>= (\w -> liftX $ withDisplay $ \d -> fmap (fromMaybe "") $ io
|
||||
resource = ask >>= (\w -> liftX $ withDisplay $ \d -> fmap resName $ io $ getClassHint d w)
|
||||
className = ask >>= (\w -> liftX $ withDisplay $ \d -> fmap resClass $ io $ getClassHint d w)
|
||||
|
||||
-- | A query that can return an arbitrary X property of type String,
|
||||
-- identified by name.
|
||||
stringProperty :: String -> Query String
|
||||
stringProperty p = ask >>= (\w -> liftX $ withDisplay $ \d -> fmap (fromMaybe "") $ getStringProperty d w p)
|
||||
|
||||
getStringProperty :: Display -> Window -> String -> X (Maybe String)
|
||||
getStringProperty d w p = do
|
||||
a <- getAtom p
|
||||
md <- io $ getWindowProperty8 d a w
|
||||
return $ fmap (map (toEnum . fromIntegral)) md
|
||||
|
||||
-- | Modify the 'WindowSet' with a pure function.
|
||||
doF :: (WindowSet -> WindowSet) -> ManageHook
|
||||
doF = return . Endo
|
||||
|
@@ -23,6 +23,7 @@ import XMonad.Layout (Full(..))
|
||||
import qualified XMonad.StackSet as W
|
||||
|
||||
import Data.Maybe
|
||||
import Data.Monoid (appEndo)
|
||||
import Data.List (nub, (\\), find)
|
||||
import Data.Bits ((.|.), (.&.), complement)
|
||||
import Data.Ratio
|
||||
@@ -30,10 +31,12 @@ import qualified Data.Map as M
|
||||
import qualified Data.Set as S
|
||||
|
||||
import Control.Applicative
|
||||
import Control.Monad.State
|
||||
import Control.Monad.Reader
|
||||
import Control.Monad.State
|
||||
import qualified Control.Exception as C
|
||||
|
||||
import System.IO
|
||||
import System.Posix.Process (executeFile)
|
||||
import Graphics.X11.Xlib
|
||||
import Graphics.X11.Xinerama (getScreenInfo)
|
||||
import Graphics.X11.Xlib.Extras
|
||||
@@ -65,7 +68,7 @@ manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do
|
||||
where i = fromMaybe (W.tag . W.workspace . W.current $ ws) $ W.lookupWorkspace sc ws
|
||||
|
||||
mh <- asks (manageHook . config)
|
||||
g <- runManageHook mh w `catchX` return id
|
||||
g <- fmap appEndo (runQuery mh w) `catchX` return id
|
||||
windows (g . f)
|
||||
|
||||
-- | unmanage. A window no longer exists, remove it from the window
|
||||
@@ -119,17 +122,17 @@ windows f = do
|
||||
|
||||
-- notify non visibility
|
||||
let tags_oldvisible = map (W.tag . W.workspace) $ W.current old : W.visible old
|
||||
gottenhidden = filter (`elem` tags_oldvisible) $ map W.tag $ W.hidden ws
|
||||
sendMessageToWorkspaces Hide gottenhidden
|
||||
gottenhidden = filter (flip elem tags_oldvisible . W.tag) $ W.hidden ws
|
||||
mapM_ (sendMessageWithNoRefresh Hide) gottenhidden
|
||||
|
||||
-- for each workspace, layout the currently visible workspaces
|
||||
let allscreens = W.screens ws
|
||||
summed_visible = scanl (++) [] $ map (W.integrate' . W.stack . W.workspace) allscreens
|
||||
visible <- fmap concat $ forM (zip allscreens summed_visible) $ \ (w, vis) -> do
|
||||
let n = W.tag (W.workspace w)
|
||||
this = W.view n ws
|
||||
l = W.layout (W.workspace w)
|
||||
flt = filter (flip M.member (W.floating ws)) (W.index this)
|
||||
let wsp = W.workspace w
|
||||
this = W.view n ws
|
||||
n = W.tag wsp
|
||||
flt = filter (flip M.member (W.floating ws)) (W.index this)
|
||||
tiled = (W.stack . W.workspace . W.current $ this)
|
||||
>>= W.filter (`M.notMember` W.floating ws)
|
||||
>>= W.filter (`notElem` vis)
|
||||
@@ -140,11 +143,10 @@ windows f = do
|
||||
|
||||
-- just the tiled windows:
|
||||
-- now tile the windows on this workspace, modified by the gap
|
||||
(rs, ml') <- runLayout l viewrect tiled `catchX` runLayout (Layout Full) viewrect tiled
|
||||
(rs, ml') <- runLayout wsp { W.stack = tiled } viewrect `catchX`
|
||||
runLayout wsp { W.stack = tiled, W.layout = Layout Full } viewrect
|
||||
mapM_ (uncurry tileWindow) rs
|
||||
whenJust ml' $ \l' -> runOnWorkspaces (\ww -> if W.tag ww == n
|
||||
then return $ ww { W.layout = l'}
|
||||
else return ww)
|
||||
updateLayout n ml'
|
||||
|
||||
-- now the floating windows:
|
||||
-- move/resize the floating windows, if there are any
|
||||
@@ -336,13 +338,24 @@ sendMessage a = do
|
||||
{ W.workspace = (W.workspace $ W.current ws)
|
||||
{ W.layout = l' }}}
|
||||
|
||||
-- | Send a message to a list of workspaces' layouts, without necessarily refreshing.
|
||||
sendMessageToWorkspaces :: Message a => a -> [WorkspaceId] -> X ()
|
||||
sendMessageToWorkspaces a l = runOnWorkspaces $ \w ->
|
||||
if W.tag w `elem` l
|
||||
then do ml' <- handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing
|
||||
return $ w { W.layout = maybe (W.layout w) id ml' }
|
||||
else return w
|
||||
-- | Send a message to all layouts, without refreshing.
|
||||
broadcastMessage :: Message a => a -> X ()
|
||||
broadcastMessage a = withWindowSet $ \ws -> do
|
||||
let c = W.workspace . W.current $ ws
|
||||
v = map W.workspace . W.visible $ ws
|
||||
h = W.hidden ws
|
||||
mapM_ (sendMessageWithNoRefresh a) (c : v ++ h)
|
||||
|
||||
-- | Send a message to a layout, without refreshing.
|
||||
sendMessageWithNoRefresh :: Message a => a -> W.Workspace WorkspaceId (Layout Window) Window -> X ()
|
||||
sendMessageWithNoRefresh a w =
|
||||
handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing >>=
|
||||
updateLayout (W.tag w)
|
||||
|
||||
-- | Update the layout field of a workspace
|
||||
updateLayout :: WorkspaceId -> Maybe (Layout Window) -> X ()
|
||||
updateLayout i ml = whenJust ml $ \l ->
|
||||
runOnWorkspaces $ \ww -> return $ if W.tag ww == i then ww { W.layout = l} else ww
|
||||
|
||||
-- | Set the layout of the currently viewed workspace
|
||||
setLayout :: Layout Window -> X ()
|
||||
@@ -380,10 +393,24 @@ cleanMask km = do
|
||||
return (complement (nlm .|. lockMask) .&. km)
|
||||
|
||||
-- | Get the Pixel value for a named color
|
||||
initColor :: Display -> String -> IO Pixel
|
||||
initColor dpy c = (color_pixel . fst) <$> allocNamedColor dpy colormap c
|
||||
initColor :: Display -> String -> IO (Maybe Pixel)
|
||||
initColor dpy c = C.handle (\_ -> return Nothing) $
|
||||
(Just . color_pixel . fst) <$> allocNamedColor dpy colormap c
|
||||
where colormap = defaultColormap dpy (defaultScreen dpy)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
|
||||
-- | @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'.
|
||||
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 . W.mapLayout show
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- | Floating layer support
|
||||
|
||||
@@ -416,9 +443,9 @@ float :: Window -> X ()
|
||||
float w = do
|
||||
(sc, rr) <- floatLocation w
|
||||
windows $ \ws -> W.float w rr . fromMaybe ws $ do
|
||||
i <- W.findTag w ws
|
||||
i <- W.findTag w ws
|
||||
guard $ i `elem` map (W.tag . W.workspace) (W.screens ws)
|
||||
f <- W.peek ws
|
||||
f <- W.peek ws
|
||||
sw <- W.lookupWorkspace sc ws
|
||||
return (W.focusWindow f . W.shiftWin sw w $ ws)
|
||||
|
||||
|
@@ -112,7 +112,7 @@ import qualified Data.Map as M (Map,insert,delete,empty)
|
||||
-- viewable. We thus need to track which virtual workspaces are
|
||||
-- associated (viewed) on which physical screens. To keep track of
|
||||
-- this, StackSet keeps separate lists of visible but non-focused
|
||||
-- workspaces, and non-visible workspaces.
|
||||
-- workspaces, and non-visible workspaces.
|
||||
|
||||
-- $focus
|
||||
--
|
||||
@@ -122,38 +122,6 @@ import qualified Data.Map as M (Map,insert,delete,empty)
|
||||
-- 'delete'.
|
||||
--
|
||||
|
||||
-- |
|
||||
-- API changes from xmonad 0.1:
|
||||
-- StackSet constructor arguments changed. StackSet workspace window screen
|
||||
--
|
||||
-- * new, -- was: empty
|
||||
--
|
||||
-- * view,
|
||||
--
|
||||
-- * index,
|
||||
--
|
||||
-- * peek, -- was: peek\/peekStack
|
||||
--
|
||||
-- * focusUp, focusDown, -- was: rotate
|
||||
--
|
||||
-- * swapUp, swapDown
|
||||
--
|
||||
-- * focus -- was: raiseFocus
|
||||
--
|
||||
-- * insertUp, -- was: insert\/push
|
||||
--
|
||||
-- * delete,
|
||||
--
|
||||
-- * swapMaster, -- was: promote\/swap
|
||||
--
|
||||
-- * member,
|
||||
--
|
||||
-- * shift,
|
||||
--
|
||||
-- * lookupWorkspace, -- was: workspace
|
||||
--
|
||||
-- * visibleWorkspaces -- gone.
|
||||
--
|
||||
------------------------------------------------------------------------
|
||||
-- |
|
||||
-- A cursor into a non-empty list of workspaces.
|
||||
@@ -177,7 +145,7 @@ data Screen i l a sid sd = Screen { workspace :: !(Workspace i l a)
|
||||
deriving (Show, Read, Eq)
|
||||
|
||||
-- |
|
||||
-- A workspace is just a tag - its index - and a stack
|
||||
-- A workspace is just a tag, a layout, and a stack.
|
||||
--
|
||||
data Workspace i l a = Workspace { tag :: !i, layout :: l, stack :: Maybe (Stack a) }
|
||||
deriving (Show, Read, Eq)
|
||||
@@ -242,8 +210,7 @@ new _ _ _ = abort "non-positive argument to StackSet.new"
|
||||
|
||||
view :: (Eq s, Eq i) => i -> StackSet i l a s sd -> StackSet i l a s sd
|
||||
view i s
|
||||
| not (i `tagMember` s)
|
||||
|| i == tag (workspace (current s)) = s -- out of bounds or current
|
||||
| i == tag (workspace (current s)) = s -- current
|
||||
|
||||
| Just x <- L.find ((i==).tag.workspace) (visible s)
|
||||
-- if it is visible, it is just raised
|
||||
@@ -254,7 +221,7 @@ view i s
|
||||
= s { current = (current s) { workspace = x }
|
||||
, hidden = workspace (current s) : L.deleteBy (equating tag) x (hidden s) }
|
||||
|
||||
| otherwise = s -- can't happen: all workspaces are either invalid, current, visible, or hidden
|
||||
| otherwise = s -- not a member of the stackset
|
||||
|
||||
where equating f = \x y -> f x == f y
|
||||
|
||||
@@ -333,7 +300,7 @@ integrate (Stack x l r) = reverse l ++ x : r
|
||||
integrate' :: Maybe (Stack a) -> [a]
|
||||
integrate' = maybe [] integrate
|
||||
|
||||
-- |
|
||||
-- |
|
||||
-- /O(n)/. Turn a list into a possibly empty stack (i.e., a zipper):
|
||||
-- the first element of the list is current, and the rest of the list
|
||||
-- is down.
|
||||
@@ -446,7 +413,7 @@ mapLayout f (StackSet v vs hs m) = StackSet (fScreen v) (map fScreen vs) (map fW
|
||||
fScreen (Screen ws s sd) = Screen (fWorkspace ws) s sd
|
||||
fWorkspace (Workspace t l s) = Workspace t (f l) s
|
||||
|
||||
-- | /O(n)/. Is a window in the StackSet.
|
||||
-- | /O(n)/. Is a window in the StackSet?
|
||||
member :: Eq a => a -> StackSet i l a s sd -> Bool
|
||||
member a s = isJust (findTag a s)
|
||||
|
||||
|
@@ -9,23 +9,20 @@ xmonad \- a tiling window manager
|
||||
.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.
|
||||
.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 500 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 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.
|
||||
.SH USAGE
|
||||
.PP
|
||||
\fBxmonad\fR places each window into a "workspace". Each workspace can have any number of windows, which you can cycle though with mod-j and mod-k. Windows are either displayed full screen, tiled horizontally, or tiled vertically. You can toggle the layout mode with mod-space, which will cycle through the available modes.
|
||||
.PP
|
||||
You can switch to workspace N with mod-N. For example, to switch to workspace 5, you would press mod-5. Similarly, you can move the current window to another workspace with mod-shift-N.
|
||||
.PP
|
||||
When running with multiple monitors (Xinerama), each screen has exactly 1 workspace visible. mod-{w,e,r} switch the focus between screens, while shift-mod-{w,e,r} move the current window to that screen. When \fBxmonad\fR starts, workspace 1 is on screen 1, workspace 2 is on screen 2, etc. When switching workspaces to one that is already visible, the current and visible workspaces are swapped.
|
||||
When running with multiple monitors (Xinerama), each screen has exactly 1 workspace visible. mod-{w,e,r} switch the focus between screens, while shift-mod-{w,e,r} move the current window to that screen. When \fBxmonad\fR starts, workspace 1 is on screen 1, workspace 2 is on screen 2, etc. When switching workspaces to one that is already visible, the current and visible workspaces are swapped.
|
||||
.PP
|
||||
.SS Flags
|
||||
\fBxmonad\fR has several flags which you may pass to the executable. These flags are:
|
||||
.TP
|
||||
\fB--recompile
|
||||
Recompiles your configuration in ~/.xmonad/xmonad.hs if it is newer than your already existing ~/.xmonad/xmonad executable.
|
||||
.TP
|
||||
\fB--recompile-force
|
||||
Unconditionally recompiles your configuration in ~/.xmonad/xmonad.hs.
|
||||
\fB--recompile
|
||||
Recompiles your configuration in ~/.xmonad/xmonad.hs
|
||||
.TP
|
||||
\fB--version
|
||||
Display version of \fBxmonad\fR.
|
||||
|
@@ -247,6 +247,16 @@ myFocusFollowsMouse = True
|
||||
--
|
||||
myLogHook = return ()
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- Startup hook
|
||||
|
||||
-- Perform an arbitrary action each time xmonad starts or is restarted
|
||||
-- with mod-q. Used by, e.g., XMonad.Layout.PerWorkspace to initialize
|
||||
-- per-workspace layout choices.
|
||||
--
|
||||
-- By default, do nothing.
|
||||
myStartupHook = return ()
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- Now run xmonad with all the defaults we set up.
|
||||
|
||||
@@ -279,5 +289,6 @@ defaults = defaultConfig {
|
||||
-- hooks, layouts
|
||||
layoutHook = myLayout,
|
||||
manageHook = myManageHook,
|
||||
logHook = myLogHook
|
||||
logHook = myLogHook,
|
||||
startupHook = myStartupHook
|
||||
}
|
||||
|
@@ -2,6 +2,9 @@
|
||||
module Properties where
|
||||
|
||||
import XMonad.StackSet hiding (filter)
|
||||
import XMonad.Layout
|
||||
import XMonad.Core hiding (workspaces,trace)
|
||||
import XMonad.Operations ( applyResizeIncHint, applyMaxSizeHint )
|
||||
import qualified XMonad.StackSet as S (filter)
|
||||
|
||||
import Debug.Trace
|
||||
@@ -136,10 +139,10 @@ prop_empty_I (n :: Positive Int) l = forAll (choose (1,fromIntegral n)) $ \m -
|
||||
invariant $ new l [0..fromIntegral n-1] ms
|
||||
|
||||
prop_view_I (n :: NonNegative Int) (x :: T) =
|
||||
n `tagMember` x ==> invariant $ view (fromIntegral n) x
|
||||
invariant $ view (fromIntegral n) x
|
||||
|
||||
prop_greedyView_I (n :: NonNegative Int) (x :: T) =
|
||||
n `tagMember` x ==> invariant $ view (fromIntegral n) x
|
||||
invariant $ greedyView (fromIntegral n) x
|
||||
|
||||
prop_focusUp_I (n :: NonNegative Int) (x :: T) =
|
||||
invariant $ foldr (const focusUp) x [1..n]
|
||||
@@ -236,6 +239,13 @@ prop_greedyView_current (x :: T) (n :: NonNegative Int) = i `tagMember` x ==>
|
||||
where
|
||||
i = fromIntegral n
|
||||
|
||||
-- greedyView leaves things unchanged for invalid workspaces
|
||||
prop_greedyView_current_id (x :: T) (n :: NonNegative Int) = not (i `tagMember` x) ==>
|
||||
tag (workspace $ current (greedyView i x)) == j
|
||||
where
|
||||
i = fromIntegral n
|
||||
j = tag (workspace (current x))
|
||||
|
||||
-- greedyView *only* sets the current workspace, and touches Xinerama.
|
||||
-- no workspace contents will be changed.
|
||||
prop_greedyView_local (x :: T) (n :: NonNegative Int) = i `tagMember` x ==>
|
||||
@@ -348,6 +358,10 @@ prop_focusWindow_local (n :: NonNegative Int) (x::T ) =
|
||||
i = fromIntegral n `mod` length s
|
||||
in hidden_spaces (focusWindow (s !! i) x) == hidden_spaces x
|
||||
|
||||
-- On an invalid window, the stackset is unmodified
|
||||
prop_focusWindow_identity (n :: Char) (x::T ) =
|
||||
not (n `member` x) ==> focusWindow n x == x
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
-- member/findTag
|
||||
|
||||
@@ -540,13 +554,19 @@ prop_float_reversible n (x :: T) =
|
||||
where
|
||||
geom = RationalRect 100 100 100 100
|
||||
|
||||
-- check rectanges were set
|
||||
{-
|
||||
prop_float_sets_geometry n (x :: T) =
|
||||
n `member` x ==> let y = float n geom x in M.lookup y (floating x) == Just geom
|
||||
prop_float_geometry n (x :: T) =
|
||||
n `member` x ==> let s = float n geom x
|
||||
in M.lookup n (floating s) == Just geom
|
||||
where
|
||||
geom = RationalRect 100 100 100 100
|
||||
-}
|
||||
|
||||
prop_float_delete n (x :: T) =
|
||||
n `member` x ==> let s = float n geom x
|
||||
t = delete n s
|
||||
in not (n `member` t)
|
||||
where
|
||||
geom = RationalRect 100 100 100 100
|
||||
|
||||
|
||||
------------------------------------------------------------------------
|
||||
|
||||
@@ -605,9 +625,26 @@ prop_rename1 (x::T) o n = o `tagMember` x && not (n `tagMember` x) ==>
|
||||
let y = renameTag o n x
|
||||
in n `tagMember` y
|
||||
|
||||
-- |
|
||||
-- Ensure that a given set of workspace tags is present by renaming
|
||||
-- existing workspaces and\/or creating new hidden workspaces as
|
||||
-- necessary.
|
||||
--
|
||||
prop_ensure (x :: T) l xs = let y = ensureTags l xs x
|
||||
in and [ n `tagMember` y | n <- xs ]
|
||||
|
||||
-- adding a tag should create a new hidden workspace
|
||||
prop_ensure_append (x :: T) l n =
|
||||
not (n `tagMember` x)
|
||||
==>
|
||||
(hidden y /= hidden x -- doesn't append, renames
|
||||
&&
|
||||
and [ isNothing (stack z) && layout z == l | z <- hidden y, tag z == n ]
|
||||
)
|
||||
where
|
||||
y = ensureTags l (n:ts) x
|
||||
ts = [ tag z | z <- workspaces x ]
|
||||
|
||||
prop_mapWorkspaceId (x::T) = x == mapWorkspace id x
|
||||
|
||||
prop_mapWorkspaceInverse (x::T) = x == mapWorkspace predTag (mapWorkspace succTag x)
|
||||
@@ -619,17 +656,145 @@ prop_mapLayoutId (x::T) = x == mapLayout id x
|
||||
prop_mapLayoutInverse (x::T) = x == mapLayout pred (mapLayout succ x)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- some properties for layouts:
|
||||
-- The Tall layout
|
||||
|
||||
-- 1 window should always be tiled fullscreen
|
||||
{-
|
||||
prop_tile_fullscreen rect = tile pct rect 1 1 == [rect]
|
||||
where pct = 1/2
|
||||
|
||||
-- multiple windows
|
||||
prop_tile_non_overlap rect windows nmaster = noOverlaps (tile pct rect nmaster windows)
|
||||
where _ = rect :: Rectangle
|
||||
pct = 3 % 100
|
||||
|
||||
pct = 3 % 100
|
||||
-- splitting horizontally yields sensible results
|
||||
prop_split_hoziontal (NonNegative n) x =
|
||||
{-
|
||||
trace (show (rect_x x
|
||||
,rect_width x
|
||||
,rect_x x + fromIntegral (rect_width x)
|
||||
,map rect_x xs))
|
||||
$
|
||||
-}
|
||||
|
||||
sum (map rect_width xs) == rect_width x
|
||||
&&
|
||||
all (== rect_height x) (map rect_height xs)
|
||||
&&
|
||||
(map rect_x xs) == (sort $ map rect_x xs)
|
||||
|
||||
where
|
||||
xs = splitHorizontally n x
|
||||
|
||||
-- splitting horizontally yields sensible results
|
||||
prop_splitVertically (r :: Rational) x =
|
||||
|
||||
rect_x x == rect_x a && rect_x x == rect_x b
|
||||
&&
|
||||
rect_width x == rect_width a && rect_width x == rect_width b
|
||||
|
||||
{-
|
||||
trace (show (rect_x x
|
||||
,rect_width x
|
||||
,rect_x x + fromIntegral (rect_width x)
|
||||
,map rect_x xs))
|
||||
$
|
||||
-}
|
||||
|
||||
where
|
||||
(a,b) = splitVerticallyBy r x
|
||||
|
||||
|
||||
-- pureLayout works.
|
||||
prop_purelayout_tall n r1 r2 rect (t :: T) =
|
||||
isJust (peek t) ==>
|
||||
length ts == length (index t)
|
||||
&&
|
||||
noOverlaps (map snd ts)
|
||||
&&
|
||||
description layoot == "Tall"
|
||||
where layoot = Tall n r1 r2
|
||||
st = fromJust . stack . workspace . current $ t
|
||||
ts = pureLayout layoot rect st
|
||||
|
||||
-- Test message handling of Tall
|
||||
|
||||
-- what happens when we send a Shrink message to Tall
|
||||
prop_shrink_tall (NonNegative n) (NonZero (NonNegative delta)) (NonNegative frac) =
|
||||
n == n' && delta == delta' -- these state components are unchanged
|
||||
&& frac' <= frac && (if frac' < frac then frac' == 0 || frac' == frac - delta
|
||||
else frac == 0 )
|
||||
-- remaining fraction should shrink
|
||||
where
|
||||
l1 = Tall n delta frac
|
||||
Just l2@(Tall n' delta' frac') = l1 `pureMessage` (SomeMessage Shrink)
|
||||
-- pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
|
||||
|
||||
|
||||
-- what happens when we send a Shrink message to Tall
|
||||
prop_expand_tall (NonNegative n)
|
||||
(NonZero (NonNegative delta))
|
||||
(NonNegative n1)
|
||||
(NonZero (NonNegative d1)) =
|
||||
|
||||
n == n'
|
||||
&& delta == delta' -- these state components are unchanged
|
||||
&& frac' >= frac
|
||||
&& (if frac' > frac
|
||||
then frac' == 1 || frac' == frac + delta
|
||||
else frac == 1 )
|
||||
|
||||
-- remaining fraction should shrink
|
||||
where
|
||||
frac = min 1 (n1 % d1)
|
||||
l1 = Tall n delta frac
|
||||
Just l2@(Tall n' delta' frac') = l1 `pureMessage` (SomeMessage Expand)
|
||||
-- pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
|
||||
|
||||
-- what happens when we send an IncMaster message to Tall
|
||||
prop_incmaster_tall (NonNegative n) (NonZero (NonNegative delta)) (NonNegative frac)
|
||||
(NonNegative k) =
|
||||
delta == delta' && frac == frac' && n' == n + k
|
||||
where
|
||||
l1 = Tall n delta frac
|
||||
Just l2@(Tall n' delta' frac') = l1 `pureMessage` (SomeMessage (IncMasterN k))
|
||||
-- pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
|
||||
|
||||
|
||||
|
||||
-- toMessage LT = SomeMessage Shrink
|
||||
-- toMessage EQ = SomeMessage Expand
|
||||
-- toMessage GT = SomeMessage (IncMasterN 1)
|
||||
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- Full layout
|
||||
|
||||
-- pureLayout works for Full
|
||||
prop_purelayout_full rect (t :: T) =
|
||||
isJust (peek t) ==>
|
||||
length ts == 1 -- only one window to view
|
||||
&&
|
||||
snd (head ts) == rect -- and sets fullscreen
|
||||
&&
|
||||
fst (head ts) == fromJust (peek t) -- and the focused window is shown
|
||||
|
||||
where layoot = Full
|
||||
st = fromJust . stack . workspace . current $ t
|
||||
ts = pureLayout layoot rect st
|
||||
|
||||
-- what happens when we send an IncMaster message to Full --- Nothing
|
||||
prop_sendmsg_full (NonNegative k) =
|
||||
isNothing (Full `pureMessage` (SomeMessage (IncMasterN k)))
|
||||
|
||||
prop_desc_full = description Full == show Full
|
||||
|
||||
------------------------------------------------------------------------
|
||||
|
||||
prop_desc_mirror n r1 r2 = description (Mirror $! t) == "Mirror Tall"
|
||||
where t = Tall n r1 r2
|
||||
|
||||
------------------------------------------------------------------------
|
||||
|
||||
noOverlaps [] = True
|
||||
noOverlaps [_] = True
|
||||
@@ -645,7 +810,28 @@ noOverlaps xs = and [ verts a `notOverlap` verts b
|
||||
= (top1 < bottom2 || top2 < bottom1)
|
||||
|| (right1 < left2 || right2 < left1)
|
||||
|
||||
-}
|
||||
------------------------------------------------------------------------
|
||||
-- Aspect ratios
|
||||
|
||||
prop_resize_inc (NonZero (NonNegative inc_w),NonZero (NonNegative inc_h)) b@(w,h) =
|
||||
w' `mod` inc_w == 0 && h' `mod` inc_h == 0
|
||||
where (w',h') = applyResizeIncHint a b
|
||||
a = (inc_w,inc_h)
|
||||
|
||||
prop_resize_inc_extra ((NonNegative inc_w)) b@(w,h) =
|
||||
(w,h) == (w',h')
|
||||
where (w',h') = applyResizeIncHint a b
|
||||
a = (-inc_w,0::Dimension)-- inc_h)
|
||||
|
||||
prop_resize_max (NonZero (NonNegative inc_w),NonZero (NonNegative inc_h)) b@(w,h) =
|
||||
w' <= inc_w && h' <= inc_h
|
||||
where (w',h') = applyMaxSizeHint a b
|
||||
a = (inc_w,inc_h)
|
||||
|
||||
prop_resize_max_extra ((NonNegative inc_w)) b@(w,h) =
|
||||
(w,h) == (w',h')
|
||||
where (w',h') = applyMaxSizeHint a b
|
||||
a = (-inc_w,0::Dimension)-- inc_h)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
|
||||
@@ -653,7 +839,7 @@ main :: IO ()
|
||||
main = do
|
||||
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
|
||||
(results, passed) <- liftM unzip $ mapM (\(s,a) -> printf "%-40s: " s >> a n) tests
|
||||
printf "Passed %d tests!\n" (sum passed)
|
||||
when (not . and $ results) $ fail "Not all tests passed!"
|
||||
where
|
||||
@@ -675,6 +861,7 @@ main = do
|
||||
|
||||
,("greedyView : invariant" , mytest prop_greedyView_I)
|
||||
,("greedyView sets current" , mytest prop_greedyView_current)
|
||||
,("greedyView is safe " , mytest prop_greedyView_current_id)
|
||||
,("greedyView idempotent" , mytest prop_greedyView_idem)
|
||||
,("greedyView reversible" , mytest prop_greedyView_reversible)
|
||||
,("greedyView is local" , mytest prop_greedyView_local)
|
||||
@@ -704,6 +891,7 @@ main = do
|
||||
|
||||
,("focusWindow is local", mytest prop_focusWindow_local)
|
||||
,("focusWindow works" , mytest prop_focusWindow_works)
|
||||
,("focusWindow identity", mytest prop_focusWindow_identity)
|
||||
|
||||
,("findTag" , mytest prop_findIndex)
|
||||
,("allWindows/member" , mytest prop_allWindowsMember)
|
||||
@@ -748,13 +936,17 @@ main = do
|
||||
,("shiftWin fix current" , mytest prop_shift_win_fix_current)
|
||||
|
||||
,("floating is reversible" , mytest prop_float_reversible)
|
||||
,("floating sets geometry" , mytest prop_float_geometry)
|
||||
,("floats can be deleted", mytest prop_float_delete)
|
||||
,("screens includes current", mytest prop_screens)
|
||||
|
||||
,("differentiate works", mytest prop_differentiate)
|
||||
,("lookupTagOnScreen", mytest prop_lookup_current)
|
||||
,("lookupTagOnVisbleScreen", mytest prop_lookup_visible)
|
||||
,("screens works", mytest prop_screens_works)
|
||||
,("renaming works", mytest prop_rename1)
|
||||
,("ensure works", mytest prop_ensure)
|
||||
,("ensure hidden semantics", mytest prop_ensure_append)
|
||||
|
||||
,("mapWorkspace id", mytest prop_mapWorkspaceId)
|
||||
,("mapWorkspace inverse", mytest prop_mapWorkspaceInverse)
|
||||
@@ -766,12 +958,31 @@ main = do
|
||||
,("new fails with abort", mytest prop_new_abort)
|
||||
,("shiftWin identity", mytest prop_shift_win_indentity)
|
||||
|
||||
-- renaming
|
||||
-- tall layout
|
||||
|
||||
{-
|
||||
,("tile 1 window fullsize", mytest prop_tile_fullscreen)
|
||||
,("tiles never overlap", mytest prop_tile_non_overlap)
|
||||
-}
|
||||
,("split hozizontally", mytest prop_split_hoziontal)
|
||||
,("split verticalBy", mytest prop_splitVertically)
|
||||
|
||||
,("pure layout tall", mytest prop_purelayout_tall)
|
||||
,("send shrink tall", mytest prop_shrink_tall)
|
||||
,("send expand tall", mytest prop_expand_tall)
|
||||
,("send incmaster tall", mytest prop_incmaster_tall)
|
||||
|
||||
-- full layout
|
||||
|
||||
,("pure layout full", mytest prop_purelayout_full)
|
||||
,("send message full", mytest prop_sendmsg_full)
|
||||
,("describe full", mytest prop_desc_full)
|
||||
|
||||
,("describe mirror", mytest prop_desc_mirror)
|
||||
|
||||
-- resize hints
|
||||
,("window hints: inc", mytest prop_resize_inc)
|
||||
,("window hints: inc all", mytest prop_resize_inc_extra)
|
||||
,("window hints: max", mytest prop_resize_max)
|
||||
,("window hints: max all ", mytest prop_resize_max_extra)
|
||||
|
||||
]
|
||||
|
||||
|
10
tests/coverage.hs
Normal file
10
tests/coverage.hs
Normal file
@@ -0,0 +1,10 @@
|
||||
#!/usr/bin/env runhaskell
|
||||
|
||||
import System.Cmd
|
||||
|
||||
-- generate appropriate .hpc files
|
||||
main = do
|
||||
system $ "rm -rf *.tix"
|
||||
system $ "dist/build/xmonad/xmonad --run-tests"
|
||||
system $ "hpc markup xmonad --exclude=Main --exclude=Properties --exclude=XMonad --exclude=Paths_xmonad"
|
||||
system $ "hpc report xmonad --exclude=Main --exclude=Properties --exclude=XMonad --exclude=Paths_xmonad"
|
@@ -1,5 +1,5 @@
|
||||
name: xmonad
|
||||
version: 0.6
|
||||
version: 0.7
|
||||
homepage: http://xmonad.org
|
||||
synopsis: A tiling window manager
|
||||
description:
|
||||
@@ -21,6 +21,7 @@ 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
|
||||
util/GenerateManpage.hs
|
||||
cabal-version: >= 1.2
|
||||
build-type: Simple
|
||||
|
||||
flag small_base
|
||||
description: Choose the new smaller, split-up base package.
|
||||
|
Reference in New Issue
Block a user