Skip to content
John J. Foerch edited this page Dec 18, 2017 · 2 revisions

Mowedline works great as a statbar for XMonad. Here is some code to help you get started.

Respect Mowedline's struts

Use XMonad.Hooks.EwmhDesktops to let XMonad leave room on the screen for Mowedline.

Connect logHook to Mowedline

Create ~/.xmonad/lib/XMonad/Util/Mowedline.hs:

{-# LANGUAGE OverloadedStrings #-}

module XMonad.Util.Mowedline
  (mowedlineUpdate) where

import qualified Data.Map as M

import DBus
import DBus.Client

import XMonad

import qualified XMonad.Util.ExtensibleState as XS


newtype MowedlineConnection = MowedlineConnection { getMowedlineConnection :: Maybe Client }
  deriving (Typeable)
instance ExtensionClass MowedlineConnection where
  initialValue = MowedlineConnection Nothing

newtype MowedlineState = MowedlineState { getMowedlineState :: M.Map String String }
  deriving (Typeable)
instance ExtensionClass MowedlineState where
  initialValue = MowedlineState M.empty

mowedlineUpdate :: String -> String -> X ()
mowedlineUpdate widget value = do
  client' <- XS.get :: X MowedlineConnection
  let client = getMowedlineConnection client'
  case client of
    Nothing -> do
      dbusClient <- io connectSession
      XS.put $ MowedlineConnection (Just dbusClient)
      mowedlineUpdate widget value
    Just client -> do
      state <- XS.get :: X MowedlineState
      let mv = getMowedlineState state
      case M.lookup widget mv of
        Just v | v == value -> return ()
        otherwise -> do
          io $ callNoReply client (methodCall "/net/retroj/mowedline"
                                   "net.retroj.mowedline" "update")
                           { methodCallDestination = Just "net.retroj.mowedline"
                           , methodCallBody = [toVariant widget, toVariant value]
                           }
          XS.put $ MowedlineState (M.insert widget value mv)

Put this in your ~/.xmonad/xmonad.hs:

import XMonad.Util.Mowedline

Now send information to Mowedline from your logHook:

import XMonad.Hooks.DynamicLog

workspacesLoggerPP :: PP
workspacesLoggerPP = defaultPP
        { ppCurrent         = wrap "[" "]"
        , ppHiddenNoWindows = const ""
        , ppUrgent          = ('!':)
        , ppWsSep           = " "
        , ppSep             = " "
        , ppLayout          = const ""
        , ppOrder           = \(a:b:_:c) -> a:b:c
        }

main = xmonad $ defaultConfig
    { ...
    , logHook = dynamicLogString workspacesLoggerPP >>=
                  mowedlineUpdate "workspaces"
    ...
    }