xmonad-contrib-0.17.1: Community-maintained extensions for xmonad
Copyright(c) Don Stewart <dons@cse.unsw.edu.au>
LicenseBSD3-style (see LICENSE)
MaintainerDon Stewart <dons@cse.unsw.edu.au>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Hooks.StatusBar.PP

Description

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.

This module provides a pretty-printing abstraction and utilities that can be used to customize what is logged to a status bar. See XMonad.Hooks.StatusBar for an abstraction over starting these status bars. Together these are a modern replacement for XMonad.Hooks.DynamicLog, which is now just a compatibility wrapper.

Synopsis

Usage

An example usage for this module would be:

import XMonad
import XMonad.Hooks.StatusBar
import XMonad.Hooks.StatusBar.PP

myPP = def { ppCurrent = xmobarColor "black" "white" }
mySB = statusBarProp "xmobar" (pure myPP)
main = xmonad . withEasySB mySB defToggleStrutsKey $ myConfig

Check XMonad.Hooks.StatusBar for more examples and an in depth explanation.

Build your own formatter

data PP Source #

The PP type allows the user to customize the formatting of status information.

Constructors

PP 

Fields

Instances

Instances details
Default PP Source #

The default pretty printing options:

1 2 [3] 4 7 : full : title

That is, the currently populated workspaces, the current workspace layout, and the title of the focused window.

Instance details

Defined in XMonad.Hooks.StatusBar.PP

Methods

def :: PP #

def :: Default a => a #

dynamicLogString :: PP -> X String Source #

The same as dynamicLogWithPP, 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.

dynamicLogWithPP :: PP -> X () Source #

Format the current status using the supplied pretty-printing format, and write it to stdout.

Predicates and formatters

Using WSPP with ppPrinters allows extension modules (and users) to extend PP with new workspace types beyond ppCurrent, ppUrgent, and the rest.

data WS Source #

The data available to WSPP'.

Constructors

WS 

Fields

type WSPP = WSPP' (WorkspaceId -> String) Source #

The type allowing to build formatters (and predicates). See the source fallbackPrinters for an example.

fallbackPrinters :: WSPP Source #

For a PP pp, fallbackPrinters pp returns the default WSPP used to format workspaces: the formatter chosen corresponds to the first matching workspace type, respecting the following precedence: ppUrgent, ppCurrent, ppVisible, ppVisibleNoWindows, ppHidden, ppHiddenNoWindows.

This can be useful if one needs to use the default set of formatters and post-process their output. (For pre-processing their input, there's ppRename.)

isUrgent :: WS -> Bool Source #

Predicate for urgent workspaces.

isCurrent :: WS -> Bool Source #

Predicate for the current workspace.

isVisible :: WS -> Bool Source #

Predicate for visible workspaces.

isVisibleNoWindows :: WS -> Bool Source #

Predicate for visible workspaces that have no windows.

isHidden :: WS -> Bool Source #

Predicate for hidden workspaces.

Example formatters

dzenPP :: PP Source #

Settings to emulate dwm's statusbar, dzen only.

xmobarPP :: PP Source #

Some nice xmobar defaults.

sjanssenPP :: PP Source #

The options that sjanssen likes to use with xmobar, as an example. Note the use of xmobarColor and the record update on def.

byorgeyPP :: PP Source #

The options that byorgey likes to use with dzen, as another example.

Formatting utilities

wrap Source #

Arguments

:: String

left delimiter

-> String

right delimiter

-> String

output string

-> String 

Wrap a string in delimiters, unless it is empty.

pad :: String -> String Source #

Pad a string with a leading and trailing space.

trim :: String -> String Source #

Trim leading and trailing whitespace from a string.

shorten :: Int -> String -> String Source #

Limit a string to a certain length, adding "..." if truncated.

shorten' :: String -> Int -> String -> String Source #

Limit a string to a certain length, adding end if truncated.

shortenLeft :: Int -> String -> String Source #

Like shorten, but truncate from the left instead of right.

shortenLeft' :: String -> Int -> String -> String Source #

Like shorten', but truncate from the left instead of right.

xmobarColor Source #

Arguments

:: String

foreground color: a color name, or #rrggbb format

-> String

background color

-> String

output string

-> String 

Use xmobar escape codes to output a string with given foreground and background colors.

xmobarFont Source #

Arguments

:: Int

index: index of the font to use (0: standard font)

-> String

output string

-> String 

Use xmobar escape codes to output a string with the font at the given index

xmobarAction Source #

Arguments

:: String

Command. Use of backticks (`) will cause a parse error.

-> String

Buttons 1-5, such as "145". Other characters will cause a parse error.

-> String

Displayed/wrapped text.

-> String 

Encapsulate text with an action. The text will be displayed, and the action executed when the displayed text is clicked. Illegal input is not filtered, allowing xmobar to display any parse errors. Uses xmobar's new syntax wherein the command is surrounded by backticks.

xmobarBorder Source #

Arguments

:: String

Border type. Possible values: VBoth, HBoth, Full, Top, Bottom, Left or Right

-> String

color: a color name, or #rrggbb format

-> Int

width in pixels

-> String

output string

-> String 

Use xmobar box to add a border to an arbitrary string.

xmobarRaw :: String -> String Source #

Encapsulate arbitrary text for display only, i.e. untrusted content if wrapped (perhaps from window titles) will be displayed only, with all tags ignored. Introduced in xmobar 0.21; see their documentation. Be careful not to shorten the result.

xmobarStrip :: String -> String Source #

Strip xmobar markup, specifically the fc, icon and action tags and the matching tags like /fc.

xmobarStripTags Source #

Arguments

:: [String]

tags

-> String 
-> String

with all tag.../tag removed

dzenColor Source #

Arguments

:: String

foreground color: a color name, or #rrggbb format

-> String

background color

-> String

output string

-> String 

Use dzen escape codes to output a string with given foreground and background colors.

dzenEscape :: String -> String Source #

Escape any dzen metacharacters.

dzenStrip :: String -> String Source #

Strip dzen formatting or commands.

filterOutWsPP :: [WorkspaceId] -> PP -> PP Source #

Transforms a pretty-printer into one not displaying the given workspaces.

For example, filtering out the NSP workspace before giving the PP to dynamicLogWithPP:

logHook = dynamicLogWithPP . filterOutWsPP [scratchpadWorkspaceTag] $ def

Here is another example, when using XMonad.Layout.IndependentScreens. If you have handles hLeft and hRight for bars on the left and right screens, respectively, and pp is a pretty-printer function that takes a handle, you could write

logHook = let log screen handle = dynamicLogWithPP . filterOutWsPP [scratchpadWorkspaceTag] . marshallPP screen . pp $ handle
          in log 0 hLeft >> log 1 hRight

Internal formatting functions

pprWindowSet :: WorkspaceSort -> [Window] -> PP -> WindowSet -> String Source #

Format the workspace information, given a workspace sorting function, a list of urgent windows, a pretty-printer format, and the current WindowSet.