Remove trailing whitespace from many modules

This commit is contained in:
Adam Vogt 2009-07-05 20:12:05 +00:00
parent d65e40f09d
commit 5cd48cac7c
32 changed files with 146 additions and 146 deletions

View File

@ -25,7 +25,7 @@ import qualified XMonad.StackSet as S
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
--
-- > import XMonad hiding ((|||))
-- > import XMonad.Layout.LayoutCombinators ((|||))
-- > import XMonad.Actions.CycleSelectedLayouts

View File

@ -18,7 +18,7 @@
-- * Cycle windows through the focused position.
--
-- * Cycle unfocused windows.
--
--
-- These bindings are especially useful with layouts that hide some of
-- the windows in the stack, such as Full, "XMonad.Layout.TwoPane" or
-- "XMonad.Layout.Mosaic" with three or four panes. See also
@ -70,7 +70,7 @@ import XMonad.Actions.RotSlaves
--
-- Also, if you use focus follows mouse, you will want to read the section
-- on updating the mouse pointer below. For detailed instructions on
-- editing your key bindings, see "XMonad.Doc.Extending#Editing_key_bindings".
-- editing your key bindings, see "XMonad.Doc.Extending#Editing_key_bindings".
{- $pointer
With FocusFollowsMouse == True, the focus is updated after binding
actions, possibly focusing a window you didn't intend to focus. Most

View File

@ -230,7 +230,7 @@ hsv2rgb (h,s,v) =
-- | Default colorizer for Strings
defaultColorizer :: String -> Bool -> X (String, String)
defaultColorizer s active =
defaultColorizer s active =
let seed x = toInteger (sum $ map ((*x).fromEnum) s) :: Integer
(r,g,b) = hsv2rgb ((seed 83) `mod` 360,
(fromInteger ((seed 191) `mod` 1000))/2500+0.4,
@ -254,17 +254,17 @@ colorRangeFromClassName :: (Word8, Word8, Word8) -- ^ Beginning of the color ran
-> (Word8, Word8, Word8) -- ^ Inactive text color
-> (Word8, Word8, Word8) -- ^ Active text color
-> Window -> Bool -> X (String, String)
colorRangeFromClassName startC endC activeC inactiveT activeT w active =
colorRangeFromClassName startC endC activeC inactiveT activeT w active =
do classname <- runQuery className w
if active
if active
then return (rgbToHex activeC, rgbToHex activeT)
else return (rgbToHex $ mix startC endC
else return (rgbToHex $ mix startC endC
$ stringToRatio classname, rgbToHex inactiveT)
where rgbToHex :: (Word8, Word8, Word8) -> String
rgbToHex (r, g, b) = '#':twodigitHex r
++twodigitHex g++twodigitHex b
-- | Creates a mix of two colors according to a ratio
-- | Creates a mix of two colors according to a ratio
-- (1 -> first color, 0 -> second color).
mix :: (Word8, Word8, Word8) -> (Word8, Word8, Word8)
-> Double -> (Word8, Word8, Word8)

View File

@ -52,8 +52,8 @@ import Control.Applicative ((<$>))
--
-- is mis-typed. For this reason, this module provides alternatives (ending with
-- an underscore, e.g. tryMessage_) that discard their result and return an @X ()@.
-- For example, to correct the previous example:
--
-- For example, to correct the previous example:
--
-- > ((modKey, xK_Left), tryMessage_ Shrink (MoveLeft 50))
--

View File

@ -178,7 +178,7 @@ raiseMaster raisef thatUserQuery = raiseAndDo raisef thatUserQuery (\_ -> window
{- | If the window is found the window is focused and set to master
otherwise, action is run.
> runOrRaiseMaster \"firefox\" (className =? \"Firefox\"))
> runOrRaiseMaster \"firefox\" (className =? \"Firefox\"))
-}
runOrRaiseMaster :: String -> Query Bool -> X ()
runOrRaiseMaster run query = runOrRaiseAndDo run query (\_ -> windows W.swapMaster)

View File

@ -95,7 +95,7 @@ keys x = M.fromList $
, ((modMask x .|. controlMask .|. shiftMask, xK_Left), sendMessage $ Move L)
, ((modMask x .|. controlMask .|. shiftMask, xK_Up), sendMessage $ Move U)
, ((modMask x .|. controlMask .|. shiftMask, xK_Down), sendMessage $ Move D)
, ((0, xK_F2 ), spawn "gnome-terminal") -- %! Launch gnome-terminal
, ((0, xK_F3 ), shellPrompt myXPConfig) -- %! Launch program
, ((0, xK_F11 ), spawn "ksnapshot") -- %! Take snapshot
@ -112,7 +112,7 @@ keys x = M.fromList $
, ((modMask x, xK_space), sendMessage Toggle)
]
++
zip (zip (repeat $ modMask x) [xK_F1..xK_F12]) (map (withNthWorkspace W.greedyView) [0..])
++
@ -143,12 +143,12 @@ config = defaultConfig
mytab = tabbed CustomShrink defaultTheme
instance Shrinker CustomShrink where
shrinkIt shr s | Just s' <- dropFromHead " " s = shrinkIt shr s'
shrinkIt shr s | Just s' <- dropFromTail " " s = shrinkIt shr s'
shrinkIt shr s | Just s' <- dropFromTail "- Iceweasel" s = shrinkIt shr s'
shrinkIt shr s | Just s' <- dropFromTail "- KPDF" s = shrinkIt shr s'
shrinkIt shr s | Just s' <- dropFromHead "file://" s = shrinkIt shr s'
shrinkIt shr s | Just s' <- dropFromHead "http://" s = shrinkIt shr s'
shrinkIt shr s | Just s' <- dropFromHead " " s = shrinkIt shr s'
shrinkIt shr s | Just s' <- dropFromTail " " s = shrinkIt shr s'
shrinkIt shr s | Just s' <- dropFromTail "- Iceweasel" s = shrinkIt shr s'
shrinkIt shr s | Just s' <- dropFromTail "- KPDF" s = shrinkIt shr s'
shrinkIt shr s | Just s' <- dropFromHead "file://" s = shrinkIt shr s'
shrinkIt shr s | Just s' <- dropFromHead "http://" s = shrinkIt shr s'
shrinkIt _ s | n > 9 = s : map cut [2..(halfn-3)] ++ shrinkIt shrinkText s
where n = length s
halfn = n `div` 2

View File

@ -30,7 +30,7 @@ import qualified Data.Map as M
-- > import XMonad.Config.Gnome
-- >
-- > main = xmonad gnomeConfig
--
--
gnomeConfig = desktopConfig
{ terminal = "gnome-terminal"

View File

@ -32,7 +32,7 @@ import qualified Data.Map as M
-- > main = xmonad kdeConfig
--
-- For KDE 4, replace 'kdeConfig' with 'kde4Config'
--
--
kdeConfig = desktopConfig
{ terminal = "konsole"

View File

@ -38,7 +38,7 @@ layout = fromSetGet (\x c -> c { layoutHook = x }) layoutHook
terminal = fromSetGet (\x c -> c { X.terminal = x }) X.terminal
keys = fromSetGet (\x c -> c { X.keys = x }) X.keys
set :: Accessor (XConfig LayoutList) a -> a -> Config ()
set :: Accessor (XConfig LayoutList) a -> a -> Config ()
set r x = tell (mkW $ r ^= x)
add r x = tell (mkW (r ^: mappend x))

View File

@ -29,7 +29,7 @@ import qualified Data.Map as M
-- > import XMonad.Config.Xfce
-- >
-- > main = xmonad xfceConfig
--
--
xfceConfig = desktopConfig
{ terminal = "Terminal"

View File

@ -53,11 +53,11 @@ import Data.IORef
-- You must include this @dynHooksRef@ value when using the functions in this
-- module:
--
-- > xmonad { keys = myKeys `Data.Map.union` Data.Map.fromList
-- > [((modMask conf, xK_i), oneShotHook dynHooksRef
-- > "FFlaunchHook" (className =? "firefox") (doShift "3")
-- > xmonad { keys = myKeys `Data.Map.union` Data.Map.fromList
-- > [((modMask conf, xK_i), oneShotHook dynHooksRef
-- > "FFlaunchHook" (className =? "firefox") (doShift "3")
-- > >> spawn "firefox")
-- > ,((modMask conf, xK_u), addDynamicHook dynHooksRef
-- > ,((modMask conf, xK_u), addDynamicHook dynHooksRef
-- > (className =? "example" --> doFloat))
-- > ,((modMask conf, xK_y), updatePermanentHook dynHooksRef
-- > (const idHook))) ] -- resets the permanent hook.
@ -66,7 +66,7 @@ import Data.IORef
data DynamicHooks = DynamicHooks
{ transients :: [(Query Bool, ManageHook)]
, permanent :: ManageHook }
-- | Creates the 'IORef' that stores the dynamically created 'ManageHook's.
initDynamicHooks :: IO (IORef DynamicHooks)
@ -80,7 +80,7 @@ initDynamicHooks = newIORef (DynamicHooks { transients = [],
-- doFloat and doIgnore are idempotent.
-- | Master 'ManageHook' that must be in your @xmonad.hs@ 'ManageHook'.
dynamicMasterHook :: IORef DynamicHooks -> ManageHook
dynamicMasterHook ref = return True -->
dynamicMasterHook ref = return True -->
(ask >>= \w -> liftX (do
dh <- io $ readIORef ref
(Endo f) <- runQuery (permanent dh) w
@ -99,7 +99,7 @@ addDynamicHook ref m = updateDynamicHook ref (<+> m)
-- | Modifies the permanent 'ManageHook' with an arbitrary function.
updateDynamicHook :: IORef DynamicHooks -> (ManageHook -> ManageHook) -> X ()
updateDynamicHook ref f =
updateDynamicHook ref f =
io $ modifyIORef ref $ \dh -> dh { permanent = f (permanent dh) }
@ -108,10 +108,10 @@ updateDynamicHook ref f =
--
-- > className =? "example" --> doFloat
--
-- you must call 'oneShotHook' as
-- you must call 'oneShotHook' as
--
-- > oneShotHook dynHooksRef (className =? "example) doFloat
--
--
oneShotHook :: IORef DynamicHooks -> Query Bool -> ManageHook -> X ()
oneShotHook ref q a =
io $ modifyIORef ref

View File

@ -100,7 +100,7 @@ ewmhDesktopsLogHookCustom f = withWindowSet $ \s -> do
setWindowDesktop win curr
forM_ (W.hidden s) $ \w ->
case elemIndex (W.tag w) (map W.tag ws) of
case elemIndex (W.tag w) (map W.tag ws) of
Nothing -> return ()
Just wn -> forM_ (W.integrate' (W.stack w)) $ \win -> do
setWindowDesktop win wn

View File

@ -8,7 +8,7 @@
-- Stability : unstable
-- Portability : unportable
--
-- Hook and keybindings for automatically sending the next
-- Hook and keybindings for automatically sending the next
-- spawned window(s) to the floating layer.
--
-----------------------------------------------------------------------------
@ -72,11 +72,11 @@ floatModeMVar = unsafePerformIO $ newMVar (False, False)
-- $usage
-- This module provides actions (that can be set as keybindings)
-- to automatically send the next spawned window(s) to the floating
-- to automatically send the next spawned window(s) to the floating
-- layer.
--
-- You can use it by including the following in your @~\/.xmonad\/xmonad.hs@:
--
--
-- > import XMonad.Hooks.FloatNext
--
-- and adding 'floatNextHook' to your 'ManageHook':
@ -130,23 +130,23 @@ willFloatAllNew = _get snd
-- $pp
-- The following functions are used to display the current
-- state of 'floatNext' and 'floatAllNew' in your
-- state of 'floatNext' and 'floatAllNew' in your
-- 'XMonad.Hooks.DynamicLog.dynamicLogWithPP'.
-- 'willFloatNextPP' and 'willFloatAllNewPP' should be added
-- to the 'XMonad.Hooks.DynamicLog.ppExtras' field of your
-- to the 'XMonad.Hooks.DynamicLog.ppExtras' field of your
-- 'XMonad.Hooks.DynamicLog.PP'.
--
-- Use 'runLogHook' to refresh the output of your 'logHook', so
-- that the effects of a 'floatNext'/... will be visible
-- immediately:
--
--
-- > , ((modMask, xK_e), toggleFloatNext >> runLogHook)
--
-- The @String -> String@ parameters to 'willFloatNextPP' and
-- 'willFloatAllNewPP' will be applied to their output, you
-- 'willFloatAllNewPP' will be applied to their output, you
-- can use them to set the text color, etc., or you can just
-- pass them 'id'.
willFloatNextPP :: (String -> String) -> X (Maybe String)
willFloatNextPP = _pp fst "Next"

View File

@ -14,7 +14,7 @@
module XMonad.Hooks.Place ( -- * Usage
-- $usage
-- * Placement actions
placeFocused
, placeHook
@ -53,7 +53,7 @@ import Control.Monad.Trans (lift)
-- as an 'X' action to manually trigger repositioning.
--
-- You can use this module by including the following in your @~\/.xmonad\/xmonad.hs@:
--
--
-- > import XMonad.Hooks.Place
--
-- and adding 'placeHook' to your 'manageHook', for example:
@ -61,7 +61,7 @@ import Control.Monad.Trans (lift)
-- > main = xmonad $ defaultConfig { manageHook = placeHook simpleSmart
-- > <+> manageHook defaultConfig }
--
-- Note that 'placeHook' should be applied after most other hooks, especially hooks
-- Note that 'placeHook' should be applied after most other hooks, especially hooks
-- such as 'doFloat' and 'doShift'. Since hooks combined with '<+>' are applied from
-- right to left, this means that 'placeHook' should be the /first/ hook in your chain.
--
@ -71,7 +71,7 @@ import Control.Monad.Trans (lift)
-- > , ((modMask, xK_w), placeFocused simpleSmart)
--
-- Both 'placeHook' and 'placeFocused' take a 'Placement' parameter, which specifies
-- the placement policy to use (smart, under the mouse, fixed position, etc.). See
-- the placement policy to use (smart, under the mouse, fixed position, etc.). See
-- 'Placement' for a list of available policies.
@ -118,12 +118,12 @@ simpleSmart = inBounds $ smart (0,0)
-- | Place windows at a fixed position
fixed :: (Rational, Rational) -- ^ Where windows should go.
--
-- * (0,0) -> top left of the screen
--
fixed :: (Rational, Rational) -- ^ Where windows should go.
--
-- * (0,0) -> top left of the screen
--
-- * (1,0) -> top right of the screen
--
--
-- * etc
-> Placement
fixed = Fixed
@ -136,14 +136,14 @@ underMouse :: (Rational, Rational) -- ^ Where the pointer should be relative to
underMouse = UnderMouse
-- | Apply the given placement policy, constraining the
-- | Apply the given placement policy, constraining the
-- placed windows inside the screen boundaries.
inBounds :: Placement -> Placement
inBounds :: Placement -> Placement
inBounds = Bounds (0,0,0,0)
-- | Same as 'inBounds', but allows specifying gaps along the screen's edges
withGaps :: (Dimension, Dimension, Dimension, Dimension)
withGaps :: (Dimension, Dimension, Dimension, Dimension)
-- ^ top, right, bottom and left gaps
-> Placement -> Placement
withGaps = Bounds
@ -160,7 +160,7 @@ placeFocused :: Placement -> X ()
placeFocused p = withFocused $ \window -> do
info <- gets $ screenInfo . S.current . windowset
floats <- gets $ M.keys . S.floating . windowset
r'@(Rectangle x' y' _ _) <- placeWindow p window info floats
-- use X.A.FloatKeys if the window is floating, send
@ -182,8 +182,8 @@ placeHook p = do window <- ask
floats = M.keys $ S.floating theWS
guard(window `elem` floats )
-- Look for the workspace(s) on which the window is to be
-- Look for the workspace(s) on which the window is to be
-- spawned. Each of them also needs an associated screen
-- rectangle; for hidden workspaces, we use the current
-- workspace's screen.
@ -191,7 +191,7 @@ placeHook p = do window <- ask
$ [screenInfo $ S.current theWS]
++ (map screenInfo $ S.visible theWS)
++ zip (S.hidden theWS) (repeat currentRect)
guard(not $ null infos)
let (workspace, screen) = head infos
@ -223,7 +223,7 @@ purePlaceWindow :: Placement -- ^ The placement strategy
-> (Position, Position) -- ^ The pointer's position.
-> Rectangle -- ^ The window to be placed
-> Rectangle
purePlaceWindow (Bounds (t,r,b,l) p') (Rectangle sx sy sw sh) rs p w
purePlaceWindow (Bounds (t,r,b,l) p') (Rectangle sx sy sw sh) rs p w
= let s' = (Rectangle (sx + fi l) (sy + fi t) (sw - l - r) (sh - t - b))
in checkBounds s' $ purePlaceWindow p' s' rs p w
@ -267,9 +267,9 @@ fi = fromIntegral
r2rr :: Rectangle -> Rectangle -> S.RationalRect
r2rr (Rectangle x0 y0 w0 h0) (Rectangle x y w h)
= S.RationalRect ((fi x-fi x0) % fi w0)
((fi y-fi y0) % fi h0)
(fi w % fi w0)
= S.RationalRect ((fi x-fi x0) % fi w0)
((fi y-fi y0) % fi h0)
(fi w % fi w0)
(fi h % fi h0)
@ -286,7 +286,7 @@ getWindowRectangle :: Window -> X Rectangle
getWindowRectangle window
= do d <- asks display
(_, x, y, w, h, _, _) <- io $ getGeometry d window
-- We can't use the border width returned by
-- getGeometry because it will be 0 if the
-- window isn't mapped yet.
@ -305,11 +305,11 @@ getAllRectangles = do ws <- gets windowset
return $ M.fromList $ zip allWindows allRects
organizeClients :: S.Workspace a b Window -> Window -> [Window] -> [Window]
organizeClients ws w floats
= let (floatCs, layoutCs) = partition (`elem` floats) $ filter (/= w)
organizeClients ws w floats
= let (floatCs, layoutCs) = partition (`elem` floats) $ filter (/= w)
$ stackContents $ S.stack ws
in reverse layoutCs ++ reverse floatCs
-- About the ordering: the smart algorithm will overlap windows
-- About the ordering: the smart algorithm will overlap windows
-- starting ith the head of the list. So:
-- - we put the non-floating windows first since they'll
-- probably be below the floating ones,
@ -323,18 +323,18 @@ getPointer window = do d <- asks display
-- | Return values are, in order: window's rectangle,
-- other windows' rectangles and pointer's coordinates.
getNecessaryData :: Window
getNecessaryData :: Window
-> S.Workspace WorkspaceId (Layout Window) Window
-> [Window]
-> X (Rectangle, [Rectangle], (Position, Position))
getNecessaryData window ws floats
= do r <- getWindowRectangle window
rs <- return (organizeClients ws window floats)
>>= mapM getWindowRectangle
pointer <- getPointer window
return (r, rs, pointer)
@ -343,7 +343,7 @@ getNecessaryData window ws floats
{- Smart placement algorithm -}
-- | Alternate representation for rectangles.
data SmartRectangle a = SR
data SmartRectangle a = SR
{ sr_x0, sr_y0 :: a -- ^ Top left coordinates, inclusive
, sr_x1, sr_y1 :: a -- ^ Bottom right coorsinates, exclusive
} deriving (Show, Eq)
@ -380,12 +380,12 @@ placeSmart :: (Rational, Rational) -- ^ point of the screen where windows
-> Rectangle
placeSmart (rx, ry) s@(Rectangle sx sy sw sh) rs w h
= let free = map sr2r $ findSpace (r2sr s) (map r2sr rs) (fi w) (fi h)
in position free (scale rx sx (sx + fi sw - fi w))
(scale ry sy (sy + fi sh - fi h))
in position free (scale rx sx (sx + fi sw - fi w))
(scale ry sy (sy + fi sh - fi h))
w h
-- | Second part of the algorithm:
-- Chooses the best position in which to place a window,
-- | Second part of the algorithm:
-- Chooses the best position in which to place a window,
-- according to a list of free areas and an ideal position for
-- the top-left corner.
-- We can't use semi-open surfaces for this, so we go back to
@ -395,17 +395,17 @@ position :: [Rectangle] -- ^ Free areas
-> Dimension -> Dimension -- ^ Width and height of the window
-> Rectangle
position rs x y w h = minimumBy distanceOrder $ map closest rs
where distanceOrder r1 r2
where distanceOrder r1 r2
= compare (distance (rect_x r1,rect_y r1) (x,y) :: Dimension)
(distance (rect_x r2,rect_y r2) (x,y) :: Dimension)
distance (x1,y1) (x2,y2) = truncate $ (sqrt :: Double -> Double)
$ fi $ (x1 - x2)^(2::Int)
distance (x1,y1) (x2,y2) = truncate $ (sqrt :: Double -> Double)
$ fi $ (x1 - x2)^(2::Int)
+ (y1 - y2)^(2::Int)
closest r = checkBounds r (Rectangle x y w h)
-- | First part of the algorithm:
-- Tries to find an area in which to place a new
-- Tries to find an area in which to place a new
-- rectangle so that it overlaps as little as possible with
-- other rectangles already present. The first rectangles in
-- the list will be overlapped first.
@ -425,10 +425,10 @@ findSpace total rs@(_:rs') w h
-- | Subtracts smaller rectangles from a total rectangle
-- , returning a list of remaining rectangular areas.
subtractRects :: Real a => SmartRectangle a
subtractRects :: Real a => SmartRectangle a
-> [SmartRectangle a] -> [SmartRectangle a]
subtractRects total [] = [total]
subtractRects total (r:rs)
subtractRects total (r:rs)
= do total' <- subtractRects total rs
filter (not . isEmpty)
[ total' {sr_y1 = min (sr_y1 total') (sr_y0 r)} -- Above
@ -439,7 +439,7 @@ subtractRects total (r:rs)
-- | "Nubs" a list of rectangles, dropping all those that are
-- already contained in another rectangle of the list.
-- already contained in another rectangle of the list.
cleanup :: Real a => [SmartRectangle a] -> [SmartRectangle a]
cleanup rs = foldr dropIfContained [] $ sortBy sizeOrder rs
@ -453,7 +453,7 @@ sizeOrder r1 r2 | w1 < w2 = LT
h1 = height r1
h2 = height r2
dropIfContained :: Real a => SmartRectangle a
dropIfContained :: Real a => SmartRectangle a
-> [SmartRectangle a] -> [SmartRectangle a]
dropIfContained r rs = if any (`contains` r) rs
then rs

View File

@ -34,7 +34,7 @@ import XMonad.ManageHook ((-->))
-- > import XMonad.Actions.TagWindows
-- > import Data.List
--
-- > manageHook = xPropManageHook xPropMatches
-- > manageHook = xPropManageHook xPropMatches
-- >
-- > xPropMatches :: [XPropMatch]
-- > xPropMatches = [ ([ (wM_CLASS, any ("gimp"==))], (\w -> float w >> return (W.shift "2")))
@ -71,7 +71,7 @@ xPropManageHook tms = mconcat $ map propToHook tms
where
propToHook (ms, f) = fmap and (mapM mkQuery ms) --> mkHook f
mkQuery (a, tf) = fmap tf (getQuery a)
mkHook func = ask >>= Query . lift . fmap Endo . func
mkHook func = ask >>= Query . lift . fmap Endo . func
getProp :: Display -> Window -> Atom -> X ([String])
getProp d w p = do

View File

@ -9,7 +9,7 @@
-- Stability : unstable
-- Portability : unportable
--
-- Provides layout modifier AutoMaster. It separates screen in two parts -
-- Provides layout modifier AutoMaster. It separates screen in two parts -
-- master and slave. Size of slave area automatically changes depending on
-- number of slave windows.
--
@ -49,7 +49,7 @@ data AutoMaster a = AutoMaster Int Float Float
deriving (Read,Show)
instance LayoutModifier AutoMaster Window where
modifyLayout (AutoMaster k bias _) = autoLayout k bias
modifyLayout (AutoMaster k bias _) = autoLayout k bias
pureMess = autoMess
-- | Handle Shrink/Expand and IncMasterN messages
@ -101,7 +101,7 @@ slaveRect (Rectangle sx sy sw sh) n bias = Rectangle sx (sy+mh) sw h
where mh = round $ (fromIntegral sh)*(masterHeight n bias)
h = round $ (fromIntegral sh)*(1-masterHeight n bias)
-- | Divide rectangle between windows
-- | Divide rectangle between windows
divideRow :: Rectangle -> [a] -> [(a, Rectangle)]
divideRow (Rectangle x y w h) ws = zip ws rects
where n = length ws
@ -109,7 +109,7 @@ divideRow (Rectangle x y w h) ws = zip ws rects
oneRect = Rectangle x y (fromIntegral oneW) h
rects = take n $ iterate (shiftR (fromIntegral oneW)) oneRect
-- | Shift rectangle right
-- | Shift rectangle right
shiftR :: Position -> Rectangle -> Rectangle
shiftR s (Rectangle x y w h) = Rectangle (x+s) y w h

View File

@ -9,9 +9,9 @@
-- Stability : unstable
-- Portability : unportable
--
-- Two layout modifiers. centerMaster places master window at center,
-- on top of all other windows, which are managed by base layout.
-- topRightMaster is similar, but places master window in top right corner
-- Two layout modifiers. centerMaster places master window at center,
-- on top of all other windows, which are managed by base layout.
-- topRightMaster is similar, but places master window in top right corner
-- instead of center.
--
-----------------------------------------------------------------------------
@ -30,22 +30,22 @@ import qualified XMonad.StackSet as W
-- $usage
-- This module defines two new layout modifiers: centerMaster and topRightMaster.
-- centerMaster places master window at center of screen, on top of others.
-- centerMaster places master window at center of screen, on top of others.
-- All other windows in background are managed by base layout.
-- topRightMaster is like centerMaster, but places master window in top right corner instead of center.
--
--
-- Yo can use this module by adding folowing in your @xmonad.hs@:
--
-- > import XMonad.Layout.CenteredMaster
--
--
-- Then add layouts to your layoutHook:
--
--
-- > myLayoutHook = centerMaster Grid ||| ...
-- | Function that decides where master window should be placed
type Positioner = Rectangle -> Rectangle
-- | Data type for LayoutModifier
-- | Data type for LayoutModifier
data CenteredMaster a = CenteredMaster deriving (Read,Show)
instance LayoutModifier CenteredMaster Window where
@ -56,12 +56,12 @@ data TopRightMaster a = TopRightMaster deriving (Read,Show)
instance LayoutModifier TopRightMaster Window where
modifyLayout TopRightMaster = applyPosition (topRight (3/7) (1/2))
-- | Modifier that puts master window in center, other windows in background
-- | Modifier that puts master window in center, other windows in background
-- are managed by given layout
centerMaster :: LayoutClass l a => l a -> ModifiedLayout CenteredMaster l a
centerMaster = ModifiedLayout CenteredMaster
-- | Modifier that puts master window in top right corner, other windows in background
-- | Modifier that puts master window in top right corner, other windows in background
-- are managed by given layout
topRightMaster :: LayoutClass l a => l a -> ModifiedLayout TopRightMaster l a
topRightMaster = ModifiedLayout TopRightMaster

View File

@ -65,7 +65,7 @@ mkRect (Rectangle xs ys ws _) (h,y) = Rectangle xs (ys+fromIntegral y) ws h
xn :: Int -> Rectangle -> Float -> Int -> Dimension
xn n (Rectangle _ _ _ h) q k = if q==1 then
h `div` (fromIntegral n)
else
else
round ((fromIntegral h)*q^(n-k)*(1-q)/(1-q^n))

View File

@ -7,7 +7,7 @@
-- David Roundy <droundy@darcs.net>,
-- Andrea Rossato <andrea.rossato@unibz.it>
-- License : BSD3-style (see LICENSE)
--
--
-- Maintainer : Andrea Rossato <andrea.rossato@unibz.it>
-- Stability : unstable
-- Portability : unportable
@ -29,7 +29,7 @@ module XMonad.Layout.DragPane (
import XMonad
import Data.Unique
import qualified XMonad.StackSet as W
import qualified XMonad.StackSet as W
import XMonad.Util.Invisible
import XMonad.Util.XUtils
@ -56,8 +56,8 @@ handleColor = "#000000"
dragPane :: DragType -> Double -> Double -> DragPane a
dragPane t x y = DragPane (I Nothing) t x y
data DragPane a =
DragPane (Invisible Maybe (Window,Rectangle,Int)) DragType Double Double
data DragPane a =
DragPane (Invisible Maybe (Window,Rectangle,Int)) DragType Double Double
deriving ( Show, Read )
data DragType = Horizontal | Vertical deriving ( Show, Read )
@ -86,7 +86,7 @@ handleMess d@(DragPane mb@(I (Just (win,_,ident))) ty delta split) x
handleMess _ _ = return Nothing
handleEvent :: DragPane a -> Event -> X ()
handleEvent (DragPane (I (Just (win,r,ident))) ty _ _)
handleEvent (DragPane (I (Just (win,r,ident))) ty _ _)
(ButtonEvent {ev_window = thisw, ev_subwindow = thisbw, ev_event_type = t })
| t == buttonPress && thisw == win || thisbw == win = do
mouseDrag (\ex ey -> do
@ -114,12 +114,12 @@ doLay mirror (DragPane mw ty delta split) r s = do
[] -> case W.down s of
(next:_) -> [(W.focus s,left),(next,right)]
[] -> [(W.focus s, r)]
if length wrs > 1
if length wrs > 1
then case mw of
I (Just (w,_,ident)) -> do
I (Just (w,_,ident)) -> do
w' <- deleteWindow w >> newDragWin handr
return (wrs, Just $ DragPane (I $ Just (w',r',ident)) ty delta split)
I Nothing -> do
I Nothing -> do
w <- newDragWin handr
i <- io $ newUnique
return (wrs, Just $ DragPane (I $ Just (w,r',hashUnique i)) ty delta split)

View File

@ -51,7 +51,7 @@ import Control.Monad
-- > ( (layoutN 1 (absBox (-512-200) 0 512 0) (Just $ relBox 0 0 1 1) $ simpleTabbed)
-- > $ (layoutN 1 (absBox (-200) 0 0 0) Nothing $ simpleTabbed)
-- > $ (layoutAll (absBox 0 0 (-512-200) 0) $ simpleTabbed)
-- > ) ||| Full ||| etc...
-- > ) ||| Full ||| etc...
-- > main = xmonad defaultConfig { layoutHook = myLayouts }
--
-- This will produce a layout similar to DragPane, but with the possibility to have multiple windows in the left half

View File

@ -92,7 +92,7 @@ data LayoutHints a = LayoutHints (Double, Double)
instance LayoutModifier LayoutHints Window where
modifierDescription _ = "Hinted"
redoLayout _ _ Nothing xs = return (xs, Nothing)
redoLayout (LayoutHints al) _ (Just s) xs
redoLayout (LayoutHints al) _ (Just s) xs
= do xs' <- mapM (\x@(_, r) -> second (placeRectangle al r) <$> applyHint x) xs
return (xs', Nothing)
where

View File

@ -47,14 +47,14 @@ import Control.Monad
-- and 'rect' should be set here. Also consider setting 'persistent' to True.
--
-- Minimal example:
--
--
-- > myMonitor = monitor
-- > { prop = ClassName "SomeClass"
-- > , rect = Rectangle 0 0 40 20 -- rectangle 40x20 in upper left corner
-- > }
-- > }
--
-- More interesting example:
--
--
-- > clock = monitor {
-- > -- Cairo-clock creates 2 windows with the same classname, thus also using title
-- > prop = ClassName "Cairo-clock" `And` Title "MacSlow's Cairo-Clock"
@ -71,19 +71,19 @@ import Control.Monad
-- > }
--
-- Add ManageHook to de-manage monitor windows and apply opacity settings.
--
--
-- > manageHook = myManageHook <+> manageMonitor clock
--
--
-- Apply layout modifier.
--
--
-- > myLayouts = ModifiedLayout clock $ tall ||| Full ||| ...
--
--
-- After that, if there exists a window with specified properties, it will be
-- displayed on top of all /tiled/ (not floated) windows on specified
-- position.
--
-- It's also useful to add some keybinding to toggle monitor visibility:
--
--
-- > , ((mod1Mask, xK_u ), broadcastMessage ToggleMonitor >> refresh)
--
-- Screenshot: <http://www.haskell.org/haskellwiki/Image:Xmonad-clock.png>
@ -145,7 +145,7 @@ instance LayoutModifier Monitor Window where
if name mon == n then Just $ mon { visible = False } else Nothing
| Just Hide <- fromMessage mess = do unless (persistent mon) $ withMonitor (prop mon) () hide; return Nothing
| otherwise = return Nothing
-- | ManageHook which demanages monitor window and applies opacity settings.
manageMonitor :: Monitor a -> ManageHook
manageMonitor mon = propertyToQuery (prop mon) --> do

View File

@ -5,12 +5,12 @@
-- Module : XMonad.Layout.MosaicAlt
-- Copyright : (c) 2007 James Webb
-- License : BSD-style (see xmonad/LICENSE)
--
--
-- Maintainer : xmonad#jwebb,sygneca,com
-- Stability : unstable
-- Portability : unportable
--
-- A layout which gives each window a specified amount of screen space
-- A layout which gives each window a specified amount of screen space
-- relative to the others. Compared to the 'Mosaic' layout, this one
-- divides the space in a more balanced way.
--

View File

@ -54,7 +54,7 @@ oneBigMessage (OneBig cx cy) m = fmap resize (fromMessage m)
-- | Main layout function
oneBigLayout :: OneBig a -> Rectangle -> W.Stack a -> [(a, Rectangle)]
oneBigLayout (OneBig cx cy) rect stack = [(master,masterRect)]
oneBigLayout (OneBig cx cy) rect stack = [(master,masterRect)]
++ (divideBottom bottomRect bottomWs)
++ (divideRight rightRect rightWs)
where ws = W.integrate stack
@ -106,7 +106,7 @@ cright cx cy (Rectangle sx sy sw sh) = Rectangle x sy w h
x = round (fromIntegral sw*cx+(fromIntegral sx))
h = round (fromIntegral sh*cy)
-- | Divide bottom rectangle between windows
-- | Divide bottom rectangle between windows
divideBottom :: Rectangle -> [a] -> [(a, Rectangle)]
divideBottom (Rectangle x y w h) ws = zip ws rects
where n = length ws
@ -122,7 +122,7 @@ divideRight (Rectangle x y w h) ws = if (n==0) then [] else zip ws rects
oneRect = Rectangle x y w (fromIntegral oneH)
rects = take n $ iterate (shiftB (fromIntegral oneH)) oneRect
-- | Shift rectangle right
-- | Shift rectangle right
shiftR :: Position -> Rectangle -> Rectangle
shiftR s (Rectangle x y w h) = Rectangle (x+s) y w h

View File

@ -27,7 +27,7 @@ import Data.Ratio
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.Roledex
-- > import XMonad.Layout.Roledex
--
-- Then edit your @layoutHook@ by adding the Roledex layout:
--
@ -51,8 +51,8 @@ roledexLayout sc ws = return ([(W.focus ws, mainPane)] ++
where ups = W.up ws
dns = W.down ws
c = length ups + length dns
rect = fst $ splitHorizontallyBy (2%3 :: Ratio Int) $ fst (splitVerticallyBy (2%3 :: Ratio Int) sc)
gw = div' (w - rw) (fromIntegral c)
rect = fst $ splitHorizontallyBy (2%3 :: Ratio Int) $ fst (splitVerticallyBy (2%3 :: Ratio Int) sc)
gw = div' (w - rw) (fromIntegral c)
where
(Rectangle _ _ w _) = sc
(Rectangle _ _ rw _) = rect
@ -60,12 +60,12 @@ roledexLayout sc ws = return ([(W.focus ws, mainPane)] ++
where
(Rectangle _ _ _ h) = sc
(Rectangle _ _ _ rh) = rect
mainPane = mrect (gw * fromIntegral c) (gh * fromIntegral c) rect
mainPane = mrect (gw * fromIntegral c) (gh * fromIntegral c) rect
mrect mx my (Rectangle x y w h) = Rectangle (x + (fromIntegral mx)) (y + (fromIntegral my)) w h
tops = map f $ cd c (length dns)
bottoms = map f $ [0..(length dns)]
f n = mrect (gw * (fromIntegral n)) (gh * (fromIntegral n)) rect
cd n m = if n > m
cd n m = if n > m
then (n - 1) : (cd (n-1) m)
else []

View File

@ -33,7 +33,7 @@ import XMonad.Layout.LayoutModifier
--
-- and modifying your layoutHook as follows (for example):
--
-- > layoutHook = spacing 2 $ Tall 1 (3/100) (1/2)
-- > layoutHook = spacing 2 $ Tall 1 (3/100) (1/2)
-- > -- put a 2px space around every window
--

View File

@ -54,7 +54,7 @@ import XMonad.Layout.Simplest ( Simplest(Simplest) )
-- > main = xmonad defaultConfig { layoutHook = myLayouts }
--
-- This layout has hardcoded behaviour for mouse clicks on tab decorations:
-- Left click on the tab switches focus to that window.
-- Left click on the tab switches focus to that window.
-- Middle click on the tab closes the window.
--
-- The default Tabbar behaviour is to hide it when only one window is open
@ -99,21 +99,21 @@ simpleTabbedBottomAlways = tabbedBottomAlways shrinkText defaultTheme
-- | A layout decorated with tabs and the possibility to set a custom
-- shrinker and theme.
tabbed :: (Eq a, Shrinker s) => s -> Theme
tabbed :: (Eq a, Shrinker s) => s -> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbed s c = addTabs s c Simplest
tabbedAlways :: (Eq a, Shrinker s) => s -> Theme
tabbedAlways :: (Eq a, Shrinker s) => s -> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedAlways s c = addTabsAlways s c Simplest
-- | A layout decorated with tabs at the bottom and the possibility to set a custom
-- shrinker and theme.
tabbedBottom :: (Eq a, Shrinker s) => s -> Theme
tabbedBottom :: (Eq a, Shrinker s) => s -> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedBottom s c = addTabsBottom s c Simplest
tabbedBottomAlways :: (Eq a, Shrinker s) => s -> Theme
tabbedBottomAlways :: (Eq a, Shrinker s) => s -> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedBottomAlways s c = addTabsBottomAlways s c Simplest
@ -160,13 +160,13 @@ instance Eq a => DecorationStyle TabbedDecoration a where
, ev_button = eb }
| et == buttonPress
, Just ((w,_),_) <-findWindowByDecoration ew ds =
if eb == button2
if eb == button2
then killWindow w
else focus w
decorationMouseFocusHook _ _ _ = return ()
decorationMouseDragHook _ _ _ = return ()
pureDecoration (Tabbed lc sh) _ ht _ s wrs (w,r@(Rectangle x y wh hh))
pureDecoration (Tabbed lc sh) _ ht _ s wrs (w,r@(Rectangle x y wh hh))
= if ((sh == Always && numWindows > 0) || numWindows > 1)
then Just $ case lc of
Top -> upperTab
@ -179,7 +179,7 @@ instance Eq a => DecorationStyle TabbedDecoration a where
upperTab = Rectangle nx y wid (fi ht)
lowerTab = Rectangle nx (y+fi(hh-ht)) wid (fi ht)
numWindows = length ws
shrink (Tabbed loc _ ) (Rectangle _ _ _ dh) (Rectangle x y w h)
shrink (Tabbed loc _ ) (Rectangle _ _ _ dh) (Rectangle x y w h)
= case loc of
Top -> Rectangle x (y + fi dh) w (h - dh)
Bottom -> Rectangle x y w (h - dh)

View File

@ -5,7 +5,7 @@
-- Module : XMonad.Layout.TwoPane
-- Copyright : (c) Spencer Janssen <spencerjanssen@gmail.com>
-- License : BSD3-style (see LICENSE)
--
--
-- Maintainer : Spencer Janssen <spencerjanssen@gmail.com>
-- Stability : unstable
-- Portability : unportable
@ -39,8 +39,8 @@ import XMonad.StackSet ( focus, up, down)
--
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
data TwoPane a =
TwoPane Rational Rational
data TwoPane a =
TwoPane Rational Rational
deriving ( Show, Read )
instance LayoutClass TwoPane a where
@ -53,7 +53,7 @@ instance LayoutClass TwoPane a where
[] -> [(focus st, rect)]
where (left, right) = splitHorizontallyBy split rect
handleMessage (TwoPane delta split) x =
handleMessage (TwoPane delta split) x =
return $ case fromMessage x of
Just Shrink -> Just (TwoPane delta (split - delta))
Just Expand -> Just (TwoPane delta (split + delta))

View File

@ -719,7 +719,7 @@ writeHistory :: History -> IO ()
writeHistory hist = do
path <- getHistoryFile
catch (writeFile path (show hist)) $ const $ hPutStrLn stderr "error in writing"
setFileMode path mode
setFileMode path mode
where mode = ownerReadMode .|. ownerWriteMode
-- $xutils

View File

@ -8,7 +8,7 @@
-- Stability : unstable
-- Portability : unportable
--
-- A module for launch applicationes that receive parameters in the command
-- A module for launch applicationes that receive parameters in the command
-- line. The launcher call a prompt to get the parameters.
--
-----------------------------------------------------------------------------
@ -31,7 +31,7 @@ import XMonad.Prompt.Shell (getShellCompl)
you want to open a image in gimp program, you can open gimp and then use
the File Menu to open the image or you can use this module to select
the image in the command line.
We use Prompt to get the user command line. This also allow to autoexpand
the names of the files when we are writing the command line.
-}

View File

@ -5,7 +5,7 @@
-- Module : XMonad.Util.Invisible
-- Copyright : (c) 2007 Andrea Rossato, David Roundy
-- License : BSD-style (see xmonad/LICENSE)
--
--
-- Maintainer : andrea.rossato@unibz.it, droundy@darcs.net
-- Stability : unstable
-- Portability : unportable
@ -14,7 +14,7 @@
--
-----------------------------------------------------------------------------
module XMonad.Util.Invisible (
module XMonad.Util.Invisible (
-- * Usage:
-- $usage
Invisible (..)

View File

@ -38,7 +38,7 @@ data Property = Title String
| ClassName String
| Resource String
| Role String -- ^ WM_WINDOW_ROLE property
| And Property Property
| And Property Property
| Or Property Property
| Not Property
| Const Bool