mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-03 13:41:53 -07:00
Big DynamicLog refactor. Added statusBar, improved compositionality for dzen and xmobar
Compatibility notes: - dzen type change - xmobar type change - dynamicLogDzen removed - dynamicLogXmobar removed
This commit is contained in:
@@ -1,3 +1,5 @@
|
|||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : XMonad.Hooks.DynamicLog
|
-- Module : XMonad.Hooks.DynamicLog
|
||||||
@@ -23,15 +25,17 @@ module XMonad.Hooks.DynamicLog (
|
|||||||
-- * Drop-in loggers
|
-- * Drop-in loggers
|
||||||
dzen,
|
dzen,
|
||||||
xmobar,
|
xmobar,
|
||||||
|
statusBar,
|
||||||
dynamicLog,
|
dynamicLog,
|
||||||
dynamicLogDzen,
|
|
||||||
dynamicLogXmobar,
|
|
||||||
dynamicLogXinerama,
|
dynamicLogXinerama,
|
||||||
|
|
||||||
-- * Build your own formatter
|
-- * Build your own formatter
|
||||||
dynamicLogWithPP,
|
dynamicLogWithPP,
|
||||||
dynamicLogString,
|
dynamicLogString,
|
||||||
PP(..), defaultPP, dzenPP, xmobarPP, sjanssenPP, byorgeyPP,
|
PP(..), defaultPP,
|
||||||
|
|
||||||
|
-- * Example formatters
|
||||||
|
dzenPP, xmobarPP, sjanssenPP, byorgeyPP,
|
||||||
|
|
||||||
-- * Formatting utilities
|
-- * Formatting utilities
|
||||||
wrap, pad, shorten,
|
wrap, pad, shorten,
|
||||||
@@ -50,6 +54,7 @@ module XMonad.Hooks.DynamicLog (
|
|||||||
-- Useful imports
|
-- Useful imports
|
||||||
--
|
--
|
||||||
import XMonad
|
import XMonad
|
||||||
|
import Control.Monad
|
||||||
import Data.Maybe ( isJust, catMaybes )
|
import Data.Maybe ( isJust, catMaybes )
|
||||||
import Data.List
|
import Data.List
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
@@ -72,21 +77,17 @@ import XMonad.Hooks.ManageDocks
|
|||||||
-- > import XMonad.Hooks.DynamicLog
|
-- > import XMonad.Hooks.DynamicLog
|
||||||
--
|
--
|
||||||
-- If you just want a quick-and-dirty status bar with zero effort, try
|
-- 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
|
-- the 'xmobar' or 'dzen' functions:
|
||||||
-- format:
|
|
||||||
--
|
--
|
||||||
-- > main = dzen xmonad
|
-- > main = xmonad =<< xmobar conf
|
||||||
--
|
--
|
||||||
-- or, to use this with your own custom xmonad configuration,
|
-- 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!
|
||||||
--
|
--
|
||||||
-- > main = dzen $ \conf -> xmonad $ conf { <your customizations> }
|
-- Alternatively, you can choose among several default status bar formats
|
||||||
--
|
-- ('dynamicLog' or 'dynamicLogXinerama') by simply setting your logHook to the
|
||||||
-- Also you can use 'xmobar' function instead of 'dzen' in the examples above,
|
|
||||||
-- if you have xmobar installed.
|
|
||||||
--
|
|
||||||
-- 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:
|
-- appropriate function, for instance:
|
||||||
--
|
--
|
||||||
-- > main = xmonad $ defaultConfig {
|
-- > main = xmonad $ defaultConfig {
|
||||||
@@ -139,69 +140,65 @@ import XMonad.Hooks.ManageDocks
|
|||||||
|
|
||||||
------------------------------------------------------------------------
|
------------------------------------------------------------------------
|
||||||
|
|
||||||
-- | Run xmonad with a dzen status bar set to some nice defaults. Output
|
-- | Run xmonad with a dzen status bar set to some nice defaults.
|
||||||
-- is taken from the dynamicLogWithPP hook.
|
|
||||||
--
|
--
|
||||||
-- > main = dzen xmonad
|
-- > main = xmonad =<< xmonad conf
|
||||||
--
|
--
|
||||||
-- The intent is that the above config file should provide a nice
|
-- The intent is that the above config file should provide a nice
|
||||||
-- status bar with minimal effort. If you want to customize your xmonad
|
-- status bar with minimal effort.
|
||||||
-- 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
|
-- If you wish to customize the status bar format at all, you'll have to
|
||||||
-- use something like 'dynamicLogWithPP' instead.
|
-- use the 'statusBar' function instead.
|
||||||
--
|
--
|
||||||
-- The binding uses the XMonad.Hooks.ManageDocks module to automatically
|
-- The binding uses the XMonad.Hooks.ManageDocks module to automatically
|
||||||
-- handle screen placement for dzen, and enables 'mod-b' for toggling
|
-- handle screen placement for dzen, and enables 'mod-b' for toggling
|
||||||
-- the menu bar.
|
-- the menu bar.
|
||||||
--
|
--
|
||||||
dzen ::
|
dzen :: LayoutClass l Window
|
||||||
(XConfig
|
=> XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))
|
||||||
(ModifiedLayout AvoidStruts
|
dzen conf = statusBar ("dzen2" ++ flags) dzenPP toggleStrutsKey conf
|
||||||
(Choose Tall (Choose (Mirror Tall) Full))) -> IO t) -> IO t
|
|
||||||
dzen f = do
|
|
||||||
h <- spawnPipe ("dzen2" ++ " " ++ flags)
|
|
||||||
f $ defaultConfig
|
|
||||||
{ logHook = dynamicLogWithPP dzenPP
|
|
||||||
{ ppOutput = hPutStrLn h }
|
|
||||||
,layoutHook = avoidStrutsOn [U] (layoutHook defaultConfig)
|
|
||||||
,keys = \c -> toggleStrutsKey c `M.union` keys defaultConfig c
|
|
||||||
,manageHook = manageHook defaultConfig <+> manageDocks
|
|
||||||
}
|
|
||||||
where
|
where
|
||||||
fg = "'#a8a3f7'" -- n.b quoting
|
fg = "'#a8a3f7'" -- n.b quoting
|
||||||
bg = "'#3f3c6d'"
|
bg = "'#3f3c6d'"
|
||||||
flags = "-e 'onstart=lower' -w 400 -ta l -fg " ++ fg ++ " -bg " ++ bg
|
flags = "-e 'onstart=lower' -w 400 -ta l -fg " ++ fg ++ " -bg " ++ bg
|
||||||
|
|
||||||
|
|
||||||
-- | Run xmonad with a xmobar status bar set to some nice defaults. Output
|
-- | Run xmonad with a xmobar status bar set to some nice defaults.
|
||||||
-- is taken from the dynamicLogWithPP hook.
|
|
||||||
--
|
--
|
||||||
-- > main = xmobar xmonad
|
-- > main = xmonad =<< xmobar config
|
||||||
--
|
--
|
||||||
-- This works pretty much the same as 'dzen' function above
|
-- This works pretty much the same as 'dzen' function above.
|
||||||
--
|
--
|
||||||
xmobar ::
|
xmobar :: LayoutClass l Window
|
||||||
(XConfig
|
=> XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))
|
||||||
(ModifiedLayout AvoidStruts
|
xmobar conf = statusBar "xmobar" xmobarPP toggleStrutsKey conf
|
||||||
(Choose Tall (Choose (Mirror Tall) Full))) -> IO t) -> IO t
|
|
||||||
xmobar f = do
|
-- | Modifies the given base configuration to launch the given status bar,
|
||||||
h <- spawnPipe "xmobar"
|
-- send status information to that bar, and allocate space on the screen edges
|
||||||
f $ defaultConfig
|
-- for the bar.
|
||||||
{ logHook = dynamicLogWithPP xmobarPP { ppOutput = hPutStrLn h }
|
statusBar :: LayoutClass l Window
|
||||||
, layoutHook = avoidStruts $ layoutHook defaultConfig
|
=> String -- ^ the command line to launch the status bar
|
||||||
, keys = \c -> toggleStrutsKey c `M.union` keys defaultConfig c
|
-> PP -- ^ the pretty printing options
|
||||||
, manageHook = manageHook defaultConfig <+> manageDocks
|
-> (XConfig Layout -> ((KeyMask, KeySym), X ()))
|
||||||
}
|
-- ^ the desired key binding to toggle bar visibility
|
||||||
|
-> XConfig l -- ^ the base config
|
||||||
|
-> IO (XConfig (ModifiedLayout AvoidStruts l))
|
||||||
|
statusBar cmd pp k conf = do
|
||||||
|
h <- spawnPipe cmd
|
||||||
|
return $ conf
|
||||||
|
{ layoutHook = avoidStruts (layoutHook conf)
|
||||||
|
, logHook = do
|
||||||
|
logHook conf
|
||||||
|
dynamicLogWithPP pp { ppOutput = hPutStrLn h }
|
||||||
|
, manageHook = manageHook conf <+> manageDocks
|
||||||
|
, keys = liftM2 M.union (uncurry M.singleton . k) (keys conf)
|
||||||
|
}
|
||||||
|
|
||||||
-- |
|
-- |
|
||||||
-- Helper function which provides ToggleStruts keybinding
|
-- Helper function which provides ToggleStruts keybinding
|
||||||
--
|
--
|
||||||
toggleStrutsKey :: XConfig t -> M.Map (KeyMask, KeySym) (X ())
|
toggleStrutsKey :: XConfig t -> ((KeyMask, KeySym), X ())
|
||||||
toggleStrutsKey XConfig{modMask = modm} = M.fromList
|
toggleStrutsKey XConfig{modMask = modm} = ((modm, xK_b ), sendMessage ToggleStruts)
|
||||||
[ ((modm, xK_b ), sendMessage ToggleStruts) ]
|
|
||||||
|
|
||||||
------------------------------------------------------------------------
|
------------------------------------------------------------------------
|
||||||
|
|
||||||
@@ -218,16 +215,6 @@ toggleStrutsKey XConfig{modMask = modm} = M.fromList
|
|||||||
dynamicLog :: X ()
|
dynamicLog :: X ()
|
||||||
dynamicLog = dynamicLogWithPP defaultPP
|
dynamicLog = dynamicLogWithPP defaultPP
|
||||||
|
|
||||||
-- | 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,
|
-- | Format the current status using the supplied pretty-printing format,
|
||||||
-- and write it to stdout.
|
-- and write it to stdout.
|
||||||
dynamicLogWithPP :: PP -> X ()
|
dynamicLogWithPP :: PP -> X ()
|
||||||
|
Reference in New Issue
Block a user