aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--XMonad/Layout/Accordion.hs (renamed from Accordion.hs)8
-rw-r--r--XMonad/Layout/Circle.hs (renamed from Circle.hs)8
-rw-r--r--XMonad/Layout/Combo.hs (renamed from Combo.hs)12
-rw-r--r--XMonad/Layout/Dishes.hs (renamed from Dishes.hs)8
-rw-r--r--XMonad/Layout/DragPane.hs (renamed from DragPane.hs)10
-rw-r--r--XMonad/Layout/Grid.hs (renamed from Grid.hs)8
-rw-r--r--XMonad/Layout/HintedTile.hs (renamed from HintedTile.hs)12
-rw-r--r--XMonad/Layout/LayoutCombinators.hs (renamed from LayoutCombinators.hs)8
-rw-r--r--XMonad/Layout/LayoutHints.hs (renamed from LayoutHints.hs)10
-rw-r--r--XMonad/Layout/LayoutModifier.hs (renamed from LayoutModifier.hs)4
-rw-r--r--XMonad/Layout/LayoutScreens.hs (renamed from LayoutScreens.hs)10
-rw-r--r--XMonad/Layout/MagicFocus.hs (renamed from MagicFocus.hs)8
-rw-r--r--XMonad/Layout/Magnifier.hs (renamed from Magnifier.hs)10
-rw-r--r--XMonad/Layout/Maximize.hs (renamed from Maximize.hs)10
-rw-r--r--XMonad/Layout/Mosaic.hs (renamed from Mosaic.hs)12
-rw-r--r--XMonad/Layout/MosaicAlt.hs (renamed from MosaicAlt.hs)8
-rw-r--r--XMonad/Layout/NoBorders.hs (renamed from NoBorders.hs)10
-rw-r--r--XMonad/Layout/ResizableTile.hs (renamed from ResizableTile.hs)6
-rw-r--r--XMonad/Layout/Roledex.hs (renamed from Roledex.hs)8
-rw-r--r--XMonad/Layout/Spiral.hs (renamed from Spiral.hs)8
-rw-r--r--XMonad/Layout/Square.hs (renamed from Square.hs)12
-rw-r--r--XMonad/Layout/SwitchTrans.hs (renamed from SwitchTrans.hs)6
-rw-r--r--XMonad/Layout/Tabbed.hs (renamed from Tabbed.hs)14
-rw-r--r--XMonad/Layout/ThreeColumns.hs (renamed from ThreeColumns.hs)8
-rw-r--r--XMonad/Layout/TilePrime.hs (renamed from TilePrime.hs)6
-rw-r--r--XMonad/Layout/ToggleLayouts.hs (renamed from ToggleLayouts.hs)6
-rw-r--r--XMonad/Layout/TwoPane.hs (renamed from TwoPane.hs)8
-rw-r--r--XMonad/Layout/WindowNavigation.hs (renamed from WindowNavigation.hs)14
-rw-r--r--XMonad/Layout/WorkspaceDir.hs (renamed from WorkspaceDir.hs)16
29 files changed, 134 insertions, 134 deletions
diff --git a/Accordion.hs b/XMonad/Layout/Accordion.hs
index f5c24d8..f844c22 100644
--- a/Accordion.hs
+++ b/XMonad/Layout/Accordion.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.Accordion
+-- Module : XMonad.Layout.Accordion
-- Copyright : (c) glasser@mit.edu
-- License : BSD
--
@@ -14,7 +14,7 @@
-- of the screen.
-----------------------------------------------------------------------------
-module XMonadContrib.Accordion (
+module XMonad.Layout.Accordion (
-- * Usage
-- $usage
Accordion(Accordion)) where
@@ -26,10 +26,10 @@ import Graphics.X11.Xlib
import Data.Ratio
-- $usage
--- > import XMonadContrib.Accordion
+-- > import XMonad.Layout.Accordion
-- > layouts = [ Layout Accordion ]
--- %import XMonadContrib.Accordion
+-- %import XMonad.Layout.Accordion
-- %layout , Layout Accordion
data Accordion a = Accordion deriving ( Read, Show )
diff --git a/Circle.hs b/XMonad/Layout/Circle.hs
index d0f343b..2d85dfc 100644
--- a/Circle.hs
+++ b/XMonad/Layout/Circle.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.Circle
+-- Module : XMonad.Layout.Circle
-- Copyright : (c) Peter De Wachter
-- License : BSD-style (see LICENSE)
--
@@ -14,7 +14,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.Circle (
+module XMonad.Layout.Circle (
-- * Usage
-- $usage
Circle (..)
@@ -28,10 +28,10 @@ import XMonad.StackSet (integrate, peek)
-- $usage
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.Circle
+-- > import XMonad.Layout.Circle
-- > layouts = [ Layout Circle ]
--- %import XMonadContrib.Circle
+-- %import XMonad.Layout.Circle
data Circle a = Circle deriving ( Read, Show )
diff --git a/Combo.hs b/XMonad/Layout/Combo.hs
index 15c7155..a89f281 100644
--- a/Combo.hs
+++ b/XMonad/Layout/Combo.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.Combo
+-- Module : XMonad.Layout.Combo
-- Copyright : (c) David Roundy <droundy@darcs.net>
-- License : BSD-style (see LICENSE)
--
@@ -14,7 +14,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.Combo (
+module XMonad.Layout.Combo (
-- * Usage
-- $usage
combineTwo,
@@ -26,15 +26,15 @@ import Data.List ( delete, intersect, (\\) )
import Data.Maybe ( isJust )
import XMonad
import XMonad.StackSet ( integrate, Stack(..) )
-import XMonadContrib.Invisible
-import XMonadContrib.WindowNavigation ( MoveWindowToWindow(..) )
+import XMonad.Util.Invisible
+import XMonad.Layout.WindowNavigation ( MoveWindowToWindow(..) )
import qualified XMonad.StackSet as W ( differentiate )
-- $usage
--
-- To use this layout write, in your Config.hs:
--
--- > import XMonadContrib.Combo
+-- > import XMonad.Layout.Combo
--
-- and add something like
--
@@ -62,7 +62,7 @@ import qualified XMonad.StackSet as W ( differentiate )
-- don't like this, lobby for hierarchical stacks in core xmonad or go
-- reimelement the core of xmonad yourself.
--- %import XMonadContrib.Combo
+-- %import XMonad.Layout.Combo
-- %layout , combineTwo (TwoPane 0.03 0.5) (tabbed shrinkText defaultTConf) (tabbed shrinkText defaultTConf)
data CombineTwo l l1 l2 a = C2 [a] [a] (l ()) (l1 a) (l2 a)
diff --git a/Dishes.hs b/XMonad/Layout/Dishes.hs
index a1eae21..ecc27db 100644
--- a/Dishes.hs
+++ b/XMonad/Layout/Dishes.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.Dishes
+-- Module : XMonad.Layout.Dishes
-- Copyright : (c) Jeremy Apthorp
-- License : BSD-style (see LICENSE)
--
@@ -15,7 +15,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.Dishes (
+module XMonad.Layout.Dishes (
-- * Usage
-- $usage
Dishes (..)
@@ -31,13 +31,13 @@ import Graphics.X11.Xlib
-- $usage
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.Dishes
+-- > import XMonad.Layout.Dishes
--
-- and add the following line to your 'layouts'
--
-- > , Layout $ Dishes 2 (1%6)
--- %import XMonadContrib.Dishes
+-- %import XMonad.Layout.Dishes
-- %layout , Layout $ Dishes 2 (1%6)
data Dishes a = Dishes Int Rational deriving (Show, Read)
diff --git a/DragPane.hs b/XMonad/Layout/DragPane.hs
index 0ae9761..8428d2b 100644
--- a/DragPane.hs
+++ b/XMonad/Layout/DragPane.hs
@@ -3,7 +3,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.DragPane
+-- Module : XMonad.Layout.DragPane
-- Copyright : (c) Spencer Janssen <sjanssen@cse.unl.edu>
-- David Roundy <droundy@darcs.net>,
-- Andrea Rossato <andrea.rossato@unibz.it>
@@ -21,7 +21,7 @@
-----------------------------------------------------------------------------
-module XMonadContrib.DragPane (
+module XMonad.Layout.DragPane (
-- * Usage
-- $usage
dragPane
@@ -37,14 +37,14 @@ import Data.Unique
import XMonad.Layouts
import XMonad.Operations
import qualified XMonad.StackSet as W
-import XMonadContrib.Invisible
-import XMonadContrib.XUtils
+import XMonad.Util.Invisible
+import XMonad.Util.XUtils
-- $usage
--
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.DragPane
+-- > import XMonad.Layout.DragPane
--
-- and add, to the list of layouts:
--
diff --git a/Grid.hs b/XMonad/Layout/Grid.hs
index c18f997..b10a8ac 100644
--- a/Grid.hs
+++ b/XMonad/Layout/Grid.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.Grid
+-- Module : XMonad.Layout.Grid
-- Copyright : (c) Lukas Mai
-- License : BSD-style (see LICENSE)
--
@@ -14,7 +14,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.Grid (
+module XMonad.Layout.Grid (
-- * Usage
-- $usage
Grid(..)
@@ -27,13 +27,13 @@ import Graphics.X11.Xlib.Types
-- $usage
-- Put the following in your Config.hs file:
--
--- > import XMonadContrib.Grid
+-- > import XMonad.Layout.Grid
-- > ...
-- > layouts = [ ...
-- > , Layout Grid
-- > ]
--- %import XMonadContrib.Grid
+-- %import XMonad.Layout.Grid
-- %layout , Layout Grid
data Grid a = Grid deriving (Read, Show)
diff --git a/HintedTile.hs b/XMonad/Layout/HintedTile.hs
index c641896..2ec9d3c 100644
--- a/HintedTile.hs
+++ b/XMonad/Layout/HintedTile.hs
@@ -1,6 +1,6 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.HintedTile
+-- Module : XMonad.Layout.HintedTile
-- Copyright : (c) Peter De Wachter <pdewacht@gmail.com>
-- License : BSD3-style (see LICENSE)
--
@@ -13,7 +13,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.HintedTile (
+module XMonad.Layout.HintedTile (
-- * Usage
-- $usage
tall, wide) where
@@ -29,13 +29,13 @@ import Control.Monad
-- $usage
-- You can use this module with the following in your Config.hs file:
--
--- > import qualified XMonadContrib.HintedTile
+-- > import qualified XMonad.Layout.HintedTile
--
--- > layouts = [ XMonadContrib.HintedTile.tall nmaster delta ratio, ... ]
+-- > layouts = [ XMonad.Layout.HintedTile.tall nmaster delta ratio, ... ]
--- %import qualified XMonadContrib.HintedTile
+-- %import qualified XMonad.Layout.HintedTile
--
--- %layout , XMonadContrib.HintedTile.tall nmaster delta ratio
+-- %layout , XMonad.Layout.HintedTile.tall nmaster delta ratio
-- this sucks
addBorder, substractBorder :: (Dimension, Dimension) -> (Dimension, Dimension)
diff --git a/LayoutCombinators.hs b/XMonad/Layout/LayoutCombinators.hs
index a368481..4b2aa09 100644
--- a/LayoutCombinators.hs
+++ b/XMonad/Layout/LayoutCombinators.hs
@@ -3,7 +3,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.LayoutCombinators
+-- Module : XMonad.Layout.LayoutCombinators
-- Copyright : (c) David Roundy <droundy@darcs.net>
-- License : BSD
--
@@ -14,7 +14,7 @@
-- A module for combining Layouts
-----------------------------------------------------------------------------
-module XMonadContrib.LayoutCombinators (
+module XMonad.Layout.LayoutCombinators (
-- * Usage
-- $usage
(<|>), (</>), (<||>), (<//>), (|||), JumpToLayout(JumpToLayout)
@@ -24,8 +24,8 @@ import Data.Maybe ( isJust )
import XMonad
import Layouts ( Tall(..), Mirror(..), ChangeLayout(NextLayout) )
-import XMonadContrib.Combo
-import XMonadContrib.DragPane
+import XMonad.Layout.Combo
+import XMonad.Layout.DragPane
-- $usage
-- Use LayoutCombinators to easily combine Layouts.
diff --git a/LayoutHints.hs b/XMonad/Layout/LayoutHints.hs
index 8f6f110..1268b3f 100644
--- a/LayoutHints.hs
+++ b/XMonad/Layout/LayoutHints.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.LayoutHints
+-- Module : XMonad.Layout.LayoutHints
-- Copyright : (c) David Roundy <droundy@darcs.net>
-- License : BSD
--
@@ -13,7 +13,7 @@
-- Make layouts respect size hints.
-----------------------------------------------------------------------------
-module XMonadContrib.LayoutHints (
+module XMonad.Layout.LayoutHints (
-- * usage
-- $usage
layoutHints,
@@ -24,13 +24,13 @@ import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras ( getWMNormalHints )
import {-#SOURCE#-} Config (borderWidth)
import XMonad hiding ( trace )
-import XMonadContrib.LayoutModifier
+import XMonad.Layout.LayoutModifier
-- $usage
--- > import XMonadContrib.LayoutHints
+-- > import XMonad.Layout.LayoutHints
-- > layouts = [ layoutHints tiled , layoutHints $ Mirror tiled ]
--- %import XMonadContrib.LayoutHints
+-- %import XMonad.Layout.LayoutHints
-- %layout , layoutHints $ tiled
-- %layout , layoutHints $ Mirror tiled
diff --git a/LayoutModifier.hs b/XMonad/Layout/LayoutModifier.hs
index 16bdbcb..7d8c615 100644
--- a/LayoutModifier.hs
+++ b/XMonad/Layout/LayoutModifier.hs
@@ -3,7 +3,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.LayoutModifier
+-- Module : XMonad.Layout.LayoutModifier
-- Copyright : (c) David Roundy <droundy@darcs.net>
-- License : BSD
--
@@ -14,7 +14,7 @@
-- A module for writing easy Layouts
-----------------------------------------------------------------------------
-module XMonadContrib.LayoutModifier (
+module XMonad.Layout.LayoutModifier (
-- * Usage
-- $usage
LayoutModifier(..), ModifiedLayout(..)
diff --git a/LayoutScreens.hs b/XMonad/Layout/LayoutScreens.hs
index 10e1fc9..7277681 100644
--- a/LayoutScreens.hs
+++ b/XMonad/Layout/LayoutScreens.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.LayoutScreens
+-- Module : XMonad.Layout.LayoutScreens
-- Copyright : (c) David Roundy <droundy@darcs.net>
-- License : BSD3-style (see LICENSE)
--
@@ -12,7 +12,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.LayoutScreens (
+module XMonad.Layout.LayoutScreens (
-- * Usage
-- $usage
layoutScreens, fixedLayout
@@ -37,7 +37,7 @@ import Graphics.X11.Xlib.Extras
--
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.LayoutScreens
+-- > import XMonad.Layout.LayoutScreens
--
-- > , ((modMask .|. shiftMask, xK_space), layoutScreens 2 (TwoPane 0.5 0.5))
-- > , ((controlMask .|. modMask .|. shiftMask, xK_space), rescreen)
@@ -46,13 +46,13 @@ import Graphics.X11.Xlib.Extras
-- work properly (e.g. a VNC X server in my case) and you want to be able
-- to resize your screen (e.g. to match the size of a remote VNC client):
--
--- > import XMonadContrib.LayoutScreens
+-- > import XMonad.Layout.LayoutScreens
--
-- > , ((modMask .|. shiftMask, xK_space),
-- > layoutScreens 1 (fixedLayout $ Rectangle 0 0 1024 768))
-- > , ((controlMask .|. modMask .|. shiftMask, xK_space), rescreen)
--- %import XMonadContrib.LayoutScreens
+-- %import XMonad.Layout.LayoutScreens
-- %keybind , ((modMask .|. shiftMask, xK_space), layoutScreens 2 (twoPane 0.5 0.5))
-- %keybind , ((controlMask .|. modMask .|. shiftMask, xK_space), rescreen)
diff --git a/MagicFocus.hs b/XMonad/Layout/MagicFocus.hs
index 91f38ee..57e5b7a 100644
--- a/MagicFocus.hs
+++ b/XMonad/Layout/MagicFocus.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.MagicFocus
+-- Module : XMonad.Layout.MagicFocus
-- Copyright : (c) Peter De Wachter <pdewacht@gmail.com>
-- License : BSD
--
@@ -13,7 +13,7 @@
-- Automagically put the focused window in the master area.
-----------------------------------------------------------------------------
-module XMonadContrib.MagicFocus
+module XMonad.Layout.MagicFocus
(-- * Usage
-- $usage
MagicFocus(MagicFocus)
@@ -24,10 +24,10 @@ import XMonad
import XMonad.StackSet
-- $usage
--- > import XMonadContrib.MagicFocus
+-- > import XMonad.Layout.MagicFocus
-- > layouts = [ Layout $ MagicFocus tiled , Layout $ MagicFocus $ Mirror tiled ]
--- %import XMonadContrib.MagicFocus
+-- %import XMonad.Layout.MagicFocus
-- %layout , Layout $ MagicFocus tiled
-- %layout , Layout $ MagicFocus $ Mirror tiled
diff --git a/Magnifier.hs b/XMonad/Layout/Magnifier.hs
index 3997d5d..bcff71d 100644
--- a/Magnifier.hs
+++ b/XMonad/Layout/Magnifier.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.Magnifier
+-- Module : XMonad.Layout.Magnifier
-- Copyright : (c) Peter De Wachter 2007
-- License : BSD-style (see xmonad/LICENSE)
--
@@ -17,7 +17,7 @@
-----------------------------------------------------------------------------
-module XMonadContrib.Magnifier (
+module XMonad.Layout.Magnifier (
-- * Usage
-- $usage
magnifier, magnifier') where
@@ -25,13 +25,13 @@ module XMonadContrib.Magnifier (
import Graphics.X11.Xlib (Window, Rectangle(..))
import XMonad
import XMonad.StackSet
-import XMonadContrib.LayoutHelpers
+import XMonad.Layout.LayoutHelpers
-- $usage
--- > import XMonadContrib.Magnifier
+-- > import XMonad.Layout.Magnifier
-- > layouts = [ magnifier tiled , magnifier $ mirror tiled ]
--- %import XMonadContrib.Magnifier
+-- %import XMonad.Layout.Magnifier
-- %layout , magnifier tiled
-- %layout , magnifier $ mirror tiled
diff --git a/Maximize.hs b/XMonad/Layout/Maximize.hs
index 2138917..cf1e938 100644
--- a/Maximize.hs
+++ b/XMonad/Layout/Maximize.hs
@@ -3,7 +3,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.Maximize
+-- Module : XMonad.Layout.Maximize
-- Copyright : (c) 2007 James Webb
-- License : BSD3-style (see LICENSE)
--
@@ -16,7 +16,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.Maximize (
+module XMonad.Layout.Maximize (
-- * Usage
-- $usage
maximize,
@@ -25,13 +25,13 @@ module XMonadContrib.Maximize (
import Graphics.X11.Xlib
import XMonad
-import XMonadContrib.LayoutModifier
+import XMonad.Layout.LayoutModifier
import Data.List ( partition )
-- $usage
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.Maximize
+-- > import XMonad.Layout.Maximize
--
-- > layouts = ...
-- > , Layout $ maximize $ tiled ...
@@ -41,7 +41,7 @@ import Data.List ( partition )
-- > , ((modMask, xK_backslash), withFocused (sendMessage . maximizeRestore))
-- > ...
--- %import XMonadContrib.Maximize
+-- %import XMonad.Layout.Maximize
-- %layout , Layout $ maximize $ tiled
data Maximize a = Maximize (Maybe Window) deriving ( Read, Show )
diff --git a/Mosaic.hs b/XMonad/Layout/Mosaic.hs
index 8defbc7..aec7aab 100644
--- a/Mosaic.hs
+++ b/XMonad/Layout/Mosaic.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.Mosaic
+-- Module : XMonad.Layout.Mosaic
-- Copyright : (c) David Roundy <droundy@darcs.net>
-- License : BSD3-style (see LICENSE)
--
@@ -15,7 +15,7 @@
-- ratios configurable at run-time by the user.
--
-----------------------------------------------------------------------------
-module XMonadContrib.Mosaic (
+module XMonad.Layout.Mosaic (
-- * Usage
-- $usage
mosaic, expandWindow, shrinkWindow, squareWindow, myclearWindow,
@@ -35,8 +35,8 @@ import Data.List ( sort )
import Data.Typeable ( Typeable )
import Control.Monad ( mplus )
-import XMonadContrib.NamedWindows
-import XMonadContrib.Anneal
+import XMonad.Util.NamedWindows
+import XMonad.Util.Anneal
-- $usage
--
@@ -44,7 +44,7 @@ import XMonadContrib.Anneal
--
-- You can use this module with the following in your Config.hs:
--
--- > import XMonadContrib.Mosaic
+-- > import XMonad.Layout.Mosaic
--
-- > layouts :: [Layout Window]
-- > layouts = [ mosaic 0.25 0.5 M.empty, full ]
@@ -60,7 +60,7 @@ import XMonadContrib.Anneal
-- > , ((controlMask .|. modMask .|. shiftMask, xK_o ), withNamedWindow (sendMessage . flexibleWindow))
--
--- %import XMonadContrib.Mosaic
+-- %import XMonad.Layout.Mosaic
-- %keybind , ((controlMask .|. modMask .|. shiftMask, xK_h), withNamedWindow (sendMessage . tallWindow))
-- %keybind , ((controlMask .|. modMask .|. shiftMask, xK_l), withNamedWindow (sendMessage . wideWindow))
-- %keybind , ((modMask .|. shiftMask, xK_h ), withNamedWindow (sendMessage . shrinkWindow))
diff --git a/MosaicAlt.hs b/XMonad/Layout/MosaicAlt.hs
index 0129028..a2b9e6a 100644
--- a/MosaicAlt.hs
+++ b/XMonad/Layout/MosaicAlt.hs
@@ -3,7 +3,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.MosaicAlt
+-- Module : XMonad.Layout.MosaicAlt
-- Copyright : (c) 2007 James Webb
-- License : BSD-style (see xmonad/LICENSE)
--
@@ -17,7 +17,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.MosaicAlt (
+module XMonad.Layout.MosaicAlt (
-- * Usage:
-- $usage
MosaicAlt(..)
@@ -40,7 +40,7 @@ import Graphics.X11.Types ( Window )
-- $usage
-- You can use this module with the following in your configuration file:
--
--- > import XMonadContrib.MosaicAlt
+-- > import XMonad.Layout.MosaicAlt
--
-- > layouts = ...
-- > , Layout $ MosaicAlt M.empty
@@ -54,7 +54,7 @@ import Graphics.X11.Types ( Window )
-- > , ((modMask .|. controlMask, xK_space), sendMessage resetAlt)
-- > ...
--- %import XMonadContrib.MosaicAlt
+-- %import XMonad.Layout.MosaicAlt
-- %layout , Layout $ MosaicAlt M.empty
data HandleWindowAlt =
diff --git a/NoBorders.hs b/XMonad/Layout/NoBorders.hs
index a1fdc96..8aa64fb 100644
--- a/NoBorders.hs
+++ b/XMonad/Layout/NoBorders.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.NoBorders
+-- Module : XMonad.Layout.NoBorders
-- Copyright : (c) David Roundy <droundy@darcs.net>
-- License : BSD3-style (see LICENSE)
--
@@ -17,7 +17,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.NoBorders (
+module XMonad.Layout.NoBorders (
-- * Usage
-- $usage
noBorders,
@@ -30,14 +30,14 @@ import Control.Monad.Reader (asks)
import Graphics.X11.Xlib
import XMonad
-import XMonadContrib.LayoutModifier
+import XMonad.Layout.LayoutModifier
import qualified XMonad.StackSet as W
import Data.List ((\\))
-- $usage
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.NoBorders
+-- > import XMonad.Layout.NoBorders
--
-- and modify the layouts to call noBorders on the layouts you want to lack
-- borders
@@ -45,7 +45,7 @@ import Data.List ((\\))
-- > layouts = [ Layout (noBorders Full), ... ]
--
--- %import XMonadContrib.NoBorders
+-- %import XMonad.Layout.NoBorders
-- %layout -- prepend noBorders to default layouts above to remove their borders, like so:
-- %layout , noBorders Full
diff --git a/ResizableTile.hs b/XMonad/Layout/ResizableTile.hs
index c41f225..a70a987 100644
--- a/ResizableTile.hs
+++ b/XMonad/Layout/ResizableTile.hs
@@ -3,7 +3,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.ResizableTile
+-- Module : XMonad.Layout.ResizableTile
-- Copyright : (c) MATSUYAMA Tomohiro <t.matsuyama.pub@gmail.com>
-- License : BSD-style (see LICENSE)
--
@@ -15,7 +15,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.ResizableTile (
+module XMonad.Layout.ResizableTile (
-- * Usage
-- $usage
ResizableTall(..), MirrorResize(..)
@@ -32,7 +32,7 @@ import Control.Monad
--
-- To use, modify your Config.hs to:
--
--- > import XMonadContrib.ResizableTile
+-- > import XMonad.Layout.ResizableTile
--
-- and add a keybinding:
--
diff --git a/Roledex.hs b/XMonad/Layout/Roledex.hs
index 66c58ba..0c4eb5f 100644
--- a/Roledex.hs
+++ b/XMonad/Layout/Roledex.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.Roledex
+-- Module : XMonad.Layout.Roledex
-- Copyright : (c) tim.thelion@gmail.com
-- License : BSD
--
@@ -15,7 +15,7 @@
-- This is a completely pointless layout which acts like Microsoft's Flip 3D
-----------------------------------------------------------------------------
-module XMonadContrib.Roledex (
+module XMonad.Layout.Roledex (
-- * Usage
-- $usage
Roledex(Roledex)) where
@@ -28,10 +28,10 @@ import Data.Ratio
-- $usage
--
--- > import XMonadContrib.Roledex
+-- > import XMonad.Layout.Roledex
-- > layouts = [ Layout Roledex ]
--- %import XMonadContrib.Roledex
+-- %import XMonad.Layout.Roledex
-- %layout , Layout Roledex
data Roledex a = Roledex deriving ( Show, Read )
diff --git a/Spiral.hs b/XMonad/Layout/Spiral.hs
index 0aba738..013a017 100644
--- a/Spiral.hs
+++ b/XMonad/Layout/Spiral.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.Spiral
+-- Module : XMonad.Layout.Spiral
-- Copyright : (c) Joe Thornber <joe.thornber@gmail.com>
-- License : BSD3-style (see LICENSE)
--
@@ -14,7 +14,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.Spiral (
+module XMonad.Layout.Spiral (
-- * Usage
-- $usage
spiral
@@ -33,11 +33,11 @@ import XMonad.StackSet ( integrate )
-- $usage
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.Spiral
+-- > import XMonad.Layout.Spiral
--
-- > layouts = [ ..., Layout $ spiral (1 % 1), ... ]
--- %import XMonadContrib.Spiral
+-- %import XMonad.Layout.Spiral
-- %layout , Layout $ spiral (1 % 1)
fibs :: [Integer]
diff --git a/Square.hs b/XMonad/Layout/Square.hs
index 46ad2e7..e05f549 100644
--- a/Square.hs
+++ b/XMonad/Layout/Square.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.Square
+-- Module : XMonad.Layout.Square
-- Copyright : (c) David Roundy <droundy@darcs.net>
-- License : BSD3-style (see LICENSE)
--
@@ -13,13 +13,13 @@
-- A layout that splits the screen into a square area and the rest of the
-- screen.
-- This is probably only ever useful in combination with
--- "XMonadContrib.Combo".
+-- "XMonad.Layout.Combo".
-- It sticks one window in a square region, and makes the rest
-- of the windows live with what's left (in a full-screen sense).
--
-----------------------------------------------------------------------------
-module XMonadContrib.Square (
+module XMonad.Layout.Square (
-- * Usage
-- $usage
Square(..) ) where
@@ -31,16 +31,16 @@ import XMonad.StackSet ( integrate )
-- $usage
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.Square
+-- > import XMonad.Layout.Square
--
--- An example layout using square together with "XMonadContrib.Combo"
+-- An example layout using square together with "XMonad.Layout.Combo"
-- to make the very last area square:
--
-- > , combo (combo (mirror $ twoPane 0.03 0.85),1)] (twoPane 0.03 0.5) )
-- > [(twoPane 0.03 0.2,1),(combo [(twoPane 0.03 0.8,1),(square,1)]
-- > [(tabbed,3),(tabbed,30),(tabbed,1),(tabbed,1)]
--- %import XMonadContrib.Square
+-- %import XMonad.Layout.Square
data Square a = Square deriving ( Read, Show )
diff --git a/SwitchTrans.hs b/XMonad/Layout/SwitchTrans.hs
index 3050924..986202e 100644
--- a/SwitchTrans.hs
+++ b/XMonad/Layout/SwitchTrans.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.SwitchTrans
+-- Module : XMonad.Layout.SwitchTrans
-- Copyright : (c) Lukas Mai
-- License : BSD-style (see LICENSE)
--
@@ -39,7 +39,7 @@
-- > ])
-- > ) [ Layout tiled ]
--
--- (The @noBorders@ transformer is from "XMonadContrib.NoBorders".)
+-- (The @noBorders@ transformer is from "XMonad.Layout.NoBorders".)
--
-- This example is probably overkill but it's very close to what I actually use.
-- Anyway, this layout behaves like the default @tiled@ layout, until you send it
@@ -68,7 +68,7 @@
-- transformer.
-----------------------------------------------------------------------------
-module XMonadContrib.SwitchTrans (
+module XMonad.Layout.SwitchTrans (
Toggle(..),
Enable(..),
Disable(..),
diff --git a/Tabbed.hs b/XMonad/Layout/Tabbed.hs
index 0b61cf3..92ef150 100644
--- a/Tabbed.hs
+++ b/XMonad/Layout/Tabbed.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.Tabbed
+-- Module : XMonad.Layout.Tabbed
-- Copyright : (c) 2007 David Roundy, Andrea Rossato
-- License : BSD-style (see xmonad/LICENSE)
--
@@ -14,7 +14,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.Tabbed (
+module XMonad.Layout.Tabbed (
-- * Usage:
-- $usage
tabbed
@@ -35,14 +35,14 @@ import XMonad
import XMonad.Operations
import qualified XMonad.StackSet as W
-import XMonadContrib.NamedWindows
-import XMonadContrib.Invisible
-import XMonadContrib.XUtils
+import XMonad.Util.NamedWindows
+import XMonad.Util.Invisible
+import XMonad.Util.XUtils
-- $usage
-- You can use this module with the following in your configuration file:
--
--- > import XMonadContrib.Tabbed
+-- > import XMonad.Layout.Tabbed
--
-- > layouts :: [Layout Window]
-- > layouts = [ Layout tiled
@@ -65,7 +65,7 @@ import XMonadContrib.XUtils
-- > layouts = [ ...
-- > , Layout $ tabbed shrinkText myTabConfig ]
--- %import XMonadContrib.Tabbed
+-- %import XMonad.Layout.Tabbed
-- %layout , tabbed shrinkText defaultTConf
tabbed :: Shrinker -> TConf -> Tabbed a
diff --git a/ThreeColumns.hs b/XMonad/Layout/ThreeColumns.hs
index 9b10cc4..2dd2551 100644
--- a/ThreeColumns.hs
+++ b/XMonad/Layout/ThreeColumns.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.ThreeColumns
+-- Module : XMonad.Layout.ThreeColumns
-- Copyright : (c) Kai Grossjohann <kai@emptydomain.de>
-- License : BSD3-style (see LICENSE)
--
@@ -14,7 +14,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.ThreeColumns (
+module XMonad.Layout.ThreeColumns (
-- * Usage
-- $usage
ThreeCol(..)
@@ -35,13 +35,13 @@ import Graphics.X11.Xlib
--
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.ThreeColumns
+-- > import XMonad.Layout.ThreeColumns
--
-- and add, to the list of layouts:
--
-- > ThreeCol nmaster delta ratio
--- %import XMonadContrib.ThreeColumns
+-- %import XMonad.Layout.ThreeColumns
-- %layout , ThreeCol nmaster delta ratio
data ThreeCol a = ThreeCol Int Rational Rational deriving (Show,Read)
diff --git a/TilePrime.hs b/XMonad/Layout/TilePrime.hs
index c939d81..36d54f6 100644
--- a/TilePrime.hs
+++ b/XMonad/Layout/TilePrime.hs
@@ -14,7 +14,7 @@
-- -----------------------------------------------------------------------------
--
-module XMonadContrib.TilePrime (
+module XMonad.Layout.TilePrime (
-- * Usage
-- $usage
TilePrime(TilePrime)
@@ -32,7 +32,7 @@ import {-#SOURCE#-} Config (borderWidth)
-- $usage
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.TilePrime
+-- > import XMonad.Layout.TilePrime
--
-- and add the following line to your 'layouts'
--
@@ -40,7 +40,7 @@ import {-#SOURCE#-} Config (borderWidth)
--
-- Use True as the last argument to get a wide layout.
--- %import XMonadContrib.TilePrime
+-- %import XMonad.Layout.TilePrime
-- %layout , Layout $ TilePrime nmaster delta ratio False
data TilePrime a = TilePrime
diff --git a/ToggleLayouts.hs b/XMonad/Layout/ToggleLayouts.hs
index efcaab7..0130cf7 100644
--- a/ToggleLayouts.hs
+++ b/XMonad/Layout/ToggleLayouts.hs
@@ -3,7 +3,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.ToggleLayouts
+-- Module : XMonad.Layout.ToggleLayouts
-- Copyright : (c) David Roundy <droundy@darcs.net>
-- License : BSD
--
@@ -14,7 +14,7 @@
-- A module for writing easy Layouts
-----------------------------------------------------------------------------
-module XMonadContrib.ToggleLayouts (
+module XMonad.Layout.ToggleLayouts (
-- * Usage
-- $usage
toggleLayouts, ToggleLayout(..)
@@ -25,7 +25,7 @@ import XMonad
-- $usage
-- Use toggleLayouts to toggle between two layouts.
--
--- import XMonadContrib.ToggleLayouts
+-- import XMonad.Layout.ToggleLayouts
--
-- and add to your layoutHook something like
--
diff --git a/TwoPane.hs b/XMonad/Layout/TwoPane.hs
index 2dc266f..bca49a7 100644
--- a/TwoPane.hs
+++ b/XMonad/Layout/TwoPane.hs
@@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.TwoPane
+-- Module : XMonad.Layout.TwoPane
-- Copyright : (c) Spencer Janssen <sjanssen@cse.unl.edu>
-- License : BSD3-style (see LICENSE)
--
@@ -16,7 +16,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.TwoPane (
+module XMonad.Layout.TwoPane (
-- * Usage
-- $usage
TwoPane (..)
@@ -30,13 +30,13 @@ import XMonad.StackSet ( focus, up, down)
--
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.TwoPane
+-- > import XMonad.Layout.TwoPane
--
-- and add, to the list of layouts:
--
-- > , (Layout $ TwoPane 0.03 0.5)
--- %import XMonadContrib.TwoPane
+-- %import XMonad.Layout.TwoPane
-- %layout , (Layout $ TwoPane 0.03 0.5)
data TwoPane a =
diff --git a/WindowNavigation.hs b/XMonad/Layout/WindowNavigation.hs
index 05c3bb8..4608ba5 100644
--- a/WindowNavigation.hs
+++ b/XMonad/Layout/WindowNavigation.hs
@@ -3,7 +3,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.WindowNavigation
+-- Module : XMonad.Layout.WindowNavigation
-- Copyright : (c) 2007 David Roundy <droundy@darcs.net>
-- License : BSD3-style (see LICENSE)
--
@@ -15,7 +15,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.WindowNavigation (
+module XMonad.Layout.WindowNavigation (
-- * Usage
-- $usage
windowNavigation, configurableNavigation,
@@ -32,14 +32,14 @@ import Data.List ( nub, sortBy, (\\) )
import XMonad
import qualified XMonad.StackSet as W
import XMonad.Operations ( windows, focus )
-import XMonadContrib.LayoutModifier
-import XMonadContrib.Invisible
-import XMonadContrib.XUtils
+import XMonad.Layout.LayoutModifier
+import XMonad.Util.Invisible
+import XMonad.Util.XUtils
-- $usage
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.WindowNavigation
+-- > import XMonad.Layout.WindowNavigation
-- >
-- > layoutHook = Layout $ windowNavigation $ Select ...
--
@@ -54,7 +54,7 @@ import XMonadContrib.XUtils
-- > , ((modMask, xK_Up ), sendMessage $ Go U)
-- > , ((modMask, xK_Down ), sendMessage $ Go D)
--- %import XMonadContrib.WindowNavigation
+-- %import XMonad.Layout.WindowNavigation
-- %keybind , ((modMask, xK_Right), sendMessage $ Go R)
-- %keybind , ((modMask, xK_Left ), sendMessage $ Go L)
-- %keybind , ((modMask, xK_Up ), sendMessage $ Go U)
diff --git a/WorkspaceDir.hs b/XMonad/Layout/WorkspaceDir.hs
index a967741..e5f15ce 100644
--- a/WorkspaceDir.hs
+++ b/XMonad/Layout/WorkspaceDir.hs
@@ -3,7 +3,7 @@
-----------------------------------------------------------------------------
-- |
--- Module : XMonadContrib.WorkspaceDir
+-- Module : XMonad.Layout.WorkspaceDir
-- Copyright : (c) 2007 David Roundy <droundy@darcs.net>
-- License : BSD3-style (see LICENSE)
--
@@ -22,7 +22,7 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.WorkspaceDir (
+module XMonad.Layout.WorkspaceDir (
-- * Usage
-- $usage
workspaceDir,
@@ -33,15 +33,15 @@ import System.Directory ( setCurrentDirectory )
import XMonad
import XMonad.Operations ( sendMessage )
-import XMonadContrib.Run ( runProcessWithInput )
-import XMonadContrib.XPrompt ( XPConfig )
-import XMonadContrib.DirectoryPrompt ( directoryPrompt )
-import XMonadContrib.LayoutModifier
+import XMonad.Util.Run ( runProcessWithInput )
+import XMonad.Prompt ( XPConfig )
+import XMonad.Prompt.Directory ( directoryPrompt )
+import XMonad.Layout.LayoutModifier
-- $usage
-- You can use this module with the following in your Config.hs file:
--
--- > import XMonadContrib.WorkspaceDir
+-- > import XMonad.Layout.WorkspaceDir
-- >
-- > layouts = map (workspaceDir "~") [ tiled, ... ]
--
@@ -49,7 +49,7 @@ import XMonadContrib.LayoutModifier
--
-- > , ((modMask .|. shiftMask, xK_x ), changeDir defaultXPConfig)
--- %import XMonadContrib.WorkspaceDir
+-- %import XMonad.Layout.WorkspaceDir
-- %keybind , ((modMask .|. shiftMask, xK_x ), changeDir defaultXPConfig)
-- %layout -- prepend 'map (workspaceDir "~")' to layouts definition above,
-- %layout -- just before the list, like the following (don't uncomment next line):