Copyright | Quentin Moser <moserq@gmail.com> |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | orphaned |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Two-level layout with windows split in individual layout groups, themselves managed by a user-provided layout.
Synopsis
- group :: l Window -> l2 (Group l Window) -> Groups l l2 Window
- data GroupsMessage
- type ModifySpec = forall l. WithID l Window -> Zipper (Group l Window) -> Zipper (Group l Window)
- type ModifySpecX = forall l. WithID l Window -> Zipper (Group l Window) -> X (Zipper (Group l Window))
- swapUp :: ModifySpec
- swapDown :: ModifySpec
- swapMaster :: ModifySpec
- focusUp :: ModifySpec
- focusDown :: ModifySpec
- focusMaster :: ModifySpec
- swapGroupUp :: ModifySpec
- swapGroupDown :: ModifySpec
- swapGroupMaster :: ModifySpec
- focusGroupUp :: ModifySpec
- focusGroupDown :: ModifySpec
- focusGroupMaster :: ModifySpec
- moveToGroupUp :: Bool -> ModifySpec
- moveToGroupDown :: Bool -> ModifySpec
- moveToNewGroupUp :: ModifySpec
- moveToNewGroupDown :: ModifySpec
- splitGroup :: ModifySpec
- data Groups l l2 a
- data Group l a = G {}
- onZipper :: (Zipper a -> Zipper a) -> Group l a -> Group l a
- onLayout :: (WithID l a -> WithID l a) -> Group l a -> Group l a
- data WithID l a
- sameID :: WithID l a -> WithID l a -> Bool
Usage
This module provides a layout combinator that allows you to manage your windows in independent groups. You can provide both the layout with which to arrange the windows inside each group, and the layout with which the groups themselves will be arranged on the screen.
The XMonad.Layout.Groups.Examples and XMonad.Layout.Groups.Wmii modules contain examples of layouts that can be defined with this combinator. They're also the recommended starting point if you are a beginner and looking for something you can use easily.
One thing to note is that Groups
-based layout have their own
notion of the order of windows, which is completely separate
from XMonad's. For this reason, operations like SwapUp
will have no visible effect, and those like focusUp
will focus the windows in an unpredictable order. For a better way of
rearranging windows and moving focus in such a layout, see the
example ModifySpec
s (to be passed to the Modify
message) provided
by this module.
If you use both Groups
-based and other layouts, The XMonad.Layout.Groups.Helpers
module provides actions that can work correctly with both, defined using
functions from XMonad.Actions.MessageFeedback.
Messages
data GroupsMessage Source #
Messages accepted by Groups
-based layouts.
All other messages are forwarded to the layout of the currently
focused subgroup (as if they had been wrapped in ToFocused
).
ToEnclosing SomeMessage | Send a message to the enclosing layout (the one that places the groups themselves) |
ToGroup Int SomeMessage | Send a message to the layout for nth group (starting at 0) |
ToFocused SomeMessage | Send a message to the layout for the focused group |
ToAll SomeMessage | Send a message to all the sub-layouts |
Refocus | Refocus the window which should be focused according to the layout. |
Modify ModifySpec | Modify the ordering/grouping/focusing
of windows according to a |
ModifyX ModifySpecX |
Instances
Show GroupsMessage Source # | |
Defined in XMonad.Layout.Groups showsPrec :: Int -> GroupsMessage -> ShowS # show :: GroupsMessage -> String # showList :: [GroupsMessage] -> ShowS # | |
Message GroupsMessage Source # | |
Defined in XMonad.Layout.Groups |
type ModifySpec = forall l. WithID l Window -> Zipper (Group l Window) -> Zipper (Group l Window) Source #
Type of functions describing modifications to a Groups
layout. They
are transformations on Zipper
s of groups.
Things you shouldn't do:
- Forge new windows (they will be ignored)
- Duplicate windows (whatever happens is your problem)
- Remove windows (they will be added again)
- Duplicate layouts (only one will be kept, the rest will get the base layout)
Note that ModifySpec
is a rank-2 type (indicating that ModifySpec
s must
be polymorphic in the layout type), so if you define functions taking
ModifySpec
s as arguments, or returning them, you'll need to write a type
signature and add {-# LANGUAGE Rank2Types #-}
at the beginning
type ModifySpecX = forall l. WithID l Window -> Zipper (Group l Window) -> X (Zipper (Group l Window)) Source #
This is the same as ModifySpec
, but it allows the function to use
actions inside the X
monad. This is useful, for example, if the function
has to make decisions based on the results of a runQuery
.
Useful ModifySpec
s
swapUp :: ModifySpec Source #
Swap the focused window with the previous one.
swapDown :: ModifySpec Source #
Swap the focused window with the next one.
swapMaster :: ModifySpec Source #
Swap the focused window with the (group's) master window.
focusUp :: ModifySpec Source #
Move focus to the previous window in the group.
focusDown :: ModifySpec Source #
Move focus to the next window in the group.
focusMaster :: ModifySpec Source #
Move focus to the group's master window.
swapGroupUp :: ModifySpec Source #
Swap the focused group with the previous one.
swapGroupDown :: ModifySpec Source #
Swap the focused group with the next one.
swapGroupMaster :: ModifySpec Source #
Swap the focused group with the master group.
focusGroupUp :: ModifySpec Source #
Move focus to the previous group.
focusGroupDown :: ModifySpec Source #
Move focus to the next group.
focusGroupMaster :: ModifySpec Source #
Move focus to the master group.
moveToGroupUp :: Bool -> ModifySpec Source #
moveToGroupDown :: Bool -> ModifySpec Source #
moveToNewGroupUp :: ModifySpec Source #
Move the focused window to a new group before the current one.
moveToNewGroupDown :: ModifySpec Source #
Move the focused window to a new group after the current one.
splitGroup :: ModifySpec Source #
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).
Types
The type of our layouts.
Instances
(LayoutClass l Window, LayoutClass l2 (Group l Window)) => LayoutClass (Groups l l2) Window Source # | |
Defined in XMonad.Layout.Groups runLayout :: Workspace WorkspaceId (Groups l l2 Window) Window -> Rectangle -> X ([(Window, Rectangle)], Maybe (Groups l l2 Window)) # doLayout :: Groups l l2 Window -> Rectangle -> Stack Window -> X ([(Window, Rectangle)], Maybe (Groups l l2 Window)) # pureLayout :: Groups l l2 Window -> Rectangle -> Stack Window -> [(Window, Rectangle)] # emptyLayout :: Groups l l2 Window -> Rectangle -> X ([(Window, Rectangle)], Maybe (Groups l l2 Window)) # handleMessage :: Groups l l2 Window -> SomeMessage -> X (Maybe (Groups l l2 Window)) # pureMessage :: Groups l l2 Window -> SomeMessage -> Maybe (Groups l l2 Window) # description :: Groups l l2 Window -> String # | |
(Read a, Read (l a), Read (l2 (Group l a))) => Read (Groups l l2 a) Source # | |
(Show a, Show (l a), Show (l2 (Group l a))) => Show (Groups l l2 a) Source # | |
A group of windows and its layout algorithm.
Split an infinite list into two. I ended up not needing this, but let's keep it just in case. split :: [a] -> ([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.
Instances
LayoutClass l a => LayoutClass (WithID l) a Source # | |
Defined in XMonad.Layout.Groups runLayout :: Workspace WorkspaceId (WithID l a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (WithID l a)) # doLayout :: WithID l a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (WithID l a)) # pureLayout :: WithID l a -> Rectangle -> Stack a -> [(a, Rectangle)] # emptyLayout :: WithID l a -> Rectangle -> X ([(a, Rectangle)], Maybe (WithID l a)) # handleMessage :: WithID l a -> SomeMessage -> X (Maybe (WithID l a)) # pureMessage :: WithID l a -> SomeMessage -> Maybe (WithID l a) # description :: WithID l a -> String # | |
Read (l a) => Read (WithID l a) Source # | |
Show (l a) => Show (WithID l a) Source # | |
Eq (WithID l a) Source # | |