xmonad-contrib-0.16.999: Community-maintained extensions extensions for xmonad
Copyright(c) Brent Yorgey Wirt Wolff
LicenseBSD-style (see LICENSE)
Maintainer<byorgey@gmail.com>
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell98

XMonad.Util.Loggers

Description

A collection of simple logger functions and formatting utilities which can be used in the ppExtras field of a pretty-printing status logger format. See XMonad.Hooks.StatusBar.PP for more information.

Synopsis

Usage

Use this module by importing it into your ~/.xmonad/xmonad.hs:

import XMonad.Util.Loggers

Then, add one or more loggers to the ppExtras field of your XMonad.Hooks.StatusBar.PP, possibly with extra formatting . For example:

myPP = def {
           ppExtras = [ padL loadAvg, logCmd "fortune -n 40 -s" ]
        }
  -- gives something like " 3.27 3.52 3.26 Drive defensively.  Buy a tank."

See the formatting section below for another example using a where block to define some formatted loggers for a top-level myPP.

Loggers are named either for their function, as in battery, aumixVolume, and maildirNew, or are prefixed with "log" when making use of other functions or by analogy with the pp* functions. For example, the logger version of ppTitle is logTitle, and logFileCount loggerizes the result of file counting code.

Formatting utility names are generally as short as possible and carry the suffix "L". For example, the logger version of shorten is shortenL.

Of course, there is nothing really special about these so-called "loggers": they are just X (Maybe String) actions. So you can use them anywhere you would use an X (Maybe String), not just with PP.

Additional loggers welcome!

type Logger = X (Maybe String) Source #

Logger is just a convenient synonym for X (Maybe String).

System Loggers

 

aumixVolume :: Logger Source #

Get the current volume with aumix. http://jpj.net/~trevor/aumix.html

battery :: Logger Source #

Get the battery status (percent charge and charging/discharging status). This is an ugly hack and may not work for some people. At some point it would be nice to make this more general/have fewer dependencies (assumes acpi and sed are installed.)

date :: String -> Logger Source #

Get the current date and time, and format them via the given format string. The format used is the same as that used by the C library function strftime; for example, date "%a %b %d" might display something like Tue Feb 19. For more information see something like http://www.cplusplus.com/reference/clibrary/ctime/strftime.html.

loadAvg :: Logger Source #

Get the load average. This assumes that you have a utility called uptime and that you have sed installed; these are fairly common on GNU/Linux systems but it would be nice to make this more general.

maildirNew :: FilePath -> Logger Source #

Get a count of new mails in a maildir.

maildirUnread :: FilePath -> Logger Source #

Get a count of unread mails in a maildir. For maildir format details, to write loggers for other classes of mail, see http://cr.yp.to/proto/maildir.html and logFileCount.

logCmd :: String -> Logger Source #

Create a Logger from an arbitrary shell command.

logFileCount Source #

Arguments

:: FilePath

directory in which to count files

-> (String -> Bool)

predicate to match if file should be counted

-> Logger 

Get a count of filtered files in a directory. See maildirUnread and maildirNew source for usage examples.

XMonad Loggers

A very small sample of what you can log since you have access to X. For example you can loggerize the number of windows on each workspace, or titles on other workspaces, or the id of the previously focused workspace....

logCurrent :: Logger Source #

Get the name of the current workspace.

logLayout :: Logger Source #

Get the name of the current layout.

logTitle :: Logger Source #

Get the title (name) of the focused window.

logTitles :: (String -> String) -> (String -> String) -> Logger Source #

Like logTitlesOnScreen, but directly use the "focused" screen (the one with the currently focused workspace).

logConst :: String -> Logger Source #

Log the given string, as is.

logDefault :: Logger -> Logger -> Logger Source #

If the first logger returns Nothing, the default logger is used. For example, to display a quote when no windows are on the screen, you can do:

logDefault logTitle (logConst "Hey, you, you're finally awake.")

(.|) :: Logger -> Logger -> Logger Source #

An infix operator for logDefault, which can be more convenient to combine multiple loggers.

logTitle .| logWhenActive 0 (logConst "*") .| logConst "There's nothing here"

XMonad: Screen-specific Loggers

It is also possible to bind loggers like logTitle to a specific screen. For example, using logTitleOnScreen 1 will log the title of the focused window on screen 1, even if screen 1 is not currently active.

logCurrentOnScreen :: ScreenId -> Logger Source #

Get the name of the visible workspace on the given screen.

logLayoutOnScreen :: ScreenId -> Logger Source #

Get the name of the current layout on the given screen.

logTitleOnScreen :: ScreenId -> Logger Source #

Get the title (name) of the focused window, on the given screen.

logWhenActive :: ScreenId -> Logger -> Logger Source #

Only display the Logger if the screen with the given ScreenId is active. For example, this can be used to create a marker that is only displayed when the primary screen is active.

logWhenActive 0 (logConst "*")

logTitlesOnScreen Source #

Arguments

:: ScreenId

Screen to log the titles on

-> (String -> String)

Formatting for the focused window

-> (String -> String)

Formatting for the unfocused window

-> Logger 

Get the titles of all windows on the visible workspace of the given screen and format them according to the given functions.

Example

Expand
myXmobarPP :: X PP
myXmobarPP = pure $ def
  { ppOrder  = [ws, l, _, wins] -> [ws, l, wins]
  , ppExtras = [logTitles formatFocused formatUnfocused]
  }
 where
  formatFocused   = wrap "[" "]" . xmobarColor "#ff79c6" "" . shorten 50 . xmobarStrip
  formatUnfocused = wrap "(" ")" . xmobarColor "#bd93f9" "" . shorten 30 . xmobarStrip

Formatting Utilities

Combine logger formatting functions to make your ppExtras more colorful and readable. (For convenience, you can use <$> instead of '.' or '$' in hard to read formatting lines. For example:

myPP = def {
    -- skipped
    , ppExtras = [lLoad, lTitle, logSp 3, wrapL "[" "]" $ date "%a %d %b"]
    , ppOrder = \(ws:l:_:xs) -> [l,ws] ++ xs
    }
  where
    -- lTitle = fixedWidthL AlignCenter "." 99 . dzenColorL "cornsilk3" "" . padL . shortenL 80 $ logTitle
    -- or something like:
    lTitle = fixedWidthL AlignCenter "." 99 <$> dzenColorL "cornsilk3" "" <$> padL . shortenL 80 $ logTitle

    lLoad = dzenColorL "#6A5ACD" "" . wrapL loadIcon "   " . padL $ loadAvg
    loadIcon = " ^i(/home/me/.dzen/icons/load.xbm)"

For more information on how to add the pretty-printer to your status bar, please check XMonad.Hooks.StatusBar.

Note: When applying shortenL or fixedWidthL to logger strings containing colors or other formatting commands, apply the formatting after the length adjustment, or include "invisible" characters in the length specification, e.g. in the above '^fg(cornsilk3)' and '^fg()' yields 19 invisible and 80 visible characters.

onLogger :: (String -> String) -> Logger -> Logger Source #

Use a string formatting function to edit a Logger string. For example, to create a tag function to prefix or label loggers, as in 'tag: output', use:

tagL l = onLogger $ wrap (l ++ ": ") ""

   tagL "bat" battery
   tagL "load" loadAvg

If you already have a (String -> String) function you want to apply to a logger:

revL = onLogger trim

See formatting utility source code for more onLogger usage examples.

wrapL :: String -> String -> Logger -> Logger Source #

Wrap a logger's output in delimiters, unless it is X (Nothing) or X (Just ""). Some examples:

   wrapL " | " " | " (date "%a %d %b") -- ' | Tue 19 Feb | '

   wrapL "bat: " "" battery            -- ' bat: battery_logger_output'

fixedWidthL Source #

Arguments

:: Align

AlignCenter, AlignRight, or AlignLeft

-> String

String to cycle to pad missing logger output

-> Int

Fixed length to output (including invisible formatting characters)

-> Logger 
-> Logger 

Make a logger's output constant width by padding with the given string, even if the logger is X (Nothing) or X (Just ""). Useful to reduce visual noise as a title logger shrinks and grows, to use a fixed width for a logger that sometimes becomes Nothing, or even to create fancy spacers or character based art effects.

It fills missing logger output with a repeated character like ".", ":" or pattern, like " -.-". The cycling padding string is reversed on the left of the logger output. This is mainly useful with AlignCenter.

logSp :: Int -> Logger Source #

Create a "spacer" logger, e.g. logSp 3 -- loggerizes ' '. For more complex "spacers", use fixedWidthL with return Nothing.

padL :: Logger -> Logger Source #

Pad a logger's output with a leading and trailing space, unless it is X (Nothing) or X (Just "").

shortenL :: Int -> Logger -> Logger Source #

Limit a logger's length, adding "..." if truncated.

dzenColorL :: String -> String -> Logger -> Logger Source #

Color a logger's output with dzen foreground and background colors.

 dzenColorL "green" "#2A4C3F" battery

xmobarColorL :: String -> String -> Logger -> Logger Source #

Color a logger's output with xmobar foreground and background colors.

 xmobarColorL "#6A5ACD" "gray6" loadAverage