aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Layout')
-rw-r--r--XMonad/Layout/AutoMaster.hs8
-rw-r--r--XMonad/Layout/CenteredMaster.hs20
-rw-r--r--XMonad/Layout/Column.hs2
-rw-r--r--XMonad/Layout/DragPane.hs16
-rw-r--r--XMonad/Layout/LayoutBuilder.hs2
-rw-r--r--XMonad/Layout/LayoutHints.hs2
-rw-r--r--XMonad/Layout/Monitor.hs18
-rw-r--r--XMonad/Layout/MosaicAlt.hs4
-rw-r--r--XMonad/Layout/OneBig.hs6
-rw-r--r--XMonad/Layout/Roledex.hs10
-rw-r--r--XMonad/Layout/Spacing.hs2
-rw-r--r--XMonad/Layout/Tabbed.hs16
-rw-r--r--XMonad/Layout/TwoPane.hs8
13 files changed, 57 insertions, 57 deletions
diff --git a/XMonad/Layout/AutoMaster.hs b/XMonad/Layout/AutoMaster.hs
index 5e74331..7a912c8 100644
--- a/XMonad/Layout/AutoMaster.hs
+++ b/XMonad/Layout/AutoMaster.hs
@@ -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
diff --git a/XMonad/Layout/CenteredMaster.hs b/XMonad/Layout/CenteredMaster.hs
index 75462c7..41a3dc0 100644
--- a/XMonad/Layout/CenteredMaster.hs
+++ b/XMonad/Layout/CenteredMaster.hs
@@ -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
diff --git a/XMonad/Layout/Column.hs b/XMonad/Layout/Column.hs
index 279525e..a77b3d8 100644
--- a/XMonad/Layout/Column.hs
+++ b/XMonad/Layout/Column.hs
@@ -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))
diff --git a/XMonad/Layout/DragPane.hs b/XMonad/Layout/DragPane.hs
index 8f43d82..f78ca98 100644
--- a/XMonad/Layout/DragPane.hs
+++ b/XMonad/Layout/DragPane.hs
@@ -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)
diff --git a/XMonad/Layout/LayoutBuilder.hs b/XMonad/Layout/LayoutBuilder.hs
index c2e1d8a..0b16a93 100644
--- a/XMonad/Layout/LayoutBuilder.hs
+++ b/XMonad/Layout/LayoutBuilder.hs
@@ -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
diff --git a/XMonad/Layout/LayoutHints.hs b/XMonad/Layout/LayoutHints.hs
index 5925972..3b324fd 100644
--- a/XMonad/Layout/LayoutHints.hs
+++ b/XMonad/Layout/LayoutHints.hs
@@ -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
diff --git a/XMonad/Layout/Monitor.hs b/XMonad/Layout/Monitor.hs
index f5d7de9..5d13830 100644
--- a/XMonad/Layout/Monitor.hs
+++ b/XMonad/Layout/Monitor.hs
@@ -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
diff --git a/XMonad/Layout/MosaicAlt.hs b/XMonad/Layout/MosaicAlt.hs
index 8bae199..d06d7fd 100644
--- a/XMonad/Layout/MosaicAlt.hs
+++ b/XMonad/Layout/MosaicAlt.hs
@@ -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.
--
diff --git a/XMonad/Layout/OneBig.hs b/XMonad/Layout/OneBig.hs
index 73f1adb..be38e13 100644
--- a/XMonad/Layout/OneBig.hs
+++ b/XMonad/Layout/OneBig.hs
@@ -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
diff --git a/XMonad/Layout/Roledex.hs b/XMonad/Layout/Roledex.hs
index e5b1101..1d4343e 100644
--- a/XMonad/Layout/Roledex.hs
+++ b/XMonad/Layout/Roledex.hs
@@ -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 []
diff --git a/XMonad/Layout/Spacing.hs b/XMonad/Layout/Spacing.hs
index 1ff2202..1904638 100644
--- a/XMonad/Layout/Spacing.hs
+++ b/XMonad/Layout/Spacing.hs
@@ -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
--
diff --git a/XMonad/Layout/Tabbed.hs b/XMonad/Layout/Tabbed.hs
index 41aff9c..fbd8600 100644
--- a/XMonad/Layout/Tabbed.hs
+++ b/XMonad/Layout/Tabbed.hs
@@ -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)
diff --git a/XMonad/Layout/TwoPane.hs b/XMonad/Layout/TwoPane.hs
index 941209a..ef43ae1 100644
--- a/XMonad/Layout/TwoPane.hs
+++ b/XMonad/Layout/TwoPane.hs
@@ -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))