Copyright | (c) 2009 Max Rabkin |
---|---|
License | BSD-style (see xmonad/LICENSE) |
Maintainer | max.rabkin@gmail.com |
Stability | unstable |
Portability | unportable |
Safe Haskell | None |
Language | Haskell2010 |
XMonad.Layout.Drawer
Contents
Description
A layout modifier that puts some windows in a "drawer" which retracts and expands depending on whether any window in it has focus.
Useful for music players, tool palettes, etc.
Synopsis
- simpleDrawer :: Rational -> Rational -> Property -> Drawer Tall a
- drawer :: Rational -> Rational -> Property -> l a -> Drawer l a
- onLeft :: forall (l :: Type -> Type) a l'. Drawer l a -> l' a -> ModifiedLayout (Drawer l) l' a
- onTop :: forall (l :: Type -> Type) a l'. Drawer l a -> l' a -> Mirror (ModifiedLayout (Drawer l) (Mirror l')) a
- onRight :: forall (l :: Type -> Type) a l'. Drawer l a -> l' a -> Reflected (ModifiedLayout (Drawer l) (Reflected l')) a
- onBottom :: forall (l :: Type -> Type) a l'. Drawer l a -> l' a -> Reflected (Mirror (ModifiedLayout (Drawer l) (Mirror (Reflected l')))) a
- module XMonad.Util.WindowProperties
- data Drawer (l :: Type -> Type) a
- type Reflected (l :: Type -> Type) = ModifiedLayout Reflect l
Usage
To use this module, add the following import to xmonad.hs
:
import XMonad.Layout.Drawer
myLayout = drawer `onTop` (Tall 1 0.03 0.5) ||| Full ||| RandomOtherLayout... where drawer = simpleDrawer 0.01 0.3 (ClassName "Rhythmbox" `Or` ClassName "Xchat") main = xmonad def { layoutHook = myLayout }
This will place the Rhythmbox and Xchat windows in at the top of the screen
only when using the Tall
layout. See XMonad.Util.WindowProperties for
more information on selecting windows.
Drawers
Arguments
:: Rational | The portion of the screen taken up by the drawer when closed |
-> Rational | The portion of the screen taken up by the drawer when open |
-> Property | Which windows to put in the drawer |
-> Drawer Tall a |
Construct a drawer with a simple layout of the windows inside
Arguments
:: Rational | The portion of the screen taken up by the drawer when closed |
-> Rational | The portion of the screen taken up by the drawer when open |
-> Property | Which windows to put in the drawer |
-> l a | The layout of windows in the drawer |
-> Drawer l a |
Construct a drawer with an arbitrary layout for windows inside
Placing drawers
onLeft :: forall (l :: Type -> Type) a l'. Drawer l a -> l' a -> ModifiedLayout (Drawer l) l' a Source #
onTop :: forall (l :: Type -> Type) a l'. Drawer l a -> l' a -> Mirror (ModifiedLayout (Drawer l) (Mirror l')) a Source #
onRight :: forall (l :: Type -> Type) a l'. Drawer l a -> l' a -> Reflected (ModifiedLayout (Drawer l) (Reflected l')) a Source #
onBottom :: forall (l :: Type -> Type) a l'. Drawer l a -> l' a -> Reflected (Mirror (ModifiedLayout (Drawer l) (Mirror (Reflected l')))) a Source #
module XMonad.Util.WindowProperties
data Drawer (l :: Type -> Type) a Source #