aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--XMonad/Hooks/DynamicLog.hs218
-rw-r--r--XMonad/Util/Loggers.hs88
-rw-r--r--xmonad-contrib.cabal3
3 files changed, 245 insertions, 64 deletions
diff --git a/XMonad/Hooks/DynamicLog.hs b/XMonad/Hooks/DynamicLog.hs
index ed0b1ef..77fece5 100644
--- a/XMonad/Hooks/DynamicLog.hs
+++ b/XMonad/Hooks/DynamicLog.hs
@@ -21,16 +21,15 @@ module XMonad.Hooks.DynamicLog (
-- $usage
-- * Drop-in loggers
- makeSimpleDzenConfig,
dzen,
dynamicLog,
- dynamicLogString,
dynamicLogDzen,
dynamicLogXmobar,
- dynamicLogWithPP,
dynamicLogXinerama,
-- * Build your own formatter
+ dynamicLogWithPP,
+ dynamicLogString,
PP(..), defaultPP, dzenPP, sjanssenPP, byorgeyPP,
-- * Formatting utilities
@@ -41,13 +40,16 @@ module XMonad.Hooks.DynamicLog (
pprWindowSet,
pprWindowSetXinerama
+ -- * To Do
+ -- $todo
+
) where
--
-- Useful imports
--
import XMonad
-import Data.Maybe ( isJust )
+import Data.Maybe ( isJust, catMaybes )
import Data.List
import Data.Ord ( comparing )
import qualified XMonad.StackSet as S
@@ -63,41 +65,80 @@ import XMonad.Hooks.UrgencyHook
-- > import XMonad
-- > import XMonad.Hooks.DynamicLog
--
--- Then set your logHook to an appropriate function, for example
+-- If you just want a quick-and-dirty status bar with zero effort, try
+-- the 'dzen' function, which sets up a dzen status bar with a default
+-- format:
+--
+-- > main = dzen xmonad
+--
+-- or, to use this with your own custom xmonad configuration,
+--
+-- > main = dzen $ \conf -> xmonad $ conf { <your customizations> }
--
+-- Alternatively, you can choose among several default status bar
+-- formats ('dynamicLog', 'dynamicLogDzen', 'dynamicLogXmobar', 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:
--
--- or, for more flexibility, something like
+-- > -- use sjanssen's pretty-printer format, but with the sections
+-- > -- in reverse
+-- > logHook = dynamicLogWithPP $ sjanssenPP { ppOrder = reverse }
--
--- > logHook = dynamicLogWithPP myDynamicLogPP
--- > ...
--- > myDynamicLogPP = defaultPP { ... -- override pretty-printer with specific settings
+-- 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:
--
--- If you don't use statusbar, you can use dynamicLogString to show on-screen
--- notifications in response to some events. E.g. to show current layout when
--- it's changed create apropriate PP and add to keybindings:
+-- > 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))
+--
--- | An example xmonad config that spawns a new dzen toolbar and uses
--- the default dynamic log output.
-makeSimpleDzenConfig :: IO (XConfig (Choose Tall (Choose (Mirror Tall) Full)))
-makeSimpleDzenConfig = do
- h <- spawnPipe "dzen2"
- return defaultConfig
- { defaultGaps = [(18,0,0,0)]
- , logHook = dynamicLogWithPP dzenPP
- { ppOutput = hPutStrLn h } }
-
--- |
+-- $todo
+--
+-- * incorporate dynamicLogXinerama into the PP framework somehow
--
--- Run xmonad with a dzen status bar set to some nice defaults. Output
+-- * add an xmobarEscape function
+
+-- | Run xmonad with a dzen status bar set to some nice defaults. Output
-- is taken from the dynamicLogWithPP hook.
--
-- > main = dzen xmonad
--
--- The intent is that the above config file should provide a nice status
--- bar with minimal effort.
+-- The intent is that the above config file should provide a nice
+-- status bar with minimal effort. If you want to customize your xmonad
+-- configuration while using this, you'll have to do something like
+--
+-- > main = dzen $ \conf -> xmonad $ conf { <your customized settings...> }
+--
+-- If you wish to customize the status bar format at all, you'll have to
+-- use something like 'dynamicLogWithPP' instead.
--
dzen :: (XConfig (Choose Tall (Choose (Mirror Tall) Full)) -> IO ()) -> IO ()
dzen f = do
@@ -111,51 +152,68 @@ dzen f = do
bg = "'#3f3c6d'"
flags = "-e '' -w 400 -ta l -fg " ++ fg ++ " -bg " ++ bg
--- |
--- An example log hook, print a status bar output to stdout, in the form:
+-- | 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'.
+--
dynamicLog :: X ()
dynamicLog = dynamicLogWithPP defaultPP
--- |
--- Returns formatted log message.
+-- | An example log hook that emulates dwm's status bar, using colour
+-- codes printed to dzen. Requires dzen. Workspaces, xinerama,
+-- layouts and the window title are handled.
+dynamicLogDzen :: X ()
+dynamicLogDzen = dynamicLogWithPP dzenPP
+
+-- | These are good defaults to be used with the xmobar status bar.
+dynamicLogXmobar :: X ()
+dynamicLogXmobar = dynamicLogWithPP xmobarPP
+
+-- | Format the current status using the supplied pretty-printing format,
+-- and write it to stdout.
+dynamicLogWithPP :: PP -> X ()
+dynamicLogWithPP pp = dynamicLogString pp >>= io . ppOutput pp
+
+-- | 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.
dynamicLogString :: PP -> X String
dynamicLogString pp = do
+
winset <- gets windowset
urgents <- readUrgents
sort' <- ppSort pp
+
-- layout description
let ld = description . S.layout . S.workspace . S.current $ winset
+
-- workspace list
let ws = pprWindowSet sort' urgents pp winset
+
-- window title
wt <- maybe (return "") (fmap show . getName) . S.peek $ winset
+ -- run extra loggers, ignoring any that generate errors.
+ extras <- sequence $ map (flip catchX (return Nothing)) $ ppExtras pp
+
return $ sepBy (ppSep pp) . ppOrder pp $
[ ws
, ppLayout pp ld
, ppTitle pp wt
]
+ ++ catMaybes extras
--- |
--- A log function that uses the 'PP' hooks to customize output.
-dynamicLogWithPP :: PP -> X ()
-dynamicLogWithPP pp = dynamicLogString pp >>= io . ppOutput pp
-
--- | An example log hook that emulates dwm's status bar, using colour
--- codes printed to dzen. Requires dzen. Workspaces, xinerama,
--- layouts and the window title are handled.
---
-dynamicLogDzen :: X ()
-dynamicLogDzen = dynamicLogWithPP dzenPP
-
--- | Do the actual status formatting, using a pretty-printer.
-pprWindowSet :: ([WindowSpace] -> [WindowSpace]) -> [Window] -> PP -> WindowSet -> String
+-- | Format the workspace information, given a workspace sorting function,
+-- a list of urgent windows, a pretty-printer format, and the current
+-- WindowSet.
+pprWindowSet :: WorkspaceSort -> [Window] -> PP -> WindowSet -> String
pprWindowSet sort' urgents pp s = sepBy (ppWsSep pp) . map fmt . sort' $
map S.workspace (S.current s : S.visible s) ++ S.hidden s
where this = S.tag (S.workspace (S.current s))
@@ -176,6 +234,10 @@ pprWindowSet sort' urgents pp s = sepBy (ppWsSep pp) . map fmt . sort' $
-- 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.
dynamicLogXinerama :: X ()
dynamicLogXinerama = withWindowSet $ io . putStrLn . pprWindowSetXinerama
@@ -237,21 +299,28 @@ xmobarColor :: String -- ^ foreground color: a color name, or #rrggbb format
xmobarColor fg bg = wrap t "</fc>"
where t = concat ["<fc=", fg, if null bg then "" else "," ++ bg, ">"]
--- | The 'PP' type allows the user to customize various behaviors of
--- dynamicLogPP.
+-- ??? add an xmobarEscape function?
+
+-- | The 'PP' type allows the user to customize the formatting of
+-- status information.
data PP = PP { ppCurrent :: WorkspaceId -> String
- -- ^ how to print the tag of the currently focused workspace
+ -- ^ how to print the tag of the currently focused
+ -- workspace
, ppVisible :: WorkspaceId -> String
- -- ^ how to print tags of visible but not focused workspaces (xinerama only)
+ -- ^ how to print tags of visible but not focused
+ -- workspaces (xinerama only)
, ppHidden :: WorkspaceId -> String
- -- ^ how to print tags of hidden workspaces which contain windows
+ -- ^ how to print tags of hidden workspaces which
+ -- contain windows
, ppHiddenNoWindows :: WorkspaceId -> String
-- ^ how to print tags of empty hidden workspaces
, ppUrgent :: WorkspaceId -> String
-- ^ format to be applied to tags of urgent workspaces.
- -- NOTE that 'ppUrgent' is applied /in addition to/ 'ppHidden'!
+ -- NOTE that 'ppUrgent' is applied /in addition to/
+ -- 'ppHidden'!
, ppSep :: String
- -- ^ separator to use between different log sections (window name, layout, workspaces)
+ -- ^ separator to use between different log sections
+ -- (window name, layout, workspaces)
, ppWsSep :: String
-- ^ separator to use between workspace tags
, ppTitle :: String -> String
@@ -259,11 +328,32 @@ data PP = PP { ppCurrent :: WorkspaceId -> String
, ppLayout :: String -> String
-- ^ layout name format
, ppOrder :: [String] -> [String]
- -- ^ how to order the different log sections
+ -- ^ 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.
+ -- ^ 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 ()
- -- ^ formatter that gets applied to the entire log string before it is output.
+ -- ^ 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.
}
-- | The default pretty printing options, as seen in 'dynamicLog'.
@@ -280,6 +370,7 @@ defaultPP = PP { ppCurrent = wrap "[" "]"
, ppOrder = id
, ppOutput = putStrLn
, ppSort = getSortByIndex
+ , ppExtras = []
}
-- | Settings to emulate dwm's statusbar, dzen only.
@@ -301,8 +392,16 @@ dzenPP = defaultPP { ppCurrent = dzenColor "white" "#2b4f98" . pad
, ppTitle = ("^bg(#324c80) " ++) . dzenEscape
}
--- | The options that sjanssen likes to use, as an example. Note the use of
--- 'xmobarColor' and the record update on 'defaultPP'.
+-- | Some nice xmobar defaults.
+xmobarPP :: PP
+xmobarPP = defaultPP { ppCurrent = xmobarColor "yellow" "" . wrap "[" "]"
+ , ppTitle = xmobarColor "green" "" . shorten 40
+ , ppVisible = wrap "(" ")"
+ }
+
+-- | The options that sjanssen likes to use with xmobar, as an
+-- example. Note the use of 'xmobarColor' and the record update on
+-- 'defaultPP'.
sjanssenPP :: PP
sjanssenPP = defaultPP { ppCurrent = xmobarColor "white" "#ff000000"
, ppTitle = xmobarColor "#00ee00" "" . shorten 80
@@ -323,10 +422,3 @@ byorgeyPP = defaultPP { ppHiddenNoWindows = showNamedWorkspaces
then pad wsId
else ""
--- | These are good defaults to be used with the xmobar status bar.
-dynamicLogXmobar :: X ()
-dynamicLogXmobar =
- dynamicLogWithPP defaultPP { ppCurrent = xmobarColor "yellow" "" . wrap "[" "]"
- , ppTitle = xmobarColor "green" "" . shorten 40
- , ppVisible = wrap "(" ")"
- }
diff --git a/XMonad/Util/Loggers.hs b/XMonad/Util/Loggers.hs
new file mode 100644
index 0000000..dcf3b99
--- /dev/null
+++ b/XMonad/Util/Loggers.hs
@@ -0,0 +1,88 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Util.Loggers
+-- Copyright : (c) Brent Yorgey
+-- License : BSD-style (see LICENSE)
+--
+-- Maintainer : <byorgey@gmail.com>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- A collection of simple logger functions which can be used in the
+-- 'XMonad.Hooks.DynamicLog.ppExtras' field of a pretty-printing status
+-- logger format. See "XMonad.Hooks.DynamicLog" for more information.
+-----------------------------------------------------------------------------
+
+module XMonad.Util.Loggers (
+ -- * Usage
+ -- $usage
+
+ Logger
+
+ , date
+ , loadAvg
+ , battery
+ , logCmd
+
+ ) where
+
+import XMonad.Core
+
+import System.Time
+import System.IO
+import System.Process
+import System.Locale
+
+-- $usage
+-- You can use this module by importing it into your @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Util.Loggers
+--
+-- Then, add one or more loggers to the
+-- 'XMonad.Hooks.DynamicLog.ppExtras' field of your
+-- 'XMonad.Hooks.DynamicLoc.PP' format. For example:
+--
+-- > -- display load averages and a pithy quote along with xmonad status.
+-- > , logHook = dynamicLogWithPP $ defaultPP { ppExtras = [ loadAvg, logCmd "fortune -n 40 -s" ] }
+--
+-- 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 DynamicLog.
+--
+-- Additional loggers welcome!
+--
+
+-- | 'Logger' is just a convenient synonym for @X (Maybe String)@.
+type Logger = X (Maybe String)
+
+-- | 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>.
+date :: String -> Logger
+date fmt = io $ do cal <- (getClockTime >>= toCalendarTime)
+ return . Just $ formatCalendarTime defaultTimeLocale fmt cal
+
+-- | Get the load average. This assumes that you have a
+-- utility called @\/usr\/bin\/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.
+loadAvg :: Logger
+loadAvg = logCmd "/usr/bin/uptime | sed 's/.*: //; s/,//g'"
+
+-- | 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.
+battery :: Logger
+battery = logCmd "/usr/bin/acpi | sed -r 's/.*?: (.*%).*/\\1/; s/discharging, ([0-9]+%)/\\1-/; s/charging, ([0-9]+%)/\\1+/; s/charged, //'"
+
+-- | Create a 'Logger' from an arbitrary shell command.
+logCmd :: String -> Logger
+logCmd c = io $ do (_, out, _, proc) <- runInteractiveCommand c
+ output <- hGetLine out
+ waitForProcess proc
+ return $ Just output
diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal
index 9fa9444..3bf3305 100644
--- a/xmonad-contrib.cabal
+++ b/xmonad-contrib.cabal
@@ -40,7 +40,7 @@ flag testing
library
if flag(small_base)
- build-depends: base >= 3, containers, directory, process, random
+ build-depends: base >= 3, containers, directory, process, random, old-time, old-locale
else
build-depends: base < 3
@@ -157,6 +157,7 @@ library
XMonad.Util.EZConfig
XMonad.Util.Font
XMonad.Util.Invisible
+ XMonad.Util.Loggers
XMonad.Util.NamedWindows
XMonad.Util.Run
XMonad.Util.Themes