Copyright | (c) 2009 Anders Engstrom <ankaan@gmail.com> 2011 Ilya Portnov <portnov84@rambler.ru> |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | Ilya Portnov <portnov84@rambler.ru> |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Deprecated: Use XMonad.Layout.LayoutBuilder instead
DEPRECATED. Use LayoutBuilder
instead.
Synopsis
- data LayoutP p l1 l2 a = LayoutP (Maybe a) (Maybe a) p SubBox (Maybe SubBox) (l1 a) (Maybe (l2 a))
- 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
- layoutAll :: forall l1 p a. (Read a, Eq a, LayoutClass l1 a, Predicate p a) => SubBox -> l1 a -> LayoutP p l1 Full a
- relBox :: Rational -> Rational -> Rational -> Rational -> SubBox
- absBox :: Int -> Int -> Int -> Int -> SubBox
- class Predicate p w where
- alwaysTrue :: Proxy w -> p
- checkPredicate :: p -> w -> X Bool
- data Proxy a = Proxy
Documentation
data LayoutP p l1 l2 a Source #
Data type for our layout.
Instances
(LayoutClass l1 w, LayoutClass l2 w, Predicate p w, Show w, Read w, Eq w, Typeable w, Show p, Typeable p) => LayoutClass (LayoutP p l1 l2) w Source # | |
Defined in XMonad.Layout.LayoutBuilderP runLayout :: Workspace WorkspaceId (LayoutP p l1 l2 w) w -> Rectangle -> X ([(w, Rectangle)], Maybe (LayoutP p l1 l2 w)) # doLayout :: LayoutP p l1 l2 w -> Rectangle -> Stack w -> X ([(w, Rectangle)], Maybe (LayoutP p l1 l2 w)) # pureLayout :: LayoutP p l1 l2 w -> Rectangle -> Stack w -> [(w, Rectangle)] # emptyLayout :: LayoutP p l1 l2 w -> Rectangle -> X ([(w, Rectangle)], Maybe (LayoutP p l1 l2 w)) # handleMessage :: LayoutP p l1 l2 w -> SomeMessage -> X (Maybe (LayoutP p l1 l2 w)) # pureMessage :: LayoutP p l1 l2 w -> SomeMessage -> Maybe (LayoutP p l1 l2 w) # description :: LayoutP p l1 l2 w -> String # | |
(Read a, Read p, Read (l1 a), Read (l2 a)) => Read (LayoutP p l1 l2 a) Source # | |
(Show a, Show p, Show (l1 a), Show (l2 a)) => Show (LayoutP p l1 l2 a) Source # | |
:: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a, LayoutClass l3 a, Predicate p a) | |
=> p | |
-> SubBox | The box to place the windows in |
-> Maybe SubBox | Possibly an alternative box that is used when this layout handles all windows that are left |
-> l1 a | The layout to use in the specified area |
-> LayoutP p l2 l3 a | Where to send the remaining windows |
-> LayoutP p l1 (LayoutP p l2 l3) a | The resulting layout |
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.
:: forall l1 p a. (Read a, Eq a, LayoutClass l1 a, Predicate p a) | |
=> SubBox | The box to place the windows in |
-> l1 a | The layout to use in the specified area |
-> LayoutP p l1 Full a | The resulting layout |
Use the specified layout in the described area for all remaining windows.
:: Rational | Relative X-Position with respect to the surrounding area |
-> Rational | Relative Y-Position with respect to the surrounding area |
-> Rational | Relative width with respect to the remaining width |
-> Rational | Relative height with respect to the remaining height |
-> SubBox | The resulting |
Create a box with only relative measurements.
:: Int | Absolute X-Position |
-> Int | Absolute Y-Position |
-> Int | Absolute width |
-> Int | Absolute height |
-> SubBox | The resulting |
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.
Overloading ways to select windows
Predicate
exists because layouts are required to be serializable, and
XMonad.Util.WindowProperties is not sufficient (for example it does not
allow using regular expressions).
compare XMonad.Util.Invisible