xmonad-contrib-0.17.1: Community-maintained extensions for xmonad
Copyright(c) 2008 Brent Yorgey
LicenseBSD3
Maintainer<byorgey@gmail.com>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Layout.Gaps

Contents

Description

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 1: For gaps/space around windows see XMonad.Layout.Spacing.

Note 2: XMonad.Hooks.ManageDocks 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.

Synopsis

Usage

You can use this module by importing it into your ~/.xmonad/xmonad.hs file:

import XMonad.Layout.Gaps

and applying the gaps modifier to your layouts as follows (for example):

layoutHook = gaps [(U,18), (R,23)] $ Tall 1 (3/100) (1/2) ||| Full  -- leave gaps at the top and right

You can additionally add some keybindings to toggle or modify the gaps, for example:

, ((modm .|. controlMask, xK_g), sendMessage $ ToggleGaps)               -- toggle all gaps
, ((modm .|. controlMask, xK_t), sendMessage $ ToggleGap U)              -- toggle the top gap
, ((modm .|. controlMask, xK_w), sendMessage $ IncGap 5 R)               -- increment the right-hand gap
, ((modm .|. controlMask, xK_q), sendMessage $ DecGap 5 R)               -- decrement the right-hand gap
, ((modm .|. controlMask, xK_r), sendMessage $ ModifyGaps rotateGaps)    -- rotate gaps 90 degrees clockwise
, ((modm .|. controlMask, xK_h), sendMessage $ weakModifyGaps halveHor)  -- halve the left and right-hand gaps
, ((modm .|. controlMask, xK_d), sendMessage $ modifyGap (*2) L)         -- double the left-hand gap
, ((modm .|. controlMask, xK_s), sendMessage $ setGaps [(U,18), (R,23)]) -- reset the GapSpec
, ((modm .|. controlMask, xK_b), sendMessage $ setGap 30 D)              -- set the bottom gap to 30
]
  where rotateGaps gs = zip (map (rotate . fst) gs) (map snd gs)
        rotate U = R
        rotate R = D
        rotate D = L
        rotate L = U
        halveHor d i | d `elem` [L, R] = i `div` 2
                     | otherwise       = i

If you want complete control over all gaps, you could include something like this in your keybindings, assuming in this case you are using mkKeymap or additionalKeysP from XMonad.Util.EZConfig for string keybinding specifications:

++
[ ("M-g " ++ f ++ " " ++ k, sendMessage $ m d)
    | (k, d) <- [("a",L), ("s",D), ("w",U), ("d",R)]
    , (f, m) <- [("v", ToggleGap), ("h", IncGap 10), ("f", DecGap 10)]
]

Given the above keybinding definition, for example, you could type M-g, v, a to toggle the top gap.

To configure gaps differently per-screen, use XMonad.Layout.PerScreen (coming soon).

Warning: If you also use the avoidStruts layout modifier, it must come before any of these modifiers. See the documentation of avoidStruts for details.

data Direction2D Source #

Two-dimensional directions:

Constructors

U

Up

D

Down

R

Right

L

Left

Instances

Instances details
Bounded Direction2D Source # 
Instance details

Defined in XMonad.Util.Types

Enum Direction2D Source # 
Instance details

Defined in XMonad.Util.Types

Read Direction2D Source # 
Instance details

Defined in XMonad.Util.Types

Show Direction2D Source # 
Instance details

Defined in XMonad.Util.Types

Eq Direction2D Source # 
Instance details

Defined in XMonad.Util.Types

Ord Direction2D Source # 
Instance details

Defined in XMonad.Util.Types

data Gaps a Source #

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.

Instances

Instances details
LayoutModifier Gaps a Source # 
Instance details

Defined in XMonad.Layout.Gaps

Methods

modifyLayout :: LayoutClass l a => Gaps a -> Workspace WorkspaceId (l a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (l a)) Source #

modifyLayoutWithUpdate :: LayoutClass l a => Gaps a -> Workspace WorkspaceId (l a) a -> Rectangle -> X (([(a, Rectangle)], Maybe (l a)), Maybe (Gaps a)) Source #

handleMess :: Gaps a -> SomeMessage -> X (Maybe (Gaps a)) Source #

handleMessOrMaybeModifyIt :: Gaps a -> SomeMessage -> X (Maybe (Either (Gaps a) SomeMessage)) Source #

pureMess :: Gaps a -> SomeMessage -> Maybe (Gaps a) Source #

redoLayout :: Gaps a -> Rectangle -> Maybe (Stack a) -> [(a, Rectangle)] -> X ([(a, Rectangle)], Maybe (Gaps a)) Source #

pureModifier :: Gaps a -> Rectangle -> Maybe (Stack a) -> [(a, Rectangle)] -> ([(a, Rectangle)], Maybe (Gaps a)) Source #

hook :: Gaps a -> X () Source #

unhook :: Gaps a -> X () Source #

modifierDescription :: Gaps a -> String Source #

modifyDescription :: LayoutClass l a => Gaps a -> l a -> String Source #

Read (Gaps a) Source # 
Instance details

Defined in XMonad.Layout.Gaps

Show (Gaps a) Source # 
Instance details

Defined in XMonad.Layout.Gaps

Methods

showsPrec :: Int -> Gaps a -> ShowS #

show :: Gaps a -> String #

showList :: [Gaps a] -> ShowS #

type GapSpec = [(Direction2D, Int)] Source #

A manual gap configuration. Each side of the screen on which a gap is enabled is paired with a size in pixels.

gaps Source #

Arguments

:: GapSpec

The gaps to allow, paired with their initial sizes.

-> l a

The layout to modify.

-> ModifiedLayout Gaps l a 

Add togglable manual gaps to a layout.

gaps' Source #

Arguments

:: [((Direction2D, Int), Bool)]

The gaps to allow and their initial states.

-> l a

The layout to modify.

-> ModifiedLayout Gaps l a 

Add togglable manual gaps to a layout, explicitly specifying the initial states.

data GapMessage Source #

Messages which can be sent to a gap modifier.

Constructors

ToggleGaps

Toggle all gaps.

ToggleGap !Direction2D

Toggle a single gap.

IncGap !Int !Direction2D

Increase a gap by a certain number of pixels.

DecGap !Int !Direction2D

Decrease a gap.

ModifyGaps (GapSpec -> GapSpec)

Modify arbitrarily.

Instances

Instances details
Message GapMessage Source # 
Instance details

Defined in XMonad.Layout.Gaps

weakModifyGaps :: (Direction2D -> Int -> Int) -> GapMessage Source #

Modifies gaps weakly, for convenience.

modifyGap :: (Int -> Int) -> Direction2D -> GapMessage Source #

Arbitrarily modify a single gap with the given function.

setGaps :: GapSpec -> GapMessage Source #

Set the GapSpec.

setGap :: Int -> Direction2D -> GapMessage Source #

Set a gap to the given value.