Sophie

Sophie

distrib > Fedora > 18 > i386 > by-pkgid > 16551e78563a5b49ff9624ee1c8b8101 > files > 1424

ghc-xmonad-contrib-devel-0.11-1.1.fc18.i686.rpm

-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/


-- | Third party extensions for xmonad
--   
--   Third party tiling algorithms, configurations and scripts to xmonad, a
--   tiling window manager for X.
--   
--   For an introduction to building, configuring and using xmonad
--   extensions, see <a>XMonad.Doc</a>. In particular:
--   
--   <a>XMonad.Doc.Configuring</a>, a guide to configuring xmonad
--   
--   <a>XMonad.Doc.Extending</a>, using the contributed extensions library
--   
--   <a>XMonad.Doc.Developing</a>, introduction to xmonad internals and
--   writing your own extensions.
@package xmonad-contrib
@version 0.11


-- | Internal utility functions for storing Strings with the root window.
--   
--   Used for global state like IORefs with string keys, but more latency,
--   persistent between xmonad restarts.
module XMonad.Util.StringProp
type StringProp = String

-- | Get the name of a string property and returns it as a <a>Maybe</a>.
getStringProp :: MonadIO m => Display -> StringProp -> m (Maybe [Char])

-- | Set the value of a string property.
setStringProp :: MonadIO m => Display -> StringProp -> [Char] -> m ()

-- | Given a property name, returns its contents as a list. It uses the
--   empty list as default value.
getStringListProp :: MonadIO m => Display -> StringProp -> m [String]

-- | Given a property name and a list, sets the value of this property with
--   the list given as argument.
setStringListProp :: MonadIO m => Display -> StringProp -> [String] -> m ()


-- | Implements a <tt>--replace</tt> behavior outside of core.
module XMonad.Util.Replace

-- | <tt>replace</tt> must be run before xmonad starts to signals to
--   compliant window managers that they must exit and let xmonad take
--   over.
replace :: IO ()


-- | Customized key bindings.
--   
--   (See also <a>XMonad.Util.EZConfig</a> in xmonad-contrib.)
module XMonad.Util.CustomKeys

-- | Customize <a>defaultConfig</a> -- delete needless shortcuts and insert
--   those you will use.
customKeys :: (XConfig Layout -> [(KeyMask, KeySym)]) -> (XConfig Layout -> [((KeyMask, KeySym), X ())]) -> XConfig Layout -> Map (KeyMask, KeySym) (X ())

-- | General variant of <a>customKeys</a>: customize key bindings of
--   third-party configuration.
customKeysFrom :: XConfig l -> (XConfig Layout -> [(KeyMask, KeySym)]) -> (XConfig Layout -> [((KeyMask, KeySym), X ())]) -> XConfig Layout -> Map (KeyMask, KeySym) (X ())


-- | A layout similar to tall but with three columns. With 2560x1600 pixels
--   this layout can be used for a huge main window and up to six
--   reasonable sized slave windows.
module XMonad.Layout.ThreeColumns

-- | Arguments are nmaster, delta, fraction
data ThreeCol a
ThreeColMid :: !Int -> !Rational -> !Rational -> ThreeCol a
threeColNMaster :: ThreeCol a -> !Int
threeColDelta :: ThreeCol a -> !Rational
threeColFrac :: ThreeCol a -> !Rational
ThreeCol :: !Int -> !Rational -> !Rational -> ThreeCol a
threeColNMaster :: ThreeCol a -> !Int
threeColDelta :: ThreeCol a -> !Rational
threeColFrac :: ThreeCol a -> !Rational
instance Show (ThreeCol a)
instance Read (ThreeCol a)
instance LayoutClass ThreeCol a


-- | A stacking layout, like dishes but with the ability to resize master
--   pane. Mostly useful on small screens.
module XMonad.Layout.StackTile
data StackTile a
StackTile :: !Int -> !Rational -> !Rational -> StackTile a
instance Show (StackTile a)
instance Read (StackTile a)
instance LayoutClass StackTile a


-- | A spiral tiling layout.
module XMonad.Layout.Spiral

-- | A spiral layout. The parameter controls the size ratio between
--   successive windows in the spiral. Sensible values range from 0 up to
--   the aspect ratio of your monitor (often 4/3).
--   
--   By default, the spiral is counterclockwise, starting to the east. See
--   also <a>spiralWithDir</a>.
spiral :: Rational -> SpiralWithDir a

-- | Create a spiral layout, specifying the starting cardinal direction,
--   the spiral direction (clockwise or counterclockwise), and the size
--   ratio.
spiralWithDir :: Direction -> Rotation -> Rational -> SpiralWithDir a
data Rotation
CW :: Rotation
CCW :: Rotation
data Direction
East :: Direction
South :: Direction
West :: Direction
North :: Direction
data SpiralWithDir a
instance Read Rotation
instance Show Rotation
instance Eq Direction
instance Enum Direction
instance Read Direction
instance Show Direction
instance Read (SpiralWithDir a)
instance Show (SpiralWithDir a)
instance LayoutClass SpiralWithDir a


-- | This is a completely pointless layout which acts like Microsoft's Flip
--   3D
module XMonad.Layout.Roledex
data Roledex a
Roledex :: Roledex a
instance Show (Roledex a)
instance Read (Roledex a)
instance LayoutClass Roledex Window


-- | More useful tiled layout that allows you to change a width/height of
--   window.
module XMonad.Layout.ResizableTile
data ResizableTall a
ResizableTall :: Int -> Rational -> Rational -> [Rational] -> ResizableTall a

-- | number of master windows
_nmaster :: ResizableTall a -> Int

-- | change when resizing by <a>Shrink</a>, <a>Expand</a>,
--   <a>MirrorShrink</a>, <a>MirrorExpand</a>
_delta :: ResizableTall a -> Rational

-- | width of master
_frac :: ResizableTall a -> Rational

-- | fraction to multiply the window height that would be given when
--   divided equally.
--   
--   slave windows are assigned their modified heights in order, from top
--   to bottom
--   
--   unspecified values are replaced by 1
_slaves :: ResizableTall a -> [Rational]
data MirrorResize
MirrorShrink :: MirrorResize
MirrorExpand :: MirrorResize
instance Typeable MirrorResize
instance Show (ResizableTall a)
instance Read (ResizableTall a)
instance LayoutClass ResizableTall a
instance Message MirrorResize


-- | Provides layout named OneBig. It places one (master) window at top
--   left corner of screen, and other (slave) windows at top
module XMonad.Layout.OneBig

-- | Data type for layout
data OneBig a
OneBig :: Float -> Float -> OneBig a
instance Read (OneBig a)
instance Show (OneBig a)
instance LayoutClass OneBig a


-- | Dynamically apply and unapply transformers to your window layout. This
--   can be used to rotate your window layout by 90 degrees, or to make the
--   currently focused window occupy the whole screen ("zoom in") then undo
--   the transformation ("zoom out").
module XMonad.Layout.MultiToggle

-- | A class to identify custom transformers (and look up transforming
--   functions by type).
class (Eq t, Typeable t) => Transformer t a | t -> a
transform :: (Transformer t a, LayoutClass l a) => t -> l a -> (forall l'. LayoutClass l' a => l' a -> (l' a -> l a) -> b) -> b

-- | Toggle the specified layout transformer.
data Toggle a
Toggle :: t -> Toggle a

-- | Prepend an element to a heterogeneous list. Used to build transformer
--   tables for <a>mkToggle</a>.
(??) :: HList b w => a -> b -> HCons a b

-- | Marks the end of a transformer list.
data EOT
EOT :: EOT

-- | Construct a singleton transformer table.
single :: a -> HCons a EOT

-- | Construct a <tt>MultiToggle</tt> layout from a transformer table and a
--   base layout.
mkToggle :: LayoutClass l a => ts -> l a -> MultiToggle ts l a

-- | Construct a <tt>MultiToggle</tt> layout from a single transformer and
--   a base layout.
mkToggle1 :: LayoutClass l a => t -> l a -> MultiToggle (HCons t EOT) l a
class HList c a
data HCons a b
data MultiToggle ts l a
instance Typeable1 Toggle
instance (Read ts, Read (l a)) => Read (MultiToggleS ts l a)
instance (Show ts, Show (l a)) => Show (MultiToggleS ts l a)
instance Read EOT
instance Show EOT
instance (Read a, Read b) => Read (HCons a b)
instance (Show a, Show b) => Show (HCons a b)
instance (Typeable a, Show ts, HList ts a, LayoutClass l a) => LayoutClass (MultiToggle ts l) a
instance (Transformer a w, HList b w) => HList (HCons a b) w
instance HList EOT w
instance (Show ts, Show (l a), LayoutClass l a) => Show (MultiToggle ts l a)
instance (LayoutClass l a, Read (l a), HList ts a, Read ts) => Read (MultiToggle ts l a)
instance Typeable a => Message (Toggle a)


-- | This layout tiles windows in a growing number of columns. The number
--   of windows in each column can be controlled by messages.
module XMonad.Layout.MultiColumns

-- | Layout constructor.
multiCol :: [Int] -> Int -> Rational -> Rational -> MultiCol a
data MultiCol a
instance Show (MultiCol a)
instance Read (MultiCol a)
instance Eq (MultiCol a)
instance LayoutClass MultiCol a


-- | A layout which gives each window a specified amount of screen space
--   relative to the others. Compared to the <tt>Mosaic</tt> layout, this
--   one divides the space in a more balanced way.
module XMonad.Layout.MosaicAlt
data MosaicAlt a
MosaicAlt :: Params -> MosaicAlt a
shrinkWindowAlt, expandWindowAlt :: Window -> HandleWindowAlt
tallWindowAlt, wideWindowAlt :: Window -> HandleWindowAlt
resetAlt :: HandleWindowAlt
type Params = Map Window Param
data Param
data HandleWindowAlt
instance Typeable HandleWindowAlt
instance Eq HandleWindowAlt
instance Show Param
instance Read Param
instance Show (MosaicAlt a)
instance Read (MosaicAlt a)
instance LayoutClass MosaicAlt Window
instance Message HandleWindowAlt


-- | Based on MosaicAlt, but aspect ratio messages always change the aspect
--   ratios, and rearranging the window stack changes the window sizes.
module XMonad.Layout.Mosaic
data Aspect
Taller :: Aspect
Wider :: Aspect
Reset :: Aspect
SlopeMod :: ([Rational] -> [Rational]) -> Aspect

-- | The relative magnitudes (the sign is ignored) of the rational numbers
--   in the second argument determine the relative areas that the windows
--   receive. The first number represents the size of the master window,
--   the second is for the next window in the stack, and so on.
--   
--   The list is extended with <tt>++ repeat 1</tt>, so <tt>mosaic 1.5
--   []</tt> is like a resizable grid.
--   
--   The first parameter is the multiplicative factor to use when
--   responding to the <a>Expand</a> message.
mosaic :: Rational -> [Rational] -> Mosaic a

-- | These sample functions are meant to be applied to the list of window
--   sizes through the <a>SlopeMod</a> message.
changeMaster :: (Rational -> Rational) -> X ()

-- | Apply a function to the Rational that represents the currently focused
--   window.
--   
--   <a>Expand</a> and <a>Shrink</a> messages are responded to with
--   <tt>changeFocused (*delta)</tt> or <tt>changeFocused (delta/)</tt>
--   where <tt>delta</tt> is the first argument to <a>mosaic</a>.
--   
--   This is exported because other functions (ex. <tt>const 1</tt>,
--   <tt>(+1)</tt>) may be useful to apply to the current area.
changeFocused :: (Rational -> Rational) -> X ()
data Mosaic a
instance Typeable Aspect
instance Read (Mosaic a)
instance Show (Mosaic a)
instance Monoid (Tree a)
instance Functor Tree
instance Foldable Tree
instance LayoutClass Mosaic a
instance Message Aspect


-- | A layout combinator that sends a specified number of windows to one
--   rectangle and the rest to another.
module XMonad.Layout.LayoutBuilder

-- | Use the specified layout in the described area for N windows and send
--   the rest of the windows to the next layout in the chain. It is
--   possible to supply an alternative area that will then be used instead,
--   if there are no windows to send to the next layout.
layoutN :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a, LayoutClass l3 a) => Int -> SubBox -> Maybe SubBox -> l1 a -> LayoutN l2 l3 a -> LayoutN l1 (LayoutN l2 l3) a

-- | As layoutN, but the number of windows is given relative to the total
--   number of windows remaining to be handled. The first argument is how
--   much to change the ratio when using IncLayoutN, and the second is the
--   initial ratio.
layoutR :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a, LayoutClass l3 a) => Rational -> Rational -> SubBox -> Maybe SubBox -> l1 a -> LayoutN l2 l3 a -> LayoutN l1 (LayoutN l2 l3) a

-- | Use the specified layout in the described area for all remaining
--   windows.
layoutAll :: (Read a, Eq a, LayoutClass l1 a) => SubBox -> l1 a -> LayoutN l1 Full a

-- | Change the number of windows handled by the focused layout.
data IncLayoutN
IncLayoutN :: Int -> IncLayoutN

-- | The absolute or relative measures used to describe the area a layout
--   should be placed in. For negative absolute values the total remaining
--   space will be added. For sizes, the remaining space will also be added
--   for zeroes. Relative values are applied on the remaining space after
--   the top-left corner of the box have been removed.
data SubMeasure
Abs :: Int -> SubMeasure
Rel :: Rational -> SubMeasure

-- | A box to place a layout in. The stored values are xpos, ypos, width
--   and height.
data SubBox
SubBox :: SubMeasure -> SubMeasure -> SubMeasure -> SubMeasure -> SubBox

-- | Create a box with only absolute measurements. If the values are
--   negative, the total remaining space will be added. For sizes it will
--   also be added for zeroes.
absBox :: Int -> Int -> Int -> Int -> SubBox

-- | Create a box with only relative measurements.
relBox :: Rational -> Rational -> Rational -> Rational -> SubBox

-- | Use one layout in the specified area for a number of windows and
--   possibly let another layout handle the rest.
data LayoutN l1 l2 a
instance Typeable IncLayoutN
instance Show SubMeasure
instance Read SubMeasure
instance Show SubBox
instance Read SubBox
instance (Show a, Show (l1 a), Show (l2 a)) => Show (LayoutN l1 l2 a)
instance (Read a, Read (l1 a), Read (l2 a)) => Read (LayoutN l1 l2 a)
instance (LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, Eq a, Typeable a) => LayoutClass (LayoutN l1 l2) a
instance Message IncLayoutN


-- | A not so simple layout that attempts to put all windows in a square
--   grid while obeying their size hints.
module XMonad.Layout.HintedGrid

-- | Automatic mirroring of hinted layouts doesn't work very well, so this
--   <a>Grid</a> comes with built-in mirroring. <tt>Grid False</tt> is the
--   normal layout, <tt>Grid True</tt> is the mirrored variant (rotated by
--   90 degrees).
data Grid a
Grid :: Bool -> Grid a
GridRatio :: Double -> Bool -> Grid a

-- | The internal function for computing the grid layout.
arrange :: Double -> Bool -> Rectangle -> [Window] -> X [(Window, Rectangle)]
defaultRatio :: Double
instance Read (Grid a)
instance Show (Grid a)
instance LayoutClass Grid Window


-- | A very simple layout. The simplest, afaik.
module XMonad.Layout.Simplest
data Simplest a
Simplest :: Simplest a
instance Show (Simplest a)
instance Read (Simplest a)
instance LayoutClass Simplest a


-- | Utility functions for manipulating <tt>Maybe Stack</tt>s.
module XMonad.Util.Stack
type Zipper a = Maybe (Stack a)
emptyZ :: Zipper a
singletonZ :: a -> Zipper a

-- | Create a stack from a list, and the 0-based index of the focused
--   element. If the index is out of bounds, focus will go to the first
--   element.
fromIndex :: [a] -> Int -> Zipper a

-- | Turn a stack into a list and the index of its focused element.
toIndex :: Zipper a -> ([a], Maybe Int)

-- | Create a stack from a list of <a>Either</a>-tagged values. Focus will
--   go to the first <a>Right</a> value, or if there is none, to the first
--   <a>Left</a> one.
fromTags :: [Either a a] -> Zipper a

-- | Turn a stack into an <a>Either</a>-tagged list. The focused element
--   will be tagged with <a>Right</a>, the others with <a>Left</a>.
toTags :: Zipper a -> [Either a a]

-- | Insert an element before the focused one, and focus it
insertUpZ :: a -> Zipper a -> Zipper a

-- | Insert an element after the focused one, and focus it
insertDownZ :: a -> Zipper a -> Zipper a

-- | Swap the focused element with the previous one
swapUpZ :: Zipper a -> Zipper a

-- | Swap the focused element with the next one
swapDownZ :: Zipper a -> Zipper a

-- | Swap the focused element with the first one
swapMasterZ :: Zipper a -> Zipper a

-- | Move the focus to the previous element
focusUpZ :: Zipper a -> Zipper a

-- | Move the focus to the next element
focusDownZ :: Zipper a -> Zipper a

-- | Move the focus to the first element
focusMasterZ :: Zipper a -> Zipper a

-- | Get the focused element
getFocusZ :: Zipper a -> Maybe a

-- | Get the element at a given index
getIZ :: Int -> Zipper a -> Maybe a

-- | Sort a stack of elements supporting <a>Ord</a>
sortZ :: Ord a => Zipper a -> Zipper a

-- | Sort a stack with an arbitrary sorting function
sortByZ :: (a -> a -> Ordering) -> Zipper a -> Zipper a

-- | Map a function over a stack. The boolean argument indcates whether the
--   current element is the focused one
mapZ :: (Bool -> a -> b) -> Zipper a -> Zipper b

-- | <a>mapZ</a> without the <a>Bool</a> argument
mapZ_ :: (a -> b) -> Zipper a -> Zipper b

-- | Monadic version of <a>mapZ</a>
mapZM :: Monad m => (Bool -> a -> m b) -> Zipper a -> m (Zipper b)

-- | Monadic version of <a>mapZ_</a>
mapZM_ :: Monad m => (a -> m b) -> Zipper a -> m (Zipper b)

-- | Apply a function to the focused element
onFocusedZ :: (a -> a) -> Zipper a -> Zipper a

-- | Monadic version of <a>onFocusedZ</a>
onFocusedZM :: Monad m => (a -> m a) -> Zipper a -> m (Zipper a)

-- | Apply a function to the element at the given index
onIndexZ :: Int -> (a -> a) -> Zipper a -> Zipper a

-- | Monadic version of <a>onIndexZ</a>
onIndexZM :: Monad m => Int -> (a -> m a) -> Zipper a -> m (Zipper a)

-- | Fiter a stack according to a predicate. The refocusing behavior mimics
--   XMonad's usual one. The boolean argument indicates whether the current
--   element is the focused one.
filterZ :: (Bool -> a -> Bool) -> Zipper a -> Zipper a

-- | <a>filterZ</a> without the <a>Bool</a> argument
filterZ_ :: (a -> Bool) -> Zipper a -> Zipper a

-- | Delete the focused element
deleteFocusedZ :: Zipper a -> Zipper a

-- | Delete the ith element
deleteIndexZ :: Int -> Zipper a -> Zipper a

-- | Analogous to <a>foldr</a>. The <a>Bool</a> argument to the step
--   functions indicates whether the current element is the focused one
foldrZ :: (Bool -> a -> b -> b) -> b -> Zipper a -> b

-- | Analogous to <a>foldl</a>. The <a>Bool</a> argument to the step
--   functions indicates whether the current element is the focused one
foldlZ :: (Bool -> b -> a -> b) -> b -> Zipper a -> b

-- | <a>foldrZ</a> without the <a>Bool</a> argument.
foldrZ_ :: (a -> b -> b) -> b -> Zipper a -> b

-- | <a>foldlZ</a> without the <a>Bool</a> argument.
foldlZ_ :: (b -> a -> b) -> b -> Zipper a -> b

-- | Find whether an element is present in a stack.
elemZ :: Eq a => a -> Zipper a -> Bool

-- | Safe version of <a>!!</a>
getI :: Int -> [a] -> Maybe a

-- | Tag the element with <a>Right</a> if the property is true, <a>Left</a>
--   otherwise
tagBy :: (a -> Bool) -> a -> Either a a

-- | Get the <tt>a</tt> from an <tt>Either a a</tt>
fromE :: Either a a -> a

-- | Map a function across both <a>Left</a>s and <a>Right</a>s. The
--   <a>Bool</a> argument is <a>True</a> in a <a>Right</a>, <a>False</a> in
--   a <a>Left</a>.
mapE :: (Bool -> a -> b) -> Either a a -> Either b b
mapE_ :: (a -> b) -> Either a a -> Either b b

-- | Monadic version of <a>mapE</a>
mapEM :: Monad m => (Bool -> a -> m b) -> Either a a -> m (Either b b)
mapEM_ :: Monad m => (a -> m b) -> Either a a -> m (Either b b)


-- | Two-level layout with windows split in individual layout groups,
--   themselves managed by a user-provided layout.
module XMonad.Layout.Groups

-- | Create a <a>Groups</a> layout.
--   
--   Note that the second parameter (the layout for arranging the groups)
--   is not used on <tt>Windows</tt>, but on <a>Group</a>s. For this
--   reason, you can only use layouts that don't specifically need to
--   manage <a>Window</a>s. This is obvious, when you think about it.
group :: l Window -> l2 (Group l Window) -> Groups l l2 Window

-- | Messages accepted by <a>Groups</a>-based layouts. All other messages
--   are forwarded to the layout of the currently focused subgroup (as if
--   they had been wrapped in <a>ToFocused</a>).
data GroupsMessage

-- | Send a message to the enclosing layout (the one that places the groups
--   themselves)
ToEnclosing :: SomeMessage -> GroupsMessage

-- | Send a message to the layout for nth group (starting at 0)
ToGroup :: Int -> SomeMessage -> GroupsMessage

-- | Send a message to the layout for the focused group
ToFocused :: SomeMessage -> GroupsMessage

-- | Send a message to all the sub-layouts
ToAll :: SomeMessage -> GroupsMessage

-- | Refocus the window which should be focused according to the layout.
Refocus :: GroupsMessage

-- | Modify the ordering/grouping/focusing of windows according to a
--   <a>ModifySpec</a>
Modify :: ModifySpec -> GroupsMessage

-- | Type of functions describing modifications to a <a>Groups</a> layout.
--   They are transformations on <a>Zipper</a>s of groups.
--   
--   Things you shouldn't do:
--   
--   <ul>
--   <li>Forge new windows (they will be ignored)</li>
--   <li>Duplicate windows (whatever happens is your problem)</li>
--   <li>Remove windows (they will be added again)</li>
--   <li>Duplicate layouts (only one will be kept, the rest will get the
--   base layout)</li>
--   </ul>
--   
--   Note that <a>ModifySpec</a> is a rank-2 type (indicating that
--   <a>ModifySpec</a>s must be polymorphic in the layout type), so if you
--   define functions taking <a>ModifySpec</a>s as arguments, or returning
--   them, you'll need to write a type signature and add <tt>{--}</tt> at
--   the beginning
type ModifySpec = forall l. WithID l Window -> Zipper (Group l Window) -> Zipper (Group l Window)

-- | Swap the focused window with the previous one.
swapUp :: ModifySpec

-- | Swap the focused window with the next one.
swapDown :: ModifySpec

-- | Swap the focused window with the (group's) master window.
swapMaster :: ModifySpec

-- | Move focus to the previous window in the group.
focusUp :: ModifySpec

-- | Move focus to the next window in the group.
focusDown :: ModifySpec

-- | Move focus to the group's master window.
focusMaster :: ModifySpec

-- | Swap the focused group with the previous one.
swapGroupUp :: ModifySpec

-- | Swap the focused group with the next one.
swapGroupDown :: ModifySpec

-- | Swap the focused group with the master group.
swapGroupMaster :: ModifySpec

-- | Move focus to the previous group.
focusGroupUp :: ModifySpec

-- | Move focus to the next group.
focusGroupDown :: ModifySpec

-- | Move focus to the master group.
focusGroupMaster :: ModifySpec

-- | Move the focused window to the previous group. If <a>True</a>, when in
--   the first group, wrap around to the last one. If <a>False</a>, create
--   a new group before it.
moveToGroupUp :: Bool -> ModifySpec

-- | Move the focused window to the next group. If <a>True</a>, when in the
--   last group, wrap around to the first one. If <a>False</a>, create a
--   new group after it.
moveToGroupDown :: Bool -> ModifySpec

-- | Move the focused window to a new group before the current one.
moveToNewGroupUp :: ModifySpec

-- | Move the focused window to a new group after the current one.
moveToNewGroupDown :: ModifySpec

-- | Split the focused group into two at the position of the focused window
--   (below it, unless it's the last window - in that case, above it).
splitGroup :: ModifySpec

-- | The type of our layouts.
data Groups l l2 a

-- | A group of windows and its layout algorithm.
data Group l a
G :: WithID l a -> Zipper a -> Group l a
gLayout :: Group l a -> WithID l a
gZipper :: Group l a -> Zipper a
onZipper :: (Zipper a -> Zipper a) -> Group l a -> Group l a
onLayout :: (WithID l a -> WithID l a) -> Group l a -> Group l a

-- | Split an infinite list into two. I ended up not needing this, but
--   let's keep it just in case. split :: [a] -&gt; ([a], [a]) split as =
--   snd $ foldr step (True, ([], [])) as where step a (True, (as1, as2)) =
--   (False, (a:as1, as2)) step a (False, (as1, as2)) = (True, (as1,
--   a:as2))
--   
--   Add a unique identity to a layout so we can follow it around.
data WithID l a

-- | Compare the ids of two <a>WithID</a> values
sameID :: WithID l a -> WithID l a -> Bool
instance Typeable GroupsMessage
instance (Read a, Read (l a), Read (l2 (Group l a))) => Read (Groups l l2 a)
instance (Show a, Show (l a), Show (l2 (Group l a))) => Show (Groups l l2 a)
instance Eq Uniq
instance Show Uniq
instance Read Uniq
instance Show (l a) => Show (WithID l a)
instance Read (l a) => Read (WithID l a)
instance (Show a, Show (l a)) => Show (Group l a)
instance (Read a, Read (l a)) => Read (Group l a)
instance Eq a => Eq (Group l a)
instance (LayoutClass l Window, LayoutClass l2 (Group l Window)) => LayoutClass (Groups l l2) Window
instance Message GroupsMessage
instance Show GroupsMessage
instance LayoutClass l a => LayoutClass (WithID l) a
instance Eq (WithID l a)


-- | Two layouts: one is a variant of the Grid layout that allows the
--   desired aspect ratio of windows to be specified. The other is like
--   Tall but places a grid with fixed number of rows and columns in the
--   master area and uses an aspect-ratio-specified layout for the slaves.
module XMonad.Layout.GridVariants

-- | The geometry change message understood by the master grid
data ChangeMasterGridGeom

-- | Change the number of master rows
IncMasterRows :: !Int -> ChangeMasterGridGeom

-- | Change the number of master columns
IncMasterCols :: !Int -> ChangeMasterGridGeom

-- | Set the number of master rows to absolute value
SetMasterRows :: !Int -> ChangeMasterGridGeom

-- | Set the number of master columns to absolute value
SetMasterCols :: !Int -> ChangeMasterGridGeom

-- | Set the fraction of the screen used by the master grid
SetMasterFraction :: !Rational -> ChangeMasterGridGeom

-- | Geometry change messages understood by Grid and SplitGrid
data ChangeGridGeom
SetGridAspect :: !Rational -> ChangeGridGeom
ChangeGridAspect :: !Rational -> ChangeGridGeom

-- | Grid layout. The parameter is the desired x:y aspect ratio of windows
data Grid a
Grid :: !Rational -> Grid a

-- | TallGrid layout. Parameters are
--   
--   <ul>
--   <li>number of master rows - number of master columns - portion of
--   screen used for master grid - x:y aspect ratio of slave windows -
--   increment for resize messages</li>
--   </ul>
--   
--   This exists mostly because it was introduced in an earlier version.
--   It's a fairly thin wrapper around <a>SplitGrid L</a>.
data TallGrid a
TallGrid :: !Int -> !Int -> !Rational -> !Rational -> !Rational -> TallGrid a

-- | SplitGrid layout. Parameters are
--   
--   <ul>
--   <li>side where the master is - number of master rows - number of
--   master columns - portion of screen used for master grid - x:y aspect
--   ratio of slave windows - increment for resize messages</li>
--   </ul>
data SplitGrid a
SplitGrid :: Orientation -> !Int -> !Int -> !Rational -> !Rational -> !Rational -> SplitGrid a

-- | Type to specify the side of the screen that holds the master area of a
--   SplitGrid.
data Orientation
T :: Orientation
B :: Orientation
L :: Orientation
R :: Orientation
instance Typeable ChangeGridGeom
instance Typeable ChangeMasterGridGeom
instance Read (Grid a)
instance Show (Grid a)
instance Eq Orientation
instance Read Orientation
instance Show Orientation
instance Read (SplitGrid a)
instance Show (SplitGrid a)
instance Read (TallGrid a)
instance Show (TallGrid a)
instance LayoutClass TallGrid a
instance Message ChangeMasterGridGeom
instance LayoutClass SplitGrid a
instance Message ChangeGridGeom
instance LayoutClass Grid a


-- | A simple layout that attempts to put all windows in a square grid.
module XMonad.Layout.Grid
data Grid a
Grid :: Grid a
GridRatio :: Double -> Grid a
arrange :: Double -> Rectangle -> [a] -> [(a, Rectangle)]
defaultRatio :: Double
instance Read (Grid a)
instance Show (Grid a)
instance LayoutClass Grid a


-- | A layout much like Tall, but using a multiple of a window's minimum
--   resize amount instead of a percentage of screen to decide where to
--   split. This is useful when you usually leave a text editor or terminal
--   in the master pane and like it to be 80 columns wide.
module XMonad.Layout.FixedColumn

-- | A tiling mode based on preserving a nice fixed width window. Supports
--   <a>Shrink</a>, <a>Expand</a> and <a>IncMasterN</a>.
data FixedColumn a
FixedColumn :: !Int -> !Int -> !Int -> !Int -> FixedColumn a
instance Read (FixedColumn a)
instance Show (FixedColumn a)
instance LayoutClass FixedColumn Window


-- | Dishes is a layout that stacks extra windows underneath the master
--   windows.
module XMonad.Layout.Dishes
data Dishes a
Dishes :: Int -> Rational -> Dishes a
instance Show (Dishes a)
instance Read (Dishes a)
instance LayoutClass Dishes a


-- | A data type to store the layout state
module XMonad.Util.Invisible
newtype Invisible m a
I :: (m a) -> Invisible m a
whenIJust :: Monad m => Invisible Maybe a -> (a -> m ()) -> m ()
fromIMaybe :: a -> Invisible Maybe a -> a
instance Monad m => Monad (Invisible m)
instance Functor m => Functor (Invisible m)
instance Monad m => Show (Invisible m a)
instance (Functor m, Monad m) => Read (Invisible m a)


-- | A Cross Layout with the main window in the center.
module XMonad.Layout.Cross

-- | A simple Cross Layout. It places the focused window in the center. The
--   proportion of the screen used by the main window is 4/5.
simpleCross :: Cross a

-- | The Cross Layout draws the focused window in the center of the screen
--   and part of the other windows on the sides. The <a>Shrink</a> and
--   <a>Expand</a> messages increment the size of the main window.
--   
--   The focus keybindings change the center window, while other windows
--   cycle through the side positions. With the Cross layout only four
--   windows are shown around the focused window, two ups and two downs, no
--   matter how many are in the current stack. I.e. focus down cycles the
--   window below focused into the center; focus up cycles the window
--   above.
data Cross a
Cross :: !Rational -> !Rational -> Cross a

-- | Proportion of screen occupied by the main window.
crossProp :: Cross a -> !Rational

-- | Percent of main window to increment by when resizing.
crossInc :: Cross a -> !Rational
instance Show (Cross a)
instance Read (Cross a)
instance LayoutClass Cross a


-- | Provides Column layout that places all windows in one column. Windows
--   heights are calculated from equation: H1<i>H2 = H2</i>H3 = ... = q,
--   where q is given. With Shrink/Expand messages you can change the q
--   value.
module XMonad.Layout.Column
data Column a
Column :: Float -> Column a
instance Read (Column a)
instance Show (Column a)
instance LayoutClass Column a


-- | Circle is an elliptical, overlapping layout, by Peter De Wachter
module XMonad.Layout.Circle
data Circle a
Circle :: Circle a
instance Read (Circle a)
instance Show (Circle a)
instance LayoutClass Circle Window


-- | A ManageHook matching on XProperties.
module XMonad.Hooks.XPropManage
xPropManageHook :: [XPropMatch] -> ManageHook
type XPropMatch = ([(Atom, [String] -> Bool)], Window -> X (WindowSet -> WindowSet))
pmX :: (Window -> X ()) -> Window -> X (WindowSet -> WindowSet)
pmP :: (WindowSet -> WindowSet) -> Window -> X (WindowSet -> WindowSet)


-- | Provides a simple interface for running a ~/.xmonad/hooks script with
--   the name of a hook.
module XMonad.Hooks.Script

-- | Execute a named script hook
execScriptHook :: MonadIO m => String -> m ()


-- | Configure where new windows should be added and which window should be
--   focused.
module XMonad.Hooks.InsertPosition

-- | insertPosition. A manage hook for placing new windows. XMonad's
--   default is the same as using: <tt>insertPosition Above Newer</tt>.
insertPosition :: Position -> Focus -> ManageHook
data Focus
Newer :: Focus
Older :: Focus
data Position
Master :: Position
End :: Position
Above :: Position
Below :: Position


-- | Makes XMonad set the _NET_WM_WINDOW_OPACITY atom for inactive windows,
--   which causes those windows to become slightly translucent if something
--   like xcompmgr is running
module XMonad.Hooks.FadeInactive

-- | Sets the opacity of a window
setOpacity :: Window -> Rational -> X ()

-- | Returns True if the window doesn't have the focus.
isUnfocused :: Query Bool

-- | Returns True if the window doesn't have the focus, and the window is
--   on the current workspace. This is specifically handy in a multi
--   monitor setup (xinerama) where multiple workspaces are visible. Using
--   this, non-focused workspaces are are not faded out making it easier to
--   look and read the content on them.
isUnfocusedOnCurrentWS :: Query Bool

-- | Makes a window completely opaque
fadeIn :: Window -> X ()

-- | Fades a window out by setting the opacity
fadeOut :: Rational -> Window -> X ()

-- | Fades a window by the specified amount if it satisfies the first
--   query, otherwise makes it opaque.
fadeIf :: Query Bool -> Rational -> Query Rational

-- | Sets the opacity of inactive windows to the specified amount
fadeInactiveLogHook :: Rational -> X ()

-- | Set the opacity of inactive windows, on the current workspace, to the
--   specified amount. This is specifically usefull in a multi monitor
--   setup. See <a>isUnfocusedOnCurrentWS</a>.
fadeInactiveCurrentWSLogHook :: Rational -> X ()

-- | Fades out every window by the amount returned by the query.
fadeOutLogHook :: Query Rational -> X ()


-- | A more flexible and general compositing interface than FadeInactive.
--   Windows can be selected and opacity specified by means of FadeHooks,
--   which are very similar to ManageHooks and use the same machinery.
module XMonad.Hooks.FadeWindows

-- | A <a>logHook</a> to fade windows under control of a <a>FadeHook</a>,
--   which is similar to but not identical to <a>ManageHook</a>.
fadeWindowsLogHook :: FadeHook -> X ()

-- | A FadeHook is similar to a ManageHook, but records window opacity.
type FadeHook = Query Opacity
data Opacity

-- | The identity <a>FadeHook</a>, which renders windows <a>opaque</a>.
idFadeHook :: FadeHook

-- | Render a window fully opaque.
opaque :: FadeHook

-- | An alias for <a>transparent</a>.
invisible, solid :: FadeHook

-- | Render a window fully transparent.
transparent :: FadeHook

-- | Specify a window's transparency.
transparency :: Rational -> FadeHook

-- | An alias for <a>transparency</a>.
--   
--   An alias for <a>transparency</a>.
fadeTo, fadeBy, translucence :: Rational -> FadeHook

-- | Specify a window's opacity; this is the inverse of
--   <a>transparency</a>.
opacity :: Rational -> FadeHook

-- | A <a>handleEventHook</a> to handle fading and unfading of newly mapped
--   or unmapped windows; this avoids problems with layouts such as
--   <a>XMonad.Layout.Full</a> or <a>XMonad.Layout.Tabbed</a>. This hook
--   may also be useful with <a>XMonad.Hooks.FadeInactive</a>.
fadeWindowsEventHook :: Event -> X All

-- | Like <tt>doF</tt>, but usable with <a>ManageHook</a>-like hooks that
--   aren't <a>Query</a> wrapped around transforming functions
--   (<a>Endo</a>).
doS :: Monoid m => m -> Query m

-- | A Query to determine if a window is floating.
isFloating :: Query Bool

-- | Returns True if the window doesn't have the focus.
isUnfocused :: Query Bool
instance Monoid Opacity


-- | EDSL for specifying window properties; various utilities related to
--   window properties.
module XMonad.Util.WindowProperties

-- | Most of the property constructors are quite self-explaining.
data Property
Title :: String -> Property
ClassName :: String -> Property
Resource :: String -> Property

-- | WM_WINDOW_ROLE property
Role :: String -> Property

-- | WM_CLIENT_MACHINE property
Machine :: String -> Property
And :: Property -> Property -> Property
Or :: Property -> Property -> Property
Not :: Property -> Property
Const :: Bool -> Property

-- | Does given window have this property?
hasProperty :: Property -> Window -> X Bool

-- | Does the focused window have this property?
focusedHasProperty :: Property -> X Bool

-- | Find all existing windows with specified property
allWithProperty :: Property -> X [Window]

-- | Convert property to <a>Query</a> <a>Bool</a> (see
--   <a>XMonad.ManageHook</a>)
propertyToQuery :: Property -> Query Bool

-- | Get a window property from atom
getProp32 :: Atom -> Window -> X (Maybe [CLong])

-- | Get a window property from string
getProp32s :: String -> Window -> X (Maybe [CLong])
instance Read Property
instance Show Property


-- | A layout combinator that sends windows matching given predicate to one
--   rectangle and the rest to another.
module XMonad.Layout.LayoutBuilderP

-- | Data type for our layout.
data LayoutP p l1 l2 a
LayoutP :: (Maybe a) -> (Maybe a) -> p -> SubBox -> (Maybe SubBox) -> (l1 a) -> (Maybe (l2 a)) -> LayoutP p l1 l2 a

-- | Use the specified layout in the described area windows that match
--   given predicate and send the rest of the windows to the next layout in
--   the chain. It is possible to supply an alternative area that will then
--   be used instead, if there are no windows to send to the next layout.
layoutP :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a, LayoutClass l3 a, Predicate p a) => p -> SubBox -> Maybe SubBox -> l1 a -> LayoutP p l2 l3 a -> LayoutP p l1 (LayoutP p l2 l3) a

-- | Use the specified layout in the described area for all remaining
--   windows.
layoutAll :: (Read a, Eq a, LayoutClass l1 a, Predicate p a) => SubBox -> l1 a -> LayoutP p l1 Full a

-- | Create a box with only relative measurements.
relBox :: Rational -> Rational -> Rational -> Rational -> SubBox

-- | Create a box with only absolute measurements. If the values are
--   negative, the total remaining space will be added. For sizes it will
--   also be added for zeroes.
absBox :: Int -> Int -> Int -> Int -> SubBox

-- | Type class for predicates. This enables us to manage not only Windows,
--   but any objects, for which instance Predicate is defined.
--   
--   Another instance exists in XMonad.Util.WindowPropertiesRE in
--   xmonad-extras
class Predicate p w
alwaysTrue :: Predicate p w => Proxy w -> p
checkPredicate :: Predicate p w => p -> w -> X Bool

-- | Contains no actual data, but is needed to help select the correct
--   instance of <a>Predicate</a>
data Proxy a
Proxy :: Proxy a
instance (Show p, Show a, Show (l1 a), Show (l2 a)) => Show (LayoutP p l1 l2 a)
instance (Read p, Read a, Read (l1 a), Read (l2 a)) => Read (LayoutP p l1 l2 a)
instance Predicate Property Window
instance (LayoutClass l1 w, LayoutClass l2 w, Predicate p w, Show w, Read w, Eq w, Typeable w, Show p) => LayoutClass (LayoutP p l1 l2) w


-- | Sets the WM name to a given string, so that it could be detected using
--   _NET_SUPPORTING_WM_CHECK protocol.
--   
--   May be useful for making Java GUI programs work, just set WM name to
--   <a>LG3D</a> and use Java 1.6u1 (1.6.0_01-ea-b03 works for me) or
--   later.
--   
--   To your <tt>~/.xmonad/xmonad.hs</tt> file, add the following line:
--   
--   <pre>
--   import XMonad.Hooks.SetWMName
--   </pre>
--   
--   Then edit your <tt>startupHook</tt>:
--   
--   <pre>
--   startupHook = setWMName "LG3D"
--   </pre>
--   
--   For details on the problems with running Java GUI programs in
--   non-reparenting WMs, see
--   <a>http://bugs.sun.com/bugdatabase/view_bug.do?bug_id=6429775</a> and
--   related bugs.
--   
--   Setting WM name to <a>compiz</a> does not solve the problem, because
--   of yet another bug in AWT code (related to insets). For LG3D insets
--   are explicitly set to 0, while for other WMs the insets are "guessed"
--   and the algorithm fails miserably by guessing absolutely bogus values.
--   
--   For detailed instructions on editing your hooks, see
--   <a>XMonad.Doc.Extending#4</a>.
module XMonad.Hooks.SetWMName

-- | sets WM name
setWMName :: String -> X ()


-- | Implemented in your <tt>logHook</tt>, Java swing applications will not
--   misbehave when it comes to taking and losing focus.
--   
--   This has been done by taking the patch in
--   <a>http://code.google.com/p/xmonad/issues/detail?id=177</a> and
--   refactoring it so that it can be included in
--   <tt>~/.xmonad/xmonad.hs</tt>.
--   
--   <pre>
--   conf' =
--     conf {
--       logHook = takeTopFocus
--     }
--   </pre>
module XMonad.Hooks.ICCCMFocus

-- | Common non-predefined atoms
atom_WM_TAKE_FOCUS :: X Atom
takeFocusX :: Window -> X ()

-- | The value to add to your log hook configuration.
takeTopFocus :: X ()


-- | Module to dump window information for diagnostic/debugging purposes.
--   See <a>XMonad.Hooks.DebugEvents</a> and <a>XMonad.Hooks.DebugStack</a>
--   for practical uses.
module XMonad.Util.DebugWindow

-- | Output a window by ID in hex, decimal, its ICCCM resource name and
--   class, and its title if available. Also indicate override_redirect
--   with an exclamation mark, and wrap in brackets if it is unmapped or
--   withdrawn.
debugWindow :: Window -> X String


-- | Dump the state of the <tt>StackSet</tt>. A <tt>logHook</tt> and
--   <tt>handleEventHook</tt> are also provided.
module XMonad.Hooks.DebugStack

-- | Print the state of the current window stack to <tt>stderr</tt>, which
--   for most installations goes to <tt>~/.xsession-errors</tt>.
--   <a>XMonad.Util.DebugWindow</a> is used to display the individual
--   windows.
debugStack :: X ()

-- | Dump the state of the current <tt>StackSet</tt> as a multiline
--   <a>String</a>. <tt> stack [ mm ,(*) ww , ww ] float { ww , ww } </tt>
--   
--   One thing I'm not sure of is where the zipper is when focus is on a
--   floating window.
debugStackString :: X String

-- | The above packaged as a <a>logHook</a>. (Currently this is identical.)
debugStackLogHook :: X ()

-- | The above packaged as a <a>handleEventHook</a>. You almost certainly
--   do not want to use this unconditionally, as it will cause massive
--   amounts of output and possibly slow <tt>xmonad</tt> down severely.
debugStackEventHook :: Event -> X All


-- | A debugging module to track key events, useful when you can't tell
--   whether xmonad is processing some or all key events.
module XMonad.Hooks.DebugKeyEvents

-- | Print key events to stderr for debugging
debugKeyEvents :: Event -> X All


-- | Module to dump diagnostic information about X11 events received by
--   <tt>xmonad</tt>. This is incomplete due to <a>Event</a> being
--   incomplete and not providing information about a number of events, and
--   enforcing artificial constraints on others (for example
--   <tt>ClientMessage</tt>); the <tt>X11</tt> package will require a
--   number of changes to fix these problems.
module XMonad.Hooks.DebugEvents

-- | Event hook to dump all received events. You should probably not use
--   this unconditionally; it will produce massive amounts of output.
debugEventsHook :: Event -> X All
instance Functor Decoder
instance Monad Decoder
instance MonadIO Decoder
instance MonadState DecodeState Decoder
instance MonadReader Decode Decoder


-- | A layout that splits the screen horizontally and shows two windows.
--   The left window is always the master window, and the right is either
--   the currently focused window or the second window in layout order.
module XMonad.Layout.TwoPane
data TwoPane a
TwoPane :: Rational -> Rational -> TwoPane a
instance Show (TwoPane a)
instance Read (TwoPane a)
instance LayoutClass TwoPane a


-- | Divide a single screen into multiple screens.
module XMonad.Layout.LayoutScreens

-- | Modify all screens.
layoutScreens :: LayoutClass l Int => Int -> l Int -> X ()

-- | Modify current screen.
layoutSplitScreen :: LayoutClass l Int => Int -> l Int -> X ()
fixedLayout :: [Rectangle] -> FixedLayout a
data FixedLayout a
instance Read (FixedLayout a)
instance Show (FixedLayout a)
instance LayoutClass FixedLayout a


-- | A gapless tiled layout that attempts to obey window size hints, rather
--   than simply ignoring them.
module XMonad.Layout.HintedTile
data HintedTile a
HintedTile :: !Int -> !Rational -> !Rational -> !Alignment -> !Orientation -> HintedTile a

-- | number of windows in the master pane
nmaster :: HintedTile a -> !Int

-- | how much to change when resizing
delta :: HintedTile a -> !Rational

-- | ratio between master/nonmaster panes
frac :: HintedTile a -> !Rational

-- | Where to place windows that are smaller than their preordained
--   rectangles.
alignment :: HintedTile a -> !Alignment

-- | Tall or Wide (mirrored) layout?
orientation :: HintedTile a -> !Orientation
data Orientation

-- | Lay out windows similarly to Mirror tiled.
Wide :: Orientation

-- | Lay out windows similarly to tiled.
Tall :: Orientation
data Alignment
TopLeft :: Alignment
Center :: Alignment
BottomRight :: Alignment
instance Show Orientation
instance Read Orientation
instance Eq Orientation
instance Ord Orientation
instance Show Alignment
instance Read Alignment
instance Eq Alignment
instance Ord Alignment
instance Show (HintedTile a)
instance Read (HintedTile a)
instance LayoutClass HintedTile Window


-- | A module to toggle between two layouts.
module XMonad.Layout.ToggleLayouts
toggleLayouts :: (LayoutClass lt a, LayoutClass lf a) => lt a -> lf a -> ToggleLayouts lt lf a
data ToggleLayout
ToggleLayout :: ToggleLayout
Toggle :: String -> ToggleLayout
data ToggleLayouts lt lf a
instance Typeable ToggleLayout
instance (Read (lt a), Read (lf a)) => Read (ToggleLayouts lt lf a)
instance (Show (lt a), Show (lf a)) => Show (ToggleLayouts lt lf a)
instance Read ToggleLayout
instance Show ToggleLayout
instance (LayoutClass lt a, LayoutClass lf a) => LayoutClass (ToggleLayouts lt lf) a
instance Message ToggleLayout


-- | 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
--   <a>XMonad.Layout.Combo</a>. 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 XMonad.Layout.Square
data Square a
Square :: Square a
instance Read (Square a)
instance Show (Square a)
instance LayoutClass Square a


-- | A module for setting the default mouse cursor.
--   
--   Some ideas shamelessly stolen from Nils Schweinsberg; thanks!
module XMonad.Util.Cursor

-- | Set the default (root) cursor
setDefaultCursor :: Glyph -> X ()


-- | This module fixes some of the keybindings for the francophone among
--   you who use an AZERTY keyboard layout. Config stolen from TeXitoi's
--   config on the wiki.
module XMonad.Config.Azerty
azertyConfig :: XConfig (Choose Tall (Choose (Mirror Tall) Full))
azertyKeys :: XConfig l -> Map (KeyMask, KeySym) (X ())


-- | LayoutClass that puts non-focused windows in ribbons at the top and
--   bottom of the screen.
module XMonad.Layout.Accordion
data Accordion a
Accordion :: Accordion a
instance Read (Accordion a)
instance Show (Accordion a)
instance LayoutClass Accordion Window


-- | A module for writing easy layout modifiers, which do not define a
--   layout in and of themselves, but modify the behavior of or add new
--   functionality to other layouts. If you ever find yourself writing a
--   layout which takes another layout as a parameter, chances are you
--   should be writing a LayoutModifier instead!
--   
--   In case it is not clear, this module is not intended to help you
--   configure xmonad, it is to help you write other extension modules. So
--   get hacking!
module XMonad.Layout.LayoutModifier
class (Show (m a), Read (m a)) => LayoutModifier m a where modifyLayout _ w r = runLayout w r modifyLayoutWithUpdate m w r = flip (,) Nothing `fmap` modifyLayout m w r handleMess m mess | Just Hide <- fromMessage mess = doUnhook | Just ReleaseResources <- fromMessage mess = doUnhook | otherwise = return $ pureMess m mess where doUnhook = do { unhook m; return Nothing } handleMessOrMaybeModifyIt m mess = do { mm' <- handleMess m mess; return (Left `fmap` mm') } pureMess _ _ = Nothing redoLayout m r ms wrs = do { hook m; return $ pureModifier m r ms wrs } pureModifier _ _ _ wrs = (wrs, Nothing) hook _ = return () unhook _ = return () modifierDescription = const "" modifyDescription m l = modifierDescription m <> description l where "" <> x = x x <> y = x ++ " " ++ y
modifyLayout :: (LayoutModifier m a, LayoutClass l a) => m a -> Workspace WorkspaceId (l a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (l a))
modifyLayoutWithUpdate :: (LayoutModifier m a, LayoutClass l a) => m a -> Workspace WorkspaceId (l a) a -> Rectangle -> X (([(a, Rectangle)], Maybe (l a)), Maybe (m a))
handleMess :: LayoutModifier m a => m a -> SomeMessage -> X (Maybe (m a))
handleMessOrMaybeModifyIt :: LayoutModifier m a => m a -> SomeMessage -> X (Maybe (Either (m a) SomeMessage))
pureMess :: LayoutModifier m a => m a -> SomeMessage -> Maybe (m a)
redoLayout :: LayoutModifier m a => m a -> Rectangle -> Maybe (Stack a) -> [(a, Rectangle)] -> X ([(a, Rectangle)], Maybe (m a))
pureModifier :: LayoutModifier m a => m a -> Rectangle -> Maybe (Stack a) -> [(a, Rectangle)] -> ([(a, Rectangle)], Maybe (m a))
hook :: LayoutModifier m a => m a -> X ()
unhook :: LayoutModifier m a => m a -> X ()
modifierDescription :: LayoutModifier m a => m a -> String
modifyDescription :: (LayoutModifier m a, LayoutClass l a) => m a -> l a -> String

-- | A <a>ModifiedLayout</a> is simply a container for a layout modifier
--   combined with an underlying layout. It is, of course, itself a layout
--   (i.e. an instance of <a>LayoutClass</a>).
data ModifiedLayout m l a
ModifiedLayout :: (m a) -> (l a) -> ModifiedLayout m l a
instance (Read (m a), Read (l a)) => Read (ModifiedLayout m l a)
instance (Show (m a), Show (l a)) => Show (ModifiedLayout m l a)
instance (LayoutModifier m a, LayoutClass l a) => LayoutClass (ModifiedLayout m l) a


-- | Make a given layout display without borders. This is useful for
--   full-screen or tabbed layouts, where you don't really want to waste a
--   couple of pixels of real estate just to inform yourself that the
--   visible window has focus.
module XMonad.Layout.NoBorders

-- | Removes all window borders from the specified layout.
noBorders :: LayoutClass l Window => l Window -> ModifiedLayout WithBorder l Window

-- | Removes the borders from a window under one of the following
--   conditions:
--   
--   <ul>
--   <li>There is only one screen and only one window. In this case it's
--   obvious that it has the focus, so no border is needed.</li>
--   <li>A floating window covers the entire screen (e.g. mplayer).</li>
--   </ul>
smartBorders :: LayoutClass l a => l a -> ModifiedLayout SmartBorder l a

-- | Forces a layout to use the specified border width. <a>noBorders</a> is
--   equivalent to <tt><a>withBorder</a> 0</tt>.
withBorder :: LayoutClass l a => Dimension -> l a -> ModifiedLayout WithBorder l a

-- | Apply a datatype that has a SetsAmbiguous instance to provide a list
--   of windows that should not have borders.
--   
--   This gives flexibility over when borders should be drawn, in
--   particular with xinerama setups: <a>Ambiguity</a> has a number of
--   useful <a>SetsAmbiguous</a> instances
lessBorders :: (SetsAmbiguous p, Read p, Show p, LayoutClass l a) => p -> l a -> ModifiedLayout (ConfigurableBorder p) l a

-- | SetsAmbiguous allows custom actions to generate lists of windows that
--   should not have borders drawn through <a>ConfigurableBorder</a>
--   
--   To add your own (though perhaps those options would better belong as
--   an aditional constructor to <a>Ambiguity</a>), you can add the
--   function as such:
--   
--   <pre>
--   data MyAmbiguity = MyAmbiguity deriving (Read, Show)
--   </pre>
--   
--   <pre>
--   instance SetsAmbiguous MyAmbiguity where
--    hiddens _ wset mst wrs = otherHiddens Screen \\ otherHiddens OnlyFloat
--       where otherHiddens p = hiddens p wset mst wrs
--   </pre>
--   
--   The above example is redundant, because you can have the same result
--   with:
--   
--   <pre>
--   layoutHook = lessBorders (Combine Difference Screen OnlyFloat) (Tall 1 0.5 0.03 ||| ... )
--   </pre>
--   
--   To get the same result as <a>smartBorders</a>:
--   
--   <pre>
--   layoutHook = lessBorders Never (Tall 1 0.5 0.03 ||| ...)
--   </pre>
--   
--   This indirect method is required to keep the <a>Read</a> and
--   <a>Show</a> for ConfigurableBorder so that xmonad can serialize state.
class SetsAmbiguous p
hiddens :: SetsAmbiguous p => p -> WindowSet -> Maybe (Stack Window) -> [(Window, Rectangle)] -> [Window]

-- | In order of increasing ambiguity (less borders more frequently), where
--   subsequent constructors add additional cases where borders are not
--   drawn than their predecessors. These behaviors make most sense with
--   with multiple screens: for single screens, <a>Never</a> or
--   <a>smartBorders</a> makes more sense.
data Ambiguity

-- | This constructor is used to combine the borderless windows provided by
--   the SetsAmbiguous instances from two other <a>Ambiguity</a> data
--   types.
Combine :: With -> Ambiguity -> Ambiguity -> Ambiguity

-- | Only remove borders on floating windows that cover the whole screen
OnlyFloat :: Ambiguity

-- | Never remove borders when ambiguous: this is the same as smartBorders
Never :: Ambiguity

-- | Focus in an empty screens does not count as ambiguous.
EmptyScreen :: Ambiguity

-- | No borders on full when all other screens have borders.
OtherIndicated :: Ambiguity

-- | Borders are never drawn on singleton screens. With this one you really
--   need another way such as a statusbar to detect focus.
Screen :: Ambiguity

-- | Used to indicate to the <a>SetsAmbiguous</a> instance for
--   <a>Ambiguity</a> how two lists should be combined.
data With

-- | uses <a>union</a>
Union :: With

-- | uses <a>\\</a>
Difference :: With

-- | uses <a>intersect</a>
Intersection :: With
type SmartBorder = ConfigurableBorder Ambiguity
data WithBorder a
data ConfigurableBorder p w
instance Read a => Read (WithBorder a)
instance Show a => Show (WithBorder a)
instance (Read p, Read w) => Read (ConfigurableBorder p w)
instance (Show p, Show w) => Show (ConfigurableBorder p w)
instance Read With
instance Show With
instance Read Ambiguity
instance Show Ambiguity
instance SetsAmbiguous Ambiguity
instance (Read p, Show p, SetsAmbiguous p) => LayoutModifier (ConfigurableBorder p) Window
instance LayoutModifier WithBorder Window


-- | BoringWindows is an extension to allow windows to be marked boring
module XMonad.Layout.BoringWindows
boringWindows :: (LayoutClass l a, Eq a) => l a -> ModifiedLayout BoringWindows l a

-- | Mark windows that are not given rectangles as boring
boringAuto :: (LayoutClass l a, Eq a) => l a -> ModifiedLayout BoringWindows l a
markBoring, focusMaster, focusDown, focusUp, clearBoring :: X ()

-- | UpdateBoring is sent before attempting to view another boring window,
--   so that layouts have a chance to mark boring windows.
data UpdateBoring
UpdateBoring :: UpdateBoring
data BoringMessage
Replace :: String -> [Window] -> BoringMessage
Merge :: String -> [Window] -> BoringMessage
data BoringWindows a
instance Typeable BoringMessage
instance Typeable UpdateBoring
instance Typeable1 BoringWindows
instance Read BoringMessage
instance Show BoringMessage
instance Show a => Show (BoringWindows a)
instance Read a => Read (BoringWindows a)
instance LayoutModifier BoringWindows Window
instance Message UpdateBoring
instance Message BoringMessage


-- | A helper module to visualize the process of dragging a window by
--   making it follow the mouse cursor. See
--   <a>XMonad.Layout.WindowSwitcherDecoration</a> for a module that makes
--   use of this.
module XMonad.Layout.DraggingVisualizer
draggingVisualizer :: LayoutClass l Window => l Window -> ModifiedLayout DraggingVisualizer l Window
data DraggingVisualizerMsg
DraggingWindow :: Window -> Rectangle -> DraggingVisualizerMsg
DraggingStopped :: DraggingVisualizerMsg
data DraggingVisualizer a
instance Typeable DraggingVisualizerMsg
instance Read (DraggingVisualizer a)
instance Show (DraggingVisualizer a)
instance Eq DraggingVisualizerMsg
instance LayoutModifier DraggingVisualizer Window
instance Message DraggingVisualizerMsg


-- | 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.
module XMonad.Layout.AutoMaster

-- | User interface function
autoMaster :: LayoutClass l a => Int -> Float -> l a -> ModifiedLayout AutoMaster l a

-- | Data type for layout modifier
data AutoMaster a
instance Read (AutoMaster a)
instance Show (AutoMaster a)
instance Eq w => LayoutModifier AutoMaster w


-- | 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.
module XMonad.Layout.CenteredMaster

-- | 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

-- | 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

-- | Data type for LayoutModifier
data CenteredMaster a
data TopRightMaster a
instance Read (CenteredMaster a)
instance Show (CenteredMaster a)
instance Read (TopRightMaster a)
instance Show (TopRightMaster a)
instance LayoutModifier TopRightMaster Window
instance LayoutModifier CenteredMaster Window


-- | Layout modifier that can modify the description of its underlying
--   layout on a (hopefully) flexible way.
module XMonad.Layout.Renamed

-- | Apply a list of <a>Rename</a> values to a layout, from left to right.
renamed :: [Rename a] -> l a -> ModifiedLayout Rename l a

-- | The available renaming operations
data Rename a

-- | Remove a number of characters from the left
CutLeft :: Int -> Rename a

-- | Remove a number of characters from the right
CutRight :: Int -> Rename a

-- | Add a string on the right
Append :: String -> Rename a

-- | Add a string on the left
Prepend :: String -> Rename a

-- | Remove a number of words from the left
CutWordsLeft :: Int -> Rename a

-- | Remove a number of words from the right
CutWordsRight :: Int -> Rename a

-- | Add a string to the right, prepending a space to it if necessary
AppendWords :: String -> Rename a

-- | Add a string to the left, appending a space to it if necessary
PrependWords :: String -> Rename a

-- | Repace with another wtring
Replace :: String -> Rename a

-- | Apply a list of modifications in left-to-right order
Chain :: [Rename a] -> Rename a
instance Show (Rename a)
instance Read (Rename a)
instance Eq (Rename a)
instance LayoutModifier Rename a


-- | A module for assigning a name to a given layout. Deprecated, use
--   <a>XMonad.Layout.Renamed</a> instead.
module XMonad.Layout.Named

-- | (Deprecated) Rename a layout.
named :: String -> l a -> ModifiedLayout Rename l a

-- | (Deprecated) Remove the first word of the name.
nameTail :: l a -> ModifiedLayout Rename l a


-- | Provides message "escaping" and filtering facilities which help
--   control complex nested layouts.
module XMonad.Layout.MessageControl

-- | the Ignore layout modifier. Prevents its inner layout from receiving
--   messages of a certain type.
data Ignore m l w

-- | Applies the Ignore layout modifier to a layout, blocking all messages
--   of the same type as the one passed as its first argument.
ignore :: (Message m, LayoutClass l w) => m -> l w -> (Ignore m l w)

-- | the UnEscape layout modifier. Listens to <a>EscapedMessage</a>s and
--   sends their nested message to the inner layout.
data UnEscape w

-- | Applies the UnEscape layout modifier to a layout.
unEscape :: LayoutClass l w => l w -> ModifiedLayout UnEscape l w

-- | Data type for an escaped message. Send with <a>escape</a>.
newtype EscapedMessage
Escape :: SomeMessage -> EscapedMessage

-- | Creates an <a>EscapedMessage</a>.
escape :: Message m => m -> EscapedMessage
instance Typeable EscapedMessage
instance Show (l w) => Show (Ignore m l w)
instance Read (l w) => Read (Ignore m l w)
instance Show (UnEscape w)
instance Read (UnEscape w)
instance Message EscapedMessage
instance LayoutModifier UnEscape a
instance (Message m, LayoutClass l w) => LayoutClass (Ignore m l) w


-- | Layout modfier suitable for workspace with multi-windowed instant
--   messenger (like Psi or Tkabber).
module XMonad.Layout.IM

-- | Most of the property constructors are quite self-explaining.
data Property
Title :: String -> Property
ClassName :: String -> Property
Resource :: String -> Property

-- | WM_WINDOW_ROLE property
Role :: String -> Property

-- | WM_CLIENT_MACHINE property
Machine :: String -> Property
And :: Property -> Property -> Property
Or :: Property -> Property -> Property
Not :: Property -> Property
Const :: Bool -> Property

-- | This is for compatibility with old configs only and will be removed in
--   future versions!
data IM a
IM :: Rational -> Property -> IM a

-- | Modifier which converts given layout to IM-layout (with dedicated
--   space for roster and original layout for chat windows)
withIM :: LayoutClass l a => Rational -> Property -> l a -> ModifiedLayout AddRoster l a

-- | IM layout modifier applied to the Grid layout
gridIM :: Rational -> Property -> ModifiedLayout AddRoster Grid a

-- | Data type for LayoutModifier which converts given layout to IM-layout
--   (with dedicated space for the roster and original layout for chat
--   windows)
data AddRoster a
instance Read (AddRoster a)
instance Show (AddRoster a)
instance Read (IM a)
instance Show (IM a)
instance LayoutClass IM Window
instance LayoutModifier AddRoster Window


-- | A layout modifier that limits the number of windows that can be shown.
--   See <a>XMonad.Layout.Minimize</a> for manually setting hidden windows.
module XMonad.Layout.LimitWindows

-- | Only display the first <tt>n</tt> windows.
limitWindows :: Int -> l a -> ModifiedLayout LimitWindows l a

-- | Only display <tt>n</tt> windows around the focused window. This makes
--   sense with layouts that arrange windows linearily, like
--   <a>Accordion</a>.
limitSlice :: Int -> l a -> ModifiedLayout LimitWindows l a

-- | Only display the first <tt>m</tt> windows and <tt>r</tt> others. The
--   <tt>IncMasterN</tt> message will change <tt>m</tt>, as well as passing
--   it onto the underlying layout.
limitSelect :: Int -> Int -> l a -> ModifiedLayout Selection l a
increaseLimit :: X ()
decreaseLimit :: X ()
setLimit :: Int -> X ()
data LimitWindows a
data Selection a
instance Typeable LimitChange
instance Read SliceStyle
instance Show SliceStyle
instance Read (LimitWindows a)
instance Show (LimitWindows a)
instance Read (Selection a)
instance Show (Selection a)
instance Eq (Selection a)
instance LayoutModifier Selection a
instance LayoutModifier LimitWindows a
instance Message LimitChange


-- | Layout modfier that adds a master window to another layout.
module XMonad.Layout.Master
mastered :: LayoutClass l a => Rational -> Rational -> l a -> ModifiedLayout AddMaster l a

-- | Modifier which converts given layout to a mastered one
multimastered :: LayoutClass l a => Int -> Rational -> Rational -> l a -> ModifiedLayout AddMaster l a

-- | Data type for LayoutModifier which converts given layout to a mastered
--   layout
data AddMaster a
instance Show (AddMaster a)
instance Read (AddMaster a)
instance LayoutModifier AddMaster Window


-- | Some convenient common instances of the <a>Transformer</a> class, for
--   use with <a>XMonad.Layout.MultiToggle</a>.
module XMonad.Layout.MultiToggle.Instances
data StdTransformers

-- | switch to Full layout
FULL :: StdTransformers

-- | switch to Full with no borders
NBFULL :: StdTransformers

-- | Mirror the current layout.
MIRROR :: StdTransformers

-- | Remove borders.
NOBORDERS :: StdTransformers

-- | Apply smart borders.
SMARTBORDERS :: StdTransformers
instance Typeable StdTransformers
instance Read StdTransformers
instance Show StdTransformers
instance Eq StdTransformers
instance Transformer StdTransformers Window


-- | Configure layouts on a per-host basis: use layouts and apply layout
--   modifiers selectively, depending on the host. Heavily based on
--   <a>XMonad.Layout.PerWorkspace</a> by Brent Yorgey.
module XMonad.Layout.OnHost

-- | Structure for representing a host-specific layout along with a layout
--   for all other hosts. We store the names of hosts to be matched, and
--   the two layouts. We save the layout choice in the Bool, to be used to
--   implement description.
data OnHost l1 l2 a

-- | Specify one layout to use on a particular host, and another to use on
--   all others. The second layout can be another call to <a>onHost</a>,
--   and so on.
onHost :: (LayoutClass l1 a, LayoutClass l2 a) => String -> (l1 a) -> (l2 a) -> OnHost l1 l2 a

-- | Specify one layout to use on a particular set of hosts, and another to
--   use on all other hosts.
onHosts :: (LayoutClass l1 a, LayoutClass l2 a) => [String] -> (l1 a) -> (l2 a) -> OnHost l1 l2 a

-- | Specify a layout modifier to apply on a particular host; layouts on
--   all other hosts will remain unmodified.
modHost :: LayoutClass l a => String -> (l a -> ModifiedLayout lm l a) -> l a -> OnHost (ModifiedLayout lm l) l a

-- | Specify a layout modifier to apply on a particular set of hosts;
--   layouts on all other hosts will remain unmodified.
modHosts :: LayoutClass l a => [String] -> (l a -> ModifiedLayout lm l a) -> l a -> OnHost (ModifiedLayout lm l) l a
instance (Read (l1 a), Read (l2 a)) => Read (OnHost l1 l2 a)
instance (Show (l1 a), Show (l2 a)) => Show (OnHost l1 l2 a)
instance (LayoutClass l1 a, LayoutClass l2 a, Show a) => LayoutClass (OnHost l1 l2) a


-- | Configure layouts on a per-workspace basis: use layouts and apply
--   layout modifiers selectively, depending on the workspace.
module XMonad.Layout.PerWorkspace

-- | Structure for representing a workspace-specific layout along with a
--   layout for all other workspaces. We store the tags of workspaces to be
--   matched, and the two layouts. We save the layout choice in the Bool,
--   to be used to implement description.
data PerWorkspace l1 l2 a

-- | Specify one layout to use on a particular workspace, and another to
--   use on all others. The second layout can be another call to
--   <a>onWorkspace</a>, and so on.
onWorkspace :: (LayoutClass l1 a, LayoutClass l2 a) => WorkspaceId -> (l1 a) -> (l2 a) -> PerWorkspace l1 l2 a

-- | Specify one layout to use on a particular set of workspaces, and
--   another to use on all other workspaces.
onWorkspaces :: (LayoutClass l1 a, LayoutClass l2 a) => [WorkspaceId] -> (l1 a) -> (l2 a) -> PerWorkspace l1 l2 a

-- | Specify a layout modifier to apply to a particular workspace; layouts
--   on all other workspaces will remain unmodified.
modWorkspace :: LayoutClass l a => WorkspaceId -> (l a -> ModifiedLayout lm l a) -> l a -> PerWorkspace (ModifiedLayout lm l) l a

-- | Specify a layout modifier to apply to a particular set of workspaces;
--   layouts on all other workspaces will remain unmodified.
modWorkspaces :: LayoutClass l a => [WorkspaceId] -> (l a -> ModifiedLayout lm l a) -> l a -> PerWorkspace (ModifiedLayout lm l) l a
instance (Read (l1 a), Read (l2 a)) => Read (PerWorkspace l1 l2 a)
instance (Show (l1 a), Show (l2 a)) => Show (PerWorkspace l1 l2 a)
instance (LayoutClass l1 a, LayoutClass l2 a, Show a) => LayoutClass (PerWorkspace l1 l2) a


-- | Layout modifier that tracks focus in the tiled layer while the
--   floating layer is in use. This is particularly helpful for tiled
--   layouts where the focus determines what is visible.
--   
--   The relevant bug is Issue 4
--   <a>http://code.google.com/p/xmonad/issues/detail?id=4</a>.
module XMonad.Layout.TrackFloating

-- | Runs another layout with a remembered focus, provided:
--   
--   <ul>
--   <li>the subset of windows doesn't include the focus in XState</li>
--   <li>it was previously run with a subset that included the XState
--   focus</li>
--   <li>the remembered focus hasn't since been killed</li>
--   </ul>
trackFloating :: l a -> ModifiedLayout TrackFloating l a
data TrackFloating a
instance Read (TrackFloating a)
instance Show (TrackFloating a)
instance Eq (TrackFloating a)
instance LayoutModifier TrackFloating Window


-- | Makes it possible to minimize windows, temporarily removing them from
--   the layout until they are restored.
module XMonad.Layout.Minimize
minimize :: LayoutClass l Window => l Window -> ModifiedLayout Minimize l Window
minimizeWindow :: Window -> X ()
data MinimizeMsg
RestoreMinimizedWin :: Window -> MinimizeMsg
RestoreNextMinimizedWin :: MinimizeMsg
data Minimize a
instance Typeable MinimizeMsg
instance Read (Minimize a)
instance Show (Minimize a)
instance Eq MinimizeMsg
instance LayoutModifier Minimize Window
instance Message MinimizeMsg


-- | Handles window manager hints to minimize and restore windows. Use this
--   with XMonad.Layout.Minimize.
module XMonad.Hooks.Minimize
minimizeEventHook :: Event -> X All


-- | (Deprecated: Use XMonad.Hooks.Minimize) Lets you restore minimized
--   windows (see <a>XMonad.Layout.Minimize</a>) by selecting them on a
--   taskbar (listens for _NET_ACTIVE_WINDOW and WM_CHANGE_STATE).
module XMonad.Hooks.RestoreMinimized
data RestoreMinimized
RestoreMinimized :: RestoreMinimized
restoreMinimizedEventHook :: Event -> X All
instance Show RestoreMinimized
instance Read RestoreMinimized


-- | Temporarily yanks the focused window out of the layout to mostly fill
--   the screen.
module XMonad.Layout.Maximize
maximize :: LayoutClass l Window => l Window -> ModifiedLayout Maximize l Window
maximizeRestore :: Window -> MaximizeRestore
data Maximize a
data MaximizeRestore
instance Typeable MaximizeRestore
instance Read (Maximize a)
instance Show (Maximize a)
instance Eq MaximizeRestore
instance LayoutModifier Maximize Window
instance Message MaximizeRestore


-- | Warp the pointer to a given window or screen.
module XMonad.Actions.Warp

-- | Move the mouse cursor to a corner of the focused window. Useful for
--   uncluttering things.
--   
--   Internally, this uses numerical parameters. We parametrize on the
--   <a>Corner</a> type so the user need not see the violence inherent in
--   the system.
--   
--   <a>warpToScreen</a> and <a>warpToWindow</a> can be used in a variety
--   of ways. Suppose you wanted to emulate Ratpoison's 'banish' command,
--   which moves the mouse pointer to a corner? warpToWindow can do that!
banish :: Corner -> X ()

-- | Same as <a>banish</a> but moves the mouse to the corner of the
--   currently focused screen
banishScreen :: Corner -> X ()
data Corner
UpperLeft :: Corner
UpperRight :: Corner
LowerLeft :: Corner
LowerRight :: Corner

-- | Warp the pointer to the given position (top left = (0,0), bottom right
--   = (1,1)) on the given screen.
warpToScreen :: ScreenId -> Rational -> Rational -> X ()

-- | Warp the pointer to a given position relative to the currently focused
--   window. Top left = (0,0), bottom right = (1,1).
warpToWindow :: Rational -> Rational -> X ()


-- | Updates the focus on mouse move in unfocused windows.
module XMonad.Actions.UpdateFocus

-- | Changes the focus if the mouse is moved within an unfocused window.
focusOnMouseMove :: Event -> X All

-- | Adjusts the event mask to pick up pointer movements.
adjustEventInput :: X ()


-- | A module that allows the user to create a sub-mapping of key bindings.
module XMonad.Actions.Submap

-- | Given a <a>Map</a> from key bindings to X () actions, return an action
--   which waits for a user keypress and executes the corresponding action,
--   or does nothing if the key is not found in the map.
submap :: Map (KeyMask, KeySym) (X ()) -> X ()

-- | Like <a>submap</a>, but executes a default action if the key did not
--   match.
submapDefault :: X () -> Map (KeyMask, KeySym) (X ()) -> X ()


-- | A wrapper for keybinding configuration that can list the available
--   keybindings.
module XMonad.Util.NamedActions

-- | <a>sendMessage</a> but add a description that is <tt>show
--   message</tt>. Note that not all messages have show instances.
sendMessage' :: (Message a, Show a) => a -> NamedAction

-- | <a>spawn</a> but the description is the string passed
spawn' :: String -> NamedAction

-- | <a>submap</a>, but propagate the descriptions of the actions. Does
--   this belong in <a>XMonad.Actions.Submap</a>?
submapName :: HasName a => [((KeyMask, KeySym), a)] -> NamedAction

-- | Merge the supplied keys with <a>defaultKeysDescr</a>, also adding a
--   keybinding to run an action for showing the keybindings.
addDescrKeys :: (HasName b1, HasName b) => ((KeyMask, KeySym), [((KeyMask, KeySym), NamedAction)] -> b) -> (XConfig Layout -> [((KeyMask, KeySym), b1)]) -> XConfig l -> XConfig l

-- | An action to send to <a>addDescrKeys</a> for showing the keybindings.
--   See also <a>showKm</a> and <a>showKmSimple</a>
xMessage :: [((KeyMask, KeySym), NamedAction)] -> NamedAction
showKmSimple :: [((KeyMask, KeySym), NamedAction)] -> [[Char]]
showKm :: [((KeyMask, KeySym), NamedAction)] -> [String]

-- | These are just the <tt>NamedAction</tt> constructor but with a more
--   specialized type, so that you don't have to supply any annotations,
--   for ex coercing spawn to <tt>X ()</tt> from the more general
--   <tt>MonadIO m =&gt; m ()</tt>
noName :: X () -> NamedAction
oneName :: (X (), String) -> NamedAction
addName :: String -> X () -> NamedAction

-- | For a prettier presentation: keymask, keysym of 0 are reserved for
--   this purpose: they do not happen, afaik, and keysymToString 0 would
--   raise an error otherwise
separator :: ((KeyMask, KeySym), NamedAction)
subtitle :: String -> ((KeyMask, KeySym), NamedAction)

-- | Combine keymap lists with actions that may or may not have names
(^++^) :: (HasName b, HasName b1) => [(d, b)] -> [(d, b1)] -> [(d, NamedAction)]

-- | An existential wrapper so that different types can be combined in
--   lists, and maps
data NamedAction
NamedAction :: a -> NamedAction
class HasName a where showName = const [""]

-- | A version of the default keys from <a>defaultConfig</a>, but with
--   <a>NamedAction</a> instead of <tt>X ()</tt>
defaultKeysDescr :: XConfig Layout -> [((KeyMask, KeySym), NamedAction)]
instance Show IncMasterN
instance Show Resize
instance HasName NamedAction
instance HasName (NamedAction, String)
instance HasName (X (), [String])
instance HasName (X (), String)
instance HasName [Char]
instance HasName (IO ())
instance HasName (X ())


-- | Useful helper functions for amending the defaultConfig, and for
--   parsing keybindings specified in a special (emacs-like) format.
--   
--   (See also <a>XMonad.Util.CustomKeys</a> in xmonad-contrib.)
module XMonad.Util.EZConfig

-- | Add or override keybindings from the existing set. Example use:
--   
--   <pre>
--   main = xmonad $ defaultConfig { terminal = "urxvt" }
--                   `additionalKeys`
--                   [ ((mod1Mask, xK_m        ), spawn "echo 'Hi, mom!' | dzen2 -p 4")
--                   , ((mod1Mask, xK_BackSpace), withFocused hide) -- N.B. this is an absurd thing to do
--                   ]
--   </pre>
--   
--   This overrides the previous definition of mod-m.
--   
--   Note that, unlike in xmonad 0.4 and previous, you can't use modMask to
--   refer to the modMask you configured earlier. You must specify mod1Mask
--   (or whichever), or add your own <tt>myModMask = mod1Mask</tt> line.
additionalKeys :: XConfig a -> [((ButtonMask, KeySym), X ())] -> XConfig a

-- | Like <a>additionalKeys</a>, except using short <tt>String</tt> key
--   descriptors like <tt>"M-m"</tt> instead of <tt>(modMask, xK_m)</tt>,
--   as described in the documentation for <a>mkKeymap</a>. For example:
--   
--   <pre>
--   main = xmonad $ defaultConfig { terminal = "urxvt" }
--                   `additionalKeysP`
--                   [ ("M-m", spawn "echo 'Hi, mom!' | dzen2 -p 4")
--                   , ("M-&lt;Backspace&gt;", withFocused hide) -- N.B. this is an absurd thing to do
--                   ]
--   </pre>
additionalKeysP :: XConfig l -> [(String, X ())] -> XConfig l

-- | Remove standard keybindings you're not using. Example use:
--   
--   <pre>
--   main = xmonad $ defaultConfig { terminal = "urxvt" }
--                   `removeKeys` [(mod1Mask .|. shiftMask, n) | n &lt;- [xK_1 .. xK_9]]
--   </pre>
removeKeys :: XConfig a -> [(ButtonMask, KeySym)] -> XConfig a

-- | Like <a>removeKeys</a>, except using short <tt>String</tt> key
--   descriptors like <tt>"M-m"</tt> instead of <tt>(modMask, xK_m)</tt>,
--   as described in the documentation for <a>mkKeymap</a>. For example:
--   
--   <pre>
--   main = xmonad $ defaultConfig { terminal = "urxvt" }
--                   `removeKeysP` ["M-S-" ++ [n] | n &lt;- ['1'..'9']]
--   </pre>
removeKeysP :: XConfig l -> [String] -> XConfig l

-- | Like <a>additionalKeys</a>, but for mouse bindings.
additionalMouseBindings :: XConfig a -> [((ButtonMask, Button), Window -> X ())] -> XConfig a

-- | Like <a>removeKeys</a>, but for mouse bindings.
removeMouseBindings :: XConfig a -> [(ButtonMask, Button)] -> XConfig a

-- | Given a config (used to determine the proper modifier key to use) and
--   a list of <tt>(String, X ())</tt> pairs, create a key map by parsing
--   the key sequence descriptions contained in the Strings. The key
--   sequence descriptions are "emacs-style": <tt>M-</tt>, <tt>C-</tt>,
--   <tt>S-</tt>, and <tt>M#-</tt> denote mod, control, shift, and
--   mod1-mod5 (where <tt>#</tt> is replaced by the appropriate number)
--   respectively. Note that if you want to make a keybinding using 'alt'
--   even though you use a different key (like the 'windows' key) for
--   'mod', you can use something like <tt>"M1-x"</tt> for alt+x (check the
--   output of <tt>xmodmap</tt> to see which mod key 'alt' is bound to).
--   Some special keys can also be specified by enclosing their name in
--   angle brackets.
--   
--   For example, <tt>"M-C-x"</tt> denotes mod+ctrl+x;
--   <tt>"S-&lt;Escape&gt;"</tt> denotes shift-escape;
--   <tt>"M1-C-&lt;Delete&gt;"</tt> denotes alt+ctrl+delete (assuming alt
--   is bound to mod1, which is common).
--   
--   Sequences of keys can also be specified by separating the key
--   descriptions with spaces. For example, <tt>"M-x y &lt;Down&gt;"</tt>
--   denotes the sequence of keys mod+x, y, down. Submaps (see
--   <a>XMonad.Actions.Submap</a>) will be automatically generated to
--   correctly handle these cases.
--   
--   So, for example, a complete key map might be specified as
--   
--   <pre>
--   keys = \c -&gt; mkKeymap c $
--       [ ("M-S-&lt;Return&gt;", spawn $ terminal c)
--       , ("M-x w", spawn "xmessage 'woohoo!'")  -- type mod+x then w to pop up 'woohoo!'
--       , ("M-x y", spawn "xmessage 'yay!'")     -- type mod+x then y to pop up 'yay!'
--       , ("M-S-c", kill)
--       ]
--   </pre>
--   
--   Alternatively, you can use <a>additionalKeysP</a> to automatically
--   create a keymap and add it to your config.
--   
--   Here is a complete list of supported special keys. Note that a few
--   keys, such as the arrow keys, have synonyms. If there are other
--   special keys you would like to see supported, feel free to submit a
--   patch, or ask on the xmonad mailing list; adding special keys is quite
--   simple.
--   
--   <pre>
--   &lt;Backspace&gt;
--   &lt;Tab&gt;
--   &lt;Return&gt;
--   &lt;Pause&gt;
--   &lt;Scroll_lock&gt;
--   &lt;Sys_Req&gt;
--   &lt;Print&gt;
--   &lt;Escape&gt;, &lt;Esc&gt;
--   &lt;Delete&gt;
--   &lt;Home&gt;
--   &lt;Left&gt;, &lt;L&gt;
--   &lt;Up&gt;, &lt;U&gt;
--   &lt;Right&gt;, &lt;R&gt;
--   &lt;Down&gt;, &lt;D&gt;
--   &lt;Page_Up&gt;
--   &lt;Page_Down&gt;
--   &lt;End&gt;
--   &lt;Insert&gt;
--   &lt;Break&gt;
--   &lt;Space&gt;
--   &lt;F1&gt;-&lt;F24&gt;
--   &lt;KP_Space&gt;
--   &lt;KP_Tab&gt;
--   &lt;KP_Enter&gt;
--   &lt;KP_F1&gt;
--   &lt;KP_F2&gt;
--   &lt;KP_F3&gt;
--   &lt;KP_F4&gt;
--   &lt;KP_Home&gt;
--   &lt;KP_Left&gt;
--   &lt;KP_Up&gt;
--   &lt;KP_Right&gt;
--   &lt;KP_Down&gt;
--   &lt;KP_Prior&gt;
--   &lt;KP_Page_Up&gt;
--   &lt;KP_Next&gt;
--   &lt;KP_Page_Down&gt;
--   &lt;KP_End&gt;
--   &lt;KP_Begin&gt;
--   &lt;KP_Insert&gt;
--   &lt;KP_Delete&gt;
--   &lt;KP_Equal&gt;
--   &lt;KP_Multiply&gt;
--   &lt;KP_Add&gt;
--   &lt;KP_Separator&gt;
--   &lt;KP_Subtract&gt;
--   &lt;KP_Decimal&gt;
--   &lt;KP_Divide&gt;
--   &lt;KP_0&gt;-&lt;KP_9&gt;
--   </pre>
--   
--   Long list of multimedia keys. Please note that not all keys may be
--   present in your particular setup although most likely they will do.
--   
--   <pre>
--   &lt;XF86ModeLock&gt;
--   &lt;XF86MonBrightnessUp&gt;
--   &lt;XF86MonBrightnessDown&gt;
--   &lt;XF86KbdLightOnOff&gt;
--   &lt;XF86KbdBrightnessUp&gt;
--   &lt;XF86KbdBrightnessDown&gt;
--   &lt;XF86Standby&gt;
--   &lt;XF86AudioLowerVolume&gt;
--   &lt;XF86AudioMute&gt;
--   &lt;XF86AudioRaiseVolume&gt;
--   &lt;XF86AudioPlay&gt;
--   &lt;XF86AudioStop&gt;
--   &lt;XF86AudioPrev&gt;
--   &lt;XF86AudioNext&gt;
--   &lt;XF86HomePage&gt;
--   &lt;XF86Mail&gt;
--   &lt;XF86Start&gt;
--   &lt;XF86Search&gt;
--   &lt;XF86AudioRecord&gt;
--   &lt;XF86Calculator&gt;
--   &lt;XF86Memo&gt;
--   &lt;XF86ToDoList&gt;
--   &lt;XF86Calendar&gt;
--   &lt;XF86PowerDown&gt;
--   &lt;XF86ContrastAdjust&gt;
--   &lt;XF86RockerUp&gt;
--   &lt;XF86RockerDown&gt;
--   &lt;XF86RockerEnter&gt;
--   &lt;XF86Back&gt;
--   &lt;XF86Forward&gt;
--   &lt;XF86Stop&gt;
--   &lt;XF86Refresh&gt;
--   &lt;XF86PowerOff&gt;
--   &lt;XF86WakeUp&gt;
--   &lt;XF86Eject&gt;
--   &lt;XF86ScreenSaver&gt;
--   &lt;XF86WWW&gt;
--   &lt;XF86Sleep&gt;
--   &lt;XF86Favorites&gt;
--   &lt;XF86AudioPause&gt;
--   &lt;XF86AudioMedia&gt;
--   &lt;XF86MyComputer&gt;
--   &lt;XF86VendorHome&gt;
--   &lt;XF86LightBulb&gt;
--   &lt;XF86Shop&gt;
--   &lt;XF86History&gt;
--   &lt;XF86OpenURL&gt;
--   &lt;XF86AddFavorite&gt;
--   &lt;XF86HotLinks&gt;
--   &lt;XF86BrightnessAdjust&gt;
--   &lt;XF86Finance&gt;
--   &lt;XF86Community&gt;
--   &lt;XF86AudioRewind&gt;
--   &lt;XF86XF86BackForward&gt;
--   &lt;XF86Launch0&gt;-&lt;XF86Launch9&gt;, &lt;XF86LaunchA&gt;-&lt;XF86LaunchF&gt;
--   &lt;XF86ApplicationLeft&gt;
--   &lt;XF86ApplicationRight&gt;
--   &lt;XF86Book&gt;
--   &lt;XF86CD&gt;
--   &lt;XF86Calculater&gt;
--   &lt;XF86Clear&gt;
--   &lt;XF86Close&gt;
--   &lt;XF86Copy&gt;
--   &lt;XF86Cut&gt;
--   &lt;XF86Display&gt;
--   &lt;XF86DOS&gt;
--   &lt;XF86Documents&gt;
--   &lt;XF86Excel&gt;
--   &lt;XF86Explorer&gt;
--   &lt;XF86Game&gt;
--   &lt;XF86Go&gt;
--   &lt;XF86iTouch&gt;
--   &lt;XF86LogOff&gt;
--   &lt;XF86Market&gt;
--   &lt;XF86Meeting&gt;
--   &lt;XF86MenuKB&gt;
--   &lt;XF86MenuPB&gt;
--   &lt;XF86MySites&gt;
--   &lt;XF86New&gt;
--   &lt;XF86News&gt;
--   &lt;XF86OfficeHome&gt;
--   &lt;XF86Open&gt;
--   &lt;XF86Option&gt;
--   &lt;XF86Paste&gt;
--   &lt;XF86Phone&gt;
--   &lt;XF86Q&gt;
--   &lt;XF86Reply&gt;
--   &lt;XF86Reload&gt;
--   &lt;XF86RotateWindows&gt;
--   &lt;XF86RotationPB&gt;
--   &lt;XF86RotationKB&gt;
--   &lt;XF86Save&gt;
--   &lt;XF86ScrollUp&gt;
--   &lt;XF86ScrollDown&gt;
--   &lt;XF86ScrollClick&gt;
--   &lt;XF86Send&gt;
--   &lt;XF86Spell&gt;
--   &lt;XF86SplitScreen&gt;
--   &lt;XF86Support&gt;
--   &lt;XF86TaskPane&gt;
--   &lt;XF86Terminal&gt;
--   &lt;XF86Tools&gt;
--   &lt;XF86Travel&gt;
--   &lt;XF86UserPB&gt;
--   &lt;XF86User1KB&gt;
--   &lt;XF86User2KB&gt;
--   &lt;XF86Video&gt;
--   &lt;XF86WheelButton&gt;
--   &lt;XF86Word&gt;
--   &lt;XF86Xfer&gt;
--   &lt;XF86ZoomIn&gt;
--   &lt;XF86ZoomOut&gt;
--   &lt;XF86Away&gt;
--   &lt;XF86Messenger&gt;
--   &lt;XF86WebCam&gt;
--   &lt;XF86MailForward&gt;
--   &lt;XF86Pictures&gt;
--   &lt;XF86Music&gt;
--   &lt;XF86TouchpadToggle&gt;
--   &lt;XF86_Switch_VT_1&gt;-&lt;XF86_Switch_VT_12&gt;
--   &lt;XF86_Ungrab&gt;
--   &lt;XF86_ClearGrab&gt;
--   &lt;XF86_Next_VMode&gt;
--   &lt;XF86_Prev_VMode&gt;
--   </pre>
mkKeymap :: XConfig l -> [(String, X ())] -> Map (KeyMask, KeySym) (X ())

-- | Given a configuration record and a list of (key sequence description,
--   action) pairs, check the key sequence descriptions for validity, and
--   warn the user (via a popup xmessage window) of any unparseable or
--   duplicate key sequences. This function is appropriate for adding to
--   your <tt>startupHook</tt>, and you are highly encouraged to do so;
--   otherwise, duplicate or unparseable keybindings will be silently
--   ignored.
--   
--   For example, you might do something like this:
--   
--   <pre>
--   main = xmonad $ myConfig
--   
--   myKeymap = [("S-M-c", kill), ...]
--   myConfig = defaultConfig {
--       ...
--       keys = \c -&gt; mkKeymap c myKeymap
--       startupHook = return () &gt;&gt; checkKeymap myConfig myKeymap
--       ...
--   }
--   </pre>
--   
--   NOTE: the <tt>return ()</tt> in the example above is very important!
--   Otherwise, you might run into problems with infinite mutual recursion:
--   the definition of myConfig depends on the definition of startupHook,
--   which depends on the definition of myConfig, ... and so on. Actually,
--   it's likely that the above example in particular would be OK without
--   the <tt>return ()</tt>, but making <tt>myKeymap</tt> take
--   <tt>myConfig</tt> as a parameter would definitely lead to problems.
--   Believe me. It, uh, happened to my friend. In... a dream. Yeah. In any
--   event, the <tt>return () &gt;&gt;</tt> introduces enough laziness to
--   break the deadlock.
checkKeymap :: XConfig l -> [(String, a)] -> X ()
mkNamedKeymap :: XConfig l -> [(String, NamedAction)] -> [((KeyMask, KeySym), NamedAction)]

-- | Parse an unmodified basic key, like <tt>"x"</tt>,
--   <tt>"<a>F1</a>"</tt>, etc.
parseKey :: ReadP KeySym


-- | This module provides helper functions to be used in
--   <tt>manageHook</tt>. Here's how you might use this:
--   
--   <pre>
--   import XMonad.Hooks.ManageHelpers
--   main =
--       xmonad defaultConfig{
--           ...
--           manageHook = composeOne [
--               isKDETrayWindow -?&gt; doIgnore,
--               transience,
--               isFullscreen -?&gt; doFullFloat,
--               resource =? "stalonetray" -?&gt; doIgnore
--           ],
--           ...
--       }
--   </pre>
module XMonad.Hooks.ManageHelpers

-- | Denotes a side of a screen. <tt>S</tt> stands for South, <tt>NE</tt>
--   for Northeast etc. <tt>C</tt> stands for Center.
data Side
SC :: Side
NC :: Side
CE :: Side
CW :: Side
SE :: Side
SW :: Side
NE :: Side
NW :: Side
C :: Side

-- | An alternative <a>ManageHook</a> composer. Unlike <a>composeAll</a> it
--   stops as soon as a candidate returns a <a>Just</a> value, effectively
--   running only the first match (whereas <a>composeAll</a> continues and
--   executes all matching rules).
composeOne :: [MaybeManageHook] -> ManageHook

-- | A helper operator for use in <a>composeOne</a>. It takes a condition
--   and an action; if the condition fails, it returns <a>Nothing</a> from
--   the <a>Query</a> so <a>composeOne</a> will go on and try the next
--   rule.
(-?>) :: Query Bool -> ManageHook -> MaybeManageHook

-- | q /=? x. if the result of q equals x, return False
(/=?) :: Eq a => Query a -> a -> Query Bool

-- | q &lt;==? x. if the result of q equals x, return True grouped with q
(<==?) :: Eq a => Query a -> a -> Query (Match a)

-- | q &lt;/=? x. if the result of q notequals x, return True grouped with
--   q
(</=?) :: Eq a => Query a -> a -> Query (Match a)

-- | A helper operator for use in <a>composeAll</a>. It takes a condition
--   and a function taking a grouped datum to action. If <tt>p</tt> is
--   true, it executes the resulting action.
(-->>) :: Query (Match a) -> (a -> ManageHook) -> ManageHook

-- | A helper operator for use in <a>composeOne</a>. It takes a condition
--   and a function taking a groupdatum to action. If <tt>p</tt> is true,
--   it executes the resulting action. If it fails, it returns
--   <a>Nothing</a> from the <a>Query</a> so <a>composeOne</a> will go on
--   and try the next rule.
(-?>>) :: Query (Match a) -> (a -> ManageHook) -> MaybeManageHook

-- | Return the current workspace
currentWs :: Query WorkspaceId

-- | Helper to check if a window property contains certain value.
isInProperty :: String -> String -> Query Bool

-- | A predicate to check whether a window is a KDE system tray icon.
isKDETrayWindow :: Query Bool

-- | A predicate to check whether a window wants to fill the whole screen.
--   See also <a>doFullFloat</a>.
isFullscreen :: Query Bool

-- | A predicate to check whether a window is a dialog.
isDialog :: Query Bool
pid :: Query (Maybe ProcessID)

-- | A predicate to check whether a window is Transient. It holds the
--   result which might be the window it is transient to or it might be
--   <a>Nothing</a>.
transientTo :: Query (Maybe Window)

-- | converts <a>MaybeManageHook</a>s to <a>ManageHook</a>s
maybeToDefinite :: MaybeManageHook -> ManageHook

-- | A ManageHook that may or may not have been executed; the outcome is
--   embedded in the Maybe
type MaybeManageHook = Query (Maybe (Endo WindowSet))

-- | A convenience <a>MaybeManageHook</a> that will check to see if a
--   window is transient, and then move it to its parent.
transience :: MaybeManageHook

-- | <a>transience</a> set to a <a>ManageHook</a>
transience' :: ManageHook

-- | Floats the new window in the given rectangle.
doRectFloat :: RationalRect -> ManageHook

-- | Floats the window and makes it use the whole screen. Equivalent to
--   <tt><a>doRectFloat</a> $ <a>RationalRect</a> 0 0 1 1</tt>.
doFullFloat :: ManageHook

-- | Floats a new window with its original size, but centered.
doCenterFloat :: ManageHook

-- | Floats a new window with its original size on the specified side of a
--   screen
doSideFloat :: Side -> ManageHook

-- | Floats a new window with its original size, and its top left corner at
--   a specific point on the screen (both coordinates should be in the
--   range 0 to 1).
doFloatAt :: Rational -> Rational -> ManageHook

-- | Floats a new window using a rectangle computed as a function of the
--   rectangle that it would have used by default.
doFloatDep :: (RationalRect -> RationalRect) -> ManageHook

-- | Hides window and ignores it.
doHideIgnore :: ManageHook

-- | A grouping type, which can hold the outcome of a predicate Query. This
--   is analogous to group types in regular expressions. TODO: create a
--   better API for aggregating multiple Matches logically
data Match a
instance Read Side
instance Show Side
instance Eq Side


-- | Hooks for sending messages about fullscreen windows to layouts, and a
--   few example layout modifier that implement fullscreen windows.
module XMonad.Layout.Fullscreen

-- | Layout modifier that makes fullscreened window fill the entire screen.
fullscreenFull :: LayoutClass l a => l a -> ModifiedLayout FullscreenFull l a

-- | Layout modifier that makes the fullscreened window fill the entire
--   screen only if it is currently focused.
fullscreenFocus :: LayoutClass l a => l a -> ModifiedLayout FullscreenFocus l a

-- | As above, but the fullscreened window will fill the specified
--   rectangle instead of the entire screen.
fullscreenFullRect :: LayoutClass l a => RationalRect -> l a -> ModifiedLayout FullscreenFull l a

-- | As above, but the fullscreened window will fill the specified
--   rectangle instead of the entire screen.
fullscreenFocusRect :: LayoutClass l a => RationalRect -> l a -> ModifiedLayout FullscreenFocus l a

-- | Hackish layout modifier that makes floating fullscreened windows fill
--   the entire screen.
fullscreenFloat :: LayoutClass l a => l a -> ModifiedLayout FullscreenFloat l a

-- | As above, but the fullscreened window will fill the specified
--   rectangle instead of the entire screen.
fullscreenFloatRect :: LayoutClass l a => RationalRect -> l a -> ModifiedLayout FullscreenFloat l a

-- | The event hook required for the layout modifiers to work
fullscreenEventHook :: Event -> X All

-- | Manage hook that sets the fullscreen property for windows that are
--   initially fullscreen
fullscreenManageHook :: ManageHook

-- | A version of fullscreenManageHook that lets you specify your own query
--   to decide whether a window should be fullscreen.
fullscreenManageHookWith :: Query Bool -> ManageHook

-- | Messages that control the fullscreen state of the window.
--   AddFullscreen and RemoveFullscreen are sent to all layouts when a
--   window wants or no longer wants to be fullscreen. FullscreenChanged is
--   sent to the current layout after one of the above have been sent.
data FullscreenMessage
AddFullscreen :: Window -> FullscreenMessage
RemoveFullscreen :: Window -> FullscreenMessage
FullscreenChanged :: FullscreenMessage
data FullscreenFloat a
data FullscreenFocus a
data FullscreenFull a
instance Typeable FullscreenMessage
instance Read a => Read (FullscreenFull a)
instance Show a => Show (FullscreenFull a)
instance Read a => Read (FullscreenFocus a)
instance Show a => Show (FullscreenFocus a)
instance (Ord a, Read a) => Read (FullscreenFloat a)
instance Show a => Show (FullscreenFloat a)
instance LayoutModifier FullscreenFloat Window
instance LayoutModifier FullscreenFocus Window
instance LayoutModifier FullscreenFull Window
instance Message FullscreenMessage


-- | Layout modfier for displaying some window (monitor) above other
--   windows
module XMonad.Layout.Monitor
data Monitor a
Monitor :: Property -> Rectangle -> Bool -> String -> Bool -> Rational -> Monitor a

-- | property which uniquely identifies monitor window
prop :: Monitor a -> Property

-- | specifies where to put monitor
rect :: Monitor a -> Rectangle

-- | is it visible by default?
visible :: Monitor a -> Bool

-- | name of monitor (useful when we have many of them)
name :: Monitor a -> String

-- | is it shown on all layouts?
persistent :: Monitor a -> Bool

-- | opacity level
opacity :: Monitor a -> Rational

-- | Template for <a>Monitor</a> record. At least <a>prop</a> and
--   <a>rect</a> should be redefined. Default settings: <a>visible</a> is
--   <a>True</a>, <a>persistent</a> is <a>False</a>.
monitor :: Monitor a

-- | Most of the property constructors are quite self-explaining.
data Property
Title :: String -> Property
ClassName :: String -> Property
Resource :: String -> Property

-- | WM_WINDOW_ROLE property
Role :: String -> Property

-- | WM_CLIENT_MACHINE property
Machine :: String -> Property
And :: Property -> Property -> Property
Or :: Property -> Property -> Property
Not :: Property -> Property
Const :: Bool -> Property

-- | Messages without names affect all monitors. Messages with names affect
--   only monitors whose names match.
data MonitorMessage
ToggleMonitor :: MonitorMessage
ShowMonitor :: MonitorMessage
HideMonitor :: MonitorMessage
ToggleMonitorNamed :: String -> MonitorMessage
ShowMonitorNamed :: String -> MonitorMessage
HideMonitorNamed :: String -> MonitorMessage

-- | Hides window and ignores it.
doHideIgnore :: ManageHook

-- | ManageHook which demanages monitor window and applies opacity
--   settings.
manageMonitor :: Monitor a -> ManageHook
instance Typeable MonitorMessage
instance Read (Monitor a)
instance Show (Monitor a)
instance Read MonitorMessage
instance Show MonitorMessage
instance Eq MonitorMessage
instance LayoutModifier Monitor Window
instance Message MonitorMessage


-- | Provides functions for performing a given action on all windows of the
--   current workspace.
module XMonad.Actions.WithAll

-- | Un-float all floating windows on the current workspace.
sinkAll :: X ()

-- | Execute an <a>X</a> action for each window on the current workspace.
withAll :: (Window -> X ()) -> X ()

-- | Apply a function to all windows on the current workspace.
withAll' :: (Window -> WindowSet -> WindowSet) -> X ()

-- | Kill all the windows on the current workspace.
killAll :: X ()


-- | Provides a simple binding that pushes all floating windows on the
--   current workspace back into tiling. Note that the functionality of
--   this module has been folded into the more general
--   <a>XMonad.Actions.WithAll</a>; this module simply re-exports the
--   <a>sinkAll</a> function for backwards compatibility.
module XMonad.Actions.SinkAll

-- | Un-float all floating windows on the current workspace.
sinkAll :: X ()


-- | A module for setting up timers
module XMonad.Util.Timer

-- | Start a timer, which will send a ClientMessageEvent after some time
--   (in seconds).
startTimer :: Rational -> X TimerId

-- | Given a <a>TimerId</a> and an <a>Event</a>, run an action when the
--   <a>Event</a> has been sent by the timer specified by the
--   <a>TimerId</a>
handleTimer :: TimerId -> Event -> X (Maybe a) -> X (Maybe a)
type TimerId = Int


-- | An action to start terminals with a random background color
module XMonad.Actions.RandomBackground

-- | <tt>randomBg'</tt> produces a random hex number in the form
--   <tt>'#xxyyzz'</tt>
randomBg' :: MonadIO m => RandomColor -> m String

-- | <tt>randomBg</tt> starts a terminal with the background color taken
--   from <a>randomBg'</a>
--   
--   This depends on the your <a>terminal</a> configuration field accepting
--   an argument like <tt>-bg '#ff0023'</tt>
randomBg :: RandomColor -> X ()

-- | RandomColor fixes constraints when generating random colors. All
--   parameters should be in the range 0 -- 0xff
data RandomColor

-- | specify the minimum and maximum lowest values for each color channel.
RGB :: Int -> Int -> RandomColor

-- | specify the saturation and value, leaving the hue random.
HSV :: Double -> Double -> RandomColor


-- | Alternate promote function for xmonad.
--   
--   Moves the focused window to the master pane. All other windows retain
--   their order. If focus is in the master, swap it with the next window
--   in the stack. Focus stays in the master.
module XMonad.Actions.Promote

-- | Move the focused window to the master pane. All other windows retain
--   their order. If focus is in the master, swap it with the next windo in
--   the stack. Focus stays in the master.
promote :: X ()


-- | Manipulate screens ordered by physical location instead of ID
module XMonad.Actions.PhysicalScreens

-- | The type of the index of a screen by location
newtype PhysicalScreen
P :: Int -> PhysicalScreen

-- | Translate a physical screen index to a <a>ScreenId</a>
getScreen :: PhysicalScreen -> X (Maybe ScreenId)

-- | Switch to a given physical screen
viewScreen :: PhysicalScreen -> X ()

-- | Send the active window to a given physical screen
sendToScreen :: PhysicalScreen -> X ()

-- | Apply operation on a WindowSet with the WorkspaceId of the next screen
--   in the physical order as parameter.
onNextNeighbour :: (WorkspaceId -> WindowSet -> WindowSet) -> X ()

-- | Apply operation on a WindowSet with the WorkspaceId of the previous
--   screen in the physical order as parameter.
onPrevNeighbour :: (WorkspaceId -> WindowSet -> WindowSet) -> X ()
instance Eq PhysicalScreen
instance Ord PhysicalScreen
instance Show PhysicalScreen
instance Read PhysicalScreen
instance Enum PhysicalScreen
instance Num PhysicalScreen
instance Integral PhysicalScreen
instance Real PhysicalScreen


-- | Define key-bindings on per-workspace basis.
module XMonad.Actions.PerWorkspaceKeys

-- | Uses supplied function to decide which action to run depending on
--   current workspace name.
chooseAction :: (String -> X ()) -> X ()

-- | If current workspace is listed, run appropriate action (only the first
--   match counts!) If it isn't listed, then run default action (marked
--   with empty string, ""), or do nothing if default isn't supplied.
bindOn :: [(String, X ())] -> X ()


-- | Control workspaces on different screens (in xinerama mode).
module XMonad.Actions.OnScreen

-- | Run any function that modifies the stack on a given screen. This
--   function will also need to know which Screen to focus after the
--   function has been run.
onScreen :: (WindowSet -> WindowSet) -> Focus -> ScreenId -> WindowSet -> WindowSet

-- | A variation of <tt>onScreen</tt> which will take any <tt>X ()</tt>
--   function and run it on the given screen. Warning: This function will
--   change focus even if the function it's supposed to run doesn't
--   succeed.
onScreen' :: X () -> Focus -> ScreenId -> X ()

-- | Focus data definitions
data Focus

-- | always focus the new screen
FocusNew :: Focus

-- | always keep the focus on the current screen
FocusCurrent :: Focus

-- | always focus tag i on the new stack
FocusTag :: WorkspaceId -> Focus

-- | focus tag i only if workspace with tag i is visible on the old stack
FocusTagVisible :: WorkspaceId -> Focus

-- | Switch to workspace <tt>i</tt> on screen <tt>sc</tt>. If <tt>i</tt> is
--   visible use <tt>view</tt> to switch focus to the workspace <tt>i</tt>.
viewOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet

-- | Switch to workspace <tt>i</tt> on screen <tt>sc</tt>. If <tt>i</tt> is
--   visible use <tt>greedyView</tt> to switch the current workspace with
--   workspace <tt>i</tt>.
greedyViewOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet

-- | Switch to workspace <tt>i</tt> on screen <tt>sc</tt>. If <tt>i</tt> is
--   visible do nothing.
onlyOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet

-- | <tt>toggleOrView</tt> as in <a>XMonad.Actions.CycleWS</a> for
--   <tt>onScreen</tt> with view
toggleOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet

-- | <tt>toggleOrView</tt> from <a>XMonad.Actions.CycleWS</a> for
--   <tt>onScreen</tt> with greedyView
toggleGreedyOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet


-- | This module provides helper functions for dealing with window borders.
module XMonad.Actions.NoBorders

-- | Toggle the border of the currently focused window. To use it, add a
--   keybinding like so:
--   
--   <pre>
--   , ((modm,  xK_g ),   withFocused toggleBorder)
--   </pre>
toggleBorder :: Window -> X ()


-- | Alternative to <a>sendMessage</a> that provides knowledge of whether
--   the message was handled, and utility functions based on this facility.
module XMonad.Actions.MessageFeedback

-- | Behaves like <a>sendMessage</a>, but returns True of the message was
--   handled by the layout, False otherwise.
send :: Message a => a -> X Bool

-- | Sends the first message, and if it was not handled, sends the second.
--   Returns True if either message was handled, False otherwise.
tryMessage :: (Message a, Message b) => a -> b -> X Bool
tryMessage_ :: (Message a, Message b) => a -> b -> X ()

-- | Tries sending every message of the list in order until one of them is
--   handled. Returns True if one of the messages was handled, False
--   otherwise.
tryInOrder :: [SomeMessage] -> X Bool
tryInOrder_ :: [SomeMessage] -> X ()

-- | Convenience shorthand for <a>SomeMessage</a>.
sm :: Message a => a -> SomeMessage
sendSM :: SomeMessage -> X Bool
sendSM_ :: SomeMessage -> X ()


-- | Utility functions for <a>XMonad.Layout.Groups</a>.
module XMonad.Layout.Groups.Helpers

-- | Swap the focused window with the previous one
swapUp :: X ()

-- | Swap the focused window with the next one
swapDown :: X ()

-- | Swap the focused window with the master window
swapMaster :: X ()

-- | If the focused window is floating, focus the next floating window.
--   otherwise, focus the next non-floating one.
focusUp :: X ()

-- | If the focused window is floating, focus the next floating window.
--   otherwise, focus the next non-floating one.
focusDown :: X ()

-- | Move focus to the master window
focusMaster :: X ()

-- | Move focus between the floating and non-floating layers
toggleFocusFloat :: X ()

-- | Swap the focused group with the previous one
swapGroupUp :: X ()

-- | Swap the focused group with the next one
swapGroupDown :: X ()

-- | Swap the focused group with the master group
swapGroupMaster :: X ()

-- | Move the focus to the previous group
focusGroupUp :: X ()

-- | Move the focus to the next group
focusGroupDown :: X ()

-- | Move the focus to the master group
focusGroupMaster :: X ()

-- | Move the focused window to the previous group. The <a>Bool</a>
--   argument determines what will be done if the focused window is in the
--   very first group: Wrap back to the end (<a>True</a>), or create a new
--   group before it (<a>False</a>).
moveToGroupUp :: Bool -> X ()

-- | Move the focused window to the next group. The <a>Bool</a> argument
--   determines what will be done if the focused window is in the very last
--   group: Wrap back to the beginning (<a>True</a>), or create a new group
--   after it (<a>False</a>).
moveToGroupDown :: Bool -> X ()

-- | Move the focused window to a new group before the current one
moveToNewGroupUp :: X ()

-- | Move the focused window to a new group after the current one
moveToNewGroupDown :: X ()

-- | Split the focused group in two at the position of the focused window.
splitGroup :: X ()


-- | This modules provides several commands to run an external process. It
--   is composed of functions formerly defined in <a>XMonad.Util.Dmenu</a>
--   (by Spencer Janssen), <a>XMonad.Util.Dzen</a> (by glasser@mit.edu) and
--   XMonad.Util.RunInXTerm (by Andrea Rossato).
module XMonad.Util.Run

-- | Returns the output.
runProcessWithInput :: MonadIO m => FilePath -> [String] -> String -> m String

-- | Wait is in μ (microseconds)
runProcessWithInputAndWait :: MonadIO m => FilePath -> [String] -> String -> Int -> m ()

-- | <a>safeSpawn</a> bypasses <a>spawn</a>, because spawn passes strings
--   to /bin/sh to be interpreted as shell commands. This is often what one
--   wants, but in many cases the passed string will contain shell
--   metacharacters which one does not want interpreted as such (URLs
--   particularly often have shell metacharacters like '&amp;' in them). In
--   this case, it is more useful to specify a file or program to be run
--   and a string to give it as an argument so as to bypass the shell and
--   be certain the program will receive the string as you typed it.
--   
--   Examples:
--   
--   <pre>
--   , ((modm, xK_Print), unsafeSpawn "import -window root $HOME/xwd-$(date +%s)$$.png")
--   , ((modm, xK_d    ), safeSpawn "firefox" [])
--   </pre>
--   
--   Note that the unsafeSpawn example must be unsafe and not safe because
--   it makes use of shell interpretation by relying on <tt>$HOME</tt> and
--   interpolation, whereas the safeSpawn example can be safe because
--   Firefox doesn't need any arguments if it is just being started.
safeSpawn :: MonadIO m => FilePath -> [String] -> m ()

-- | Simplified <a>safeSpawn</a>; only takes a program (and no arguments):
--   
--   <pre>
--   , ((modm, xK_d    ), safeSpawnProg "firefox")
--   </pre>
safeSpawnProg :: MonadIO m => FilePath -> m ()

-- | An alias for <a>spawn</a>; the name emphasizes that one is calling out
--   to a Turing-complete interpreter which may do things one dislikes; for
--   details, see <a>safeSpawn</a>.
unsafeSpawn :: MonadIO m => String -> m ()

-- | Open a terminal emulator. The terminal emulator is specified in
--   <tt>defaultConfig</tt> as xterm by default. It is then asked to pass
--   the shell a command with certain options. This is unsafe in the sense
--   of <a>unsafeSpawn</a>
runInTerm :: String -> String -> X ()

-- | Run a given program in the preferred terminal emulator; see
--   <a>runInTerm</a>. This makes use of <a>safeSpawn</a>.
safeRunInTerm :: String -> String -> X ()

-- | Multiplies by ONE MILLION, for functions that take microseconds.
--   
--   Use like:
--   
--   <pre>
--   (5.5 `seconds`)
--   </pre>
--   
--   In GHC 7 and later, you must either enable the PostfixOperators
--   extension (by adding
--   
--   <pre>
--   {-# LANGUAGE PostfixOperators #-}
--   </pre>
--   
--   to the top of your file) or use seconds in prefix form:
--   
--   <pre>
--   5.5 seconds
--   </pre>
seconds :: Rational -> Int

-- | Launch an external application through the system shell and return a
--   <tt>Handle</tt> to its standard input.
spawnPipe :: MonadIO m => String -> m Handle

-- | Computation <a>hPutStr</a> <tt>hdl s</tt> writes the string <tt>s</tt>
--   to the file or channel managed by <tt>hdl</tt>.
--   
--   This operation may fail with:
--   
--   <ul>
--   <li><a>isFullError</a> if the device is full; or</li>
--   <li><a>isPermissionError</a> if another system resource limit would be
--   exceeded.</li>
--   </ul>
hPutStr :: Handle -> String -> IO ()

-- | The same as <a>hPutStr</a>, but adds a newline character.
hPutStrLn :: Handle -> String -> IO ()


-- | This module has functions to navigate through workspaces in a
--   bidimensional manner. It allows the organization of workspaces in
--   lines, and provides functions to move and shift windows in all four
--   directions (left, up, right and down) possible in a surface.
--   
--   This functionality was inspired by GNOME (finite) and KDE (infinite)
--   keybindings for workspace navigation, and by
--   <a>XMonad.Actions.CycleWS</a> for the idea of applying this approach
--   to XMonad.
module XMonad.Actions.Plane

-- | Direction to go in the plane.
data Direction
ToLeft :: Direction
ToUp :: Direction
ToRight :: Direction
ToDown :: Direction

-- | Defines the behaviour when you're trying to move out of the limits.
data Limits

-- | Ignore the function call, and keep in the same workspace.
Finite :: Limits

-- | Get on the other side, like in the Snake game.
Circular :: Limits

-- | The plan comes as a row, so it goes to the next or prev if the
--   workspaces were numbered.
Linear :: Limits

-- | The number of lines in which the workspaces will be arranged. It's
--   possible to use a number of lines that is not a divisor of the number
--   of workspaces, but the results are better when using a divisor. If
--   it's not a divisor, the last line will have the remaining workspaces.
data Lines

-- | Use <tt>gconftool-2</tt> to find out the number of lines.
GConf :: Lines

-- | Specify the number of lines explicitly.
Lines :: Int -> Lines

-- | This is the way most people would like to use this module. It attaches
--   the <a>KeyMask</a> passed as a parameter with <a>xK_Left</a>,
--   <a>xK_Up</a>, <a>xK_Right</a> and <a>xK_Down</a>, associating it with
--   <a>planeMove</a> to the corresponding <a>Direction</a>. It also
--   associates these bindings with <a>shiftMask</a> to <a>planeShift</a>.
planeKeys :: KeyMask -> Lines -> Limits -> Map (KeyMask, KeySym) (X ())

-- | Shift a window to the next workspace in <a>Direction</a>. Note that
--   this will also move to the next workspace. It's a good idea to use the
--   same <a>Lines</a> and <a>Limits</a> for all the bindings.
planeShift :: Lines -> Limits -> Direction -> X ()

-- | Move to the next workspace in <a>Direction</a>.
planeMove :: Lines -> Limits -> Direction -> X ()
instance Enum Direction
instance Eq Limits


-- | A module for accessing and manipulating X Window's mouse selection
--   (the buffer used in copy and pasting). <a>getSelection</a> is an
--   adaptation of Hxsel.hs and Hxput.hs from the XMonad-utils, available:
--   
--   <pre>
--   $ darcs get &lt;http://gorgias.mine.nu/repos/xmonad-utils&gt;
--   </pre>
module XMonad.Util.XSelection

-- | Returns a String corresponding to the current mouse selection in X; if
--   there is none, an empty string is returned.
getSelection :: MonadIO m => m String

-- | A wrapper around <a>getSelection</a>. Makes it convenient to run a
--   program with the current selection as an argument. This is convenient
--   for handling URLs, in particular. For example, in your Config.hs you
--   could bind a key to <tt>promptSelection "firefox"</tt>; this would
--   allow you to highlight a URL string and then immediately open it up in
--   Firefox.
--   
--   <a>promptSelection</a> passes strings through the system shell,
--   /bin/sh; if you do not wish your selected text to be interpreted or
--   mangled by the shell, use <a>safePromptSelection</a>.
--   safePromptSelection will bypass the shell using <a>safeSpawn</a> from
--   <a>XMonad.Util.Run</a>; see its documentation for more details on the
--   advantages and disadvantages of using safeSpawn.
promptSelection, safePromptSelection :: String -> X ()

-- | A wrapper around <a>promptSelection</a> and its safe variant. They
--   take two parameters, the first is a function that transforms strings,
--   and the second is the application to run. The transformer essentially
--   transforms the selection in X. One example is to wrap code, such as a
--   command line action copied out of the browser to be run as
--   <tt><a>sudo</a> ++ cmd</tt> or <tt><a>su - -c "</a>++ cmd
--   ++<a>"</a></tt>.
transformPromptSelection, transformSafePromptSelection :: (String -> String) -> String -> X ()


-- | A module for sending key presses to windows. This modules provides
--   generalized and specialized functions for this task.
module XMonad.Util.Paste

-- | Paste the current X mouse selection. Note that this uses
--   <a>getSelection</a> from <a>XMonad.Util.XSelection</a> and so is heir
--   to its flaws.
pasteSelection :: X ()

-- | Send a string to the window which is currently focused. This function
--   correctly handles capitalization. Warning: in dealing with capitalized
--   characters, this assumes a QWERTY layout.
pasteString :: String -> X ()

-- | Send a character to the current window. This is more low-level.
--   Remember that you must handle the case of capitalization
--   appropriately. That is, from the window's perspective:
--   
--   <pre>
--   pasteChar mod2Mask 'F' ~&gt; "f"
--   </pre>
--   
--   You would want to do something like:
--   
--   <pre>
--   pasteChar shiftMask 'F'
--   </pre>
--   
--   Note that this function makes use of <a>stringToKeysym</a>, and so
--   will probably have trouble with any <a>Char</a> outside ASCII.
pasteChar :: KeyMask -> Char -> X ()
sendKey :: KeyMask -> KeySym -> X ()

-- | The primitive. Allows you to send any combination of <a>KeyMask</a>
--   and <a>KeySym</a> to any <a>Window</a> you specify.
sendKeyWindow :: KeyMask -> KeySym -> Window -> X ()
noModMask :: KeyMask


-- | An example external contrib module for XMonad. Provides a simple
--   binding to dzen2 to print the date as a popup menu.
module XMonad.Actions.SimpleDate
date :: X ()


-- | Handy wrapper for dzen. Requires dzen &gt;= 0.2.4.
module XMonad.Util.Dzen

-- | <tt>dzenConfig config s</tt> will display the string <tt>s</tt>
--   according to the configuration <tt>config</tt>. For example, to
--   display the string <tt>"foobar"</tt> with all the default settings,
--   you can simply call
--   
--   <pre>
--   dzenConfig return "foobar"
--   </pre>
--   
--   Or, to set a longer timeout, you could use
--   
--   <pre>
--   dzenConfig (timeout 10) "foobar"
--   </pre>
--   
--   You can combine configurations with the (&gt;=&gt;) operator. To
--   display <tt>"foobar"</tt> for 10 seconds on the first screen, you
--   could use
--   
--   <pre>
--   dzenConfig (timeout 10 &gt;=&gt; xScreen 0) "foobar"
--   </pre>
--   
--   As a final example, you could adapt the above to display
--   <tt>"foobar"</tt> for 10 seconds on the current screen with
--   
--   <pre>
--   dzenConfig (timeout 10 &gt;=&gt; onCurr xScreen) "foobar"
--   </pre>
dzenConfig :: DzenConfig -> String -> X ()
type DzenConfig = (Int, [String]) -> X (Int, [String])

-- | Set the timeout, in seconds. This defaults to 3 seconds if not
--   specified.
timeout :: Rational -> DzenConfig

-- | Specify the font. Check out xfontsel to get the format of the String
--   right; if your dzen supports xft, then you can supply that here, too.
font :: String -> DzenConfig

-- | Start dzen2 on a particular screen. Only works with versions of dzen
--   that support the <a>-xs</a> argument.
xScreen :: ScreenId -> DzenConfig

-- | <tt>vCenter height sc</tt> sets the configuration to have the dzen bar
--   appear on screen <tt>sc</tt> with height <tt>height</tt>, vertically
--   centered with respect to the actual size of that screen.
vCenter :: Int -> ScreenId -> DzenConfig

-- | <tt>hCenter width sc</tt> sets the configuration to have the dzen bar
--   appear on screen <tt>sc</tt> with width <tt>width</tt>, horizontally
--   centered with respect to the actual size of that screen.
hCenter :: Int -> ScreenId -> DzenConfig

-- | <tt>center width height sc</tt> sets the configuration to have the
--   dzen bar appear on screen <tt>sc</tt> with width <tt>width</tt> and
--   height <tt>height</tt>, centered both horizontally and vertically with
--   respect to the actual size of that screen.
center :: Int -> Int -> ScreenId -> DzenConfig

-- | Take a screen-specific configuration and supply it with the screen ID
--   of the currently focused screen, according to xmonad. For example,
--   show a 100-pixel wide bar centered within the current screen, you
--   could use
--   
--   <pre>
--   dzenConfig (onCurr (hCenter 100)) "foobar"
--   </pre>
--   
--   Of course, you can still combine these with (&gt;=&gt;); for example,
--   to center the string <tt>"foobar"</tt> both horizontally and
--   vertically in a 100x14 box using the lovely Terminus font, you could
--   use
--   
--   <pre>
--   terminus = "-*-terminus-*-*-*-*-12-*-*-*-*-*-*-*"
--   dzenConfig (onCurr (center 100 14) &gt;=&gt; font terminus) "foobar"
--   </pre>
onCurr :: (ScreenId -> DzenConfig) -> DzenConfig

-- | Put the top of the dzen bar at a particular pixel.
x :: Int -> DzenConfig

-- | Put the left of the dzen bar at a particular pixel.
y :: Int -> DzenConfig

-- | Add raw command-line arguments to the configuration. These will be
--   passed on verbatim to dzen2. The default includes no arguments.
addArgs :: [String] -> DzenConfig

-- | <tt>dzen str timeout</tt> pipes <tt>str</tt> to dzen2 for
--   <tt>timeout</tt> microseconds. Example usage:
--   
--   <pre>
--   dzen "Hi, mom!" (5 `seconds`)
--   </pre>
dzen :: String -> Int -> X ()

-- | <tt>dzenScreen sc str timeout</tt> pipes <tt>str</tt> to dzen2 for
--   <tt>timeout</tt> microseconds, and on screen <tt>sc</tt>. Requires
--   dzen to be compiled with Xinerama support.
dzenScreen :: ScreenId -> String -> Int -> X ()

-- | <tt>dzen str args timeout</tt> pipes <tt>str</tt> to dzen2 for
--   <tt>timeout</tt> seconds, passing <tt>args</tt> to dzen. Example
--   usage:
--   
--   <pre>
--   dzenWithArgs "Hi, dons!" ["-ta", "r"] (5 `seconds`)
--   </pre>
dzenWithArgs :: String -> [String] -> Int -> X ()

-- | Multiplies by ONE MILLION, for functions that take microseconds.
--   
--   Use like:
--   
--   <pre>
--   (5.5 `seconds`)
--   </pre>
--   
--   In GHC 7 and later, you must either enable the PostfixOperators
--   extension (by adding
--   
--   <pre>
--   {-# LANGUAGE PostfixOperators #-}
--   </pre>
--   
--   to the top of your file) or use seconds in prefix form:
--   
--   <pre>
--   5.5 seconds
--   </pre>
seconds :: Rational -> Int

-- | dzen wants exactly one newline at the end of its input, so this can be
--   used for your own invocations of dzen. However, all functions in this
--   module will call this for you.
chomp :: String -> String

-- | Left-to-right Kleisli composition of monads.
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c


-- | This module allows you to associate the X titles of windows with them.
module XMonad.Util.NamedWindows
data NamedWindow
getName :: Window -> X NamedWindow
withNamedWindow :: (NamedWindow -> X ()) -> X ()
unName :: NamedWindow -> Window
instance Show NamedWindow
instance Ord NamedWindow
instance Eq NamedWindow


-- | A module for abstracting a font facility over Core fonts and Xft
module XMonad.Util.Font
data XMonadFont
Core :: FontStruct -> XMonadFont
Utf8 :: FontSet -> XMonadFont
Xft :: XftFont -> XMonadFont

-- | When initXMF gets a font name that starts with 'xft:' it switches to
--   the Xft backend Example: 'xft: Sans-10'
initXMF :: String -> X XMonadFont
releaseXMF :: XMonadFont -> X ()

-- | Given a fontname returns the font structure. If the font name is not
--   valid the default font will be loaded and returned.
initCoreFont :: String -> X FontStruct
releaseCoreFont :: FontStruct -> X ()
initUtf8Font :: String -> X FontSet
releaseUtf8Font :: FontSet -> X ()

-- | String position
data Align
AlignCenter :: Align
AlignRight :: Align
AlignLeft :: Align
AlignRightOffset :: Int -> Align

-- | Return the string x and y <a>Position</a> in a <a>Rectangle</a>, given
--   a <a>FontStruct</a> and the <a>Align</a>ment
stringPosition :: (Functor m, MonadIO m) => Display -> XMonadFont -> Rectangle -> Align -> String -> m (Position, Position)
textWidthXMF :: MonadIO m => Display -> XMonadFont -> String -> m Int
textExtentsXMF :: MonadIO m => XMonadFont -> String -> m (Int32, Int32)
printStringXMF :: (Functor m, MonadIO m) => Display -> Drawable -> XMonadFont -> GC -> String -> String -> Position -> Position -> String -> m ()

-- | Get the Pixel value for a named color: if an invalid name is given the
--   black pixel will be returned.
stringToPixel :: (Functor m, MonadIO m) => Display -> String -> m Pixel

-- | Short-hand for <a>fromIntegral</a>
fi :: (Integral a, Num b) => a -> b
instance Show Align
instance Read Align


-- | Utilities for manipulating [[Bool]] as images
module XMonad.Util.Image

-- | Placement of the icon in the title bar
data Placement

-- | An exact amount of pixels from the upper left corner
OffsetLeft :: Int -> Int -> Placement

-- | An exact amount of pixels from the right left corner
OffsetRight :: Int -> Int -> Placement

-- | Centered in the y-axis, an amount of pixels from the left
CenterLeft :: Int -> Placement

-- | Centered in the y-axis, an amount of pixels from the right
CenterRight :: Int -> Placement

-- | Return the <tt>x</tt> and <tt>y</tt> positions inside a
--   <a>Rectangle</a> to start drawing the image given its <a>Placement</a>
iconPosition :: Rectangle -> Placement -> [[Bool]] -> (Position, Position)

-- | Draw an image into a X surface
drawIcon :: (Functor m, MonadIO m) => Display -> Drawable -> GC -> String -> String -> Position -> Position -> [[Bool]] -> m ()
instance Show Placement
instance Read Placement


-- | Add a configurable amount of space around windows.
module XMonad.Layout.Spacing

-- | Surround all windows by a certain number of pixels of blank space.
spacing :: Int -> l a -> ModifiedLayout Spacing l a
data Spacing a

-- | Surrounds all windows with blank space, except when the window is the
--   only visible window on the current workspace.
smartSpacing :: Int -> l a -> ModifiedLayout SmartSpacing l a
data SmartSpacing a
instance Show (Spacing a)
instance Read (Spacing a)
instance Show (SmartSpacing a)
instance Read (SmartSpacing a)
instance LayoutModifier SmartSpacing a
instance LayoutModifier Spacing a


-- | Focus the nth window of the current workspace.
module XMonad.Actions.FocusNth

-- | Give focus to the nth window of the current workspace.
focusNth :: Int -> X ()
focusNth' :: Int -> Stack a -> Stack a


-- | Like <a>XMonad.Actions.Plane</a> for an arbitrary number of
--   dimensions.
module XMonad.Actions.WorkspaceCursors
focusDepth :: Cursors t -> Int

-- | makeCursors requires a nonempty string, and each sublist must be
--   nonempty
makeCursors :: [[String]] -> Cursors String

-- | List of elements of a structure.
toList :: Foldable t => t a -> [a]

-- | The state is stored in the <a>WorkspaceCursors</a> layout modifier.
--   Put this as your outermost modifier, unless you want different cursors
--   at different times (using <a>XMonad.Layout.MultiToggle</a>)
workspaceCursors :: Cursors String -> l a -> ModifiedLayout WorkspaceCursors l a
data WorkspaceCursors a
getFocus :: Cursors b -> b

-- | <tt>modifyLayer</tt> is used to change the focus at a given depth
modifyLayer :: (Stack (Cursors String) -> Stack (Cursors String)) -> Int -> X ()

-- | example usages are <a>shiftLayer</a> and <a>shiftModifyLayer</a>
modifyLayer' :: (Stack (Cursors String) -> X (Stack (Cursors String))) -> Int -> X ()

-- | <tt>shiftModifyLayer</tt> is the same as <a>modifyLayer</a>, but also
--   shifts the currently focused window to the new workspace
shiftModifyLayer :: (Stack (Cursors String) -> Stack (Cursors WorkspaceId)) -> Int -> X ()

-- | <tt>shiftLayer</tt> is the same as <a>shiftModifyLayer</a>, but the
--   focus remains on the current workspace.
shiftLayer :: (Stack (Cursors String) -> Stack (Cursors WorkspaceId)) -> Int -> X ()
focusNth' :: Int -> Stack a -> Stack a

-- | non-wrapping version of <a>focusUp'</a>
noWrapUp :: Stack t -> Stack t

-- | non-wrapping version of <a>focusDown'</a>
noWrapDown :: Stack t -> Stack t
data Cursors a
instance Typeable1 Cursors
instance Typeable1 WorkspaceCursors
instance Typeable ChangeCursors
instance Eq a => Eq (Cursors a)
instance Show a => Show (Cursors a)
instance Read a => Read (Cursors a)
instance Read (WorkspaceCursors a)
instance Show (WorkspaceCursors a)
instance LayoutModifier WorkspaceCursors a
instance Message ChangeCursors
instance Functor Cursors
instance Foldable Cursors


-- | Move and resize floating windows.
module XMonad.Actions.FloatKeys

-- | <tt>keysMoveWindow (dx, dy)</tt> moves the window by <tt>dx</tt>
--   pixels to the right and <tt>dy</tt> pixels down.
keysMoveWindow :: D -> Window -> X ()

-- | <tt>keysMoveWindowTo (x, y) (gx, gy)</tt> moves the window relative
--   point <tt>(gx, gy)</tt> to the point <tt>(x,y)</tt>, where
--   <tt>(gx,gy)</tt> gives a position relative to the window border, i.e.
--   <tt>gx = 0</tt> is the left border, <tt>gx = 1</tt> is the right
--   border, <tt>gy = 0</tt> is the top border, and <tt>gy = 1</tt> the
--   bottom border.
--   
--   For example, on a 1024x768 screen:
--   
--   <pre>
--   keysMoveWindowTo (512,384) (1%2, 1%2) -- center the window on screen
--   keysMoveWindowTo (1024,0) (1, 0)      -- put window in the top right corner
--   </pre>
keysMoveWindowTo :: P -> G -> Window -> X ()

-- | <tt>keysResizeWindow (dx, dy) (gx, gy)</tt> changes the width by
--   <tt>dx</tt> and the height by <tt>dy</tt>, leaving the window-relative
--   point <tt>(gx, gy)</tt> fixed.
--   
--   For example:
--   
--   <pre>
--   keysResizeWindow (10, 0) (0, 0)      -- make the window 10 pixels larger to the right
--   keysResizeWindow (10, 0) (0, 1%2)    -- does the same, unless sizeHints are applied
--   keysResizeWindow (10, 10) (1%2, 1%2) -- add 5 pixels on each side
--   keysResizeWindow (-10, -10) (0, 1)   -- shrink the window in direction of the bottom-left corner
--   </pre>
keysResizeWindow :: D -> G -> Window -> X ()

-- | <tt>keysAbsResizeWindow (dx, dy) (ax, ay)</tt> changes the width by
--   <tt>dx</tt> and the height by <tt>dy</tt>, leaving the screen absolute
--   point <tt>(ax, ay)</tt> fixed.
--   
--   For example:
--   
--   <pre>
--   keysAbsResizeWindow (10, 10) (0, 0)   -- enlarge the window; if it is not in the top-left corner it will also be moved down and to the right.
--   </pre>
keysAbsResizeWindow :: D -> D -> Window -> X ()
type P = (Position, Position)
type G = (Rational, Rational)


-- | A module for painting on the screen
module XMonad.Util.XUtils

-- | Compute the weighted average the colors of two given Pixel values.
averagePixels :: Pixel -> Pixel -> Double -> X Pixel

-- | Create a simple window given a rectangle. If Nothing is given only the
--   exposureMask will be set, otherwise the Just value. Use
--   <a>showWindow</a> to map and hideWindow to unmap.
createNewWindow :: Rectangle -> Maybe EventMask -> String -> Bool -> X Window

-- | Map a window
showWindow :: Window -> X ()

-- | the list version
showWindows :: [Window] -> X ()

-- | unmap a window
hideWindow :: Window -> X ()

-- | the list version
hideWindows :: [Window] -> X ()

-- | destroy a window
deleteWindow :: Window -> X ()

-- | the list version
deleteWindows :: [Window] -> X ()

-- | Fill a window with a rectangle and a border
paintWindow :: Window -> Dimension -> Dimension -> Dimension -> String -> String -> X ()

-- | Fill a window with a rectangle and a border, and write | a number of
--   strings to given positions
paintAndWrite :: Window -> XMonadFont -> Dimension -> Dimension -> Dimension -> String -> String -> String -> String -> [Align] -> [String] -> X ()

-- | Fill a window with a rectangle and a border, and write | a number of
--   strings and a number of icons to given positions
paintTextAndIcons :: Window -> XMonadFont -> Dimension -> Dimension -> Dimension -> String -> String -> String -> String -> [Align] -> [String] -> [Placement] -> [[[Bool]]] -> X ()

-- | Get the Pixel value for a named color: if an invalid name is given the
--   black pixel will be returned.
stringToPixel :: (Functor m, MonadIO m) => Display -> String -> m Pixel

-- | Short-hand for <a>fromIntegral</a>
fi :: (Integral a, Num b) => a -> b


-- | This is a pure layout modifier that will let you move and resize
--   windows with the keyboard in any layout.
module XMonad.Layout.WindowArranger

-- | A layout modifier to float the windows in a workspace
windowArrange :: l a -> ModifiedLayout WindowArranger l a

-- | A layout modifier to float all the windows in a workspace
windowArrangeAll :: l a -> ModifiedLayout WindowArranger l a
data WindowArrangerMsg
DeArrange :: WindowArrangerMsg
Arrange :: WindowArrangerMsg
IncreaseLeft :: Int -> WindowArrangerMsg
IncreaseRight :: Int -> WindowArrangerMsg
IncreaseUp :: Int -> WindowArrangerMsg
IncreaseDown :: Int -> WindowArrangerMsg
DecreaseLeft :: Int -> WindowArrangerMsg
DecreaseRight :: Int -> WindowArrangerMsg
DecreaseUp :: Int -> WindowArrangerMsg
DecreaseDown :: Int -> WindowArrangerMsg
MoveLeft :: Int -> WindowArrangerMsg
MoveRight :: Int -> WindowArrangerMsg
MoveUp :: Int -> WindowArrangerMsg
MoveDown :: Int -> WindowArrangerMsg
SetGeometry :: Rectangle -> WindowArrangerMsg
data WindowArranger a

-- | Given a function to be applied to each member of ta list, and a
--   function to check a condition by processing this transformed member
--   with something, you get the first member that satisfy the condition,
--   or an empty list.
memberFromList :: (b -> c) -> (c -> a -> Bool) -> a -> [b] -> [b]

-- | Given a function to be applied to each member of a list, and a
--   function to check a condition by processing this transformed member
--   with the members of a list, you get the list of members that satisfy
--   the condition.
listFromList :: (b -> c) -> (c -> [a] -> Bool) -> [a] -> [b] -> [b]

-- | Get the list of elements to be deleted and the list of elements to be
--   added to the first list in order to get the second list.
diff :: Eq a => ([a], [a]) -> ([a], [a])
instance Typeable WindowArrangerMsg
instance Read a => Read (ArrangedWindow a)
instance Show a => Show (ArrangedWindow a)
instance Read a => Read (WindowArranger a)
instance Show a => Show (WindowArranger a)
instance (Show a, Read a, Eq a) => LayoutModifier WindowArranger a
instance Message WindowArrangerMsg


-- | Causes the pointer to follow whichever window focus changes to.
--   Compliments the idea of switching focus as the mouse crosses window
--   boundaries to keep the mouse near the currently focused window
module XMonad.Actions.UpdatePointer

-- | Update the pointer's location to the currently focused window or empty
--   screen unless it's already there, or unless the user was changing
--   focus with the mouse
updatePointer :: PointerPosition -> X ()
data PointerPosition
Nearest :: PointerPosition
Relative :: Rational -> Rational -> PointerPosition
TowardsCentre :: Rational -> Rational -> PointerPosition
instance Read PointerPosition
instance Show PointerPosition


-- | Automagically put the focused window in the master area.
module XMonad.Layout.MagicFocus

-- | Create a new layout which automagically puts the focused window in the
--   master area.
magicFocus :: l a -> ModifiedLayout MagicFocus l a

-- | An eventHook that overrides the normal focusFollowsMouse. When the
--   mouse it moved to another window, that window is replaced as the
--   master, and the mouse is warped to inside the new master.
--   
--   It prevents infinite loops when focusFollowsMouse is true (the
--   default), and MagicFocus is in use when changing focus with the mouse.
--   
--   This eventHook does nothing when there are floating windows on the
--   current workspace.
promoteWarp :: Event -> X All

-- | promoteWarp' allows you to specify an arbitrary PointerPosition to
--   apply when the mouse enters another window.
promoteWarp' :: PointerPosition -> Event -> X All

-- | Another event hook to override the focusFollowsMouse and make the
--   pointer only follow if a given condition is satisfied. This could be
--   used to disable focusFollowsMouse only for given workspaces or
--   layouts. Beware that your focusFollowsMouse setting is ignored if you
--   use this event hook.
followOnlyIf :: X Bool -> Event -> X All

-- | Disables focusFollow on the given workspaces:
disableFollowOnWS :: [WorkspaceId] -> X Bool
data MagicFocus a
instance Show (MagicFocus a)
instance Read (MagicFocus a)
instance LayoutModifier MagicFocus Window


-- | Screenshot : <a>http://caladan.rave.org/magnifier.png</a>
--   
--   This is a layout modifier that will make a layout increase the size of
--   the window that has focus.
module XMonad.Layout.Magnifier

-- | Increase the size of the window that has focus
magnifier :: l a -> ModifiedLayout Magnifier l a

-- | Increase the size of the window that has focus, unless if it is the
--   master window.
magnifier' :: l a -> ModifiedLayout Magnifier l a

-- | Magnifier that defaults to Off
magnifierOff :: l a -> ModifiedLayout Magnifier l a

-- | Change the size of the window that has focus by a custom zoom
magnifiercz :: Rational -> l a -> ModifiedLayout Magnifier l a

-- | Increase the size of the window that has focus by a custom zoom,
--   unless if it is the master window.
magnifiercz' :: Rational -> l a -> ModifiedLayout Magnifier l a

-- | A magnifier that greatly magnifies just the vertical direction
maximizeVertical :: l a -> ModifiedLayout Magnifier l a
data MagnifyMsg
MagnifyMore :: MagnifyMsg
MagnifyLess :: MagnifyMsg
ToggleOn :: MagnifyMsg
ToggleOff :: MagnifyMsg
Toggle :: MagnifyMsg
data Magnifier a
instance Typeable MagnifyMsg
instance Read Toggle
instance Show Toggle
instance Read MagnifyMaster
instance Show MagnifyMaster
instance Read (Magnifier a)
instance Show (Magnifier a)
instance LayoutModifier Magnifier Window
instance Message MagnifyMsg


-- | A layout in the spirit of <a>XMonad.Layout.ResizableTile</a>, but with
--   the option to use the mouse to adjust the layout.
module XMonad.Layout.MouseResizableTile
mouseResizableTile :: MouseResizableTile a

-- | May be removed in favor of <tt>mouseResizableTile { isMirrored = True
--   }</tt>
mouseResizableTileMirrored :: MouseResizableTile a
data MRTMessage
ShrinkSlave :: MRTMessage
ExpandSlave :: MRTMessage

-- | Get/set the number of windows in master pane (default: 1).
nmaster :: MouseResizableTile a -> Int

-- | Get/set the proportion of screen occupied by master pane (default:
--   1/2).
masterFrac :: MouseResizableTile a -> Rational

-- | Get/set the proportion of remaining space in a column occupied by a
--   slave window (default: 1/2).
slaveFrac :: MouseResizableTile a -> Rational

-- | Get/set the increment used when modifying masterFrac/slaveFrac by the
--   Shrink, Expand, etc. messages (default: 3/100).
fracIncrement :: MouseResizableTile a -> Rational

-- | Get/set whether the layout is mirrored (default: False).
isMirrored :: MouseResizableTile a -> Bool

-- | Get/set dragger and gap dimensions (default: FixedDragger 6 6).
draggerType :: MouseResizableTile a -> DraggerType

-- | Specifies the size of the clickable area between windows.
data DraggerType
FixedDragger :: Dimension -> Dimension -> DraggerType

-- | width of a gap between windows
gapWidth :: DraggerType -> Dimension

-- | width of the dragger itself (will overlap windows if greater than gap)
draggerWidth :: DraggerType -> Dimension

-- | no gaps, draggers overlap window borders
BordersDragger :: DraggerType
data MouseResizableTile a
instance Typeable MRTMessage
instance Show DraggerInfo
instance Read DraggerInfo
instance Show DraggerType
instance Read DraggerType
instance Show (MouseResizableTile a)
instance Read (MouseResizableTile a)
instance LayoutClass MouseResizableTile Window
instance Message MRTMessage


-- | Useful in a dual-head setup: Looks at the requested geometry of new
--   windows and moves them to the workspace of the non-focused screen if
--   necessary.
module XMonad.Hooks.WorkspaceByPos
workspaceByPos :: ManageHook


-- | This is a layout modifier that will show the workspace name
module XMonad.Layout.ShowWName

-- | A layout modifier to show the workspace name when switching
showWName :: l a -> ModifiedLayout ShowWName l a

-- | A layout modifier to show the workspace name when switching. It is
--   possible to provide a custom configuration.
showWName' :: SWNConfig -> l a -> ModifiedLayout ShowWName l a
defaultSWNConfig :: SWNConfig
data SWNConfig
SWNC :: String -> String -> String -> Rational -> SWNConfig

-- | Font name
swn_font :: SWNConfig -> String

-- | Background color
swn_bgcolor :: SWNConfig -> String

-- | String color
swn_color :: SWNConfig -> String

-- | Time in seconds of the name visibility
swn_fade :: SWNConfig -> Rational
data ShowWName a
instance Read SWNConfig
instance Show SWNConfig
instance Read (ShowWName a)
instance Show (ShowWName a)
instance LayoutModifier ShowWName a


-- | Automatic placement of floating windows.
module XMonad.Hooks.Place

-- | Repositions the focused window according to a placement policy. Works
--   for both "real" floating windows and windows in a
--   <a>WindowArranger</a>-based layout.
placeFocused :: Placement -> X ()

-- | Hook to automatically place windows when they are created.
placeHook :: Placement -> ManageHook

-- | The type of placement policies
data Placement

-- | Try to place windows with as little overlap as possible
smart :: (Rational, Rational) -> Placement
simpleSmart :: Placement

-- | Place windows at a fixed position
fixed :: (Rational, Rational) -> Placement

-- | Place windows under the mouse
underMouse :: (Rational, Rational) -> Placement

-- | Apply the given placement policy, constraining the placed windows
--   inside the screen boundaries.
inBounds :: Placement -> Placement

-- | Same as <a>inBounds</a>, but allows specifying gaps along the screen's
--   edges
withGaps :: (Dimension, Dimension, Dimension, Dimension) -> Placement -> Placement

-- | Compute the new position of a window according to a placement policy.
purePlaceWindow :: Placement -> Rectangle -> [Rectangle] -> (Position, Position) -> Rectangle -> Rectangle
instance Show Placement
instance Read Placement
instance Eq Placement
instance Show a => Show (SmartRectangle a)
instance Eq a => Eq (SmartRectangle a)


-- | Layouts that splits the screen either horizontally or vertically and
--   shows two windows. The first window is always the master window, and
--   the other is either the currently focused window or the second window
--   in layout order.
module XMonad.Layout.DragPane
dragPane :: DragType -> Double -> Double -> DragPane a
data DragPane a
data DragType
Horizontal :: DragType
Vertical :: DragType
instance Typeable SetFrac
instance Show DragType
instance Read DragType
instance Show (DragPane a)
instance Read (DragPane a)
instance Show SetFrac
instance Read SetFrac
instance Eq SetFrac
instance Message SetFrac
instance LayoutClass DragPane a


-- | Reflect a layout horizontally or vertically.
module XMonad.Layout.Reflect

-- | Apply a horizontal reflection (left &lt;--&gt; right) to a layout.
reflectHoriz :: l a -> ModifiedLayout Reflect l a

-- | Apply a vertical reflection (top &lt;--&gt; bottom) to a layout.
reflectVert :: l a -> ModifiedLayout Reflect l a
data REFLECTX
REFLECTX :: REFLECTX
data REFLECTY
REFLECTY :: REFLECTY
data Reflect a
instance Typeable REFLECTX
instance Typeable REFLECTY
instance Read ReflectDir
instance Show ReflectDir
instance Show (Reflect a)
instance Read (Reflect a)
instance Read REFLECTX
instance Show REFLECTX
instance Eq REFLECTX
instance Read REFLECTY
instance Show REFLECTY
instance Eq REFLECTY
instance Transformer REFLECTY Window
instance Transformer REFLECTX Window
instance LayoutModifier Reflect a


-- | A layout modifier that puts some windows in a <a>drawer</a> which
--   retracts and expands depending on whether any window in it has focus.
--   
--   Useful for music players, tool palettes, etc.
module XMonad.Layout.Drawer

-- | Construct a drawer with a simple layout of the windows inside
simpleDrawer :: Rational -> Rational -> Property -> Drawer Tall a

-- | Construct a drawer with an arbitrary layout for windows inside
drawer :: Rational -> Rational -> Property -> (l a) -> Drawer l a
onLeft :: Drawer l a -> l' a -> ModifiedLayout (Drawer l) l' a
onTop :: Drawer l a -> l' a -> Mirror (ModifiedLayout (Drawer l) (Mirror l')) a
onRight :: Drawer l a -> l' a -> Reflected (ModifiedLayout (Drawer l) (Reflected l')) a
onBottom :: Drawer l a -> l' a -> Reflected (Mirror (ModifiedLayout (Drawer l) (Mirror (Reflected l')))) a
data Drawer l a
type Reflected l = ModifiedLayout Reflect l
instance Read (l a) => Read (Drawer l a)
instance Show (l a) => Show (Drawer l a)
instance (LayoutClass l Window, Read (l Window)) => LayoutModifier (Drawer l) Window


-- | A basic floating layout like SimpleFloat but without the decoration.
module XMonad.Layout.SimplestFloat

-- | A simple floating layout where every window is placed according to the
--   window's initial attributes.
simplestFloat :: Eq a => (ModifiedLayout WindowArranger SimplestFloat) a
data SimplestFloat a
instance Show (SimplestFloat a)
instance Read (SimplestFloat a)
instance LayoutClass SimplestFloat Window


-- | Resize floating windows from any corner.
module XMonad.Actions.FlexibleResize

-- | Resize a floating window from whichever corner the mouse is closest
--   to.
mouseResizeWindow :: Window -> X ()

-- | Resize a floating window from whichever corner or edge the mouse is
--   closest to.
mouseResizeEdgeWindow :: Rational -> Window -> X ()


-- | Move and resize floating windows without warping the mouse.
module XMonad.Actions.FlexibleManipulate

-- | Given an interpolation function, implement an appropriate window
--   manipulation action.
mouseWindow :: (Double -> Double) -> Window -> X ()

-- | Manipulate the window based on discrete pick regions; the window is
--   divided into regions by thirds along each axis.
discrete, position, resize, linear :: Double -> Double


-- | Find an empty workspace.
module XMonad.Actions.FindEmptyWorkspace

-- | Find and view an empty workspace. Do nothing if all workspaces are in
--   use.
viewEmptyWorkspace :: X ()

-- | Tag current window to an empty workspace and view it. Do nothing if
--   all workspaces are in use.
tagToEmptyWorkspace :: X ()

-- | Send current window to an empty workspace. Do nothing if all
--   workspaces are in use.
sendToEmptyWorkspace :: X ()


-- | Module for storing custom mutable state in xmonad.
module XMonad.Util.ExtensibleState

-- | Add a value to the extensible state field. A previously stored value
--   with the same type will be overwritten. (More precisely: A value whose
--   string representation of its type is equal to the new one's)
put :: ExtensionClass a => a -> X ()

-- | Apply a function to a stored value of the matching type or the initial
--   value if there is none.
modify :: ExtensionClass a => (a -> a) -> X ()

-- | Remove the value from the extensible state field that has the same
--   type as the supplied argument
remove :: ExtensionClass a => a -> X ()

-- | Try to retrieve a value of the requested type, return an initial value
--   if there is no such value.
get :: ExtensionClass a => X a
gets :: ExtensionClass a => (a -> b) -> X b


-- | Provides methods for cycling through groups of windows across
--   workspaces, ignoring windows that do not belong to this group. A group
--   consists of all windows matching a user-provided boolean query.
--   
--   Also provides a method for jumping back to the most recently used
--   window in any given group.
module XMonad.Actions.GroupNavigation

-- | The direction in which to look for the next match
data Direction

-- | Forward from current window or workspace
Forward :: Direction

-- | Backward from current window or workspace
Backward :: Direction

-- | Backward in history
History :: Direction

-- | Focuses the next window that matches the given boolean query. Does
--   nothing if there is no such window. This is the same as
--   <a>nextMatchOrDo</a> with alternate action <tt>return ()</tt>.
nextMatch :: Direction -> Query Bool -> X ()

-- | Focuses the next window that matches the given boolean query. If there
--   is no such window, perform the given action instead.
nextMatchOrDo :: Direction -> Query Bool -> X () -> X ()

-- | Focuses the next window for which the given query produces the same
--   result as the currently focused window. Does nothing if there is no
--   focused window (i.e., the current workspace is empty).
nextMatchWithThis :: Eq a => Direction -> Query a -> X ()

-- | Action that needs to be executed as a logHook to maintain the focus
--   history of all windows as the WindowSet changes.
historyHook :: X ()
instance Typeable HistoryDB
instance Read HistoryDB
instance Show HistoryDB
instance ExtensionClass HistoryDB


-- | Remap Keybinding on the fly, e.g having Dvorak char, but everything
--   with Control/Shift is left us Layout
module XMonad.Actions.KeyRemap

-- | Using this in the keybindings to set the actual Key Translation table
setKeyRemap :: KeymapTable -> X ()

-- | Append the output of this function to your keybindings with ++
buildKeyRemapBindings :: [KeymapTable] -> [((KeyMask, KeySym), X ())]

-- | Adding this to your startupHook, to select your default Key
--   Translation table. You also must give it all the KeymapTables you are
--   willing to use
setDefaultKeyRemap :: KeymapTable -> [KeymapTable] -> X ()
data KeymapTable
KeymapTable :: [((KeyMask, KeySym), (KeyMask, KeySym))] -> KeymapTable

-- | The empty KeymapTable, does no translation
emptyKeyRemap :: KeymapTable

-- | The dvorak Programmers keymap, translates from us keybindings to
--   dvorak programmers
dvorakProgrammerKeyRemap :: KeymapTable
instance Typeable KeymapTable
instance Show KeymapTable
instance ExtensionClass KeymapTable


-- | ShowText displays text for sometime on the screen similar to
--   <a>XMonad.Util.Dzen</a> which offers more features (currently)
module XMonad.Actions.ShowText
defaultSTConfig :: ShowTextConfig

-- | Handles timer events that notify when a window should be removed
handleTimerEvent :: Event -> X All

-- | Shows a window in the center of the screen with the given text
flashText :: ShowTextConfig -> Rational -> String -> X ()
data ShowTextConfig
STC :: String -> String -> String -> ShowTextConfig

-- | Font name
st_font :: ShowTextConfig -> String

-- | Background color
st_bg :: ShowTextConfig -> String

-- | Foreground color
st_fg :: ShowTextConfig -> String
instance Typeable ShowText
instance Read ShowText
instance Show ShowText
instance ExtensionClass ShowText


-- | UrgencyHook lets you configure an action to occur when a window
--   demands your attention. (In traditional WMs, this takes the form of
--   "flashing" on your "taskbar." Blech.)
module XMonad.Hooks.UrgencyHook

-- | This is the method to enable an urgency hook. It uses the default
--   <a>urgencyConfig</a> to control behavior. To change this, use
--   <a>withUrgencyHookC</a> instead.
withUrgencyHook :: (LayoutClass l Window, UrgencyHook h) => h -> XConfig l -> XConfig l

-- | This lets you modify the defaults set in <a>urgencyConfig</a>. An
--   example:
--   
--   <pre>
--   withUrgencyHookC dzenUrgencyHook { ... } urgencyConfig { suppressWhen = Focused }
--   </pre>
--   
--   (Don't type the <tt>...</tt>, you dolt.) See <a>UrgencyConfig</a> for
--   details on configuration.
withUrgencyHookC :: (LayoutClass l Window, UrgencyHook h) => h -> UrgencyConfig -> XConfig l -> XConfig l

-- | Global configuration, applied to all types of <a>UrgencyHook</a>. See
--   <a>urgencyConfig</a> for the defaults.
data UrgencyConfig
UrgencyConfig :: SuppressWhen -> RemindWhen -> UrgencyConfig

-- | when to trigger the urgency hook
suppressWhen :: UrgencyConfig -> SuppressWhen

-- | when to re-trigger the urgency hook
remindWhen :: UrgencyConfig -> RemindWhen

-- | The default <a>UrgencyConfig</a>. suppressWhen = Visible, remindWhen =
--   Dont. Use a variation of this in your config just as you use a
--   variation of defaultConfig for your xmonad definition.
urgencyConfig :: UrgencyConfig

-- | A set of choices as to <i>when</i> you should (or rather, shouldn't)
--   be notified of an urgent window. The default is <a>Visible</a>. Prefix
--   each of the following with "don't bug me when":
data SuppressWhen

-- | the window is currently visible
Visible :: SuppressWhen

-- | the window is on the currently focused physical screen
OnScreen :: SuppressWhen

-- | the window is currently focused
Focused :: SuppressWhen

-- | ... aww, heck, go ahead and bug me, just in case.
Never :: SuppressWhen

-- | A set of choices as to when you want to be re-notified of an urgent
--   window. Perhaps you focused on something and you miss the dzen popup
--   bar. Or you're AFK. Or you feel the need to be more distracted. I
--   don't care.
--   
--   The interval arguments are in seconds. See the <a>minutes</a> helper.
data RemindWhen

-- | triggering once is enough
Dont :: RemindWhen

-- | repeat <a>arg1</a> times every <a>arg2</a> seconds
Repeatedly :: Int -> Interval -> RemindWhen

-- | repeat every <a>arg1</a> until the urgency hint is cleared
Every :: Interval -> RemindWhen

-- | Focuses the most recently urgent window. Good for what ails ya -- I
--   mean, your keybindings. Example keybinding:
--   
--   <pre>
--   , ((modm              , xK_BackSpace), focusUrgent)
--   </pre>
focusUrgent :: X ()

-- | Just makes the urgents go away. Example keybinding:
--   
--   <pre>
--   , ((modm .|. shiftMask, xK_BackSpace), clearUrgents)
--   </pre>
clearUrgents :: X ()

-- | Flashes when a window requests your attention and you can't see it.
--   Defaults to a duration of five seconds, and no extra args to dzen. See
--   <a>DzenUrgencyHook</a>.
dzenUrgencyHook :: DzenUrgencyHook

-- | Your set of options for configuring a dzenUrgencyHook.
data DzenUrgencyHook
DzenUrgencyHook :: Int -> [String] -> DzenUrgencyHook

-- | number of microseconds to display the dzen (hence, you'll probably
--   want to use <a>seconds</a>)
duration :: DzenUrgencyHook -> Int

-- | list of extra args (as <a>String</a>s) to pass to dzen
args :: DzenUrgencyHook -> [String]
data NoUrgencyHook
NoUrgencyHook :: NoUrgencyHook
data BorderUrgencyHook
BorderUrgencyHook :: !String -> BorderUrgencyHook
urgencyBorderColor :: BorderUrgencyHook -> !String
data FocusHook
FocusHook :: FocusHook

-- | A prettified way of multiplying by 60. Use like: <tt>(5
--   <a>minutes</a>)</tt>.
minutes :: Rational -> Rational

-- | Multiplies by ONE MILLION, for functions that take microseconds.
--   
--   Use like:
--   
--   <pre>
--   (5.5 `seconds`)
--   </pre>
--   
--   In GHC 7 and later, you must either enable the PostfixOperators
--   extension (by adding
--   
--   <pre>
--   {-# LANGUAGE PostfixOperators #-}
--   </pre>
--   
--   to the top of your file) or use seconds in prefix form:
--   
--   <pre>
--   5.5 seconds
--   </pre>
seconds :: Rational -> Int

-- | X action that returns a list of currently urgent windows. You might
--   use it, or <a>withUrgents</a>, in your custom logHook, to display the
--   workspaces that contain urgent windows.
readUrgents :: X [Window]

-- | An HOF version of <a>readUrgents</a>, for those who prefer that sort
--   of thing.
withUrgents :: ([Window] -> X a) -> X a
data StdoutUrgencyHook
StdoutUrgencyHook :: StdoutUrgencyHook
newtype SpawnUrgencyHook
SpawnUrgencyHook :: String -> SpawnUrgencyHook

-- | The class definition, and some pre-defined instances.
class UrgencyHook h
urgencyHook :: UrgencyHook h => h -> Window -> X ()
type Interval = Rational

-- | A hook that sets the border color of an urgent window. The color will
--   remain until the next time the window gains or loses focus, at which
--   point the standard border color from the XConfig will be applied. You
--   may want to use suppressWhen = Never with this:
--   
--   <pre>
--   withUrgencyHookC BorderUrgencyHook { urgencyBorderColor = "#ff0000" } urgencyConfig { suppressWhen = Never } ...
--   </pre>
--   
--   (This should be <tt>urgentBorderColor</tt> but that breaks
--   <a>XMonad.Layout.Decoration</a>. <tt>borderColor</tt> breaks anyone
--   using <tt>XPConfig</tt> from <a>XMonad.Prompt</a>. We need to think a
--   bit more about namespacing issues, maybe.)
borderUrgencyHook :: String -> Window -> X ()

-- | A hook which will automatically send you to anything which sets the
--   urgent flag (as opposed to printing some sort of message. You would
--   use this as usual, eg.
--   
--   <pre>
--   withUrgencyHook FocusHook $ myconfig { ...
--   </pre>
focusHook :: Window -> X ()

-- | Spawn a commandline thing, appending the window id to the prefix
--   string you provide. (Make sure to add a space if you need it.) Do your
--   crazy xcompmgr thing.
spawnUrgencyHook :: String -> Window -> X ()

-- | For debugging purposes, really.
stdoutUrgencyHook :: Window -> X ()
instance Typeable Urgents
instance Typeable Reminder
instance Read Urgents
instance Show Urgents
instance Read SuppressWhen
instance Show SuppressWhen
instance Read RemindWhen
instance Show RemindWhen
instance Read UrgencyConfig
instance Show UrgencyConfig
instance Show Reminder
instance Read Reminder
instance Eq Reminder
instance Read h => Read (WithUrgencyHook h)
instance Show h => Show (WithUrgencyHook h)
instance Read NoUrgencyHook
instance Show NoUrgencyHook
instance Read DzenUrgencyHook
instance Show DzenUrgencyHook
instance Read FocusHook
instance Show FocusHook
instance Read BorderUrgencyHook
instance Show BorderUrgencyHook
instance Read SpawnUrgencyHook
instance Show SpawnUrgencyHook
instance Read StdoutUrgencyHook
instance Show StdoutUrgencyHook
instance UrgencyHook StdoutUrgencyHook
instance UrgencyHook SpawnUrgencyHook
instance UrgencyHook BorderUrgencyHook
instance UrgencyHook FocusHook
instance UrgencyHook DzenUrgencyHook
instance UrgencyHook NoUrgencyHook
instance UrgencyHook (Window -> X ())
instance ExtensionClass [Reminder]
instance ExtensionClass Urgents


-- | A layout modifier and a class for easily creating decorated layouts.
module XMonad.Layout.Decoration

-- | A layout modifier that, with a <a>Shrinker</a>, a <a>Theme</a>, a
--   <a>DecorationStyle</a>, and a layout, will decorate this layout
--   according to the decoration style provided.
--   
--   For some usage examples see <a>XMonad.Layout.DecorationMadness</a>.
decoration :: (DecorationStyle ds a, Shrinker s) => s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a

-- | A <a>Theme</a> is a record of colors, font etc., to customize a
--   <a>DecorationStyle</a>.
--   
--   For a collection of <a>Theme</a>s see <a>XMonad.Util.Themes</a>
data Theme
Theme :: String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> Dimension -> Dimension -> [(String, Align)] -> [([[Bool]], Placement)] -> Theme

-- | Color of the active window
activeColor :: Theme -> String

-- | Color of the inactive window
inactiveColor :: Theme -> String

-- | Color of the urgent window
urgentColor :: Theme -> String

-- | Color of the border of the active window
activeBorderColor :: Theme -> String

-- | Color of the border of the inactive window
inactiveBorderColor :: Theme -> String

-- | Color of the border of the urgent window
urgentBorderColor :: Theme -> String

-- | Color of the text of the active window
activeTextColor :: Theme -> String

-- | Color of the text of the inactive window
inactiveTextColor :: Theme -> String

-- | Color of the text of the urgent window
urgentTextColor :: Theme -> String

-- | Font name
fontName :: Theme -> String

-- | Maximum width of the decorations (if supported by the
--   <a>DecorationStyle</a>)
decoWidth :: Theme -> Dimension

-- | Height of the decorations
decoHeight :: Theme -> Dimension

-- | Extra text to appear in a window's title bar. Refer to for a use
--   <a>XMonad.Layout.ImageButtonDecoration</a>
windowTitleAddons :: Theme -> [(String, Align)]

-- | Extra icons to appear in a window's title bar. Inner <tt>[Bool]</tt>
--   is a row in a icon bitmap.
windowTitleIcons :: Theme -> [([[Bool]], Placement)]

-- | The default xmonad <a>Theme</a>.
defaultTheme :: Theme

-- | The <a>Decoration</a> <a>LayoutModifier</a>. This data type is an
--   instance of the <a>LayoutModifier</a> class. This data type will be
--   passed, together with a layout, to the <a>ModifiedLayout</a> type
--   constructor to modify the layout by adding decorations according to a
--   <a>DecorationStyle</a>.
data Decoration ds s a

-- | A <a>Decoration</a> layout modifier will handle <a>SetTheme</a>, a
--   message to dynamically change the decoration <a>Theme</a>.
data DecorationMsg
SetTheme :: Theme -> DecorationMsg

-- | The <a>DecorationStyle</a> class, defines methods used in the
--   implementation of the <a>Decoration</a> <a>LayoutModifier</a>
--   instance. A type instance of this class is passed to the
--   <a>Decoration</a> type in order to decorate a layout, by using these
--   methods.
class (Read (ds a), Show (ds a), Eq a) => DecorationStyle ds a where describeDeco ds = show ds shrink _ (Rectangle _ _ _ dh) (Rectangle x y w h) = Rectangle x (y + fi dh) w (h - dh) decorationEventHook ds s e = handleMouseFocusDrag ds s e decorationCatchClicksHook _ _ _ _ = return False decorationWhileDraggingHook _ ex ey (mainw, r) x y = handleDraggingInProgress ex ey (mainw, r) x y decorationAfterDraggingHook _ds (mainw, _r) _decoWin = focus mainw pureDecoration _ _ ht _ s _ (w, Rectangle x y wh ht') = if isInStack s w && (ht < ht') then Just $ Rectangle x y wh ht else Nothing decorate ds w h r s wrs wr = return $ pureDecoration ds w h r s wrs wr
describeDeco :: DecorationStyle ds a => ds a -> String
shrink :: DecorationStyle ds a => ds a -> Rectangle -> Rectangle -> Rectangle
decorationEventHook :: DecorationStyle ds a => ds a -> DecorationState -> Event -> X ()
decorationCatchClicksHook :: DecorationStyle ds a => ds a -> Window -> Int -> Int -> X Bool
decorationWhileDraggingHook :: DecorationStyle ds a => ds a -> CInt -> CInt -> (Window, Rectangle) -> Position -> Position -> X ()
decorationAfterDraggingHook :: DecorationStyle ds a => ds a -> (Window, Rectangle) -> Window -> X ()
pureDecoration :: DecorationStyle ds a => ds a -> Dimension -> Dimension -> Rectangle -> Stack a -> [(a, Rectangle)] -> (a, Rectangle) -> Maybe Rectangle
decorate :: DecorationStyle ds a => ds a -> Dimension -> Dimension -> Rectangle -> Stack a -> [(a, Rectangle)] -> (a, Rectangle) -> X (Maybe Rectangle)

-- | The default <a>DecorationStyle</a>, with just the default methods'
--   implementations.
data DefaultDecoration a
DefaultDecoration :: DefaultDecoration a
class (Read s, Show s) => Shrinker s
shrinkIt :: Shrinker s => s -> String -> [String]
data DefaultShrinker
shrinkText :: DefaultShrinker
data CustomShrink
CustomShrink :: CustomShrink
shrinkWhile :: (String -> [String]) -> (String -> X Bool) -> String -> X String

-- | True if the window is in the <tt>Stack</tt>. The <a>Window</a> comes
--   second to facilitate list processing, even though <tt>w `isInStack`
--   s</tt> won't work...;)
isInStack :: Eq a => Stack a -> a -> Bool

-- | Given a <a>Rectangle</a> and a list of <a>Rectangle</a>s is True if
--   the <a>Rectangle</a> is not completely contained by any
--   <a>Rectangle</a> of the list.
isVisible :: Rectangle -> [Rectangle] -> Bool

-- | The contrary of <a>isVisible</a>.
isInvisible :: Rectangle -> [Rectangle] -> Bool

-- | True is the first <a>Rectangle</a> is totally within the second
--   <a>Rectangle</a>.
isWithin :: Rectangle -> Rectangle -> Bool

-- | Short-hand for <a>fromIntegral</a>
fi :: (Integral a, Num b) => a -> b
findWindowByDecoration :: Window -> DecorationState -> Maybe (OrigWin, (Window, Maybe Rectangle))

-- | The <a>Decoration</a> state component, where the list of decorated
--   window's is zipped with a list of decoration. A list of decoration is
--   a list of tuples, a <a>Maybe</a> <a>Window</a> and a 'Maybe
--   Rectangle'. The <a>Window</a> will be displayed only if the rectangle
--   is of type <a>Just</a>.
data DecorationState
type OrigWin = (Window, Rectangle)
instance Typeable DecorationMsg
instance Show Theme
instance Read Theme
instance (Show s, Show (ds a)) => Show (Decoration ds s a)
instance (Read s, Read (ds a)) => Read (Decoration ds s a)
instance Read (DefaultDecoration a)
instance Show (DefaultDecoration a)
instance Shrinker DefaultShrinker
instance Read DefaultShrinker
instance Show DefaultShrinker
instance Read CustomShrink
instance Show CustomShrink
instance (DecorationStyle ds Window, Shrinker s) => LayoutModifier (Decoration ds s) Window
instance Eq a => DecorationStyle DefaultDecoration a
instance Message DecorationMsg


-- | A layout modifier to resize windows with the mouse by grabbing the
--   window's lower right corner.
--   
--   This module must be used together with
--   <a>XMonad.Layout.WindowArranger</a>.
module XMonad.Actions.MouseResize
mouseResize :: l a -> ModifiedLayout MouseResize l a
data MouseResize a
MR :: [((a, Rectangle), Maybe a)] -> MouseResize a
instance LayoutModifier MouseResize Window
instance Read (MouseResize a)
instance Show (MouseResize a)


-- | A tabbed layout for the Xmonad Window Manager
module XMonad.Layout.Tabbed

-- | A tabbed layout with the default xmonad Theme.
--   
--   This is a minimal working configuration:
--   
--   <pre>
--   import XMonad
--   import XMonad.Layout.Tabbed
--   main = xmonad defaultConfig { layoutHook = simpleTabbed }
--   </pre>
simpleTabbed :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window

-- | A layout decorated with tabs and the possibility to set a custom
--   shrinker and theme.
tabbed :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a

-- | A layout modifier that uses the provided shrinker and theme to add
--   tabs to any layout.
addTabs :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a
simpleTabbedAlways :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
tabbedAlways :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
addTabsAlways :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a

-- | A bottom-tabbed layout with the default xmonad Theme.
simpleTabbedBottom :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window

-- | 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 -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a

-- | A layout modifier that uses the provided shrinker and theme to add
--   tabs to the bottom of any layout.
addTabsBottom :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a

-- | A bottom-tabbed layout with the default xmonad Theme.
simpleTabbedBottomAlways :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
tabbedBottomAlways :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
addTabsBottomAlways :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a

-- | A <a>Theme</a> is a record of colors, font etc., to customize a
--   <a>DecorationStyle</a>.
--   
--   For a collection of <a>Theme</a>s see <a>XMonad.Util.Themes</a>
data Theme
Theme :: String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> Dimension -> Dimension -> [(String, Align)] -> [([[Bool]], Placement)] -> Theme

-- | Color of the active window
activeColor :: Theme -> String

-- | Color of the inactive window
inactiveColor :: Theme -> String

-- | Color of the urgent window
urgentColor :: Theme -> String

-- | Color of the border of the active window
activeBorderColor :: Theme -> String

-- | Color of the border of the inactive window
inactiveBorderColor :: Theme -> String

-- | Color of the border of the urgent window
urgentBorderColor :: Theme -> String

-- | Color of the text of the active window
activeTextColor :: Theme -> String

-- | Color of the text of the inactive window
inactiveTextColor :: Theme -> String

-- | Color of the text of the urgent window
urgentTextColor :: Theme -> String

-- | Font name
fontName :: Theme -> String

-- | Maximum width of the decorations (if supported by the
--   <a>DecorationStyle</a>)
decoWidth :: Theme -> Dimension

-- | Height of the decorations
decoHeight :: Theme -> Dimension

-- | Extra text to appear in a window's title bar. Refer to for a use
--   <a>XMonad.Layout.ImageButtonDecoration</a>
windowTitleAddons :: Theme -> [(String, Align)]

-- | Extra icons to appear in a window's title bar. Inner <tt>[Bool]</tt>
--   is a row in a icon bitmap.
windowTitleIcons :: Theme -> [([[Bool]], Placement)]

-- | The default xmonad <a>Theme</a>.
defaultTheme :: Theme
data TabbedDecoration a
Tabbed :: TabbarLocation -> TabbarShown -> TabbedDecoration a
shrinkText :: DefaultShrinker
data CustomShrink
CustomShrink :: CustomShrink
class (Read s, Show s) => Shrinker s
shrinkIt :: Shrinker s => s -> String -> [String]
data TabbarShown
data TabbarLocation
instance Read TabbarLocation
instance Show TabbarLocation
instance Read TabbarShown
instance Show TabbarShown
instance Eq TabbarShown
instance Read (TabbedDecoration a)
instance Show (TabbedDecoration a)
instance Eq a => DecorationStyle TabbedDecoration a


-- | A (hopefully) growing collection of themes for decorated layouts.
module XMonad.Util.Themes
listOfThemes :: [ThemeInfo]
ppThemeInfo :: ThemeInfo -> String

-- | The default xmonad theme, by David Roundy.
xmonadTheme :: ThemeInfo

-- | Small decorations with a Ion3 remembrance, by Andrea Rossato.
smallClean :: ThemeInfo

-- | Ffrom Robert Manea's prompt theme.
robertTheme :: ThemeInfo

-- | deifl's Theme, by deifl.
deiflTheme :: ThemeInfo

-- | oxymor00n's theme, by Tom Rauchenwald.
oxymor00nTheme :: ThemeInfo

-- | Don's preferred colors - from DynamicLog...;)
donaldTheme :: ThemeInfo
wfarrTheme :: ThemeInfo

-- | Forest colours, by Kathryn Andersen
kavonForestTheme :: ThemeInfo

-- | Lake (blue/green) colours, by Kathryn Andersen
kavonLakeTheme :: ThemeInfo

-- | Peacock colours, by Kathryn Andersen
kavonPeacockTheme :: ThemeInfo

-- | Violet-Green colours, by Kathryn Andersen
kavonVioGreenTheme :: ThemeInfo

-- | Blue colours, by Kathryn Andersen
kavonBluesTheme :: ThemeInfo

-- | Autumn colours, by Kathryn Andersen
kavonAutumnTheme :: ThemeInfo

-- | Fire colours, by Kathryn Andersen
kavonFireTheme :: ThemeInfo

-- | Christmas colours, by Kathryn Andersen
kavonChristmasTheme :: ThemeInfo
data ThemeInfo
TI :: String -> String -> String -> Theme -> ThemeInfo
themeName :: ThemeInfo -> String
themeAuthor :: ThemeInfo -> String
themeDescription :: ThemeInfo -> String
theme :: ThemeInfo -> Theme


-- | This layout modifier will allow to resize windows by dragging their
--   borders with the mouse. However, it only works in layouts or modified
--   layouts that react to the <a>SetGeometry</a> message.
--   <a>XMonad.Layout.WindowArranger</a> can be used to create such a
--   setup, but it is probably must useful in a floating layout such as
--   <a>XMonad.Layout.PositionStoreFloat</a> with which it has been mainly
--   tested. See the documentation of PositionStoreFloat for a typical
--   usage example.
module XMonad.Layout.BorderResize
borderResize :: l a -> ModifiedLayout BorderResize l a
data BorderResize a
BR :: (Map Window RectWithBorders) -> BorderResize a
type RectWithBorders = (Rectangle, [BorderInfo])
data BorderInfo
instance Show BorderType
instance Read BorderType
instance Eq BorderType
instance Show BorderInfo
instance Read BorderInfo
instance Show (BorderResize a)
instance Read (BorderResize a)
instance LayoutModifier BorderResize Window


-- | A layout modifier for decorating windows in a dwm like style.
module XMonad.Layout.DwmStyle

-- | Add simple old dwm-style decorations to windows of a layout.
dwmStyle :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration DwmStyle s) l a

-- | A <a>Theme</a> is a record of colors, font etc., to customize a
--   <a>DecorationStyle</a>.
--   
--   For a collection of <a>Theme</a>s see <a>XMonad.Util.Themes</a>
data Theme
Theme :: String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> Dimension -> Dimension -> [(String, Align)] -> [([[Bool]], Placement)] -> Theme

-- | Color of the active window
activeColor :: Theme -> String

-- | Color of the inactive window
inactiveColor :: Theme -> String

-- | Color of the urgent window
urgentColor :: Theme -> String

-- | Color of the border of the active window
activeBorderColor :: Theme -> String

-- | Color of the border of the inactive window
inactiveBorderColor :: Theme -> String

-- | Color of the border of the urgent window
urgentBorderColor :: Theme -> String

-- | Color of the text of the active window
activeTextColor :: Theme -> String

-- | Color of the text of the inactive window
inactiveTextColor :: Theme -> String

-- | Color of the text of the urgent window
urgentTextColor :: Theme -> String

-- | Font name
fontName :: Theme -> String

-- | Maximum width of the decorations (if supported by the
--   <a>DecorationStyle</a>)
decoWidth :: Theme -> Dimension

-- | Height of the decorations
decoHeight :: Theme -> Dimension

-- | Extra text to appear in a window's title bar. Refer to for a use
--   <a>XMonad.Layout.ImageButtonDecoration</a>
windowTitleAddons :: Theme -> [(String, Align)]

-- | Extra icons to appear in a window's title bar. Inner <tt>[Bool]</tt>
--   is a row in a icon bitmap.
windowTitleIcons :: Theme -> [([[Bool]], Placement)]

-- | The default xmonad <a>Theme</a>.
defaultTheme :: Theme
data DwmStyle a
Dwm :: DwmStyle a
shrinkText :: DefaultShrinker
data CustomShrink
CustomShrink :: CustomShrink
class (Read s, Show s) => Shrinker s
shrinkIt :: Shrinker s => s -> String -> [String]
instance Show (DwmStyle a)
instance Read (DwmStyle a)
instance Eq a => DecorationStyle DwmStyle a


-- | A layout modifier for adding simple decorations to the windows of a
--   given layout. The decorations are in the form of ion-like tabs for
--   window titles.
module XMonad.Layout.SimpleDecoration

-- | Add simple decorations to windows of a layout.
simpleDeco :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration SimpleDecoration s) l a

-- | A <a>Theme</a> is a record of colors, font etc., to customize a
--   <a>DecorationStyle</a>.
--   
--   For a collection of <a>Theme</a>s see <a>XMonad.Util.Themes</a>
data Theme
Theme :: String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> Dimension -> Dimension -> [(String, Align)] -> [([[Bool]], Placement)] -> Theme

-- | Color of the active window
activeColor :: Theme -> String

-- | Color of the inactive window
inactiveColor :: Theme -> String

-- | Color of the urgent window
urgentColor :: Theme -> String

-- | Color of the border of the active window
activeBorderColor :: Theme -> String

-- | Color of the border of the inactive window
inactiveBorderColor :: Theme -> String

-- | Color of the border of the urgent window
urgentBorderColor :: Theme -> String

-- | Color of the text of the active window
activeTextColor :: Theme -> String

-- | Color of the text of the inactive window
inactiveTextColor :: Theme -> String

-- | Color of the text of the urgent window
urgentTextColor :: Theme -> String

-- | Font name
fontName :: Theme -> String

-- | Maximum width of the decorations (if supported by the
--   <a>DecorationStyle</a>)
decoWidth :: Theme -> Dimension

-- | Height of the decorations
decoHeight :: Theme -> Dimension

-- | Extra text to appear in a window's title bar. Refer to for a use
--   <a>XMonad.Layout.ImageButtonDecoration</a>
windowTitleAddons :: Theme -> [(String, Align)]

-- | Extra icons to appear in a window's title bar. Inner <tt>[Bool]</tt>
--   is a row in a icon bitmap.
windowTitleIcons :: Theme -> [([[Bool]], Placement)]

-- | The default xmonad <a>Theme</a>.
defaultTheme :: Theme
data SimpleDecoration a
Simple :: Bool -> SimpleDecoration a
shrinkText :: DefaultShrinker
data CustomShrink
CustomShrink :: CustomShrink
class (Read s, Show s) => Shrinker s
shrinkIt :: Shrinker s => s -> String -> [String]
instance Show (SimpleDecoration a)
instance Read (SimpleDecoration a)
instance Eq a => DecorationStyle SimpleDecoration a


-- | A basic floating layout.
module XMonad.Layout.SimpleFloat

-- | A simple floating layout where every window is placed according to the
--   window's initial attributes.
--   
--   This version is decorated with the <a>SimpleDecoration</a> style.
simpleFloat :: Eq a => ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a

-- | Same as <a>simpleFloat</a>, but with the possibility of setting a
--   custom shrinker and a custom theme.
simpleFloat' :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
data SimpleDecoration a
Simple :: Bool -> SimpleDecoration a
data SimpleFloat a
SF :: Dimension -> SimpleFloat a
shrinkText :: DefaultShrinker
data CustomShrink
CustomShrink :: CustomShrink
class (Read s, Show s) => Shrinker s
shrinkIt :: Shrinker s => s -> String -> [String]
instance Show (SimpleFloat a)
instance Read (SimpleFloat a)
instance LayoutClass SimpleFloat Window


-- | Row layout with individually resizable elements.
module XMonad.Layout.ZoomRow

-- | A layout that arranges its windows in a horizontal row, and allows to
--   change the relative size of each element independently.
data ZoomRow f a

-- | <a>ZoomRow</a> layout for laying out elements which are instances of
--   <a>Eq</a>. Perfect for <a>Window</a>s.
zoomRow :: (Eq a, Show a, Read a) => ZoomRow ClassEQ a

-- | The type of messages accepted by a <a>ZoomRow</a> layout
data ZoomMessage

-- | Multiply the focused window's size factor by the given number.
Zoom :: Rational -> ZoomMessage

-- | Set the focused window's size factor to the given number.
ZoomTo :: Rational -> ZoomMessage

-- | Set whether the focused window should occupy all available space when
--   it has focus
ZoomFull :: Bool -> ZoomMessage

-- | Toggle whether the focused window should occupy all available space
--   when it has focus
ZoomFullToggle :: ZoomMessage

-- | Increase the size of the focused window. Defined as <tt>Zoom 1.5</tt>
zoomIn :: ZoomMessage

-- | Decrease the size of the focused window. Defined as <tt>Zoom
--   (2/3)</tt>
zoomOut :: ZoomMessage

-- | Reset the size of the focused window. Defined as <tt>ZoomTo 1</tt>
zoomReset :: ZoomMessage

-- | ZoomRow layout with a custom equality predicate. It should of course
--   satisfy the laws for <a>Eq</a>, and you should also make sure that the
--   layout never has to handle two "equal" elements at the same time (it
--   won't do any huge damage, but might behave a bit strangely).
zoomRowWith :: (EQF f a, Show (f a), Read (f a), Show a, Read a) => f a -> ZoomRow f a

-- | Class for equivalence relations. Must be transitive, reflexive.
class EQF f a
eq :: EQF f a => f a -> a -> a -> Bool

-- | To use the usual <a>==</a>:
data ClassEQ a
ClassEQ :: ClassEQ a
instance Typeable ZoomMessage
instance Show (ClassEQ a)
instance Read (ClassEQ a)
instance Eq (ClassEQ a)
instance Show a => Show (Elt a)
instance Read a => Read (Elt a)
instance Eq a => Eq (Elt a)
instance (Show a, Show (f a)) => Show (ZoomRow f a)
instance (Read a, Read (f a)) => Read (ZoomRow f a)
instance (Eq a, Eq (f a)) => Eq (ZoomRow f a)
instance Show ZoomMessage
instance (EQF f a, Show a, Read a, Show (f a), Read (f a)) => LayoutClass (ZoomRow f) a
instance Message ZoomMessage
instance Eq a => EQF ClassEQ a


-- | Most basic version of decoration for windows without any additional
--   modifications. In contrast to <a>XMonad.Layout.SimpleDecoration</a>
--   this will result in title bars that span the entire window instead of
--   being only the length of the window title.
module XMonad.Layout.NoFrillsDecoration

-- | Add very simple decorations to windows of a layout.
noFrillsDeco :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration NoFrillsDecoration s) l a
data NoFrillsDecoration a
instance Show (NoFrillsDecoration a)
instance Read (NoFrillsDecoration a)
instance Eq a => DecorationStyle NoFrillsDecoration a


-- | A layout transformer to have a layout respect a given screen geometry.
--   Mostly used with <a>Decoration</a> (the Horizontal and the Vertical
--   version will react to SetTheme and change their dimension accordingly.
module XMonad.Layout.ResizeScreen
resizeHorizontal :: Int -> l a -> ModifiedLayout ResizeScreen l a
resizeVertical :: Int -> l a -> ModifiedLayout ResizeScreen l a
resizeHorizontalRight :: Int -> l a -> ModifiedLayout ResizeScreen l a
resizeVerticalBottom :: Int -> l a -> ModifiedLayout ResizeScreen l a
withNewRectangle :: Rectangle -> l a -> ModifiedLayout ResizeScreen l a
data ResizeScreen a
ResizeScreen :: ResizeMode -> Int -> ResizeScreen a
WithNewScreen :: Rectangle -> ResizeScreen a
data ResizeMode
instance Read ResizeMode
instance Show ResizeMode
instance Read (ResizeScreen a)
instance Show (ResizeScreen a)
instance LayoutModifier ResizeScreen a


-- | A workscreen permits to display a set of workspaces on several
--   screens. In xinerama mode, when a workscreen is viewed, workspaces
--   associated to all screens are visible.
--   
--   The first workspace of a workscreen is displayed on first screen,
--   second on second screen, etc. Workspace position can be easily
--   changed. If the current workscreen is called again, workspaces are
--   shifted.
--   
--   This also permits to see all workspaces of a workscreen even if just
--   one screen is present, and to move windows from workspace to
--   workscreen.
module XMonad.Actions.Workscreen

-- | Initial configuration of workscreens
configWorkscreen :: [Workscreen] -> X ()

-- | View workscreen of index <tt>WorkscreenId</tt>. If current workscreen
--   is asked workscreen, workscreen's workspaces are shifted.
viewWorkscreen :: WorkscreenId -> X ()
data Workscreen
Workscreen :: Int -> [WorkspaceId] -> Workscreen
workscreenId :: Workscreen -> Int
workspaces :: Workscreen -> [WorkspaceId]

-- | Shift a window on the first workspace of workscreen
--   <tt>WorkscreenId</tt>.
shiftToWorkscreen :: WorkscreenId -> X ()

-- | Create workscreen list from workspace list. Group workspaces to
--   packets of screens number size.
fromWorkspace :: Int -> [WorkspaceId] -> [Workscreen]

-- | Helper to group workspaces. Multiply workspace by screens number.
expandWorkspace :: Int -> [WorkspaceId] -> [WorkspaceId]
instance Typeable Workscreen
instance Typeable WorkscreenStorage
instance Show Workscreen
instance Show WorkscreenStorage
instance ExtensionClass WorkscreenStorage


-- | Ensures that the windows of the current workspace are always in front
--   of windows that are located on other visible screens. This becomes
--   important if you use decoration and drag windows from one screen to
--   another. Using this module, the dragged window will always be in front
--   of other windows.
module XMonad.Hooks.CurrentWorkspaceOnTop
currentWorkspaceOnTop :: X ()
instance Typeable CWOTState
instance ExtensionClass CWOTState


-- | A module for spawning a command once, and only once. Useful to start
--   status bars and make session settings inside startupHook.
module XMonad.Util.SpawnOnce

-- | The first time <a>spawnOnce</a> is executed on a particular command,
--   that command is executed. Subsequent invocations for a command do
--   nothing.
spawnOnce :: String -> X ()
instance Typeable SpawnOnce
instance Read SpawnOnce
instance Show SpawnOnce
instance ExtensionClass SpawnOnce


-- | One-shot and permanent ManageHooks that can be updated at runtime.
module XMonad.Hooks.DynamicHooks

-- | Master <a>ManageHook</a> that must be in your <tt>xmonad.hs</tt>
--   <a>ManageHook</a>.
dynamicMasterHook :: ManageHook

-- | Appends the given <a>ManageHook</a> to the permanent dynamic
--   <a>ManageHook</a>.
addDynamicHook :: ManageHook -> X ()

-- | Modifies the permanent <a>ManageHook</a> with an arbitrary function.
updateDynamicHook :: (ManageHook -> ManageHook) -> X ()

-- | Creates a one-shot <a>ManageHook</a>. Note that you have to specify
--   the two parts of the <a>ManageHook</a> separately. Where you would
--   usually write:
--   
--   <pre>
--   className =? "example" --&gt; doFloat
--   </pre>
--   
--   you must call <a>oneShotHook</a> as
--   
--   <pre>
--   oneShotHook dynHooksRef (className =? "example) doFloat
--   </pre>
oneShotHook :: Query Bool -> ManageHook -> X ()
instance Typeable DynamicHooks
instance ExtensionClass DynamicHooks


-- | Hook and keybindings for toggling hook behavior.
module XMonad.Hooks.ToggleHook

-- | This <a>ManageHook</a> will selectively apply a hook as set by
--   <a>hookNext</a> and <a>hookAllNew</a>.
toggleHook :: String -> ManageHook -> ManageHook
toggleHook' :: String -> ManageHook -> ManageHook -> ManageHook

-- | <tt>hookNext name True</tt> arranges for the next spawned window to
--   have the hook <tt>name</tt> applied, <tt>hookNext name False</tt>
--   cancels it.
hookNext :: String -> Bool -> X ()
toggleHookNext :: String -> X ()

-- | <tt>hookAllNew name True</tt> arranges for new windows to have the
--   hook <tt>name</tt> applied, <tt>hookAllNew name False</tt> cancels it
hookAllNew :: String -> Bool -> X ()
toggleHookAllNew :: String -> X ()

-- | Query what will happen at the next ManageHook call for the hook
--   <tt>name</tt>.
willHook :: String -> X Bool

-- | Whether the next window will trigger the hook <tt>name</tt>.
willHookNext :: String -> X Bool

-- | Whether new windows will trigger the hook <tt>name</tt>.
willHookAllNew :: String -> X Bool
willHookNextPP :: String -> (String -> String) -> X (Maybe String)
willHookAllNewPP :: String -> (String -> String) -> X (Maybe String)
runLogHook :: X ()
instance Typeable HookState
instance Read HookState
instance Show HookState
instance ExtensionClass HookState


-- | Hook and keybindings for automatically sending the next spawned
--   window(s) to the floating layer.
module XMonad.Hooks.FloatNext

-- | This <a>ManageHook</a> will selectively float windows as set by
--   <a>floatNext</a> and <a>floatAllNew</a>.
floatNextHook :: ManageHook

-- | <tt>floatNext True</tt> arranges for the next spawned window to be
--   sent to the floating layer, <tt>floatNext False</tt> cancels it.
floatNext :: Bool -> X ()
toggleFloatNext :: X ()

-- | <tt>floatAllNew True</tt> arranges for new windows to be sent to the
--   floating layer, <tt>floatAllNew False</tt> cancels it
floatAllNew :: Bool -> X ()
toggleFloatAllNew :: X ()

-- | Whether the next window will be set floating
willFloatNext :: X Bool

-- | Whether new windows will be set floating
willFloatAllNew :: X Bool
willFloatNextPP :: (String -> String) -> X (Maybe String)
willFloatAllNewPP :: (String -> String) -> X (Maybe String)
runLogHook :: X ()


-- | A utility module to store information about position and size of a
--   window. See <a>XMonad.Layout.PositionStoreFloat</a> for a layout that
--   makes use of this.
module XMonad.Util.PositionStore
getPosStore :: X (PositionStore)
modifyPosStore :: (PositionStore -> PositionStore) -> X ()
posStoreInsert :: PositionStore -> Window -> Rectangle -> Rectangle -> PositionStore
posStoreMove :: PositionStore -> Window -> Position -> Position -> Rectangle -> Rectangle -> PositionStore
posStoreQuery :: PositionStore -> Window -> Rectangle -> Maybe Rectangle
posStoreRemove :: PositionStore -> Window -> PositionStore
data PositionStore
instance Typeable PosStoreRectangle
instance Typeable PositionStore
instance Read PosStoreRectangle
instance Show PosStoreRectangle
instance Read PositionStore
instance Show PositionStore
instance ExtensionClass PositionStore


-- | A floating layout which has been designed with a dual-head setup in
--   mind. It makes use of <a>XMonad.Util.PositionStore</a> as well as
--   <a>XMonad.Hooks.PositionStoreHooks</a> . Since there is currently no
--   way to move or resize windows with the keyboard alone in this layout,
--   it is adviced to use it in combination with a decoration such as
--   <a>XMonad.Layout.NoFrillsDecoration</a> (to move windows) and the
--   layout modifier <a>XMonad.Layout.BorderResize</a> (to resize windows).
module XMonad.Layout.PositionStoreFloat
positionStoreFloat :: PositionStoreFloat a
data PositionStoreFloat a
instance Show a => Show (PositionStoreFloat a)
instance Read a => Read (PositionStoreFloat a)
instance LayoutClass PositionStoreFloat Window


-- | Run <tt>X ()</tt> actions by touching the edge of your screen with
--   your mouse.
module XMonad.Hooks.ScreenCorners
data ScreenCorner
SCUpperLeft :: ScreenCorner
SCUpperRight :: ScreenCorner
SCLowerLeft :: ScreenCorner
SCLowerRight :: ScreenCorner

-- | Add one single <tt>X ()</tt> action to a screen corner
addScreenCorner :: ScreenCorner -> X () -> X ()

-- | Add a list of <tt>(ScreenCorner, X ())</tt> tuples
addScreenCorners :: [(ScreenCorner, X ())] -> X ()

-- | Handle screen corner events
screenCornerEventHook :: Event -> X All
instance Typeable ScreenCornerState
instance Eq ScreenCorner
instance Ord ScreenCorner
instance Show ScreenCorner
instance ExtensionClass ScreenCornerState


-- | Dwm-like swap function for xmonad.
--   
--   Swaps focused window with the master window. If focus is in the
--   master, swap it with the next window in the stack. Focus stays in the
--   master.
module XMonad.Actions.DwmPromote

-- | Swap the focused window with the master window. If focus is in the
--   master, swap it with the next window in the stack. Focus stays in the
--   master.
dwmpromote :: X ()


-- | This module provides a method to cease management of a window without
--   unmapping it. This is especially useful for applications like kicker
--   and gnome-panel. See also <a>XMonad.Hooks.ManageDocks</a> for more a
--   more automated solution.
--   
--   To make a panel display correctly with xmonad:
--   
--   <ul>
--   <li>Determine the pixel size of the panel, add that value to
--   <a>defaultGaps</a></li>
--   <li>Launch the panel</li>
--   <li>Give the panel window focus, then press <tt>mod-d</tt> (or
--   whatever key you have bound <a>demanage</a> to)</li>
--   <li>Convince the panel to move/resize to the correct location.
--   Changing the panel's position setting several times seems to
--   work.</li>
--   </ul>
module XMonad.Actions.DeManage

-- | Stop managing the currently focused window.
demanage :: Window -> X ()


module XMonad.Util.WorkspaceCompare
type WorkspaceCompare = WorkspaceId -> WorkspaceId -> Ordering
type WorkspaceSort = [WindowSpace] -> [WindowSpace]

-- | Lookup the index of a workspace id in the user's config, return
--   Nothing if that workspace does not exist in the config.
getWsIndex :: X (WorkspaceId -> Maybe Int)

-- | A comparison function for WorkspaceId, based on the index of the tags
--   in the user's config.
getWsCompare :: X WorkspaceCompare

-- | A simple comparison function that orders workspaces lexicographically
--   by tag.
getWsCompareByTag :: X WorkspaceCompare

-- | A comparison function like <a>getXineramaWsCompare</a>, but uses
--   physical locations for screens.
getXineramaPhysicalWsCompare :: X WorkspaceCompare

-- | A comparison function for Xinerama based on visibility, workspace and
--   screen id. It produces the same ordering as
--   <a>pprWindowSetXinerama</a>.
getXineramaWsCompare :: X WorkspaceCompare

-- | Create a workspace sorting function from a workspace comparison
--   function.
mkWsSort :: X WorkspaceCompare -> X WorkspaceSort

-- | Sort several workspaces according to their tags' indices in the user's
--   config.
getSortByIndex :: X WorkspaceSort

-- | Sort workspaces lexicographically by tag.
getSortByTag :: X WorkspaceSort

-- | Like <a>getSortByXineramaRule</a>, but uses physical locations for
--   screens.
getSortByXineramaPhysicalRule :: X WorkspaceSort

-- | Sort serveral workspaces for xinerama displays, in the same order
--   produced by <a>pprWindowSetXinerama</a>: first visible workspaces,
--   sorted by screen, then hidden workspaces, sorted by tag.
getSortByXineramaRule :: X WorkspaceSort


-- | Makes xmonad use the EWMH hints to tell panel applications about its
--   workspaces and the windows therein. It also allows the user to
--   interact with xmonad by clicking on panels and window lists.
module XMonad.Hooks.EwmhDesktops

-- | Add EWMH functionality to the given config. See above for an example.
ewmh :: XConfig a -> XConfig a

-- | Initializes EwmhDesktops and advertises EWMH support to the X server
ewmhDesktopsStartup :: X ()

-- | Notifies pagers and window lists, such as those in the gnome-panel of
--   the current state of workspaces and windows.
ewmhDesktopsLogHook :: X ()

-- | Generalized version of ewmhDesktopsLogHook that allows an arbitrary
--   user-specified function to transform the workspace list (post-sorting)
ewmhDesktopsLogHookCustom :: ([WindowSpace] -> [WindowSpace]) -> X ()

-- | Intercepts messages from pagers and similar applications and reacts on
--   them. Currently supports:
--   
--   <ul>
--   <li>_NET_CURRENT_DESKTOP (switching desktops)</li>
--   <li>_NET_WM_DESKTOP (move windows to other desktops)</li>
--   <li>_NET_ACTIVE_WINDOW (activate another window, changing workspace if
--   needed)</li>
--   </ul>
ewmhDesktopsEventHook :: Event -> X All

-- | Generalized version of ewmhDesktopsEventHook that allows an arbitrary
--   user-specified function to transform the workspace list (post-sorting)
ewmhDesktopsEventHookCustom :: ([WindowSpace] -> [WindowSpace]) -> Event -> X All

-- | An event hook to handle applications that wish to fullscreen using the
--   _NET_WM_STATE protocol. This includes users of the
--   gtk_window_fullscreen() function, such as Totem, Evince and
--   OpenOffice.org.
--   
--   Note this is not included in <a>ewmh</a>.
fullscreenEventHook :: Event -> X All


-- | Miscellaneous commonly used types.
module XMonad.Util.Types

-- | One-dimensional directions:
data Direction1D
Next :: Direction1D
Prev :: Direction1D

-- | Two-dimensional directions:
data Direction2D

-- | Up
U :: Direction2D

-- | Down
D :: Direction2D

-- | Right
R :: Direction2D

-- | Left
L :: Direction2D
instance Typeable Direction1D
instance Typeable Direction2D
instance Eq Direction1D
instance Read Direction1D
instance Show Direction1D
instance Eq Direction2D
instance Read Direction2D
instance Show Direction2D
instance Ord Direction2D
instance Enum Direction2D
instance Bounded Direction2D


-- | A module for writing graphical prompts for XMonad
module XMonad.Prompt

-- | Creates a prompt given:
--   
--   <ul>
--   <li>a prompt type, instance of the <a>XPrompt</a> class.</li>
--   <li>a prompt configuration (<a>defaultXPConfig</a> can be used as a
--   starting point)</li>
--   <li>a completion function (<a>mkComplFunFromList</a> can be used to
--   create a completions function given a list of possible
--   completions)</li>
--   <li>an action to be run: the action must take a string and return
--   <a>X</a> ()</li>
--   </ul>
mkXPrompt :: XPrompt p => p -> XPConfig -> ComplFunction -> (String -> X ()) -> X ()

-- | Same as <a>mkXPrompt</a>, except that the action function can have
--   type <tt>String -&gt; X a</tt>, for any <tt>a</tt>, and the final
--   action returned by <a>mkXPromptWithReturn</a> will have type <tt>X
--   (Maybe a)</tt>. <tt>Nothing</tt> is yielded if the user cancels the
--   prompt (by e.g. hitting Esc or Ctrl-G). For an example of use, see the
--   <a>Input</a> module.
mkXPromptWithReturn :: XPrompt p => p -> XPConfig -> ComplFunction -> (String -> X a) -> X (Maybe a)

-- | Creates a prompt with multiple modes given:
--   
--   <ul>
--   <li>A non-empty list of modes * A prompt configuration</li>
--   </ul>
--   
--   The created prompt allows to switch between modes with
--   <a>changeModeKey</a> in <tt>conf</tt>. The modes are instances of
--   XPrompt. See XMonad.Actions.Launcher for more details
--   
--   The argument supplied to the action to execute is always the current
--   highlighted item, that means that this prompt overrides the value
--   <a>alwaysHighlight</a> for its configuration to True.
mkXPromptWithModes :: [XPType] -> XPConfig -> X ()
amberXPConfig, greenXPConfig, defaultXPConfig :: XPConfig
type XPMode = XPType
data XPType
XPT :: p -> XPType
data XPPosition
Top :: XPPosition
Bottom :: XPPosition
data XPConfig
XPC :: String -> String -> String -> String -> String -> String -> !Dimension -> XPPosition -> !Bool -> !Dimension -> !Int -> ([String] -> [String]) -> Map (KeyMask, KeySym) (XP ()) -> KeySym -> KeySym -> String -> Maybe Int -> Bool -> (String -> String -> Bool) -> XPConfig

-- | Font
font :: XPConfig -> String

-- | Background color
bgColor :: XPConfig -> String

-- | Font color
fgColor :: XPConfig -> String

-- | Font color of a highlighted completion entry
fgHLight :: XPConfig -> String

-- | Background color of a highlighted completion entry
bgHLight :: XPConfig -> String

-- | Border color
borderColor :: XPConfig -> String

-- | Border width
promptBorderWidth :: XPConfig -> !Dimension

-- | Position: <a>Top</a> or <a>Bottom</a>
position :: XPConfig -> XPPosition

-- | Always highlight an item, overriden to True with multiple modes. This
--   implies having *one* column of autocompletions only.
alwaysHighlight :: XPConfig -> !Bool

-- | Window height
height :: XPConfig -> !Dimension

-- | The number of history entries to be saved
historySize :: XPConfig -> !Int

-- | a filter to determine which history entries to remember
historyFilter :: XPConfig -> [String] -> [String]

-- | Mapping from key combinations to actions
promptKeymap :: XPConfig -> Map (KeyMask, KeySym) (XP ())

-- | Key that should trigger completion
completionKey :: XPConfig -> KeySym

-- | Key to change mode (when the prompt has multiple modes)
changeModeKey :: XPConfig -> KeySym

-- | The text by default in the prompt line
defaultText :: XPConfig -> String

-- | Just x: if only one completion remains, auto-select it,
autoComplete :: XPConfig -> Maybe Int

-- | Only show list of completions when Tab was pressed and delay by x
--   microseconds
showCompletionOnTab :: XPConfig -> Bool

-- | Given the typed string and a possible completion, is the completion
--   valid?
searchPredicate :: XPConfig -> String -> String -> Bool

-- | The class prompt types must be an instance of. In order to create a
--   prompt you need to create a data type, without parameters, and make it
--   an instance of this class, by implementing a simple method,
--   <a>showXPrompt</a>, which will be used to print the string to be
--   displayed in the command line window.
--   
--   This is an example of a XPrompt instance definition:
--   
--   <pre>
--   instance XPrompt Shell where
--        showXPrompt Shell = "Run: "
--   </pre>
class XPrompt t where nextCompletion = getNextOfLastWord commandToComplete _ = getLastWord completionToCommand _ c = c completionFunction t = \ _ -> return ["Completions for " ++ (showXPrompt t) ++ " could not be loaded"] modeAction _ _ _ = return ()
showXPrompt :: XPrompt t => t -> String
nextCompletion :: XPrompt t => t -> String -> [String] -> String
commandToComplete :: XPrompt t => t -> String -> String
completionToCommand :: XPrompt t => t -> String -> String
completionFunction :: XPrompt t => t -> ComplFunction
modeAction :: XPrompt t => t -> String -> String -> X ()
type XP = StateT XPState IO

-- | Default key bindings for prompts. Click on the "Source" link to the
--   right to see the complete list. See also <a>defaultXPKeymap'</a>.
defaultXPKeymap :: Map (KeyMask, KeySym) (XP ())

-- | A variant of <a>defaultXPKeymap</a> which lets you specify a custom
--   predicate for identifying non-word characters, which affects all the
--   word-oriented commands (move/kill word). The default is
--   <a>isSpace</a>. For example, by default a path like
--   <tt>foo/bar/baz</tt> would be considered as a single word. You could
--   use a predicate like <tt>(\c -&gt; isSpace c || c == '/')</tt> to move
--   through or delete components of the path one at a time.
defaultXPKeymap' :: (Char -> Bool) -> Map (KeyMask, KeySym) (XP ())

-- | A keymap with many emacs-like key bindings. Click on the "Source" link
--   to the right to see the complete list. See also
--   <a>emacsLikeXPKeymap'</a>.
emacsLikeXPKeymap :: Map (KeyMask, KeySym) (XP ())

-- | A variant of <a>emacsLikeXPKeymap</a> which lets you specify a custom
--   predicate for identifying non-word characters, which affects all the
--   word-oriented commands (move/kill word). The default is
--   <a>isSpace</a>. For example, by default a path like
--   <tt>foo/bar/baz</tt> would be considered as a single word. You could
--   use a predicate like <tt>(\c -&gt; isSpace c || c == '/')</tt> to move
--   through or delete components of the path one at a time.
emacsLikeXPKeymap' :: (Char -> Bool) -> Map (KeyMask, KeySym) (XP ())

-- | Quit.
quit :: XP ()

-- | Kill the portion of the command before the cursor
killBefore :: XP ()

-- | Kill the portion of the command including and after the cursor
killAfter :: XP ()

-- | Put the cursor at the start of line
startOfLine :: XP ()

-- | Put the cursor at the end of line
endOfLine :: XP ()

-- | Insert the current X selection string at the cursor position.
pasteString :: XP ()

-- | move the cursor one position
moveCursor :: Direction1D -> XP ()

-- | Sets the input string to the given value.
setInput :: String -> XP ()

-- | Returns the current input string. Intented for use in custom keymaps
--   where the <a>get</a> or similar can't be used to retrieve it.
getInput :: XP String

-- | Move the cursor one word, using <a>isSpace</a> as the default
--   predicate for non-word characters. See <a>moveWord'</a>.
moveWord :: Direction1D -> XP ()

-- | Move the cursor one word, given a predicate to identify non-word
--   characters. First move past any consecutive non-word characters; then
--   move to just before the next non-word character.
moveWord' :: (Char -> Bool) -> Direction1D -> XP ()

-- | Kill the next/previous word, using <a>isSpace</a> as the default
--   predicate for non-word characters. See <a>killWord'</a>.
killWord :: Direction1D -> XP ()

-- | Kill the next/previous word, given a predicate to identify non-word
--   characters. First delete any consecutive non-word characters; then
--   delete consecutive word characters, stopping just before the next
--   non-word character.
--   
--   For example, by default (using <a>killWord</a>) a path like
--   <tt>foo/bar/baz</tt> would be deleted in its entirety. Instead you can
--   use something like <tt>killWord' (\c -&gt; isSpace c || c == '/')</tt>
--   to delete the path one component at a time.
killWord' :: (Char -> Bool) -> Direction1D -> XP ()

-- | Remove a character at the cursor position
deleteString :: Direction1D -> XP ()
moveHistory :: (Stack String -> Stack String) -> XP ()
setSuccess :: Bool -> XP ()
setDone :: Bool -> XP ()

-- | One-dimensional directions:
data Direction1D
Next :: Direction1D
Prev :: Direction1D
type ComplFunction = String -> IO [String]

-- | Creates a window with the attribute override_redirect set to True.
--   Windows Managers should not touch this kind of windows.
mkUnmanagedWindow :: Display -> Screen -> Window -> Position -> Position -> Dimension -> Dimension -> IO Window

-- | Fills a <a>Drawable</a> with a rectangle and a border
fillDrawable :: Display -> Drawable -> GC -> Pixel -> Pixel -> Dimension -> Dimension -> Dimension -> IO ()

-- | This function takes a list of possible completions and returns a
--   completions function to be used with <a>mkXPrompt</a>
mkComplFunFromList :: [String] -> String -> IO [String]

-- | This function takes a list of possible completions and returns a
--   completions function to be used with <a>mkXPrompt</a>. If the string
--   is null it will return all completions.
mkComplFunFromList' :: [String] -> String -> IO [String]

-- | Given the prompt type, the command line and the completion list,
--   return the next completion in the list for the last word of the
--   command line. This is the default <a>nextCompletion</a>
--   implementation.
getNextOfLastWord :: XPrompt t => t -> String -> [String] -> String

-- | An alternative <a>nextCompletion</a> implementation: given a command
--   and a completion list, get the next completion in the list matching
--   the whole command line.
getNextCompletion :: String -> [String] -> String

-- | Gets the last word of a string or the whole string if formed by only
--   one word
getLastWord :: String -> String

-- | Skips the last word of the string, if the string is composed by more
--   then one word. Otherwise returns the string.
skipLastWord :: String -> String

-- | Given a maximum length, splits a list into sublists
splitInSubListsAt :: Int -> [a] -> [[a]]
breakAtSpace :: String -> (String, String)

-- | Sort a list and remove duplicates. Like <a>deleteAllDuplicates</a>,
--   but trades off laziness and stability for efficiency.
uniqSort :: Ord a => [a] -> [a]

-- | <a>historyCompletion</a> provides a canned completion function much
--   like <tt>getShellCompl</tt>; you pass it to mkXPrompt, and it will
--   make completions work from the query history stored in
--   ~/.xmonad/history.
historyCompletion :: ComplFunction

-- | Like <a>historyCompletion</a> but only uses history data from Prompts
--   whose name satisfies the given predicate.
historyCompletionP :: (String -> Bool) -> ComplFunction

-- | Functions to be used with the <a>historyFilter</a> setting.
--   <a>deleteAllDuplicates</a> will remove all duplicate entries.
--   <a>deleteConsecutive</a> will only remove duplicate elements
--   immediately next to each other.
deleteAllDuplicates, deleteConsecutive :: [String] -> [String]
data HistoryMatches

-- | Initializes a new HistoryMatches structure to be passed to
--   historyUpMatching
initMatches :: (Functor m, MonadIO m) => m HistoryMatches

-- | Retrieve the next history element that starts with the current input.
--   Pass it the result of initMatches when creating the prompt. Example:
--   
--   <pre>
--   ..
--   ((modMask,xK_p), shellPrompt . myPrompt =&lt;&lt; initMatches)
--   ..
--   myPrompt ref = defaultPrompt
--     { promptKeymap = M.union [((0,xK_Up), historyUpMatching ref)
--                              ,((0,xK_Down), historyDownMatching ref)]
--                              (promptKeymap defaultPrompt)
--     , .. }
--   </pre>
historyUpMatching, historyDownMatching :: HistoryMatches -> XP ()
data XPState
instance Show XPPosition
instance Read XPPosition
instance XPrompt XPType
instance Show XPType


-- | A workspace prompt for XMonad
module XMonad.Prompt.Workspace
workspacePrompt :: XPConfig -> (String -> X ()) -> X ()
data Wor
Wor :: String -> Wor
instance XPrompt Wor


-- | Provides bindings to add and delete workspaces.
module XMonad.Actions.DynamicWorkspaces

-- | Add a new workspace with the given name, or do nothing if a workspace
--   with the given name already exists; then switch to the newly created
--   workspace.
addWorkspace :: String -> X ()

-- | Prompt for the name of a new workspace, add it if it does not already
--   exist, and switch to it.
addWorkspacePrompt :: XPConfig -> X ()

-- | Remove the current workspace.
removeWorkspace :: X ()

-- | Remove the current workspace if it contains no windows.
removeEmptyWorkspace :: X ()

-- | Remove the current workspace after an operation if it is empty and
--   hidden. Can be used to remove a workspace if it is empty when leaving
--   it. The operation may only change workspace once, otherwise the
--   workspace will not be removed.
removeEmptyWorkspaceAfter :: X () -> X ()

-- | Like <a>removeEmptyWorkspaceAfter</a> but use a list of sticky
--   workspaces, whose entries will never be removed.
removeEmptyWorkspaceAfterExcept :: [String] -> X () -> X ()

-- | Add a new hidden workspace with the given name, or do nothing if a
--   workspace with the given name already exists.
addHiddenWorkspace :: String -> X ()
withWorkspace :: XPConfig -> (String -> X ()) -> X ()
selectWorkspace :: XPConfig -> X ()
renameWorkspace :: XPConfig -> X ()
renameWorkspaceByName :: String -> X ()
toNthWorkspace :: (String -> X ()) -> Int -> X ()
withNthWorkspace :: (String -> WindowSet -> WindowSet) -> Int -> X ()


-- | Dynamically manage "workspace groups", sets of workspaces being used
--   together for some common task or purpose, to allow switching between
--   workspace groups in a single action. Note that this only makes sense
--   for multi-head setups.
module XMonad.Actions.DynamicWorkspaceGroups
type WSGroupId = String

-- | Add a new workspace group with the given name.
addWSGroup :: WSGroupId -> [WorkspaceId] -> X ()

-- | Give a name to the current workspace group.
addCurrentWSGroup :: WSGroupId -> X ()

-- | Delete the named workspace group from the list of workspace groups.
--   Note that this has no effect on the workspaces involved; it simply
--   forgets the given name.
forgetWSGroup :: WSGroupId -> X ()

-- | View the workspace group with the given name.
viewWSGroup :: WSGroupId -> X ()

-- | Prompt for a workspace group to view.
promptWSGroupView :: XPConfig -> String -> X ()

-- | Prompt for a name for the current workspace group.
promptWSGroupAdd :: XPConfig -> String -> X ()

-- | Prompt for a workspace group to forget.
promptWSGroupForget :: XPConfig -> String -> X ()
data WSGPrompt
instance Typeable WSGroupStorage
instance Read WSGroupStorage
instance Show WSGroupStorage
instance XPrompt WSGPrompt
instance ExtensionClass WSGroupStorage


-- | A set of prompts for XMonad
module XMonad.Actions.Launcher

-- | Create a list of modes based on : a list of extensions mapped to
--   actions the path to hoogle
defaultLauncherModes :: LauncherConfig -> [XPMode]
type ExtensionActions = Map String (String -> X ())
data LauncherConfig
LauncherConfig :: String -> String -> LauncherConfig
browser :: LauncherConfig -> String
pathToHoogle :: LauncherConfig -> String

-- | Creates a prompt with the given modes
launcherPrompt :: XPConfig -> [XPMode] -> X ()
instance XPrompt HoogleMode
instance XPrompt CalculatorMode


-- | A shell prompt for XMonad
module XMonad.Prompt.Shell
data Shell
Shell :: Shell
shellPrompt :: XPConfig -> X ()
prompt, safePrompt, unsafePrompt :: FilePath -> XPConfig -> X ()
getCommands :: IO [String]

-- | Ask the shell what browser the user likes. If the user hasn't defined
--   any $BROWSER, defaults to returning "firefox", since that seems to be
--   the most common X web browser. Note that if you don't specify a GUI
--   browser but a textual one, that'll be a problem as <a>getBrowser</a>
--   will be called by functions expecting to be able to just execute the
--   string or pass it to a shell; so in that case, define $BROWSER as
--   something like "xterm -e elinks" or as the name of a shell script
--   doing much the same thing.
getBrowser :: IO String

-- | Like <a>getBrowser</a>, but should be of a text editor. This gets the
--   $EDITOR variable, defaulting to "emacs".
getEditor :: IO String
getShellCompl :: [String] -> String -> IO [String]
split :: Eq a => a -> [a] -> [[a]]
instance XPrompt Shell


module XMonad.Actions.Search

-- | Given a browser, a search engine's transformation function, and a
--   search term, perform the requested search in the browser.
search :: Browser -> Site -> Query -> X ()
data SearchEngine
SearchEngine :: Name -> Site -> SearchEngine

-- | Given a base URL, create the <a>SearchEngine</a> that escapes the
--   query and appends it to the base. You can easily define a new engine
--   locally using exported functions without needing to modify
--   <a>XMonad.Actions.Search</a>:
--   
--   <pre>
--   myNewEngine = searchEngine "site" "http://site.com/search="
--   </pre>
--   
--   The important thing is that the site has a interface which accepts the
--   escaped query string as part of the URL. Alas, the exact URL to feed
--   searchEngine varies from site to site, often considerably, so there's
--   no general way to cover this.
--   
--   Generally, examining the resultant URL of a search will allow you to
--   reverse-engineer it if you can't find the necessary URL already
--   described in other projects such as Surfraw.
searchEngine :: Name -> String -> SearchEngine

-- | If your search engine is more complex than this (you may want to
--   identify the kind of input and make the search URL dependent on the
--   input or put the query inside of a URL instead of in the end) you can
--   use the alternative <a>searchEngineF</a> function.
--   
--   <pre>
--   searchFunc :: String -&gt; String
--   searchFunc s | "wiki:"   `isPrefixOf` s = "http://en.wikipedia.org/wiki/" ++ (escape $ tail $ snd $ break (==':') s)
--                | "http://" `isPrefixOf` s = s
--                | otherwise               = (use google) s
--   myNewEngine = searchEngineF "mymulti" searchFunc
--   </pre>
--   
--   <tt>searchFunc</tt> here searches for a word in wikipedia if it has a
--   prefix of "wiki:" (you can use the <a>escape</a> function to escape
--   any forbidden characters), opens an address directly if it starts with
--   "http://" and otherwise uses the provided google search engine. You
--   can use other engines inside of your own through the <a>use</a>
--   function as shown above to make complex searches.
--   
--   The user input will be automatically escaped in search engines created
--   with <a>searchEngine</a>, <a>searchEngineF</a>, however, completely
--   depends on the transformation function passed to it.
searchEngineF :: Name -> Site -> SearchEngine

-- | Like <a>search</a>, but in this case, the string is not specified but
--   grabbed from the user's response to a prompt. Example:
--   
--   <pre>
--   , ((modm, xK_g), promptSearch greenXPConfig google)
--   </pre>
--   
--   This specializes <a>promptSearchBrowser</a> by supplying the browser
--   argument as supplied by <a>getBrowser</a> from
--   <a>XMonad.Prompt.Shell</a>.
promptSearch :: XPConfig -> SearchEngine -> X ()

-- | Like <a>search</a>, but for use with the output from a Prompt; it
--   grabs the Prompt's result, passes it to a given searchEngine and opens
--   it in a given browser.
promptSearchBrowser :: XPConfig -> Browser -> SearchEngine -> X ()

-- | Like <a>search</a>, but for use with the X selection; it grabs the
--   selection, passes it to a given searchEngine and opens it in the
--   default browser . Example:
--   
--   <pre>
--   , ((modm .|. shiftMask, xK_g), selectSearch google)
--   </pre>
--   
--   This specializes <a>selectSearchBrowser</a> by supplying the browser
--   argument as supplied by <a>getBrowser</a> from
--   <a>XMonad.Prompt.Shell</a>.
selectSearch :: SearchEngine -> X ()

-- | Like <a>search</a>, but for use with the X selection; it grabs the
--   selection, passes it to a given searchEngine and opens it in a given
--   browser.
selectSearchBrowser :: Browser -> SearchEngine -> X ()

-- | The <a>isPrefixOf</a> function takes two lists and returns <a>True</a>
--   iff the first list is a prefix of the second.
isPrefixOf :: Eq a => [a] -> [a] -> Bool

-- | Escape the search string so search engines understand it. Only digits
--   and ASCII letters are not encoded. All non ASCII characters which are
--   encoded as UTF8
escape :: String -> String

-- | Given an already defined search engine, extracts its transformation
--   function, making it easy to create compound search engines. For an
--   instance you can use <tt>use google</tt> to get a function which makes
--   the same transformation as the google search engine would.
use :: SearchEngine -> Site

-- | This function wraps up a search engine and creates a new one, which
--   works like the argument, but goes directly to a URL if one is given
--   rather than searching.
--   
--   <pre>
--   myIntelligentGoogleEngine = intelligent google
--   </pre>
--   
--   Now if you search for http://xmonad.org it will directly open in your
--   browser
intelligent :: SearchEngine -> SearchEngine

-- | Connects a few search engines into one. If the search engines' names
--   are "s1", "s2" and "s3", then the resulting engine will use s1 if the
--   query is <tt>s1:word</tt>, s2 if you type <tt>s2:word</tt> and s3 in
--   all other cases.
--   
--   Example:
--   
--   <pre>
--   multiEngine = intelligent (wikipedia !&gt; mathworld !&gt; (prefixAware google))
--   </pre>
--   
--   Now if you type "wiki:Haskell" it will search for "Haskell" in
--   Wikipedia, "mathworld:integral" will search mathworld, and everything
--   else will fall back to google. The use of intelligent will make sure
--   that URLs are opened directly.
(!>) :: SearchEngine -> SearchEngine -> SearchEngine

-- | Makes a search engine prefix-aware. Especially useful together with
--   <a>!&gt;</a>. It will automatically remove the prefix from a query so
--   that you don't end up searching for google:xmonad if google is your
--   fallback engine and you explicitly add the prefix.
prefixAware :: SearchEngine -> SearchEngine

-- | Changes search engine's name
namedEngine :: Name -> SearchEngine -> SearchEngine
amazon, youtube, wiktionary, wikipedia, wayback, thesaurus, scholar, openstreetmap, mathworld, maps, lucky, isohunt, imdb, images, hoogle, hackage, google, dictionary, debpts, debbts, deb, codesearch, alpha :: SearchEngine
multi :: SearchEngine
type Browser = FilePath
type Site = String -> String
type Query = String
type Name = String

-- | A customized prompt indicating we are searching, and the name of the
--   site.
data Search
instance XPrompt Search


-- | Provides a way to modify a window spawned by a command(e.g shift it to
--   the workspace it was launched on) by using the _NET_WM_PID property
--   that most windows set on creation. Hence this module won't work on
--   applications that don't set this property.
module XMonad.Actions.SpawnOn
data Spawner

-- | Provides a manage hook to react on process spawned with
--   <a>spawnOn</a>, <a>spawnHere</a> etc.
manageSpawn :: ManageHook

-- | Replacement for <a>spawn</a> which launches application on current
--   workspace.
spawnHere :: String -> X ()

-- | Replacement for <a>spawn</a> which launches application on given
--   workspace.
spawnOn :: WorkspaceId -> String -> X ()

-- | Spawn an application and apply the manage hook when it opens.
spawnAndDo :: ManageHook -> String -> X ()

-- | Replacement for Shell prompt (<a>XMonad.Prompt.Shell</a>) which
--   launches application on current workspace.
shellPromptHere :: XPConfig -> X ()

-- | Replacement for Shell prompt (<a>XMonad.Prompt.Shell</a>) which
--   launches application on given workspace.
shellPromptOn :: WorkspaceId -> XPConfig -> X ()
instance Typeable Spawner
instance ExtensionClass Spawner


-- | Functions for tagging windows and selecting them by tags.
module XMonad.Actions.TagWindows

-- | add a tag to the existing ones
addTag :: String -> Window -> X ()

-- | remove a tag from a window, if it exists
delTag :: String -> Window -> X ()

-- | remove all tags
unTag :: Window -> X ()

-- | set multiple tags for a window at once (overriding any previous tags)
setTags :: [String] -> Window -> X ()

-- | read all tags of a window reads from the "_XMONAD_TAGS" window
--   property
getTags :: Window -> X [String]

-- | check a window for the given tag
hasTag :: String -> Window -> X Bool

-- | apply a pure function to windows with a tag
withTaggedP, withTaggedGlobalP :: String -> (Window -> WindowSet -> WindowSet) -> X ()
withFocusedP :: (Window -> WindowSet -> WindowSet) -> X ()
withTagged, withTaggedGlobal :: String -> (Window -> X ()) -> X ()

-- | Move the focus in a group of windows, which share the same given tag.
--   The Global variants move through all workspaces, whereas the other
--   ones operate only on the current workspace
focusUpTagged, focusDownTaggedGlobal, focusUpTaggedGlobal, focusDownTagged :: String -> X ()
shiftHere :: (Ord a, Eq s, Eq i) => a -> StackSet i l a s sd -> StackSet i l a s sd
shiftToScreen :: (Ord a, Eq s, Eq i) => s -> a -> StackSet i l a s sd -> StackSet i l a s sd
tagPrompt :: XPConfig -> (String -> X ()) -> X ()
tagDelPrompt :: XPConfig -> X ()
data TagPrompt
instance XPrompt TagPrompt


-- | A ssh prompt for XMonad
module XMonad.Prompt.Ssh
sshPrompt :: XPConfig -> X ()
data Ssh
instance XPrompt Ssh


-- | A prompt for changing the theme of the current workspace
module XMonad.Prompt.Theme
themePrompt :: XPConfig -> X ()
data ThemePrompt
instance XPrompt ThemePrompt


-- | A layout modifier to add a bar of tabs to your layouts.
module XMonad.Layout.TabBarDecoration

-- | Add, on the top of the screen, a simple bar of tabs to a given |
--   layout, with the default theme and the default shrinker.
simpleTabBar :: Eq a => l a -> ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen l) a

-- | Same of <a>simpleTabBar</a>, but with the possibility of setting a
--   custom shrinker, a custom theme and the position: <a>Top</a> or
--   <a>Bottom</a>.
tabBar :: (Eq a, Shrinker s) => s -> Theme -> XPPosition -> l a -> ModifiedLayout (Decoration TabBarDecoration s) l a

-- | The default xmonad <a>Theme</a>.
defaultTheme :: Theme
shrinkText :: DefaultShrinker
data TabBarDecoration a
TabBar :: XPPosition -> TabBarDecoration a
data XPPosition
Top :: XPPosition
Bottom :: XPPosition
instance Read (TabBarDecoration a)
instance Show (TabBarDecoration a)
instance Eq a => DecorationStyle TabBarDecoration a


-- | A collection of decorated layouts: some of them may be nice, some
--   usable, others just funny.
module XMonad.Layout.DecorationMadness

-- | A <a>Circle</a> layout with the xmonad default decoration, default
--   theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/circleSimpleDefault.png</a>
circleSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) Circle Window

-- | Similar to <a>circleSimpleDefault</a> but with the possibility of
--   setting a custom shrinker and a custom theme.
circleDefault :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) Circle Window

-- | A <a>Circle</a> layout with the xmonad default decoration, default
--   theme and default shrinker, but with the possibility of moving windows
--   with the mouse, and resize/move them with the keyboard.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/circleSimpleDefaultResizable.png</a>
circleSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window

-- | Similar to <a>circleSimpleDefaultResizable</a> but with the
--   possibility of setting a custom shrinker and a custom theme.
circleDefaultResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window

-- | A <a>Circle</a> layout with the xmonad simple decoration, default
--   theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/circleSimpleDeco.png</a>
circleSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) Circle Window

-- | A <a>Circle</a> layout with the xmonad simple decoration, default
--   theme and default shrinker, but with the possibility of moving windows
--   with the mouse, and resize/move them with the keyboard.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/circleSimpleDecoResizable.png</a>
circleSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window

-- | Similar to <tt>circleSimpleDece</tt> but with the possibility of
--   setting a custom shrinker and a custom theme.
circleDeco :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) Circle Window

-- | Similar to <a>circleSimpleDecoResizable</a> but with the possibility
--   of setting a custom shrinker and a custom theme.
circleDecoResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window

-- | A <a>Circle</a> layout with the xmonad DwmStyle decoration, default
--   theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/circleSimpleDwmStyle.png</a>
circleSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) Circle Window

-- | Similar to <a>circleSimpleDwmStyle</a> but with the possibility of
--   setting a custom shrinker and a custom theme.
circleDwmStyle :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DwmStyle s) Circle Window

-- | A <a>Circle</a> layout with the xmonad tabbed decoration, default
--   theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/circleSimpleTabbed.png</a>
circleSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen Circle) Window

-- | Similar to <a>circleSimpleTabbed</a> but with the possibility of
--   setting a custom shrinker and a custom theme.
circleTabbed :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen Circle) Window

-- | An <a>Accordion</a> layout with the xmonad default decoration, default
--   theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/accordionSimpleDefault.png</a>
accordionSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) Accordion Window

-- | Similar to <a>accordionSimpleDefault</a> but with the possibility of
--   setting a custom shrinker and a custom theme.
accordionDefault :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) Accordion Window

-- | An <a>Accordion</a> layout with the xmonad default decoration, default
--   theme and default shrinker, but with the possibility of moving windows
--   with the mouse, and resize/move them with the keyboard.
accordionSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Accordion)) Window

-- | Similar to <a>accordionSimpleDefaultResizable</a> but with the
--   possibility of setting a custom shrinker and a custom theme.
accordionDefaultResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Accordion)) Window

-- | An <a>Accordion</a> layout with the xmonad simple decoration, default
--   theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/accordionSimpleDeco.png</a>
accordionSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) Accordion Window

-- | An <a>Accordion</a> layout with the xmonad simple decoration, default
--   theme and default shrinker, but with the possibility of moving windows
--   with the mouse, and resize/move them with the keyboard.
accordionSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Accordion)) Window

-- | Similar to <tt>accordionSimpleDece</tt> but with the possibility of
--   setting a custom shrinker and a custom theme.
accordionDeco :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) Accordion Window

-- | Similar to <a>accordionSimpleDecoResizable</a> but with the
--   possibility of setting a custom shrinker and a custom theme.
accordionDecoResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Accordion)) Window

-- | An <a>Accordion</a> layout with the xmonad DwmStyle decoration,
--   default theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/accordionSimpleDwmStyle.png</a>
accordionSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) Accordion Window

-- | Similar to <a>accordionSimpleDwmStyle</a> but with the possibility of
--   setting a custom shrinker and a custom theme.
accordionDwmStyle :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DwmStyle s) Accordion Window

-- | An <a>Accordion</a> layout with the xmonad tabbed decoration, default
--   theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/accordionSimpleTabbed.png</a>
accordionSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen Accordion) Window

-- | Similar to <a>accordionSimpleTabbed</a> but with the possibility of
--   setting a custom shrinker and a custom theme.
accordionTabbed :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen Accordion) Window

-- | A <a>Tall</a> layout with the xmonad default decoration, default theme
--   and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/tallSimpleDefault.png</a>
tallSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) Tall Window

-- | Similar to <a>tallSimpleDefault</a> but with the possibility of
--   setting a custom shrinker and a custom theme.
tallDefault :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) Tall Window

-- | A <a>Tall</a> layout with the xmonad default decoration, default theme
--   and default shrinker, but with the possibility of moving windows with
--   the mouse, and resize/move them with the keyboard.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/tallSimpleDefaultResizable.png</a>
tallSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall)) Window

-- | Similar to <a>tallSimpleDefaultResizable</a> but with the possibility
--   of setting a custom shrinker and a custom theme.
tallDefaultResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall)) Window

-- | A <a>Tall</a> layout with the xmonad simple decoration, default theme
--   and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/tallSimpleDeco.png</a>
tallSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) Tall Window

-- | Similar to <tt>tallSimpleDece</tt> but with the possibility of setting
--   a custom shrinker and a custom theme.
tallDeco :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) Tall Window

-- | A <a>Tall</a> layout with the xmonad simple decoration, default theme
--   and default shrinker, but with the possibility of moving windows with
--   the mouse, and resize/move them with the keyboard.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/tallSimpleDecoResizable.png</a>
tallSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall)) Window

-- | Similar to <a>tallSimpleDecoResizable</a> but with the possibility of
--   setting a custom shrinker and a custom theme.
tallDecoResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall)) Window

-- | A <a>Tall</a> layout with the xmonad DwmStyle decoration, default
--   theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/tallSimpleDwmStyle.png</a>
tallSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) Tall Window

-- | Similar to <a>tallSimpleDwmStyle</a> but with the possibility of
--   setting a custom shrinker and a custom theme.
tallDwmStyle :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DwmStyle s) Tall Window

-- | A <a>Tall</a> layout with the xmonad tabbed decoration, default theme
--   and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/tallSimpleTabbed.png</a>
tallSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen Tall) Window

-- | Similar to <a>tallSimpleTabbed</a> but with the possibility of setting
--   a custom shrinker and a custom theme.
tallTabbed :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen Tall) Window

-- | A 'Mirror Tall' layout with the xmonad default decoration, default
--   theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDefault.png</a>
mirrorTallSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (Mirror Tall) Window

-- | Similar to <a>mirrorTallSimpleDefault</a> but with the possibility of
--   setting a custom shrinker and a custom theme.
mirrorTallDefault :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) (Mirror Tall) Window

-- | A 'Mirror Tall' layout with the xmonad default decoration, default
--   theme and default shrinker, but with the possibility of moving windows
--   with the mouse, and resize/move them with the keyboard.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDefaultResizable.png</a>
mirrorTallSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger (Mirror Tall))) Window

-- | Similar to <a>mirrorTallSimpleDefaultResizable</a> but with the
--   possibility of setting a custom shrinker and a custom theme.
mirrorTallDefaultResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger (Mirror Tall))) Window

-- | A 'Mirror Tall' layout with the xmonad simple decoration, default
--   theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDeco.png</a>
mirrorTallSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (Mirror Tall) Window

-- | Similar to <tt>mirrorTallSimpleDece</tt> but with the possibility of
--   setting a custom shrinker and a custom theme.
mirrorTallDeco :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (Mirror Tall) Window

-- | A 'Mirror Tall' layout with the xmonad simple decoration, default
--   theme and default shrinker, but with the possibility of moving windows
--   with the mouse, and resize/move them with the keyboard.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDecoResizable.png</a>
mirrorTallSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger (Mirror Tall))) Window

-- | Similar to <a>mirrorTallSimpleDecoResizable</a> but with the
--   possibility of setting a custom shrinker and a custom theme.
mirrorTallDecoResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger (Mirror Tall))) Window

-- | A 'Mirror Tall' layout with the xmonad DwmStyle decoration, default
--   theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDwmStyle.png</a>
mirrorTallSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) (Mirror Tall) Window

-- | Similar to <a>mirrorTallSimpleDwmStyle</a> but with the possibility of
--   setting a custom shrinker and a custom theme.
mirrorTallDwmStyle :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DwmStyle s) (Mirror Tall) Window

-- | A 'Mirror Tall' layout with the xmonad tabbed decoration, default
--   theme and default shrinker.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleTabbed.png</a>
mirrorTallSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen (Mirror Tall)) Window

-- | Similar to <a>mirrorTallSimpleTabbed</a> but with the possibility of
--   setting a custom shrinker and a custom theme.
mirrorTallTabbed :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen (Mirror Tall)) Window

-- | A simple floating layout where every window is placed according to the
--   window's initial attributes.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/floatSimpleSimple.png</a>
floatSimpleSimple :: (Show a, Eq a) => ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
floatSimple :: (Show a, Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a

-- | This version is decorated with the <a>DefaultDecoration</a> style.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/floatSimpleDefault.png</a>
floatSimpleDefault :: (Show a, Eq a) => ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a

-- | Same as <a>floatSimpleDefault</a>, but with the possibility of setting
--   a custom shrinker and a custom theme.
floatDefault :: (Show a, Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a

-- | This version is decorated with the <a>DwmStyle</a>. Note that this is
--   a keyboard only floating layout.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/floatSimpleDwmStyle.png</a>
floatSimpleDwmStyle :: (Show a, Eq a) => ModifiedLayout (Decoration DwmStyle DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a

-- | Same as <a>floatSimpleDwmStyle</a>, but with the possibility of
--   setting a custom shrinker and a custom theme.
floatDwmStyle :: (Show a, Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration DwmStyle s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a

-- | This version is decorated with the <tt>TabbedDecoration</tt> style. |
--   Mouse dragging is somehow weird.
--   
--   Here you can find a screen shot:
--   
--   
--   <a>http://code.haskell.org/~arossato/xmonadShots/floatSimpleTabbed.png</a>
floatSimpleTabbed :: (Show a, Eq a) => ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a

-- | Same as <a>floatSimpleTabbed</a>, but with the possibility of setting
--   a custom shrinker and a custom theme.
floatTabbed :: (Show a, Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a

-- | The default xmonad <a>Theme</a>.
defaultTheme :: Theme
shrinkText :: DefaultShrinker


-- | A directory prompt for XMonad
module XMonad.Prompt.Directory
directoryPrompt :: XPConfig -> String -> (String -> X ()) -> X ()
data Dir
instance XPrompt Dir


-- | WorkspaceDir is an extension to set the current directory in a
--   workspace.
--   
--   Actually, it sets the current directory in a layout, since there's no
--   way I know of to attach a behavior to a workspace. This means that any
--   terminals (or other programs) pulled up in that workspace (with that
--   layout) will execute in that working directory. Sort of handy, I
--   think.
--   
--   Note this extension requires the <tt>directory</tt> package to be
--   installed.
module XMonad.Layout.WorkspaceDir
workspaceDir :: LayoutClass l a => String -> l a -> ModifiedLayout WorkspaceDir l a
changeDir :: XPConfig -> X ()
data WorkspaceDir a
instance Typeable Chdir
instance Read (WorkspaceDir a)
instance Show (WorkspaceDir a)
instance LayoutModifier WorkspaceDir Window
instance Message Chdir


-- | A prompt for appending a single line of text to a file. Useful for
--   keeping a file of notes, things to remember for later, and so on---
--   using a keybinding, you can write things down just about as quickly as
--   you think of them, so it doesn't have to interrupt whatever else
--   you're doing.
--   
--   Who knows, it might be useful for other purposes as well!
module XMonad.Prompt.AppendFile

-- | Given an XPrompt configuration and a file path, prompt the user for a
--   line of text, and append it to the given file.
appendFilePrompt :: XPConfig -> FilePath -> X ()
data AppendFile
instance XPrompt AppendFile


-- | A module for launch applicationes that receive parameters in the
--   command line. The launcher call a prompt to get the parameters.
module XMonad.Prompt.AppLauncher

-- | Get the user's response to a prompt an launch an application using the
--   input as command parameters of the application.
launchApp :: XPConfig -> Application -> X ()
type Application = String
data AppPrompt
instance XPrompt AppPrompt


-- | A directory file executables prompt for XMonad. This might be useful
--   if you don't want to have scripts in your PATH environment variable
--   (same executable names, different behavior) - otherwise you might want
--   to use <a>XMonad.Prompt.Shell</a> instead - but you want to have easy
--   access to these executables through the xmonad's prompt.
module XMonad.Prompt.DirExec

-- | Function <a>dirExecPrompt</a> starts the prompt with list of all
--   executable files in directory specified by <a>FilePath</a>. The name
--   of the prompt is taken from the last element of the path. If you
--   specify root directory - <tt>/</tt> - as the path, name <tt>Root:</tt>
--   will be used as the name of the prompt instead. The <a>XPConfig</a>
--   parameter can be used to customize visuals of the prompt. The runner
--   parameter specifies the function used to run the program - see usage
--   for more information
dirExecPrompt :: XPConfig -> (String -> X ()) -> FilePath -> X ()

-- | Function <a>dirExecPromptNamed</a> does the same as
--   <a>dirExecPrompt</a> except the name of the prompt is specified by
--   <a>String</a> parameter.
dirExecPromptNamed :: XPConfig -> (String -> X ()) -> FilePath -> String -> X ()
data DirExec
instance XPrompt DirExec


-- | A generic framework for prompting the user for input and passing it
--   along to some other action.
module XMonad.Prompt.Input

-- | Given a prompt configuration and some prompt text, create an X action
--   which pops up a prompt waiting for user input, and returns whatever
--   they type. Note that the type of the action is <tt>X (Maybe
--   String)</tt>, which reflects the fact that the user might cancel the
--   prompt (resulting in <tt>Nothing</tt>), or enter an input string
--   <tt>s</tt> (resulting in <tt>Just s</tt>).
inputPrompt :: XPConfig -> String -> X (Maybe String)

-- | The same as <a>inputPrompt</a>, but with a completion function. The
--   type <tt>ComplFunction</tt> is <tt>String -&gt; IO [String]</tt>, as
--   defined in <a>XMonad.Prompt</a>. The <a>mkComplFunFromList</a> utility
--   function, also defined in <a>XMonad.Prompt</a>, is useful for creating
--   such a function from a known list of possibilities.
inputPromptWithCompl :: XPConfig -> String -> ComplFunction -> X (Maybe String)

-- | A combinator for hooking up an input prompt action to a function which
--   can take the result of the input prompt and produce another action. If
--   the user cancels the input prompt, the second function will not be
--   run.
--   
--   The astute student of types will note that this is actually a very
--   general combinator and has nothing in particular to do with input
--   prompts. If you find a more general use for it and want to move it to
--   a different module, be my guest.
(?+) :: Monad m => m (Maybe a) -> (a -> m ()) -> m ()
data InputPrompt
instance XPrompt InputPrompt


-- | A prompt for sending quick, one-line emails, via the standard GNU
--   'mail' utility (which must be in your $PATH). This module is intended
--   mostly as an example of using <a>XMonad.Prompt.Input</a> to build an
--   action requiring user input.
module XMonad.Prompt.Email

-- | Prompt the user for a recipient, subject, and body, and send an email
--   via the GNU 'mail' utility. The second argument is a list of addresses
--   for autocompletion.
emailPrompt :: XPConfig -> [String] -> X ()


-- | A manual page prompt for XMonad window manager.
--   
--   TODO
--   
--   <ul>
--   <li>narrow completions by section number, if the one is specified
--   (like <tt>/etc/bash_completion</tt> does)</li>
--   </ul>
module XMonad.Prompt.Man

-- | Query for manual page to be displayed.
manPrompt :: XPConfig -> X ()

-- | Run a command using shell and return its output.
--   
--   XXX Merge into <a>Run</a>?
--   
--   (Ask "gurus" whether <tt>evaluate (length ...)</tt> approach is
--   better/more idiomatic.)
getCommandOutput :: String -> IO String
data Man
instance XPrompt Man


-- | This module provides tools to automatically manage <tt>dock</tt> type
--   programs, such as gnome-panel, kicker, dzen, and xmobar.
module XMonad.Hooks.ManageDocks

-- | Detects if the given window is of type DOCK and if so, reveals it, but
--   does not manage it. If the window has the STRUT property set, adjust
--   the gap accordingly.
manageDocks :: ManageHook

-- | Checks if a window is a DOCK or DESKTOP window
checkDock :: Query Bool
data AvoidStruts a

-- | Adjust layout automagically: don't cover up any docks, status bars,
--   etc.
avoidStruts :: LayoutClass l a => l a -> ModifiedLayout AvoidStruts l a

-- | Adjust layout automagically: don't cover up docks, status bars, etc.
--   on the indicated sides of the screen. Valid sides are U (top), D
--   (bottom), R (right), or L (left).
avoidStrutsOn :: LayoutClass l a => [Direction2D] -> l a -> ModifiedLayout AvoidStruts l a

-- | Whenever a new dock appears, refresh the layout immediately to avoid
--   the new dock.
docksEventHook :: Event -> X All

-- | Message type which can be sent to an <a>AvoidStruts</a> layout
--   modifier to alter its behavior.
data ToggleStruts
ToggleStruts :: ToggleStruts
ToggleStrut :: Direction2D -> ToggleStruts

-- | SetStruts is a message constructor used to set or unset specific
--   struts, regardless of whether or not the struts were originally set.
--   Here are some example bindings:
--   
--   Show all gaps:
--   
--   <pre>
--   ,((modm .|. shiftMask  ,xK_b),sendMessage $ SetStruts [minBound .. maxBound] [])
--   </pre>
--   
--   Hide all gaps:
--   
--   <pre>
--   ,((modm .|. controlMask,xK_b),sendMessage $ SetStruts [] [minBound .. maxBound])
--   </pre>
--   
--   Show only upper and left gaps:
--   
--   <pre>
--   ,((modm .|. controlMask .|. shiftMask,xK_b),sendMessage $ SetStruts [U,L] [minBound .. maxBound])
--   </pre>
--   
--   Hide the bottom keeping whatever the other values were:
--   
--   <pre>
--   ,((modm .|. controlMask .|. shiftMask,xK_g),sendMessage $ SetStruts [] [D])
--   </pre>
data SetStruts
SetStruts :: [Direction2D] -> [Direction2D] -> SetStruts
addedStruts :: SetStruts -> [Direction2D]

-- | These are removed from the currently set struts before
--   <a>addedStruts</a> are added.
removedStruts :: SetStruts -> [Direction2D]

-- | Goes through the list of windows and find the gap so that all STRUT
--   settings are satisfied.
calcGap :: Set Direction2D -> X (Rectangle -> Rectangle)
instance Typeable ToggleStruts
instance Typeable SetStruts
instance Read (AvoidStruts a)
instance Show (AvoidStruts a)
instance Read ToggleStruts
instance Show ToggleStruts
instance Read SetStruts
instance Show SetStruts
instance Eq RectC
instance Show RectC
instance LayoutModifier AvoidStruts a
instance Message SetStruts
instance Message ToggleStruts


-- | Move and resize floating windows using other windows and the edge of
--   the screen as guidelines.
module XMonad.Actions.FloatSnap

-- | Two-dimensional directions:
data Direction2D

-- | Up
U :: Direction2D

-- | Down
D :: Direction2D

-- | Right
R :: Direction2D

-- | Left
L :: Direction2D

-- | Move a window in the specified direction until it snaps against
--   another window or the edge of the screen.
snapMove :: Direction2D -> Maybe Int -> Window -> X ()

-- | Grow the specified edge of a window until it snaps against another
--   window or the edge of the screen.
snapGrow :: Direction2D -> Maybe Int -> Window -> X ()

-- | Shrink the specified edge of a window until it snaps against another
--   window or the edge of the screen.
snapShrink :: Direction2D -> Maybe Int -> Window -> X ()

-- | Move a window by both axises in any direction to snap against the
--   closest part of other windows or the edge of the screen.
snapMagicMove :: Maybe Int -> Maybe Int -> Window -> X ()

-- | Resize the window by each edge independently to snap against the
--   closest part of other windows or the edge of the screen.
snapMagicResize :: [Direction2D] -> Maybe Int -> Maybe Int -> Window -> X ()

-- | Resize the window by each edge independently to snap against the
--   closest part of other windows or the edge of the screen. Use the
--   location of the mouse over the window to decide which edges to snap.
--   In corners, the two adjoining edges will be snapped, along the middle
--   of an edge only that edge will be snapped. In the center of the window
--   all edges will snap. Intended to be used together with
--   <a>XMonad.Actions.FlexibleResize</a> or
--   <a>XMonad.Actions.FlexibleManipulate</a>.
snapMagicMouseResize :: Rational -> Maybe Int -> Maybe Int -> Window -> X ()


-- | xmonad calls the logHook with every internal state update, which is
--   useful for (among other things) outputting status information to an
--   external status bar program such as xmobar or dzen. DynamicLog
--   provides several drop-in logHooks for this purpose, as well as
--   flexible tools for specifying your own formatting.
module XMonad.Hooks.DynamicLog

-- | Run xmonad with a dzen status bar set to some nice defaults.
--   
--   <pre>
--   main = xmonad =&lt;&lt; dzen myConfig
--   
--   myConfig = defaultConfig { ... }
--   </pre>
--   
--   The intent is that the above config file should provide a nice status
--   bar with minimal effort.
--   
--   If you wish to customize the status bar format at all, you'll have to
--   use the <a>statusBar</a> function instead.
--   
--   The binding uses the XMonad.Hooks.ManageDocks module to automatically
--   handle screen placement for dzen, and enables 'mod-b' for toggling the
--   menu bar.
dzen :: LayoutClass l Window => XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))

-- | Run xmonad with a xmobar status bar set to some nice defaults.
--   
--   <pre>
--   main = xmonad =&lt;&lt; xmobar myConfig
--   
--   myConfig = defaultConfig { ... }
--   </pre>
--   
--   This works pretty much the same as <a>dzen</a> function above.
xmobar :: LayoutClass l Window => XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))

-- | Modifies the given base configuration to launch the given status bar,
--   send status information to that bar, and allocate space on the screen
--   edges for the bar.
statusBar :: LayoutClass l Window => String -> PP -> (XConfig Layout -> (KeyMask, KeySym)) -> XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))

-- | An example log hook, which prints status information to stdout in the
--   default format:
--   
--   <pre>
--   1 2 [3] 4 7 : full : title
--   </pre>
--   
--   That is, the currently populated workspaces, the current workspace
--   layout, and the title of the focused window.
--   
--   To customize the output format, see <a>dynamicLogWithPP</a>.
dynamicLog :: X ()

-- | Workspace logger with a format designed for Xinerama:
--   
--   <pre>
--   [1 9 3] 2 7
--   </pre>
--   
--   where 1, 9, and 3 are the workspaces on screens 1, 2 and 3,
--   respectively, and 2 and 7 are non-visible, non-empty workspaces.
--   
--   At the present time, the current layout and window title are not
--   shown. The xinerama workspace format shown above can be (mostly)
--   replicated using <a>dynamicLogWithPP</a> by setting <a>ppSort</a> to
--   <i>getSortByXineramaRule</i> from <a>XMonad.Util.WorkspaceCompare</a>.
--   For example,
--   
--   <pre>
--   defaultPP { ppCurrent = dzenColor "red" "#efebe7"
--             , ppVisible = wrap "[" "]"
--             , ppSort    = getSortByXineramaRule
--             }
--   </pre>
dynamicLogXinerama :: X ()

-- | Write a string to a property on the root window. This property is of
--   type UTF8_STRING. The string must have been processed by encodeString
--   (dynamicLogString does this).
xmonadPropLog' :: String -> String -> X ()

-- | Write a string to the _XMONAD_LOG property on the root window.
xmonadPropLog :: String -> X ()

-- | Format the current status using the supplied pretty-printing format,
--   and write it to stdout.
dynamicLogWithPP :: PP -> X ()

-- | The same as <a>dynamicLogWithPP</a>, except it simply returns the
--   status as a formatted string without actually printing it to stdout,
--   to allow for further processing, or use in some application other than
--   a status bar.
dynamicLogString :: PP -> X String

-- | The <a>PP</a> type allows the user to customize the formatting of
--   status information.
data PP
PP :: (WorkspaceId -> String) -> (WorkspaceId -> String) -> (WorkspaceId -> String) -> (WorkspaceId -> String) -> (WorkspaceId -> String) -> String -> String -> (String -> String) -> (String -> String) -> (String -> String) -> ([String] -> [String]) -> X ([WindowSpace] -> [WindowSpace]) -> [X (Maybe String)] -> (String -> IO ()) -> PP

-- | how to print the tag of the currently focused workspace
ppCurrent :: PP -> WorkspaceId -> String

-- | how to print tags of visible but not focused workspaces (xinerama
--   only)
ppVisible :: PP -> WorkspaceId -> String

-- | how to print tags of hidden workspaces which contain windows
ppHidden :: PP -> WorkspaceId -> String

-- | how to print tags of empty hidden workspaces
ppHiddenNoWindows :: PP -> WorkspaceId -> String

-- | format to be applied to tags of urgent workspaces.
ppUrgent :: PP -> WorkspaceId -> String

-- | separator to use between different log sections (window name, layout,
--   workspaces)
ppSep :: PP -> String

-- | separator to use between workspace tags
ppWsSep :: PP -> String

-- | window title format
ppTitle :: PP -> String -> String

-- | escape / sanitizes input to <a>ppTitle</a>
ppTitleSanitize :: PP -> String -> String

-- | layout name format
ppLayout :: PP -> String -> String

-- | how to order the different log sections. By default, this function
--   receives a list with three formatted strings, representing the
--   workspaces, the layout, and the current window title, respectively. If
--   you have specified any extra loggers in <a>ppExtras</a>, their output
--   will also be appended to the list. To get them in the reverse order,
--   you can just use <tt>ppOrder = reverse</tt>. If you don't want to
--   display the current layout, you could use something like <tt>ppOrder =
--   \(ws:_:t:_) -&gt; [ws,t]</tt>, and so on.
ppOrder :: PP -> [String] -> [String]

-- | how to sort the workspaces. See <a>XMonad.Util.WorkspaceCompare</a>
--   for some useful sorts.
ppSort :: PP -> X ([WindowSpace] -> [WindowSpace])

-- | loggers for generating extra information such as time and date, system
--   load, battery status, and so on. See <a>XMonad.Util.Loggers</a> for
--   examples, or create your own!
ppExtras :: PP -> [X (Maybe String)]

-- | applied to the entire formatted string in order to output it. Can be
--   used to specify an alternative output method (e.g. write to a pipe
--   instead of stdout), and/or to perform some last-minute formatting.
ppOutput :: PP -> String -> IO ()

-- | The default pretty printing options, as seen in <a>dynamicLog</a>.
defaultPP :: PP

-- | Settings to emulate dwm's statusbar, dzen only.
dzenPP :: PP

-- | Some nice xmobar defaults.
xmobarPP :: PP

-- | The options that sjanssen likes to use with xmobar, as an example.
--   Note the use of <a>xmobarColor</a> and the record update on
--   <a>defaultPP</a>.
sjanssenPP :: PP

-- | The options that byorgey likes to use with dzen, as another example.
byorgeyPP :: PP

-- | Wrap a string in delimiters, unless it is empty.
wrap :: String -> String -> String -> String

-- | Pad a string with a leading and trailing space.
pad :: String -> String

-- | Trim leading and trailing whitespace from a string.
trim :: String -> String

-- | Limit a string to a certain length, adding <a>...</a> if truncated.
shorten :: Int -> String -> String

-- | Use xmobar escape codes to output a string with given foreground and
--   background colors.
xmobarColor :: String -> String -> String -> String

-- | Strip xmobar markup.
xmobarStrip :: String -> String

-- | Use dzen escape codes to output a string with given foreground and
--   background colors.
dzenColor :: String -> String -> String -> String

-- | Escape any dzen metacharacters.
dzenEscape :: String -> String

-- | Strip dzen formatting or commands.
dzenStrip :: String -> String

-- | Format the workspace information, given a workspace sorting function,
--   a list of urgent windows, a pretty-printer format, and the current
--   WindowSet.
pprWindowSet :: WorkspaceSort -> [Window] -> PP -> WindowSet -> String
pprWindowSetXinerama :: WindowSet -> String


-- | Turns your workspaces into a more topic oriented system.
module XMonad.Actions.TopicSpace

-- | <a>Topic</a> is just an alias for <a>WorkspaceId</a>
type Topic = WorkspaceId

-- | <a>Dir</a> is just an alias for <a>FilePath</a> but should points to a
--   directory.
type Dir = FilePath

-- | Here is the topic space configuration area.
data TopicConfig
TopicConfig :: Map Topic Dir -> Map Topic (X ()) -> (Topic -> X ()) -> Topic -> Int -> TopicConfig

-- | This mapping associate a directory to each topic.
topicDirs :: TopicConfig -> Map Topic Dir

-- | This mapping associate an action to trigger when switching to a given
--   topic which workspace is empty.
topicActions :: TopicConfig -> Map Topic (X ())

-- | This is the default topic action.
defaultTopicAction :: TopicConfig -> Topic -> X ()

-- | This is the default topic.
defaultTopic :: TopicConfig -> Topic

-- | This setups the maximum depth of topic history, usually 10 is a good
--   default since we can bind all of them using numeric keypad.
maxTopicHistory :: TopicConfig -> Int
defaultTopicConfig :: TopicConfig

-- | Returns the list of last focused workspaces the empty list otherwise.
getLastFocusedTopics :: X [String]

-- | Given a <a>TopicConfig</a>, the last focused topic, and a predicate
--   that will select topics that one want to keep, this function will set
--   the property of last focused topics.
setLastFocusedTopic :: Topic -> (Topic -> Bool) -> X ()

-- | Reverse the list of <a>last focused topics</a>
reverseLastFocusedTopics :: X ()

-- | This function is a variant of <a>pprWindowSet</a> which takes a topic
--   configuration and a pretty-printing record <a>PP</a>. It will show the
--   list of topics sorted historically and highlighting topics with urgent
--   windows.
pprWindowSet :: TopicConfig -> PP -> X String

-- | Given a prompt configuration and a topic configuration, triggers the
--   action associated with the topic given in prompt.
topicActionWithPrompt :: XPConfig -> TopicConfig -> X ()

-- | Given a configuration and a topic, triggers the action associated with
--   the given topic.
topicAction :: TopicConfig -> Topic -> X ()

-- | Trigger the action associated with the current topic.
currentTopicAction :: TopicConfig -> X ()

-- | Switch to the given topic.
switchTopic :: TopicConfig -> Topic -> X ()

-- | Switch to the Nth last focused topic or failback to the
--   <a>defaultTopic</a>.
switchNthLastFocused :: TopicConfig -> Int -> X ()

-- | Shift the focused window to the Nth last focused topic, or fallback to
--   doing nothing.
shiftNthLastFocused :: Int -> X ()

-- | Returns the directory associated with current topic returns the empty
--   string otherwise.
currentTopicDir :: TopicConfig -> X String

-- | Check the given topic configuration for duplicates topics or undefined
--   topics.
checkTopicConfig :: [Topic] -> TopicConfig -> IO ()

-- | An alias for <tt>flip replicateM_</tt>
(>*>) :: Monad m => m a -> Int -> m ()
instance Typeable PrevTopics
instance Read PrevTopics
instance Show PrevTopics
instance ExtensionClass PrevTopics


-- | Manage per-screen status bars.
module XMonad.Hooks.DynamicBars
type DynamicStatusBar = ScreenId -> IO Handle
type DynamicStatusBarCleanup = IO ()
dynStatusBarStartup :: DynamicStatusBar -> DynamicStatusBarCleanup -> X ()
dynStatusBarEventHook :: DynamicStatusBar -> DynamicStatusBarCleanup -> Event -> X All
multiPP :: PP -> PP -> X ()


-- | Utility functions for simulating independent sets of workspaces on
--   each screen (like dwm's workspace model), using internal tags to
--   distinguish workspaces associated with each screen.
module XMonad.Layout.IndependentScreens
type VirtualWorkspace = WorkspaceId
type PhysicalWorkspace = WorkspaceId
workspaces' :: XConfig l -> [VirtualWorkspace]
withScreens :: ScreenId -> [VirtualWorkspace] -> [PhysicalWorkspace]
onCurrentScreen :: (VirtualWorkspace -> WindowSet -> a) -> (PhysicalWorkspace -> WindowSet -> a)

-- | This turns a naive pretty-printer into one that is aware of the
--   independent screens. That is, you can write your pretty printer to
--   behave the way you want on virtual workspaces; this function will
--   convert that pretty-printer into one that first filters out physical
--   workspaces on other screens, then converts all the physical workspaces
--   on this screen to their virtual names.
--   
--   For example, if you have handles <tt>hLeft</tt> and <tt>hRight</tt>
--   for bars on the left and right screens, respectively, and <tt>pp</tt>
--   is a pretty-printer function that takes a handle, you could write
--   
--   <pre>
--   logHook = let log screen handle = dynamicLogWithPP . marshallPP screen . pp $ handle
--             in log 0 hLeft &gt;&gt; log 1 hRight
--   </pre>
marshallPP :: ScreenId -> PP -> PP

-- | In case you don't know statically how many screens there will be, you
--   can call this in main before starting xmonad. For example, part of my
--   config reads
--   
--   <pre>
--   main = do
--     nScreens &lt;- countScreens
--     xmonad $ defaultConfig {
--       ...
--       workspaces = withScreens nScreens (workspaces defaultConfig),
--       ...
--       }
--   </pre>
countScreens :: (MonadIO m, Integral i) => m i
marshall :: ScreenId -> VirtualWorkspace -> PhysicalWorkspace
unmarshall :: PhysicalWorkspace -> (ScreenId, VirtualWorkspace)
unmarshallS :: PhysicalWorkspace -> ScreenId
unmarshallW :: PhysicalWorkspace -> VirtualWorkspace

-- | Convert the tag of the <a>WindowSpace</a> from a
--   <a>VirtualWorkspace</a> to a <a>PhysicalWorkspace</a>.
marshallWindowSpace :: ScreenId -> WindowSpace -> WindowSpace

-- | Convert the tag of the <a>WindowSpace</a> from a
--   <a>PhysicalWorkspace</a> to a <a>VirtualWorkspace</a>.
unmarshallWindowSpace :: WindowSpace -> WindowSpace


-- | A collection of simple logger functions and formatting utilities which
--   can be used in the <a>ppExtras</a> field of a pretty-printing status
--   logger format. See <a>XMonad.Hooks.DynamicLog</a> for more
--   information.
module XMonad.Util.Loggers

-- | <a>Logger</a> is just a convenient synonym for <tt>X (Maybe
--   String)</tt>.
type Logger = X (Maybe String)

-- | Get the current volume with <tt>aumix</tt>.
--   <a>http://jpj.net/~trevor/aumix.html</a>
aumixVolume :: Logger

-- | Get the battery status (percent charge and charging/discharging
--   status). This is an ugly hack and may not work for some people. At
--   some point it would be nice to make this more general/have fewer
--   dependencies (assumes <tt>/usr/bin/acpi</tt> and <tt>sed</tt> are
--   installed.)
battery :: Logger

-- | Get the current date and time, and format them via the given format
--   string. The format used is the same as that used by the C library
--   function strftime; for example, <tt>date "%a %b %d"</tt> might display
--   something like <tt>Tue Feb 19</tt>. For more information see something
--   like
--   <a>http://www.cplusplus.com/reference/clibrary/ctime/strftime.html</a>.
date :: String -> Logger

-- | Get the load average. This assumes that you have a utility called
--   <tt>/usr/bin/uptime</tt> and that you have <tt>sed</tt> installed;
--   these are fairly common on GNU/Linux systems but it would be nice to
--   make this more general.
loadAvg :: Logger

-- | Get a count of new mails in a maildir.
maildirNew :: FilePath -> Logger

-- | Get a count of unread mails in a maildir. For maildir format details,
--   to write loggers for other classes of mail, see
--   <a>http://cr.yp.to/proto/maildir.html</a> and <a>logFileCount</a>.
maildirUnread :: FilePath -> Logger

-- | Create a <a>Logger</a> from an arbitrary shell command.
logCmd :: String -> Logger

-- | Get a count of filtered files in a directory. See <a>maildirUnread</a>
--   and <a>maildirNew</a> source for usage examples.
logFileCount :: FilePath -> (String -> Bool) -> Logger

-- | Get the name of the current workspace.
logCurrent :: Logger

-- | Get the name of the current layout.
logLayout :: Logger

-- | Get the title (name) of the focused window.
logTitle :: Logger

-- | Use a string formatting function to edit a <a>Logger</a> string. For
--   example, to create a tag function to prefix or label loggers, as in
--   'tag: output', use:
--   
--   <pre>
--   tagL l = onLogger $ wrap (l ++ ": ") ""
--   
--      tagL "bat" battery
--      tagL "load" loadAvg
--   </pre>
--   
--   If you already have a (String -&gt; String) function you want to apply
--   to a logger:
--   
--   <pre>
--   revL = onLogger trim
--   </pre>
--   
--   See formatting utility source code for more <a>onLogger</a> usage
--   examples.
onLogger :: (String -> String) -> Logger -> Logger

-- | Wrap a logger's output in delimiters, unless it is <tt>X
--   (Nothing)</tt> or <tt>X (Just "")</tt>. Some examples:
--   
--   <pre>
--   wrapL " | " " | " (date "%a %d %b") -- ' | Tue 19 Feb | '
--   
--   wrapL "bat: " "" battery            -- ' bat: battery_logger_output'
--   </pre>
wrapL :: String -> String -> Logger -> Logger

-- | Make a logger's output constant width by padding with the given
--   string, <i>even if the logger is</i> <tt>X (Nothing)</tt> <i>or</i>
--   <tt>X (Just "")</tt>. Useful to reduce visual noise as a title logger
--   shrinks and grows, to use a fixed width for a logger that sometimes
--   becomes Nothing, or even to create fancy spacers or character based
--   art effects.
--   
--   It fills missing logger output with a repeated character like ".", ":"
--   or pattern, like " -.-". The cycling padding string is reversed on the
--   left of the logger output. This is mainly useful with AlignCenter.
fixedWidthL :: Align -> String -> Int -> Logger -> Logger

-- | Create a "spacer" logger, e.g. <tt>logSp 3 -- loggerizes ' '</tt>. For
--   more complex "spacers", use <a>fixedWidthL</a> with <tt>return
--   Nothing</tt>.
logSp :: Int -> Logger

-- | Pad a logger's output with a leading and trailing space, unless it is
--   <tt>X (Nothing)</tt> or <tt>X (Just "")</tt>.
padL :: Logger -> Logger

-- | Limit a logger's length, adding "..." if truncated.
shortenL :: Int -> Logger -> Logger

-- | Color a logger's output with dzen foreground and background colors.
--   
--   <pre>
--   dzenColorL "green" "#2A4C3F" battery
--   </pre>
dzenColorL :: String -> String -> Logger -> Logger

-- | Color a logger's output with xmobar foreground and background colors.
--   
--   <pre>
--   xmobarColorL "#6A5ACD" "gray6" loadAverage
--   </pre>
xmobarColorL :: String -> String -> Logger -> Logger

-- | An infix synonym for <a>fmap</a>.
(<$>) :: Functor f => (a -> b) -> f a -> f b


-- | Named scratchpads that support several arbitrary applications at the
--   same time.
module XMonad.Util.NamedScratchpad

-- | Single named scratchpad configuration
data NamedScratchpad
NS :: String -> String -> Query Bool -> ManageHook -> NamedScratchpad

-- | Scratchpad name
name :: NamedScratchpad -> String

-- | Command used to run application
cmd :: NamedScratchpad -> String

-- | Query to find already running application
query :: NamedScratchpad -> Query Bool

-- | Manage hook called for application window, use it to define the
--   placement. See <tt>nonFloating</tt>, <tt>defaultFloating</tt> and
--   <tt>customFloating</tt>
hook :: NamedScratchpad -> ManageHook

-- | Manage hook that makes the window non-floating
nonFloating :: ManageHook

-- | Manage hook that makes the window floating with the default placement
defaultFloating :: ManageHook

-- | Manage hook that makes the window floating with custom placement
customFloating :: RationalRect -> ManageHook

-- | Named scratchpads configuration
type NamedScratchpads = [NamedScratchpad]

-- | Action to pop up specified named scratchpad
namedScratchpadAction :: NamedScratchpads -> String -> X ()
allNamedScratchpadAction :: NamedScratchpads -> String -> X ()

-- | Manage hook to use with named scratchpads
namedScratchpadManageHook :: NamedScratchpads -> ManageHook

-- | Transforms a workspace list containing the NSP workspace into one that
--   doesn't contain it. Intended for use with logHooks.
namedScratchpadFilterOutWorkspace :: [WindowSpace] -> [WindowSpace]

-- | Transforms a pretty-printer into one not displaying the NSP workspace.
--   
--   A simple use could be:
--   
--   <pre>
--   logHook = dynamicLogWithPP . namedScratchpadFilterOutWorkspace $ defaultPP
--   </pre>
--   
--   Here is another example, when using
--   <a>XMonad.Layout.IndependentScreens</a>. If you have handles
--   <tt>hLeft</tt> and <tt>hRight</tt> for bars on the left and right
--   screens, respectively, and <tt>pp</tt> is a pretty-printer function
--   that takes a handle, you could write
--   
--   <pre>
--   logHook = let log screen handle = dynamicLogWithPP . namedScratchpadFilterOutWorkspacePP . marshallPP screen . pp $ handle
--             in log 0 hLeft &gt;&gt; log 1 hRight
--   </pre>
namedScratchpadFilterOutWorkspacePP :: PP -> PP


-- | Very handy hotkey-launched floating terminal window.
module XMonad.Util.Scratchpad

-- | Action to pop up the terminal, for the user to bind to a custom key.
scratchpadSpawnAction :: XConfig l -> X ()

-- | Action to pop up the terminal, with a directly specified terminal.
scratchpadSpawnActionTerminal :: String -> X ()

-- | Action to pop up any program with the user specifying how to set its
--   resource to "scratchpad". For example, with gnome-terminal:
--   
--   <pre>
--   scratchpadSpawnActionCustom "gnome-terminal --disable-factory --name scratchpad"
--   </pre>
scratchpadSpawnActionCustom :: String -> X ()

-- | The ManageHook, with the default rectangle: Half the screen wide, a
--   quarter of the screen tall, centered.
scratchpadManageHookDefault :: ManageHook

-- | The ManageHook, with a user-specified StackSet.RationalRect, e.g., for
--   a terminal 4/10 of the screen width from the left, half the screen
--   height from the top, and 6/10 of the screen width by 3/10 the screen
--   height, use:
--   
--   <pre>
--   scratchpadManageHook (W.RationalRect 0.4 0.5 0.6 0.3)
--   </pre>
scratchpadManageHook :: RationalRect -> ManageHook

-- | Transforms a workspace list containing the SP workspace into one that
--   doesn't contain it. Intended for use with logHooks.
scratchpadFilterOutWorkspace :: [WindowSpace] -> [WindowSpace]


-- | This module contains two hooks for the PositionStore (see
--   <a>XMonad.Util.PositionStore</a>) - a ManageHook and an EventHook.
--   
--   The ManageHook can be used to fill the PositionStore with position and
--   size information about new windows. The advantage of using this hook
--   is, that the information is recorded independent of the currently
--   active layout. So the floating shape of the window can later be
--   restored even if it was opened in a tiled layout initially.
--   
--   For windows, that do not request a particular position, a random
--   position will be assigned. This prevents windows from piling up
--   exactly on top of each other.
--   
--   The EventHook makes sure that windows are deleted from the
--   PositionStore when they are closed.
module XMonad.Hooks.PositionStoreHooks
positionStoreManageHook :: Maybe Theme -> ManageHook
positionStoreEventHook :: Event -> X All


-- | This module provides a config suitable for use with a desktop
--   environment such as KDE or GNOME.
module XMonad.Config.Desktop
desktopConfig :: XConfig (ModifiedLayout AvoidStruts (Choose Tall (Choose (Mirror Tall) Full)))
desktopLayoutModifiers :: LayoutClass l a => l a -> ModifiedLayout AvoidStruts l a


-- | This module provides a config suitable for use with the GNOME desktop
--   environment.
module XMonad.Config.Gnome
gnomeConfig :: XConfig (ModifiedLayout AvoidStruts (Choose Tall (Choose (Mirror Tall) Full)))

-- | Launch the <a>Run Application</a> dialog. gnome-panel must be running
--   for this to work.
gnomeRun :: X ()

-- | Register xmonad with gnome. 'dbus-send' must be in the $PATH with
--   which xmonad is started.
--   
--   This action reduces a delay on startup only only if you have
--   configured gnome-session&gt;=2.26: to start xmonad with a command as
--   such:
--   
--   <pre>
--   gconftool-2 -s /desktop/gnome/session/required_components/windowmanager xmonad --type string
--   </pre>
gnomeRegister :: MonadIO m => m ()


-- | This module provides a config suitable for use with the KDE desktop
--   environment.
module XMonad.Config.Kde
kdeConfig :: XConfig (ModifiedLayout AvoidStruts (Choose Tall (Choose (Mirror Tall) Full)))
kde4Config :: XConfig (ModifiedLayout AvoidStruts (Choose Tall (Choose (Mirror Tall) Full)))


-- | This module provides a config suitable for use with the Xfce desktop
--   environment.
module XMonad.Config.Xfce
xfceConfig :: XConfig (ModifiedLayout AvoidStruts (Choose Tall (Choose (Mirror Tall) Full)))


-- | Support for simple mouse gestures.
module XMonad.Actions.MouseGestures

-- | Two-dimensional directions:
data Direction2D

-- | Up
U :: Direction2D

-- | Down
D :: Direction2D

-- | Right
R :: Direction2D

-- | Left
L :: Direction2D

-- | <tt><a>mouseGestureH</a> moveHook endHook</tt> is a mouse button event
--   handler. It collects mouse movements, calling <tt>moveHook</tt> for
--   each update; when the button is released, it calls <tt>endHook</tt>.
mouseGestureH :: (Direction2D -> X ()) -> X () -> X ()

-- | A utility function on top of <a>mouseGestureH</a>. It uses a
--   <a>Map</a> to look up the mouse gesture, then executes the
--   corresponding action (if any).
mouseGesture :: Map [Direction2D] (Window -> X ()) -> Window -> X ()

-- | A callback generator for <a>mouseGestureH</a>. <a>mkCollect</a>
--   returns two callback functions for passing to <a>mouseGestureH</a>.
--   The move hook will collect mouse movements (and return the current
--   gesture as a list); the end hook will return a list of the completed
--   gesture, which you can access with <a>&gt;&gt;=</a>.
mkCollect :: (MonadIO m, MonadIO m') => m (Direction2D -> m' [Direction2D], m' [Direction2D])


-- | Navigation2D is an xmonad extension that allows easy directional
--   navigation of windows and screens (in a multi-monitor setup).
module XMonad.Actions.Navigation2D

-- | Modifies the xmonad configuration to store the Navigation2D
--   configuration
withNavigation2DConfig :: Navigation2DConfig -> XConfig a -> XConfig a

-- | Stores the configuration of directional navigation
data Navigation2DConfig
Navigation2DConfig :: Navigation2D -> Navigation2D -> Navigation2D -> [(String, Navigation2D)] -> [(String, Screen -> Window -> X (Maybe Rectangle))] -> Navigation2DConfig

-- | default navigation strategy for the tiled layer
defaultTiledNavigation :: Navigation2DConfig -> Navigation2D

-- | navigation strategy for the float layer
floatNavigation :: Navigation2DConfig -> Navigation2D

-- | strategy for navigation between screens
screenNavigation :: Navigation2DConfig -> Navigation2D

-- | association list of customized navigation strategies for different
--   layouts in the tiled layer. Each pair is of the form ("layout
--   description", navigation strategy). If there is no pair in this list
--   whose first component is the name of the current layout, the
--   <a>defaultTiledNavigation</a> strategy is used.
layoutNavigation :: Navigation2DConfig -> [(String, Navigation2D)]

-- | list associating functions to calculate rectangles for unmapped
--   windows with layouts to which they are to be applied. Each pair in
--   this list is of the form ("layout description", function), where the
--   function calculates a rectangle for a given unmapped window from the
--   screen it is on and its window ID. See <a>#Finer_Points</a> for how to
--   use this.
unmappedWindowRect :: Navigation2DConfig -> [(String, Screen -> Window -> X (Maybe Rectangle))]

-- | Default navigation configuration. It uses line navigation for the
--   tiled layer and for navigation between screens, and center navigation
--   for the float layer. No custom navigation strategies or rectangles for
--   unmapped windows are defined for individual layouts.
defaultNavigation2DConfig :: Navigation2DConfig

-- | Encapsulates the navigation strategy
data Navigation2D

-- | Line navigation. To illustrate this navigation strategy, consider
--   navigating to the left from the current window. In this case, we draw
--   a horizontal line through the center of the current window and
--   consider all windows that intersect this horizontal line and whose
--   right boundaries are to the left of the left boundary of the current
--   window. From among these windows, we choose the one with the rightmost
--   right boundary.
lineNavigation :: Navigation2D

-- | Center navigation. Again, consider navigating to the left. Then we
--   consider the cone bounded by the two rays shot at 45-degree angles in
--   north-west and south-west direction from the center of the current
--   window. A window is a candidate to receive the focus if its center
--   lies in this cone. We choose the window whose center has minimum
--   L1-distance from the current window center. The tie breaking strategy
--   for windows with the same distance is a bit complicated (see
--   <a>#Technical_Discussion</a>) but ensures that all windows can be
--   reached and that windows with the same center are traversed in their
--   order in the window stack, that is, in the order <a>focusUp</a> and
--   <a>focusDown</a> would traverse them.
centerNavigation :: Navigation2D

-- | Maps each window to a fullscreen rect. This may not be the same
--   rectangle the window maps to under the Full layout or a similar layout
--   if the layout respects statusbar struts. In such cases, it may be
--   better to use <a>singleWindowRect</a>.
fullScreenRect :: Screen -> Window -> X (Maybe Rectangle)

-- | Maps each window to the rectangle it would receive if it was the only
--   window in the layout. Useful, for example, for determining the default
--   rectangle for unmapped windows in a Full layout that respects
--   statusbar struts.
singleWindowRect :: Screen -> Window -> X (Maybe Rectangle)

-- | Switches focus to the closest window in the other layer (floating if
--   the current window is tiled, tiled if the current window is floating).
--   Closest means that the L1-distance between the centers of the windows
--   is minimized.
switchLayer :: X ()

-- | Moves the focus to the next window in the given direction and in the
--   same layer as the current window. The second argument indicates
--   whether navigation should wrap around (e.g., from the left edge of the
--   leftmost screen to the right edge of the rightmost screen).
windowGo :: Direction2D -> Bool -> X ()

-- | Swaps the current window with the next window in the given direction
--   and in the same layer as the current window. (In the floating layer,
--   all that changes for the two windows is their stacking order if
--   they're on the same screen. If they're on different screens, each
--   window is moved to the other window's screen but retains its position
--   and size relative to the screen.) The second argument indicates
--   wrapping (see <a>windowGo</a>).
windowSwap :: Direction2D -> Bool -> X ()

-- | Moves the current window to the next screen in the given direction.
--   The second argument indicates wrapping (see <a>windowGo</a>).
windowToScreen :: Direction2D -> Bool -> X ()

-- | Moves the focus to the next screen in the given direction. The second
--   argument indicates wrapping (see <a>windowGo</a>).
screenGo :: Direction2D -> Bool -> X ()

-- | Swaps the workspace on the current screen with the workspace on the
--   screen in the given direction. The second argument indicates wrapping
--   (see <a>windowGo</a>).
screenSwap :: Direction2D -> Bool -> X ()

-- | Two-dimensional directions:
data Direction2D

-- | Up
U :: Direction2D

-- | Down
D :: Direction2D

-- | Right
R :: Direction2D

-- | Left
L :: Direction2D
instance Typeable Navigation2DConfig
instance ExtensionClass Navigation2DConfig
instance Ord Navigation2D
instance Eq Navigation2D


-- | License : BSD3-style (see LICENSE) Stability : unstable Portability :
--   unportable
--   
--   This is a rewrite of <a>XMonad.Layout.WindowNavigation</a>.
--   WindowNavigation lets you assign keys to move up/down/left/right,
--   based on actual cartesian window coordinates, rather than just going
--   j/k on the stack.
--   
--   This module is experimental. You'll have better luck with the
--   original.
--   
--   This module differs from the other in a few ways:
--   
--   <ol>
--   <li>You can go up/down/left/right across multiple screens.</li>
--   <li>It doesn't provide little border colors for your neighboring
--   windows.</li>
--   <li>It doesn't provide the 'Move' action, which seems to be related to
--   the XMonad.Layout.Combo extension.</li>
--   <li>It tries to be slightly smarter about tracking your current
--   position.</li>
--   <li>Configuration is different.</li>
--   </ol>
module XMonad.Actions.WindowNavigation
withWindowNavigation :: (KeySym, KeySym, KeySym, KeySym) -> XConfig l -> IO (XConfig l)
withWindowNavigationKeys :: [((KeyMask, KeySym), WNAction)] -> XConfig l -> IO (XConfig l)
data WNAction
WNGo :: Direction2D -> WNAction
WNSwap :: Direction2D -> WNAction
go :: IORef WNState -> Direction2D -> X ()
swap :: IORef WNState -> Direction2D -> X ()

-- | Two-dimensional directions:
data Direction2D

-- | Up
U :: Direction2D

-- | Down
D :: Direction2D

-- | Right
R :: Direction2D

-- | Left
L :: Direction2D
type WNState = Map WorkspaceId Point


-- | WindowNavigation is an extension to allow easy navigation of a
--   workspace.
module XMonad.Layout.WindowNavigation
windowNavigation :: LayoutClass l a => l a -> ModifiedLayout WindowNavigation l a
configurableNavigation :: LayoutClass l a => WNConfig -> l a -> ModifiedLayout WindowNavigation l a
data Navigate
Go :: Direction2D -> Navigate
Swap :: Direction2D -> Navigate
Move :: Direction2D -> Navigate

-- | Apply action with destination window
Apply :: (Window -> X ()) -> Direction2D -> Navigate

-- | Two-dimensional directions:
data Direction2D

-- | Up
U :: Direction2D

-- | Down
D :: Direction2D

-- | Right
R :: Direction2D

-- | Left
L :: Direction2D
data MoveWindowToWindow a
MoveWindowToWindow :: a -> a -> MoveWindowToWindow a
navigateColor :: String -> WNConfig
navigateBrightness :: Double -> WNConfig
noNavigateBorders :: WNConfig
defaultWNConfig :: WNConfig
data WNConfig
data WindowNavigation a
instance Typeable1 MoveWindowToWindow
instance Typeable Navigate
instance Read a => Read (MoveWindowToWindow a)
instance Show a => Show (MoveWindowToWindow a)
instance Show WNConfig
instance Read WNConfig
instance Read (WindowNavigation a)
instance Show (WindowNavigation a)
instance LayoutModifier WindowNavigation Window
instance Message Navigate
instance Typeable a => Message (MoveWindowToWindow a)


-- | A layout that combines multiple layouts.
module XMonad.Layout.Combo
combineTwo :: (Read a, Eq a, LayoutClass super (), LayoutClass l1 a, LayoutClass l2 a) => super () -> l1 a -> l2 a -> CombineTwo (super ()) l1 l2 a
data CombineTwo l l1 l2 a
instance (Read l, Read a, Read (l1 a), Read (l2 a)) => Read (CombineTwo l l1 l2 a)
instance (Show l, Show a, Show (l1 a), Show (l2 a)) => Show (CombineTwo l l1 l2 a)
instance (LayoutClass l (), LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, Eq a, Typeable a) => LayoutClass (CombineTwo (l ()) l1 l2) a


-- | A layout that combines multiple layouts and allows to specify where to
--   put new windows.
module XMonad.Layout.ComboP
combineTwoP :: (LayoutClass super (), LayoutClass l1 Window, LayoutClass l2 Window) => super () -> l1 Window -> l2 Window -> Property -> CombineTwoP (super ()) l1 l2 Window
data CombineTwoP l l1 l2 a
data SwapWindow

-- | Swap window between panes
SwapWindow :: SwapWindow

-- | Swap window between panes in the N-th nested ComboP. <tt>SwapWindowN
--   0</tt> equals to SwapWindow
SwapWindowN :: Int -> SwapWindow

-- | Most of the property constructors are quite self-explaining.
data Property
Title :: String -> Property
ClassName :: String -> Property
Resource :: String -> Property

-- | WM_WINDOW_ROLE property
Role :: String -> Property

-- | WM_CLIENT_MACHINE property
Machine :: String -> Property
And :: Property -> Property -> Property
Or :: Property -> Property -> Property
Not :: Property -> Property
Const :: Bool -> Property
instance Typeable SwapWindow
instance Read SwapWindow
instance Show SwapWindow
instance (Read l, Read a, Read (l1 a), Read (l2 a)) => Read (CombineTwoP l l1 l2 a)
instance (Show l, Show a, Show (l1 a), Show (l2 a)) => Show (CombineTwoP l l1 l2 a)
instance (LayoutClass l (), LayoutClass l1 Window, LayoutClass l2 Window) => LayoutClass (CombineTwoP (l ()) l1 l2) Window
instance Message SwapWindow


-- | Create manually-sized gaps along edges of the screen which will not be
--   used for tiling, along with support for toggling gaps on and off.
--   
--   Note that <a>XMonad.Hooks.ManageDocks</a> is the preferred solution
--   for leaving space for your dock-type applications (status bars,
--   toolbars, docks, etc.), since it automatically sets up appropriate
--   gaps, allows them to be toggled, etc. However, this module may still
--   be useful in some situations where the automated approach of
--   ManageDocks does not work; for example, to work with a dock-type
--   application that does not properly set the STRUTS property, or to
--   leave part of the screen blank which is truncated by a projector, and
--   so on.
module XMonad.Layout.Gaps

-- | Two-dimensional directions:
data Direction2D

-- | Up
U :: Direction2D

-- | Down
D :: Direction2D

-- | Right
R :: Direction2D

-- | Left
L :: Direction2D

-- | The gap state. The first component is the configuration (which gaps
--   are allowed, and their current size), the second is the gaps which are
--   currently active.
data Gaps a

-- | A manual gap configuration. Each side of the screen on which a gap is
--   enabled is paired with a size in pixels.
type GapSpec = [(Direction2D, Int)]

-- | Add togglable manual gaps to a layout.
gaps :: GapSpec -> l a -> ModifiedLayout Gaps l a

-- | Messages which can be sent to a gap modifier.
data GapMessage

-- | Toggle all gaps.
ToggleGaps :: GapMessage

-- | Toggle a single gap.
ToggleGap :: !Direction2D -> GapMessage

-- | Increase a gap by a certain number of pixels.
IncGap :: !Int -> !Direction2D -> GapMessage

-- | Decrease a gap.
DecGap :: !Int -> !Direction2D -> GapMessage
instance Typeable GapMessage
instance Show (Gaps a)
instance Read (Gaps a)
instance LayoutModifier Gaps a
instance Message GapMessage


-- | Make layouts respect size hints.
module XMonad.Layout.LayoutHints
layoutHints :: LayoutClass l a => l a -> ModifiedLayout LayoutHints l a

-- | <tt>layoutHintsWithPlacement (rx, ry) layout</tt> will adapt the sizes
--   of a layout's windows according to their size hints, and position them
--   inside their originally assigned area according to the <tt>rx</tt> and
--   <tt>ry</tt> parameters. (0, 0) places the window at the top left, (1,
--   0) at the top right, (0.5, 0.5) at the center, etc.
layoutHintsWithPlacement :: LayoutClass l a => (Double, Double) -> l a -> ModifiedLayout LayoutHints l a

-- | <tt>layoutHintsToCenter layout</tt> applies hints, sliding the window
--   to the center of the screen and expanding its neighbors to fill the
--   gaps. Windows are never expanded in a way that increases overlap.
--   
--   <tt>layoutHintsToCenter</tt> only makes one pass at resizing the
--   neighbors of hinted windows, so with some layouts (ex. the arrangement
--   with two <tt>Mirror</tt> <tt>Tall</tt> stacked vertically),
--   <tt>layoutHintsToCenter</tt> may leave some gaps. Simple layouts like
--   <tt>Tall</tt> are unaffected.
layoutHintsToCenter :: LayoutClass l a => l a -> ModifiedLayout LayoutHintsToCenter l a
data LayoutHints a
data LayoutHintsToCenter a

-- | Event hook that refreshes the layout whenever a window changes its
--   hints.
hintsEventHook :: Event -> X All
instance Read (LayoutHints a)
instance Show (LayoutHints a)
instance Read (LayoutHintsToCenter a)
instance Show (LayoutHintsToCenter a)
instance LayoutModifier LayoutHintsToCenter Window
instance LayoutModifier LayoutHints Window


-- | A layout combinator that allows layouts to be nested.
module XMonad.Layout.SubLayouts

-- | The main layout modifier arguments:
--   
--   <pre>
--   subLayout advanceInnerLayouts innerLayout outerLayout
--   </pre>
--   
--   <ul>
--   <li><i><tt>advanceInnerLayouts</tt></i> When a new group at index
--   <tt>n</tt> in the outer layout is created (even with one element), the
--   <tt>innerLayout</tt> is used as the layout within that group after
--   being advanced with <tt>advanceInnerLayouts !! n</tt>
--   <a>NextLayout</a> messages. If there is no corresponding element in
--   the <tt>advanceInnerLayouts</tt> list, then <tt>innerLayout</tt> is
--   not given any <a>NextLayout</a> messages.</li>
--   <li><i><tt>innerLayout</tt></i> The single layout given to be run as a
--   sublayout.</li>
--   <li><i><tt>outerLayout</tt></i> The layout that determines the
--   rectangles given to each group.</li>
--   </ul>
--   
--   Ex. The second group is <a>Tall</a>, the third is <tt>Circle</tt>, all
--   others are tabbed with:
--   
--   <pre>
--   myLayout = addTabs shrinkText defaultTheme
--            $ subLayout [0,1,2] (Simplest ||| Tall 1 0.2 0.5 ||| Circle)
--            $ Tall 1 0.2 0.5 ||| Full
--   </pre>
subLayout :: [Int] -> subl a -> l a -> ModifiedLayout (Sublayout subl) l a

-- | <tt>subTabbed</tt> is a use of <a>subLayout</a> with <a>addTabs</a> to
--   show decorations.
subTabbed :: (Eq a, LayoutModifier (Sublayout Simplest) a, LayoutClass l a) => l a -> ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) (ModifiedLayout (Sublayout Simplest) l) a

-- | <tt>pullGroup</tt>, <tt>pushGroup</tt> allow you to merge windows or
--   groups inheriting the position of the current window (pull) or the
--   other window (push).
--   
--   <tt>pushWindow</tt> and <tt>pullWindow</tt> move individual windows
--   between groups. They are less effective at preserving window
--   positions.
pullGroup, pushWindow, pullWindow, pushGroup :: Direction2D -> Navigate

-- | Apply a function on the stack belonging to the currently focused
--   group. It works for rearranging windows and for changing focus.
onGroup :: (Stack Window -> Stack Window) -> X ()

-- | Send a message to the currently focused sublayout.
toSubl :: Message a => a -> X ()

-- | merge the window that would be focused by the function when applied to
--   the W.Stack of all windows, with the current group removed. The given
--   window should be focused by a sublayout. Example usage:
--   <tt>withFocused (sendMessage . mergeDir W.focusDown')</tt>
mergeDir :: (Stack Window -> Stack Window) -> Window -> GroupMsg Window

-- | GroupMsg take window parameters to determine which group the action
--   should be applied to
data GroupMsg a

-- | free the focused window from its tab stack
UnMerge :: a -> GroupMsg a

-- | separate the focused group into singleton groups
UnMergeAll :: a -> GroupMsg a

-- | merge the first group into the second group
Merge :: a -> a -> GroupMsg a

-- | make one large group, keeping the parameter focused
MergeAll :: a -> GroupMsg a

-- | used to the window named in the first argument to the second
--   argument's group, this may be replaced by a combination of
--   <a>UnMerge</a> and <a>Merge</a>
Migrate :: a -> a -> GroupMsg a
WithGroup :: (Stack a -> X (Stack a)) -> a -> GroupMsg a

-- | the sublayout with the given window will get the message
SubMessage :: SomeMessage -> a -> GroupMsg a
data Broadcast

-- | send a message to all sublayouts
Broadcast :: SomeMessage -> Broadcast

-- | <tt>defaultSublMap</tt> is an attempt to create a set of keybindings
--   like the defaults ones but to be used as a <tt>submap</tt> for sending
--   messages to the sublayout.
defaultSublMap :: XConfig l -> Map (KeyMask, KeySym) (X ())
data Sublayout l a
instance Typeable1 GroupMsg
instance Typeable Broadcast
instance (Read a, Read (l a)) => Read (Sublayout l a)
instance (Show a, Show (l a)) => Show (Sublayout l a)
instance (Read (l Window), Show (l Window), LayoutClass l Window) => LayoutModifier (Sublayout l) Window
instance Typeable a => Message (GroupMsg a)
instance Message Broadcast


-- | Provides bindings to cycle forward or backward through the list of
--   workspaces, to move windows between workspaces, and to cycle between
--   screens. More general combinators provide ways to cycle through
--   workspaces in various orders, to only cycle through some subset of
--   workspaces, and to cycle by more than one workspace at a time.
--   
--   Note that this module now subsumes the functionality of the former
--   <tt>XMonad.Actions.RotView</tt>. Former users of <tt>rotView</tt> can
--   simply replace <tt>rotView True</tt> with <tt>moveTo Next
--   NonEmptyWS</tt>, and so on.
--   
--   If you want to exactly replicate the action of <tt>rotView</tt>
--   (cycling through workspace in order lexicographically by tag, instead
--   of in the order specified in the config), it can be implemented as:
--   
--   <pre>
--   rotView b  = do t &lt;- findWorkspace getSortByTag (bToDir b) NonEmptyWS 1
--                   windows . greedyView $ t
--     where bToDir True  = Next
--           bToDir False = Prev
--   </pre>
module XMonad.Actions.CycleWS

-- | Switch to the next workspace.
nextWS :: X ()

-- | Switch to the previous workspace.
prevWS :: X ()

-- | Move the focused window to the next workspace.
shiftToNext :: X ()

-- | Move the focused window to the previous workspace.
shiftToPrev :: X ()

-- | Toggle to the workspace displayed previously.
toggleWS :: X ()

-- | Toggle to the previous workspace while excluding some workspaces.
--   
--   <pre>
--   -- Ignore the scratchpad workspace while toggling:
--   ("M-b", toggleWS' ["NSP"])
--   </pre>
toggleWS' :: [WorkspaceId] -> X ()

-- | <a>greedyView</a> a workspace, or if already there, view the
--   previously displayed workspace ala weechat. Change <tt>greedyView</tt>
--   to <tt>toggleOrView</tt> in your workspace bindings as in the
--   <a>view</a> faq at
--   <a>http://haskell.org/haskellwiki/Xmonad/Frequently_asked_questions</a>.
--   For more flexibility see <a>toggleOrDoSkip</a>.
toggleOrView :: WorkspaceId -> X ()

-- | View next screen
nextScreen :: X ()

-- | View prev screen
prevScreen :: X ()

-- | Move focused window to workspace on next screen
shiftNextScreen :: X ()

-- | Move focused window to workspace on prev screen
shiftPrevScreen :: X ()

-- | Swap current screen with next screen
swapNextScreen :: X ()

-- | Swap current screen with previous screen
swapPrevScreen :: X ()

-- | One-dimensional directions:
data Direction1D
Next :: Direction1D
Prev :: Direction1D

-- | What type of workspaces should be included in the cycle?
data WSType

-- | cycle through empty workspaces
EmptyWS :: WSType

-- | cycle through non-empty workspaces
NonEmptyWS :: WSType

-- | cycle through non-visible workspaces
HiddenWS :: WSType

-- | cycle through non-empty non-visible workspaces
HiddenNonEmptyWS :: WSType

-- | cycle through all workspaces
AnyWS :: WSType

-- | cycle through workspaces in the same group, the group name is all
--   characters up to the first separator character or the end of the tag
WSTagGroup :: Char -> WSType

-- | cycle through workspaces satisfying an arbitrary predicate
WSIs :: (X (WindowSpace -> Bool)) -> WSType

-- | Move the currently focused window to the next workspace in the given
--   direction that satisfies the given condition.
shiftTo :: Direction1D -> WSType -> X ()

-- | View the next workspace in the given direction that satisfies the
--   given condition.
moveTo :: Direction1D -> WSType -> X ()

-- | Using the given sort, find the next workspace in the given direction
--   of the given type, and perform the given action on it.
doTo :: Direction1D -> WSType -> X WorkspaceSort -> (WorkspaceId -> X ()) -> X ()

-- | Given a function <tt>s</tt> to sort workspaces, a direction
--   <tt>dir</tt>, a predicate <tt>p</tt> on workspaces, and an integer
--   <tt>n</tt>, find the tag of the workspace which is <tt>n</tt> away
--   from the current workspace in direction <tt>dir</tt> (wrapping around
--   if necessary), among those workspaces, sorted by <tt>s</tt>, which
--   satisfy <tt>p</tt>.
--   
--   For some useful workspace sorting functions, see
--   <a>XMonad.Util.WorkspaceCompare</a>.
--   
--   For ideas of what to do with a workspace tag once obtained, note that
--   <a>moveTo</a> and <a>shiftTo</a> are implemented by applying
--   <tt>(&gt;&gt;= (windows . greedyView))</tt> and <tt>(&gt;&gt;=
--   (windows . shift))</tt>, respectively, to the output of
--   <a>findWorkspace</a>.
findWorkspace :: X WorkspaceSort -> Direction1D -> WSType -> Int -> X WorkspaceId

-- | Allows ignoring listed workspace tags (such as scratchpad's "NSP"),
--   and running other actions such as view, shift, etc. For example:
--   
--   <pre>
--   import qualified XMonad.StackSet as W
--   import XMonad.Actions.CycleWS
--   
--   -- toggleOrView for people who prefer view to greedyView
--   toggleOrView' = toggleOrDoSkip [] W.view
--   
--   -- toggleOrView ignoring scratchpad and named scratchpad workspace
--   toggleOrViewNoSP = toggleOrDoSkip ["NSP"] W.greedyView
--   </pre>
toggleOrDoSkip :: [WorkspaceId] -> (WorkspaceId -> WindowSet -> WindowSet) -> WorkspaceId -> X ()

-- | List difference (<tt>\\</tt>) for workspaces and tags. Removes
--   workspaces matching listed tags from the given workspace list.
skipTags :: Eq i => [Workspace i l a] -> [i] -> [Workspace i l a]

-- | Get the <a>ScreenId</a> <i>d</i> places over. Example usage is a
--   variation of the the default screen keybindings:
--   
--   <pre>
--   -- mod-{w,e}, Switch to previous/next Xinerama screen
--   -- mod-shift-{w,e}, Move client to previous/next Xinerama screen
--   --
--   [((m .|. modm, key), sc &gt;&gt;= screenWorkspace &gt;&gt;= flip whenJust (windows . f))
--       | (key, sc) &lt;- zip [xK_w, xK_e] [(screenBy (-1)),(screenBy 1)]
--       , (f, m) &lt;- [(W.view, 0), (W.shift, shiftMask)]]
--   </pre>
screenBy :: Int -> X (ScreenId)


-- | Remember a dynamically updateable ordering on workspaces, together
--   with tools for using this ordering with <a>XMonad.Actions.CycleWS</a>
--   and <a>XMonad.Hooks.DynamicLog</a>.
module XMonad.Actions.DynamicWorkspaceOrder

-- | A comparison function which orders workspaces according to the stored
--   dynamic ordering.
getWsCompareByOrder :: X WorkspaceCompare

-- | Sort workspaces according to the stored dynamic ordering.
getSortByOrder :: X WorkspaceSort

-- | Swap the current workspace with another workspace in the stored
--   dynamic order.
swapWith :: Direction1D -> WSType -> X ()

-- | View the next workspace of the given type in the given direction,
--   where "next" is determined using the dynamic workspace order.
moveTo :: Direction1D -> WSType -> X ()

-- | Same as <a>moveTo</a>, but using <tt>greedyView</tt> instead of
--   <tt>view</tt>.
moveToGreedy :: Direction1D -> WSType -> X ()

-- | Shift the currently focused window to the next workspace of the given
--   type in the given direction, using the dynamic workspace order.
shiftTo :: Direction1D -> WSType -> X ()

-- | Do something with the nth workspace in the dynamic order. The callback
--   is given the workspace's tag as well as the <a>WindowSet</a> of the
--   workspace itself.
withNthWorkspace :: (String -> WindowSet -> WindowSet) -> Int -> X ()
instance Typeable WSOrderStorage
instance Read WSOrderStorage
instance Show WSOrderStorage
instance ExtensionClass WSOrderStorage


-- | Lets you swap workspace tags, so you can keep related ones next to
--   each other, without having to move individual windows.
module XMonad.Actions.SwapWorkspaces

-- | Swaps the currently focused workspace with the given workspace tag,
--   via <tt>swapWorkspaces</tt>.
swapWithCurrent :: Eq i => i -> StackSet i l a s sd -> StackSet i l a s sd

-- | Say <tt>swapTo Next</tt> or <tt>swapTo Prev</tt> to move your current
--   workspace. This is an <tt>X ()</tt> so can be hooked up to your
--   keybindings directly.
swapTo :: Direction1D -> X ()

-- | Takes two workspace tags and an existing XMonad.StackSet and returns a
--   new one with the two corresponding workspaces' tags swapped.
swapWorkspaces :: Eq i => i -> i -> StackSet i l a s sd -> StackSet i l a s sd

-- | One-dimensional directions:
data Direction1D
Next :: Direction1D
Prev :: Direction1D


-- | Provides bindings to rename workspaces, show these names in DynamicLog
--   and swap workspaces along with their names. These names survive
--   restart. Together with <a>XMonad.Layout.WorkspaceDir</a> this provides
--   for a fully dynamic topic space workflow.
module XMonad.Actions.WorkspaceNames

-- | Prompt for a new name for the current workspace and set it.
renameWorkspace :: XPConfig -> X ()

-- | Modify <a>XMonad.Hooks.DynamicLog</a>'s pretty-printing format to show
--   workspace names as well.
workspaceNamesPP :: PP -> X PP

-- | Returns a function that maps workspace tag <tt>"t"</tt> to
--   <tt>"t:name"</tt> for workspaces with a name, and to <tt>"t"</tt>
--   otherwise.
getWorkspaceNames :: X (WorkspaceId -> String)

-- | Sets the name of a workspace. Empty string makes the workspace unnamed
--   again.
setWorkspaceName :: WorkspaceId -> String -> X ()

-- | Sets the name of the current workspace. See <a>setWorkspaceName</a>.
setCurrentWorkspaceName :: String -> X ()

-- | See <a>swapTo</a>. This is the same with names.
swapTo :: Direction1D -> X ()

-- | Swap with the previous or next workspace of the given type.
swapTo' :: Direction1D -> WSType -> X ()

-- | See <a>swapWithCurrent</a>. This is almost the same with names.
swapWithCurrent :: WorkspaceId -> X ()
instance Typeable WorkspaceNames
instance Read WorkspaceNames
instance Show WorkspaceNames
instance ExtensionClass WorkspaceNames


-- | Rotate all windows except the master window and keep the focus in
--   place.
module XMonad.Actions.RotSlaves

-- | The actual rotation, as a pure function on the window stack.
rotSlaves' :: ([a] -> [a]) -> Stack a -> Stack a

-- | Rotate the windows in the current stack, excluding the first one
--   (master).
rotSlavesUp, rotSlavesDown :: X ()

-- | The actual rotation, as a pure function on the window stack.
rotAll' :: ([a] -> [a]) -> Stack a -> Stack a

-- | Rotate all the windows in the current stack.
rotAllUp, rotAllDown :: X ()


-- | Provides bindings to cycle windows up or down on the current workspace
--   stack while maintaining focus in place.
--   
--   Bindings are available to:
--   
--   <ul>
--   <li>Cycle nearby or nth windows into the focused frame</li>
--   <li>Cycle a window halfway around the stack</li>
--   <li>Cycle windows through the focused position.</li>
--   <li>Cycle unfocused windows.</li>
--   </ul>
--   
--   These bindings are especially useful with layouts that hide some of
--   the windows in the stack, such as Full, <a>XMonad.Layout.TwoPane</a>
--   or when using <a>XMonad.Layout.LimitWindows</a> to only show three or
--   four panes. See also <a>XMonad.Actions.RotSlaves</a> for related
--   actions.
module XMonad.Actions.CycleWindows
cycleRecentWindows :: [KeySym] -> KeySym -> KeySym -> X ()

-- | Cycle through a <i>finite</i> list of window stacks with repeated
--   presses of a key while a modifier key is held down. For best results
--   use the same mod key + key combination as the one used to invoke the
--   "bring from below" action. You could use cycleStacks' with a different
--   stack permutations function to, for example, cycle from one below to
--   one above to two below, etc. instead of in order. You are responsible
--   for having it generate a finite list, though, or xmonad may hang
--   seeking its length.
cycleStacks' :: (Stack Window -> [Stack Window]) -> [KeySym] -> KeySym -> KeySym -> X ()

-- | The opposite rotation on a Stack.
rotOpposite' :: Stack a -> Stack a
rotOpposite :: X ()

-- | The focused rotation on a stack.
rotFocused' :: ([a] -> [a]) -> Stack a -> Stack a

-- | Rotate windows through the focused frame, excluding the "next" window.
--   With, e.g. TwoPane, this allows cycling windows through either the
--   master or slave pane, without changing the other frame. When the
--   master is focused, the window below is skipped, when a non-master
--   window is focused, the master is skipped.
rotFocusedUp :: X ()
rotFocusedDown :: X ()

-- | Given a stack element and a stack, shift or insert the element
--   (window) at the currently focused position.
shiftToFocus' :: (Eq a, Show a, Read a) => a -> Stack a -> Stack a

-- | The unfocused rotation on a stack.
rotUnfocused' :: ([a] -> [a]) -> Stack a -> Stack a
rotUnfocusedUp :: X ()
rotUnfocusedDown :: X ()
rotUp :: [a] -> [a]
rotDown :: [a] -> [a]


-- | Provides bindings to cycle through most recently used workspaces with
--   repeated presses of a single key (as long as modifier key is held
--   down). This is similar to how many window managers handle window
--   switching.
module XMonad.Actions.CycleRecentWS

-- | Cycle through most recent workspaces with repeated presses of a key,
--   while a modifier key is held down. The recency of workspaces previewed
--   while browsing to the target workspace is not affected. That way a
--   stack of most recently used workspaces is maintained, similarly to how
--   many window managers handle window switching. For best effects use the
--   same modkey+key combination as the one used to invoke this action.
cycleRecentWS :: [KeySym] -> KeySym -> KeySym -> X ()

-- | Cycle through a finite list of WindowSets with repeated presses of a
--   key, while a modifier key is held down. For best effects use the same
--   modkey+key combination as the one used to invoke this action.
cycleWindowSets :: (WindowSet -> [WindowSet]) -> [KeySym] -> KeySym -> KeySym -> X ()


-- | Defines a few convenient operations for raising (traveling to) windows
--   based on XMonad's Query monad, such as <a>runOrRaise</a>. runOrRaise
--   will run a shell command unless it can find a specified window; you
--   would use this to automatically travel to your Firefox or Emacs
--   session, or start a new one (for example), instead of trying to
--   remember where you left it or whether you still have one running.
module XMonad.Actions.WindowGo

-- | See <a>raiseMaybe</a>. If the Window can't be found, quietly give up
--   and do nothing.
raise :: Query Bool -> X ()

-- | See <a>raise</a> and <a>raiseNextMaybe</a>. Version that allows
--   cycling through matches.
raiseNext :: Query Bool -> X ()

-- | <tt>action</tt> is an executable to be run via <a>safeSpawnProg</a>
--   (of <a>XMonad.Util.Run</a>) if the Window cannot be found. Presumably
--   this executable is the same one that you were looking for. Note that
--   this does not go through the shell. If you wish to run an arbitrary IO
--   action (such as <tt>spawn</tt>, which will run its String argument
--   through the shell), then you will want to use <a>raiseMaybe</a>
--   directly.
runOrRaise :: String -> Query Bool -> X ()

-- | See <a>runOrRaise</a> and <a>raiseNextMaybe</a>. Version that allows
--   cycling through matches.
runOrRaiseNext :: String -> Query Bool -> X ()

-- | <a>raiseMaybe</a> queries all Windows based on a boolean provided by
--   the user. Currently, there are 3 such useful booleans defined in
--   <a>XMonad.ManageHook</a>: <a>title</a>, <a>resource</a>,
--   <a>className</a>. Each one tests based pretty much as you would think.
--   ManageHook also defines several operators, the most useful of which is
--   (=?). So a useful test might be finding a <tt>Window</tt> whose class
--   is Firefox. Firefox 3 declares the class "Firefox", so you'd want to
--   pass in a boolean like <tt>(className =? "Firefox")</tt>.
--   
--   If the boolean returns <tt>True</tt> on one or more windows, then
--   XMonad will quickly make visible the first result. If no
--   <tt>Window</tt> meets the criteria, then the first argument comes into
--   play.
--   
--   The first argument is an arbitrary IO function which will be executed
--   if the tests fail. This is what enables <a>runOrRaise</a> to use
--   <a>raiseMaybe</a>: it simply runs the desired program if it isn't
--   found. But you don't have to do that. Maybe you want to do nothing if
--   the search fails (the definition of <a>raise</a>), or maybe you want
--   to write to a log file, or call some prompt function, or something
--   crazy like that. This hook gives you that flexibility. You can do some
--   cute things with this hook. Suppose you want to do the same thing for
--   Mutt which you just did for Firefox - but Mutt runs inside a terminal
--   window? No problem: you search for a terminal window calling itself
--   "mutt", and if there isn't you run a terminal with a command to run
--   Mutt! Here's an example (borrowing <tt>runInTerm</tt> from
--   <a>XMonad.Util.Run</a>):
--   
--   <pre>
--   , ((modm, xK_m), raiseMaybe (runInTerm "-title mutt" "mutt") (title =? "mutt"))
--   </pre>
raiseMaybe :: X () -> Query Bool -> X ()

-- | See <a>raiseMaybe</a>. <a>raiseNextMaybe</a> is an alternative version
--   that allows cycling through the matching windows. If the focused
--   window matches the query the next matching window is raised. If no
--   matches are found the function f is executed.
raiseNextMaybe :: X () -> Query Bool -> X ()

-- | <a>raiseBrowser</a> and <a>raiseEditor</a> grab $BROWSER and $EDITOR
--   respectively and they either take you to the specified program's
--   window, or they try to run it. This is most useful if your variables
--   are simple and look like "firefox" or "emacs".
raiseBrowser, raiseEditor :: X ()

-- | If a window matching the second argument is found, the window is
--   focused and the third argument is called; otherwise, the first
--   argument is called.
runOrRaiseAndDo :: String -> Query Bool -> (Window -> X ()) -> X ()

-- | If the window is found the window is focused and set to master
--   otherwise, action is run.
--   
--   <pre>
--   runOrRaiseMaster "firefox" (className =? "Firefox"))
--   </pre>
runOrRaiseMaster :: String -> Query Bool -> X ()

-- | If the window is found the window is focused and the third argument is
--   called otherwise, the first argument is called See <a>raiseMaster</a>
--   for an example.
raiseAndDo :: X () -> Query Bool -> (Window -> X ()) -> X ()

-- | if the window is found the window is focused and set to master
--   otherwise, the first argument is called.
--   
--   <pre>
--   raiseMaster (runInTerm "-title ghci"  "zsh -c 'ghci'") (title =? "ghci") 
--   </pre>
raiseMaster :: X () -> Query Bool -> X ()

-- | If windows that satisfy the query exist, apply the supplied function
--   to them, otherwise run the action given as second parameter.
ifWindows :: Query Bool -> ([Window] -> X ()) -> X () -> X ()

-- | The same as ifWindows, but applies a ManageHook to the first match
--   instead and discards the other matches
ifWindow :: Query Bool -> ManageHook -> X () -> X ()

-- | A manage hook that raises the window.
raiseHook :: ManageHook


-- | A prompt for XMonad which will run a program, open a file, or raise an
--   already running program, depending on context.
module XMonad.Prompt.RunOrRaise
runOrRaisePrompt :: XPConfig -> X ()
data RunOrRaisePrompt
instance XPrompt RunOrRaisePrompt


-- | Provides bindings to duplicate a window on multiple workspaces,
--   providing dwm-like tagging functionality.
module XMonad.Actions.CopyWindow

-- | Copy the focused window to a workspace.
copy :: (Eq s, Eq i, Eq a) => i -> StackSet i l a s sd -> StackSet i l a s sd

-- | Copy the focused window to all workspaces.
copyToAll :: (Eq s, Eq i, Eq a) => StackSet i l a s sd -> StackSet i l a s sd

-- | Copy an arbitrary window to a workspace.
copyWindow :: (Eq a, Eq i, Eq s) => a -> i -> StackSet i l a s sd -> StackSet i l a s sd

-- | runOrCopy will run the provided shell command unless it can find a
--   specified window in which case it will copy the window to the current
--   workspace. Similar to (i.e., stolen from)
--   <a>XMonad.Actions.WindowGo</a>.
runOrCopy :: String -> Query Bool -> X ()

-- | Kill all other copies of focused window (if they're present). 'All
--   other' means here 'copies which are not on the current workspace'.
killAllOtherCopies :: X ()

-- | Remove the focused window from this workspace. If it's present in no
--   other workspace, then kill it instead. If we do kill it, we'll get a
--   delete notify back from X.
--   
--   There are two ways to delete a window. Either just kill it, or if it
--   supports the delete protocol, send a delete event (e.g. firefox).
kill1 :: X ()

-- | A list of hidden workspaces containing a copy of the focused window.
wsContainingCopies :: X [WorkspaceId]

module XMonad.Config.Sjanssen
sjanssenConfig :: XConfig (ModifiedLayout AvoidStruts (ModifiedLayout SmartBorder (Choose (Choose HintedTile (Choose HintedTile Full)) (ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest))))


-- | Lets you constrain the aspect ratio of a floating window (by, say,
--   holding shift while you resize).
--   
--   Useful for making a nice circular XClock window.
module XMonad.Actions.ConstrainedResize

-- | Resize (floating) window with optional aspect ratio constraints.
mouseResizeWindow :: Window -> Bool -> X ()


-- | A convenient binding to dmenu.
--   
--   Requires the process-1.0 package
module XMonad.Util.Dmenu

-- | Run dmenu to select an option from a list.
dmenu :: [String] -> X String

-- | Starts dmenu on the current screen. Requires this patch to dmenu:
--   <a>http://www.jcreigh.com/dmenu/dmenu-3.2-xinerama.patch</a>
dmenuXinerama :: [String] -> X String

-- | Run dmenu to select an entry from a map based on the key.
dmenuMap :: Map String a -> X (Maybe a)

-- | like <a>dmenu</a> but also takes the command to run.
menu :: String -> [String] -> X String

-- | Like <a>menu</a> but also takes a list of command line arguments.
menuArgs :: String -> [String] -> [String] -> X String

-- | Like <a>dmenuMap</a> but also takes the command to run.
menuMap :: String -> Map String a -> X (Maybe a)

-- | Like <a>menuMap</a> but also takes a list of command line arguments.
menuMapArgs :: String -> [String] -> Map String a -> X (Maybe a)


-- | dmenu operations to bring windows to you, and bring you to windows.
--   That is to say, it pops up a dmenu with window names, in case you
--   forgot where you left your XChat.
module XMonad.Actions.WindowBringer

-- | Pops open a dmenu with window titles. Choose one, and you will be
--   taken to the corresponding workspace.
gotoMenu :: X ()

-- | Pops open an application with window titles given over stdin. Choose
--   one, and you will be taken to the corresponding workspace.
gotoMenu' :: String -> X ()

-- | Pops open a dmenu with window titles. Choose one, and you will be
--   taken to the corresponding workspace. This version takes a list of
--   arguments to pass to dmenu.
gotoMenuArgs :: [String] -> X ()

-- | Pops open an application with window titles given over stdin. Choose
--   one, and you will be taken to the corresponding workspace. This
--   version takes a list of arguments to pass to dmenu.
gotoMenuArgs' :: String -> [String] -> X ()

-- | Pops open a dmenu with window titles. Choose one, and it will be
--   dragged, kicking and screaming, into your current workspace.
bringMenu :: X ()

-- | Pops open an application with window titles given over stdin. Choose
--   one, and it will be dragged, kicking and screaming, into your current
--   workspace.
bringMenu' :: String -> X ()

-- | Pops open a dmenu with window titles. Choose one, and it will be
--   dragged, kicking and screaming, into your current workspace. This
--   version takes a list of arguments to pass to dmenu.
bringMenuArgs :: [String] -> X ()

-- | Pops open an application with window titles given over stdin. Choose
--   one, and it will be dragged, kicking and screaming, into your current
--   workspace. This version allows arguments to the chooser to be
--   specified.
bringMenuArgs' :: String -> [String] -> X ()

-- | A map from window names to Windows.
windowMap :: X (Map String Window)

-- | Brings the specified window into the current workspace.
bringWindow :: Window -> WindowSet -> WindowSet


-- | GridSelect displays items(e.g. the opened windows) in a 2D grid and
--   lets the user select from it with the cursor/hjkl keys or the mouse.
module XMonad.Actions.GridSelect
data GSConfig a
GSConfig :: Integer -> Integer -> Integer -> (a -> Bool -> X (String, String)) -> String -> TwoD a (Maybe a) -> Double -> Double -> GSConfig a
gs_cellheight :: GSConfig a -> Integer
gs_cellwidth :: GSConfig a -> Integer
gs_cellpadding :: GSConfig a -> Integer
gs_colorizer :: GSConfig a -> a -> Bool -> X (String, String)
gs_font :: GSConfig a -> String
gs_navigate :: GSConfig a -> TwoD a (Maybe a)
gs_originFractX :: GSConfig a -> Double
gs_originFractY :: GSConfig a -> Double

-- | A basic configuration for <a>gridselect</a>, with the colorizer chosen
--   based on the type.
--   
--   If you want to replace the <a>gs_colorizer</a> field, use
--   <a>buildDefaultGSConfig</a> instead, to avoid ambiguous type
--   variables.
defaultGSConfig :: HasColorizer a => GSConfig a
type TwoDPosition = (Integer, Integer)

-- | Builds a default gs config from a colorizer function.
buildDefaultGSConfig :: (a -> Bool -> X (String, String)) -> GSConfig a

-- | Brings up a 2D grid of elements in the center of the screen, and one
--   can select an element with cursors keys. The selected element is
--   returned.
gridselect :: GSConfig a -> [(String, a)] -> X (Maybe a)

-- | Like <tt>gridSelect</tt> but with the current windows and their titles
--   as elements
gridselectWindow :: GSConfig Window -> X (Maybe Window)

-- | Brings up a 2D grid of windows in the center of the screen, and one
--   can select a window with cursors keys. The selected window is then
--   passed to a callback function.
withSelectedWindow :: (Window -> X ()) -> GSConfig Window -> X ()

-- | Brings selected window to the current workspace.
bringSelected :: GSConfig Window -> X ()

-- | Switches to selected window's workspace and focuses that window.
goToSelected :: GSConfig Window -> X ()

-- | Select a workspace and view it using the given function (normally
--   <a>view</a> or <a>greedyView</a>)
--   
--   Another option is to shift the current window to the selected
--   workspace:
--   
--   <pre>
--   gridselectWorkspace (\ws -&gt; W.greedyView ws . W.shift ws)
--   </pre>
gridselectWorkspace :: GSConfig WorkspaceId -> (WorkspaceId -> WindowSet -> WindowSet) -> X ()

-- | Select an application to spawn from a given list
spawnSelected :: GSConfig String -> [String] -> X ()

-- | Select an action and run it in the X monad
runSelectedAction :: GSConfig (X ()) -> [(String, X ())] -> X ()

-- | That is <a>fromClassName</a> if you are selecting a <a>Window</a>, or
--   <a>defaultColorizer</a> if you are selecting a <a>String</a>. The
--   catch-all instance <tt>HasColorizer a</tt> uses the
--   <a>focusedBorderColor</a> and <a>normalBorderColor</a> colors.
class HasColorizer a
defaultColorizer :: HasColorizer a => a -> Bool -> X (String, String)

-- | Colorize a window depending on it's className.
fromClassName :: Window -> Bool -> X (String, String)

-- | Default colorizer for Strings
stringColorizer :: String -> Bool -> X (String, String)

-- | A colorizer that picks a color inside a range, and depending on the
--   window's class.
colorRangeFromClassName :: (Word8, Word8, Word8) -> (Word8, Word8, Word8) -> (Word8, Word8, Word8) -> (Word8, Word8, Word8) -> (Word8, Word8, Word8) -> Window -> Bool -> X (String, String)
data TwoD a b

-- | Embeds a key handler into the X event handler that dispatches key
--   events to the key handler, while non-key event go to the standard
--   handler.
makeXEventhandler :: ((KeySym, String, KeyMask) -> TwoD a (Maybe a)) -> TwoD a (Maybe a)

-- | When the map contains (KeySym,KeyMask) tuple for the given event, the
--   associated action in the map associated shadows the default key
--   handler
shadowWithKeymap :: Map (KeyMask, KeySym) a -> ((KeySym, String, KeyMask) -> a) -> (KeySym, String, KeyMask) -> a

-- | By default gridselect used the defaultNavigation action, which binds
--   left,right,up,down and vi-style h,l,j,k navigation. Return quits
--   gridselect, returning the selected element, while Escape cancels the
--   selection. Slash enters the substring search mode. In substring search
--   mode, every string-associated keystroke is added to a search string,
--   which narrows down the object selection. Substring search mode comes
--   back to regular navigation via Return, while Escape cancels the
--   search. If you want that navigation style, add
--   <a>defaultNavigation</a> as <a>gs_navigate</a> to your <a>GSConfig</a>
--   object. This is done by <a>buildDefaultGSConfig</a> automatically.
defaultNavigation :: TwoD a (Maybe a)

-- | Navigation submode used for substring search. It returns to the first
--   argument navigation style when the user hits Return.
substringSearch :: TwoD a (Maybe a) -> TwoD a (Maybe a)

-- | This navigation style combines navigation and search into one mode at
--   the cost of losing vi style navigation. With this style, there is no
--   substring search submode, but every typed character is added to the
--   substring search.
navNSearch :: TwoD a (Maybe a)

-- | Sets the absolute position of the cursor.
setPos :: (Integer, Integer) -> TwoD a ()

-- | Moves the cursor by the offsets specified
move :: (Integer, Integer) -> TwoD a ()
moveNext :: TwoD a ()
movePrev :: TwoD a ()

-- | Closes gridselect returning the element under the cursor
select :: TwoD a (Maybe a)

-- | Closes gridselect returning no element.
cancel :: TwoD a (Maybe a)

-- | Apply a transformation function the current search string
transformSearchString :: (String -> String) -> TwoD a ()
data TwoDState a
instance [overlap ok] Monad (TwoD a)
instance [overlap ok] Functor (TwoD a)
instance [overlap ok] MonadState (TwoDState a) (TwoD a)
instance [overlap ok] Applicative (TwoD a)
instance [overlap ok] HasColorizer a
instance [overlap ok] HasColorizer String
instance [overlap ok] HasColorizer Window


-- | Uses <a>XMonad.Actions.GridSelect</a> to display a number of actions
--   related to window management in the center of the focused window.
--   Actions include: Closing, maximizing, minimizing and shifting the
--   window to another workspace.
--   
--   Note: For maximizing and minimizing to actually work, you will need to
--   integrate <a>XMonad.Layout.Maximize</a> and
--   <a>XMonad.Layout.Minimize</a> into your setup. See the documentation
--   of those modules for more information.
module XMonad.Actions.WindowMenu
windowMenu :: X ()


-- | Various stuff that can be added to the decoration. Most of it is
--   intended to be used by other modules. See
--   <a>XMonad.Layout.ButtonDecoration</a> for a module that makes use of
--   this.
module XMonad.Layout.DecorationAddons

-- | A function intended to be plugged into the
--   <a>decorationCatchClicksHook</a> of a decoration. It will intercept
--   clicks on the buttons of the decoration and invoke the associated
--   action. To actually see the buttons, you will need to use a theme that
--   includes them. See <a>defaultThemeWithButtons</a> below.
titleBarButtonHandler :: Window -> Int -> Int -> X Bool

-- | Intended to be used together with <a>titleBarButtonHandler</a>. See
--   above.
defaultThemeWithButtons :: Theme

-- | A function intended to be plugged into the
--   <a>decorationAfterDraggingHook</a> of a decoration. It will check if
--   the window has been dragged onto another screen and shift it there.
--   The PositionStore is also updated accordingly, as this is designed to
--   be used together with <a>XMonad.Layout.PositionStoreFloat</a>.
handleScreenCrossing :: Window -> Window -> X Bool


-- | A decoration that includes small buttons on both ends which invoke
--   various actions when clicked on: Show a window menu (see
--   <a>XMonad.Actions.WindowMenu</a>), minimize, maximize or close the
--   window.
--   
--   Note: For maximizing and minimizing to actually work, you will need to
--   integrate <a>XMonad.Layout.Maximize</a> and
--   <a>XMonad.Layout.Minimize</a> into your setup. See the documentation
--   of those modules for more information.
module XMonad.Layout.ButtonDecoration
buttonDeco :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration ButtonDecoration s) l a
data ButtonDecoration a
instance Show (ButtonDecoration a)
instance Read (ButtonDecoration a)
instance Eq a => DecorationStyle ButtonDecoration a


-- | A decoration that includes small image buttons on both ends which
--   invoke various actions when clicked on: Show a window menu (see
--   <a>XMonad.Actions.WindowMenu</a>), minimize, maximize or close the
--   window.
--   
--   Note: For maximizing and minimizing to actually work, you will need to
--   integrate <a>XMonad.Layout.Maximize</a> and
--   <a>XMonad.Layout.Minimize</a> into your setup. See the documentation
--   of those modules for more information.
module XMonad.Layout.ImageButtonDecoration
imageButtonDeco :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration ImageButtonDecoration s) l a
defaultThemeWithImageButtons :: Theme

-- | A function intended to be plugged into the
--   <a>decorationCatchClicksHook</a> of a decoration. It will intercept
--   clicks on the buttons of the decoration and invoke the associated
--   action. To actually see the buttons, you will need to use a theme that
--   includes them. See <a>defaultThemeWithImageButtons</a> below.
imageTitleBarButtonHandler :: Window -> Int -> Int -> X Bool
data ImageButtonDecoration a
instance Show (ImageButtonDecoration a)
instance Read (ImageButtonDecoration a)
instance Eq a => DecorationStyle ImageButtonDecoration a


-- | A decoration that allows to switch the position of windows by dragging
--   them onto each other.
module XMonad.Layout.WindowSwitcherDecoration
windowSwitcherDecoration :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration WindowSwitcherDecoration s) l a
windowSwitcherDecorationWithButtons :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration WindowSwitcherDecoration s) l a
windowSwitcherDecorationWithImageButtons :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration ImageWindowSwitcherDecoration s) l a
data WindowSwitcherDecoration a
data ImageWindowSwitcherDecoration a
instance Show (WindowSwitcherDecoration a)
instance Read (WindowSwitcherDecoration a)
instance Show (ImageWindowSwitcherDecoration a)
instance Read (ImageWindowSwitcherDecoration a)
instance Eq a => DecorationStyle ImageWindowSwitcherDecoration a
instance Eq a => DecorationStyle WindowSwitcherDecoration a


-- | xprompt operations to bring windows to you, and bring you to windows.
module XMonad.Prompt.Window
windowPromptGoto, windowPromptBringCopy, windowPromptBring :: XPConfig -> X ()
data WindowPrompt
instance XPrompt WindowPrompt


-- | Allows you to run internal xmonad commands (X () actions) using a
--   dmenu menu in addition to key bindings. Requires dmenu and the Dmenu
--   XMonad.Actions module.
module XMonad.Actions.Commands

-- | Create a <a>Map</a> from <tt>String</tt>s to xmonad actions from a
--   list of pairs.
commandMap :: [(String, X ())] -> Map String (X ())

-- | Given a list of command/action pairs, prompt the user to choose a
--   command and return the corresponding action.
runCommand :: [(String, X ())] -> X ()

-- | Given the name of a command from <a>defaultCommands</a>, return the
--   corresponding action (or the null action if the command is not found).
runCommand' :: String -> X ()

-- | Generate a list of commands to switch to/send windows to workspaces.
workspaceCommands :: X [(String, X ())]

-- | Generate a list of commands dealing with multiple screens.
screenCommands :: [(String, X ())]

-- | A nice pre-defined list of commands.
defaultCommands :: X [(String, X ())]


-- | This is an <tt>EventHook</tt> that will receive commands from an
--   external client.
--   
--   This is the example of a client:
--   
--   <pre>
--   import Graphics.X11.Xlib
--   import Graphics.X11.Xlib.Extras
--   import System.Environment
--   import Data.Char
--   
--   usage :: String -&gt; String
--   usage n = "Usage: " ++ n ++ " command number\nSend a command number to a running instance of XMonad"
--   
--   main :: IO ()
--   main = do
--     args &lt;- getArgs
--     pn &lt;- getProgName
--     let com = case args of
--                 [] -&gt; error $ usage pn
--                 w -&gt; (w !! 0)
--     sendCommand com
--   
--   sendCommand :: String -&gt; IO ()
--   sendCommand s = do
--     d   &lt;- openDisplay ""
--     rw  &lt;- rootWindow d $ defaultScreen d
--     a &lt;- internAtom d "XMONAD_COMMAND" False
--     allocaXEvent $ \e -&gt; do
--                     setEventType e clientMessage
--                     setClientMessageEvent e rw a 32 (fromIntegral (read s)) currentTime
--                     sendEvent d rw False structureNotifyMask e
--                     sync d False
--   </pre>
--   
--   compile with: <tt>ghc --make sendCommand.hs</tt>
--   
--   run with
--   
--   <pre>
--   sendCommand command number
--   </pre>
--   
--   For instance:
--   
--   <pre>
--   sendCommand 0
--   </pre>
--   
--   will ask to xmonad to print the list of command numbers in stderr (so
--   you can read it in <tt>~/.xsession-errors</tt>).
module XMonad.Hooks.ServerMode
data ServerMode
ServerMode :: ServerMode

-- | Executes a command of the list when receiving its index via a special
--   ClientMessageEvent (indexing starts at 1)
serverModeEventHook :: Event -> X All

-- | serverModeEventHook' additionally takes an action to generate the list
--   of commands.
serverModeEventHook' :: X [(String, X ())] -> Event -> X All
instance Show ServerMode
instance Read ServerMode


-- | A prompt for running XMonad commands
module XMonad.Prompt.XMonad
xmonadPrompt :: XPConfig -> X ()

-- | An xmonad prompt with a custom command list
xmonadPromptC :: [(String, X ())] -> XPConfig -> X ()
data XMonad
instance XPrompt XMonad


-- | The <a>XMonad.Layout.LayoutCombinators</a> module provides combinators
--   for easily combining multiple layouts into one composite layout, as
--   well as a way to jump directly to any particular layout (say, with a
--   keybinding) without having to cycle through other layouts to get to
--   it.
module XMonad.Layout.LayoutCombinators
(*||*, *||**, *||***, **||***, *||****, ***||****, ****||***, ***||**, ****||*, ***||*, **||*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a
(*//*, *//**, *//***, **//***, *//****, ***//****, ****//***, ***//**, ****//*, ***//*, **//*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a
(*|*, *|**, *|***, **|***, *|****, ***|****, ****|***, ***|**, ****|*, ***|*, **|*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a
(*/*, */**, */***, **/***, */****, ***/****, ****/***, ***/**, ****/*, ***/*, **/*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a

-- | A reimplementation of the combinator of the same name from the xmonad
--   core, providing layout choice, and the ability to support
--   <a>JumpToLayout</a> messages.
(|||) :: (LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> NewSelect l1 l2 a
data JumpToLayout

-- | A message to jump to a particular layout , specified by its
--   description string..
JumpToLayout :: String -> JumpToLayout
NextLayoutNoWrap :: JumpToLayout
Wrap :: JumpToLayout
data NewSelect l1 l2 a
instance Typeable JumpToLayout
instance (Read (l1 a), Read (l2 a)) => Read (NewSelect l1 l2 a)
instance (Show (l1 a), Show (l2 a)) => Show (NewSelect l1 l2 a)
instance Read JumpToLayout
instance Show JumpToLayout
instance (LayoutClass l1 a, LayoutClass l2 a) => LayoutClass (NewSelect l1 l2) a
instance Message JumpToLayout


-- | This module allows to cycle through the given subset of layouts.
module XMonad.Actions.CycleSelectedLayouts

-- | If the current layout is in the list, cycle to the next layout.
--   Otherwise, apply the first layout from list.
cycleThroughLayouts :: [String] -> X ()


-- | This module specifies my xmonad defaults.
module XMonad.Config.Arossato
arossatoConfig :: MonadIO m => m (XConfig (ModifiedLayout AvoidStruts (NewSelect (ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat))) (NewSelect (ModifiedLayout WithBorder (ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest)) (ModifiedLayout WindowArranger (NewSelect (ModifiedLayout Magnifier Tall) (NewSelect (ModifiedLayout WithBorder Full) (NewSelect (Mirror Tall) Accordion))))))))


-- | A layout-selection prompt for XMonad
module XMonad.Prompt.Layout
layoutPrompt :: XPConfig -> X ()


module XMonad.Config.Droundy
config :: XConfig (ModifiedLayout ShowWName (ModifiedLayout WorkspaceDir (ModifiedLayout BoringWindows (ModifiedLayout SmartBorder (ModifiedLayout WindowNavigation (ModifiedLayout Magnifier (ToggleLayouts Full (ModifiedLayout AvoidStruts (NewSelect (ModifiedLayout Rename (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest)) (NewSelect (ModifiedLayout Rename (CombineTwo (DragPane ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (CombineTwo (Square ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest)))) (NewSelect (ModifiedLayout Rename (CombineTwo (DragPane ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (CombineTwo (DragPane ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (CombineTwo (Square ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest))))) (ModifiedLayout Rename (CombineTwo (DragPane ()) (CombineTwo (DragPane ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest)) (CombineTwo (Square ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest)))))))))))))))
mytab :: ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest Window
instance Shrinker CustomShrink


-- | Example layouts for <a>XMonad.Layout.Groups</a>.
module XMonad.Layout.Groups.Examples
rowOfColumns :: Groups (ModifiedLayout Rename (Mirror (ZoomRow ClassEQ))) (ZoomRow GroupEQ) Window

-- | Increase the width of the focused column
zoomColumnIn :: X ()

-- | Decrease the width of the focused column
zoomColumnOut :: X ()

-- | Reset the width of the focused column
zoomColumnReset :: X ()

-- | Toggle whether the currently focused column should take up all
--   available space whenever it has focus
toggleColumnFull :: X ()

-- | Increase the heigth of the focused window
zoomWindowIn :: X ()

-- | Decrease the height of the focused window
zoomWindowOut :: X ()

-- | Reset the height of the focused window
zoomWindowReset :: X ()

-- | Toggle whether the currently focused window should take up the whole
--   column whenever it has focus
toggleWindowFull :: X ()
tallTabs :: Shrinker s => TiledTabsConfig s -> ModifiedLayout Rename (ModifiedLayout (Decoration TabbedDecoration s) (Groups (ModifiedLayout Rename Simplest) (NewSelect (ModifiedLayout Rename Tall) (NewSelect (ModifiedLayout Rename (Mirror Tall)) Full)))) Window
mirrorTallTabs :: Shrinker s => TiledTabsConfig s -> ModifiedLayout Rename (ModifiedLayout (Decoration TabbedDecoration s) (Groups (ModifiedLayout Rename Simplest) (NewSelect (ModifiedLayout Rename (Mirror Tall)) (NewSelect Full (ModifiedLayout Rename Tall))))) Window
fullTabs :: Shrinker s => TiledTabsConfig s -> ModifiedLayout Rename (ModifiedLayout (Decoration TabbedDecoration s) (Groups (ModifiedLayout Rename Simplest) (NewSelect Full (NewSelect (ModifiedLayout Rename Tall) (ModifiedLayout Rename (Mirror Tall)))))) Window

-- | Configuration data for the <a>tiled tab groups</a> layout
data TiledTabsConfig s
TTC :: Int -> Rational -> Rational -> Int -> Rational -> Rational -> s -> Theme -> TiledTabsConfig s
vNMaster :: TiledTabsConfig s -> Int
vRatio :: TiledTabsConfig s -> Rational
vIncrement :: TiledTabsConfig s -> Rational
hNMaster :: TiledTabsConfig s -> Int
hRatio :: TiledTabsConfig s -> Rational
hIncrement :: TiledTabsConfig s -> Rational
tabsShrinker :: TiledTabsConfig s -> s
tabsTheme :: TiledTabsConfig s -> Theme
defaultTiledTabsConfig :: TiledTabsConfig DefaultShrinker

-- | Increase the number of master groups by one
increaseNMasterGroups :: X ()

-- | Decrease the number of master groups by one
decreaseNMasterGroups :: X ()

-- | Shrink the master area
shrinkMasterGroups :: X ()

-- | Expand the master area
expandMasterGroups :: X ()

-- | Rotate the available outer layout algorithms
nextOuterLayout :: X ()
shrinkText :: DefaultShrinker

-- | The default xmonad <a>Theme</a>.
defaultTheme :: Theme

-- | Compare two <tt>Group</tt>s by comparing the ids of their layouts.
data GroupEQ a
GroupEQ :: GroupEQ a
zoomRowG :: (Eq a, Show a, Read a, Show (l a), Read (l a)) => ZoomRow GroupEQ (Group l a)
instance Show (GroupEQ a)
instance Read (GroupEQ a)
instance Eq a => EQF GroupEQ (Group l a)


-- | A wmii-like layout algorithm.
module XMonad.Layout.Groups.Wmii

-- | A layout inspired by wmii
wmii :: Shrinker s => s -> Theme -> Groups (ModifiedLayout Rename (ModifiedLayout (Decoration TabbedDecoration s) (Ignore ChangeLayout (Ignore JumpToLayout (ModifiedLayout UnEscape (NewSelect (ModifiedLayout Rename Tall) (NewSelect (ModifiedLayout Rename Simplest) Full))))))) (ZoomRow GroupEQ) Window

-- | Increase the width of the focused group
zoomGroupIn :: X ()

-- | Decrease the size of the focused group
zoomGroupOut :: X ()

-- | Reset the size of the focused group to the default
zoomGroupReset :: X ()

-- | Toggle whether the currently focused group should be maximized
--   whenever it has focus.
toggleGroupFull :: X ()

-- | Rotate the layouts in the focused group.
groupToNextLayout :: X ()

-- | Switch the focused group to the "maximized" layout.
groupToFullLayout :: X ()

-- | Switch the focused group to the "tabbed" layout.
groupToTabbedLayout :: X ()

-- | Switch the focused group to the "column" layout.
groupToVerticalLayout :: X ()
shrinkText :: DefaultShrinker

-- | The default xmonad <a>Theme</a>.
defaultTheme :: Theme


-- | This is a list of selected commands that can be made available using
--   <a>XMonad.Hooks.ServerMode</a> to allow external programs to control
--   the window manager. Bluetile
--   (<a>http://projects.haskell.org/bluetile/</a>) uses this to enable its
--   dock application to do things like changing workspaces and layouts.
module XMonad.Actions.BluetileCommands
bluetileCommands :: X [(String, X ())]


-- | This is the default configuration of Bluetile
--   (<a>http://projects.haskell.org/bluetile/</a>). If you are migrating
--   from Bluetile to xmonad or want to create a similar setup, then this
--   will give you pretty much the same thing, except for Bluetile's helper
--   applications such as the dock.
module XMonad.Config.Bluetile
bluetileConfig :: XConfig (ModifiedLayout AvoidStruts (ModifiedLayout Minimize (ModifiedLayout BoringWindows (NewSelect (ModifiedLayout Rename (ModifiedLayout (Decoration ButtonDecoration DefaultShrinker) (ModifiedLayout Maximize (ModifiedLayout BorderResize PositionStoreFloat)))) (NewSelect (ModifiedLayout Rename (ModifiedLayout (Decoration WindowSwitcherDecoration DefaultShrinker) (ModifiedLayout DraggingVisualizer (ModifiedLayout Maximize MouseResizableTile)))) (NewSelect (ModifiedLayout Rename (ModifiedLayout (Decoration WindowSwitcherDecoration DefaultShrinker) (ModifiedLayout DraggingVisualizer (ModifiedLayout Maximize MouseResizableTile)))) (ModifiedLayout Rename (ModifiedLayout (Decoration WindowSwitcherDecoration DefaultShrinker) (ModifiedLayout DraggingVisualizer (ModifiedLayout Maximize (ModifiedLayout SmartBorder Full)))))))))))


-- | This module gives a brief overview of the xmonad internals. It is
--   intended for advanced users who are curious about the xmonad source
--   code and want an brief overview. This document may also be helpful for
--   the beginner/intermediate Haskell programmer who is motivated to write
--   an xmonad extension as a way to deepen her understanding of this
--   powerful functional language; however, there is not space here to go
--   into much detail. For a more comprehensive document covering some of
--   the same material in more depth, see the guided tour of the xmonad
--   source on the xmonad wiki:
--   <a>http://haskell.org/haskellwiki/Xmonad/Guided_tour_of_the_xmonad_source</a>.
--   
--   If you write an extension module and think it may be useful for
--   others, consider releasing it. Coding guidelines and licensing
--   policies are covered at the end of this document, and must be followed
--   if you want your code to be included in the official repositories. For
--   a basic tutorial on the nuts and bolts of developing a new extension
--   for xmonad, see the tutorial on the wiki:
--   <a>http://haskell.org/haskellwiki/Xmonad/xmonad_development_tutorial</a>.
module XMonad.Doc.Developing


-- | This module documents the xmonad-contrib library and how to use it to
--   extend the capabilities of xmonad.
--   
--   Reading this document should not require a deep knowledge of Haskell;
--   the examples are intended to be useful and understandable for those
--   users who do not know Haskell and don't want to have to learn it just
--   to configure xmonad. You should be able to get by just fine by
--   ignoring anything you don't understand and using the provided examples
--   as templates. However, relevant Haskell features are discussed when
--   appropriate, so this document will hopefully be useful for more
--   advanced Haskell users as well.
--   
--   Those wishing to be totally hardcore and develop their own xmonad
--   extensions (it's easier than it sounds, we promise!) should read the
--   documentation in <a>XMonad.Doc.Developing</a>.
--   
--   More configuration examples may be found on the Haskell wiki:
--   
--   <a>http://haskell.org/haskellwiki/Xmonad/Config_archive</a>
module XMonad.Doc.Extending


-- | This is a brief tutorial that will teach you how to create a basic
--   xmonad configuration.
--   
--   For more detailed instructions on extending xmonad with the
--   xmonad-contrib library, see <a>XMonad.Doc.Extending</a>.
module XMonad.Doc.Configuring


-- | This is the main documentation module for the xmonad-contrib library.
--   It provides a brief overview of xmonad and a link to documentation for
--   configuring and extending xmonad.
--   
--   A link to documentation describing xmonad internals is also provided.
--   This module is mainly intended for those wanting to contribute code,
--   or for those who are curious to know what's going on behind the
--   scenes.
module XMonad.Doc