xmonad-contrib-bluetilebranch-0.8.1.2: Third party extensions for xmonadSource codeContentsIndex
XMonad.Hooks.DynamicLog
Portabilityunportable
Stabilityunstable
MaintainerDon Stewart <dons@cse.unsw.edu.au>
Contents
Usage
Drop-in loggers
Build your own formatter
Example formatters
Formatting utilities
Internal formatting functions
To Do
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. DynamicLog provides several drop-in logHooks for this purpose, as well as flexible tools for specifying your own formatting.
Synopsis
dzen :: LayoutClass l Window => XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))
xmobar :: LayoutClass l Window => XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))
statusBar :: LayoutClass l Window => String -> PP -> (XConfig Layout -> (KeyMask, KeySym)) -> XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))
dynamicLog :: X ()
dynamicLogXinerama :: X ()
dynamicLogWithPP :: PP -> X ()
dynamicLogString :: PP -> X String
data PP = PP {
ppCurrent :: WorkspaceId -> String
ppVisible :: WorkspaceId -> String
ppHidden :: WorkspaceId -> String
ppHiddenNoWindows :: WorkspaceId -> String
ppUrgent :: WorkspaceId -> String
ppSep :: String
ppWsSep :: String
ppTitle :: String -> String
ppLayout :: String -> String
ppOrder :: [String] -> [String]
ppSort :: X ([WindowSpace] -> [WindowSpace])
ppExtras :: [X (Maybe String)]
ppOutput :: String -> IO ()
}
defaultPP :: PP
dzenPP :: PP
xmobarPP :: PP
sjanssenPP :: PP
byorgeyPP :: PP
wrap :: String -> String -> String -> String
pad :: String -> String
trim :: String -> String
shorten :: Int -> String -> String
xmobarColor :: String -> String -> String -> String
xmobarStrip :: String -> String
dzenColor :: String -> String -> String -> String
dzenEscape :: String -> String
dzenStrip :: String -> String
pprWindowSet :: WorkspaceSort -> [Window] -> PP -> WindowSet -> String
pprWindowSetXinerama :: WindowSet -> String
Usage

You can use this module with the following in your ~/.xmonad/xmonad.hs:

    import XMonad
    import XMonad.Hooks.DynamicLog

If you just want a quick-and-dirty status bar with zero effort, try the xmobar or dzen functions:

 main = xmonad =<< xmobar conf

There is also statusBar if you'd like to use another status bar, or would like to use different formatting options. The xmobar, dzen, and statusBar functions are preferred over the other options listed below, as they take care of all the necessary plumbing -- no shell scripting required!

Alternatively, you can choose among several default status bar formats (dynamicLog or dynamicLogXinerama) by simply setting your logHook to the appropriate function, for instance:

 main = xmonad $ defaultConfig {
    ...
    logHook = dynamicLog
    ...
  }

For more flexibility, you can also use dynamicLogWithPP and supply your own pretty-printing format (by either defining one from scratch, or customizing one of the provided examples). For example:

    -- use sjanssen's pretty-printer format, but with the sections
    -- in reverse
    logHook = dynamicLogWithPP $ sjanssenPP { ppOrder = reverse }

Note that setting the logHook only sets up xmonad's output; you are responsible for starting your own status bar program (e.g. dzen or xmobar) and making sure xmonad's output is piped into it appropriately, either by putting it in your .xsession or similar file, or by using spawnPipe in your main function, for example:

 import XMonad.Util.Run   -- for spawnPipe and hPutStrLn

 main = do
     h <- spawnPipe "xmobar -options -foo -bar"
     xmonad $ defaultConfig {
       ...
       logHook = dynamicLogWithPP $ defaultPP { ppOutput = hPutStrLn h }

If you use spawnPipe, be sure to redefine the ppOutput field of your pretty-printer as in the example above; by default the status will be printed to stdout rather than the pipe you create.

Even if you don't use a statusbar, you can still use dynamicLogString to show on-screen notifications in response to some events. For example, to show the current layout when it changes, you could make a keybinding to cycle the layout and display the current status:

    , ((mod1Mask, xK_a     ), sendMessage NextLayout >> (dynamicLogString myPP >>= \d->spawn $"xmessage "++d))
Drop-in loggers
dzen :: LayoutClass l Window => XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))Source

Run xmonad with a dzen status bar set to some nice defaults.

 main = xmonad =<< dzen conf

The intent is that the above config file should provide a nice status bar with minimal effort.

If you wish to customize the status bar format at all, you'll have to use the statusBar function instead.

The binding uses the XMonad.Hooks.ManageDocks module to automatically handle screen placement for dzen, and enables 'mod-b' for toggling the menu bar.

xmobar :: LayoutClass l Window => XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))Source

Run xmonad with a xmobar status bar set to some nice defaults.

 main = xmonad =<< xmobar conf

This works pretty much the same as dzen function above.

statusBarSource
:: LayoutClass l Window
=> Stringthe command line to launch the status bar
-> PPthe pretty printing options
-> XConfig Layout -> (KeyMask, KeySym)the desired key binding to toggle bar visibility
-> XConfig lthe base config
-> IO (XConfig (ModifiedLayout AvoidStruts l))
Modifies the given base configuration to launch the given status bar, send status information to that bar, and allocate space on the screen edges for the bar.
dynamicLog :: X ()Source

An example log hook, which prints status information to stdout in the default format:

 1 2 [3] 4 7 : full : title

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

To customize the output format, see dynamicLogWithPP.

dynamicLogXinerama :: X ()Source

Workspace logger with a format designed for Xinerama:

 [1 9 3] 2 7

where 1, 9, and 3 are the workspaces on screens 1, 2 and 3, respectively, and 2 and 7 are non-visible, non-empty workspaces.

Unfortunately, at the present time, the current layout and window title are not shown, and there is no way to incorporate the xinerama workspace format shown above with dynamicLogWithPP. Hopefully this will change soon.

Build your own formatter
dynamicLogWithPP :: PP -> X ()Source
Format the current status using the supplied pretty-printing format, and write it to stdout.
dynamicLogString :: PP -> X StringSource
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.
data PP Source
The PP type allows the user to customize the formatting of status information.
Constructors
PP
ppCurrent :: WorkspaceId -> Stringhow to print the tag of the currently focused workspace
ppVisible :: WorkspaceId -> Stringhow to print tags of visible but not focused workspaces (xinerama only)
ppHidden :: WorkspaceId -> Stringhow to print tags of hidden workspaces which contain windows
ppHiddenNoWindows :: WorkspaceId -> Stringhow to print tags of empty hidden workspaces
ppUrgent :: WorkspaceId -> Stringformat to be applied to tags of urgent workspaces. NOTE that ppUrgent is applied in addition to ppHidden!
ppSep :: Stringseparator to use between different log sections (window name, layout, workspaces)
ppWsSep :: Stringseparator to use between workspace tags
ppTitle :: String -> Stringwindow title format
ppLayout :: String -> Stringlayout name format
ppOrder :: [String] -> [String]how to order the different log sections. By default, this function receives a list with three formatted strings, representing the workspaces, the layout, and the current window title, respectively. If you have specified any extra loggers in ppExtras, their output will also be appended to the list. To get them in the reverse order, you can just use ppOrder = reverse. If you don't want to display the current layout, you could use something like ppOrder = \(ws:_:t:_) -> [ws,t], and so on.
ppSort :: X ([WindowSpace] -> [WindowSpace])how to sort the workspaces. See XMonad.Util.WorkspaceCompare for some useful sorts.
ppExtras :: [X (Maybe String)]loggers for generating extra information such as time and date, system load, battery status, and so on. See XMonad.Util.Loggers for examples, or create your own!
ppOutput :: String -> IO ()applied to the entire formatted string in order to output it. Can be used to specify an alternative output method (e.g. write to a pipe instead of stdout), and/or to perform some last-minute formatting.
defaultPP :: PPSource
The default pretty printing options, as seen in dynamicLog.
Example formatters
dzenPP :: PPSource
Settings to emulate dwm's statusbar, dzen only. Uses dzenStrip in ppUrgent.
xmobarPP :: PPSource
Some nice xmobar defaults.
sjanssenPP :: PPSource
The options that sjanssen likes to use with xmobar, as an example. Note the use of xmobarColor and the record update on defaultPP.
byorgeyPP :: PPSource
The options that byorgey likes to use with dzen, as another example.
Formatting utilities
wrapSource
:: Stringleft delimiter
-> Stringright delimiter
-> Stringoutput string
-> String
Wrap a string in delimiters, unless it is empty.
pad :: String -> StringSource
Pad a string with a leading and trailing space.
trim :: String -> StringSource
Trim leading and trailing whitespace from a string.
shorten :: Int -> String -> StringSource
Limit a string to a certain length, adding ... if truncated.
xmobarColorSource
:: Stringforeground color: a color name, or #rrggbb format
-> Stringbackground color
-> Stringoutput string
-> String
Use xmobar escape codes to output a string with given foreground and background colors.
xmobarStrip :: String -> StringSource

Strip xmobar markup. Useful to remove ppHidden color from ppUrgent field. For example:

     , ppHidden          = xmobarColor "gray20" "" . wrap "<" ">"
     , ppUrgent          = xmobarColor "dark orange" "" .  xmobarStrip
dzenColorSource
:: Stringforeground color: a color name, or #rrggbb format
-> Stringbackground color
-> Stringoutput string
-> String
Use dzen escape codes to output a string with given foreground and background colors.
dzenEscape :: String -> StringSource
Escape any dzen metacharacters.
dzenStrip :: String -> StringSource

Strip dzen formatting or commands. Useful to remove ppHidden formatting in ppUrgent field. For example:

     , ppHidden          = dzenColor "gray20" "" . wrap "(" ")"
     , ppUrgent          = dzenColor "dark orange" "" .  dzenStrip
Internal formatting functions
pprWindowSet :: WorkspaceSort -> [Window] -> PP -> WindowSet -> StringSource
Format the workspace information, given a workspace sorting function, a list of urgent windows, a pretty-printer format, and the current WindowSet.
pprWindowSetXinerama :: WindowSet -> StringSource
To Do
  • incorporate dynamicLogXinerama into the PP framework somehow
  • add an xmobarEscape function
Produced by Haddock version 2.4.2