[Xmonad] Can I use xmobar with DynamicLog?

Andrea Rossato mailing_list at istitutocolli.org
Mon Sep 24 16:55:25 EDT 2007


On Mon, Sep 24, 2007 at 10:23:02PM +0200, Andrea Rossato wrote:
> On Mon, Sep 24, 2007 at 06:30:54PM +0100, Andy Gimblett wrote:
> > Andrea, Why can xmobar read from a file but not a named pipe?
> 
> To read a named pipe you must wait for output. 

by the way I've tried. Attached you'll find my attempt that reads from
~/.xmobar-status.

Save the file in Plugins/
In Config.hs:
import Plugins.XMonadLog

and change the runnableTyope to something like:
runnableTypes :: (Command,(Monitors,(XLog,())))

in the configuration, commands, add:
, Run XLog
and
%xlog%
in the template.

If you move around through workspaces maybe xmobar will be able to
display something, but it won't last...

Andrea
-------------- next part --------------
-----------------------------------------------------------------------------
-- |
-- Module      :  Plugins.XMonadLog
-- Copyright   :  (c) Andrea Rossato
-- License     :  BSD-style (see LICENSE)
-- 
-- Maintainer  :  Andrea Rossato <andrea.rossato at unibz.it>
-- Stability   :  unstable
-- Portability :  unportable
--
-- A plugin example for Xmobar, a text based status bar 
--
-----------------------------------------------------------------------------

module Plugins.XMonadLog where

import Prelude hiding (catch)
import Control.Concurrent
import Control.Exception
--import Data.Maybe (fromMaybe)
import System.Environment
import System.Posix.Files (fileExist)
--import System.Posix.IO
import System.IO
import System.Exit

import Plugins

data XLog = XLog
    deriving (Read)

instance Exec XLog where
    run XLog = doXlog
    rate XLog = 10
    alias XLog = "xlog"

doXlog :: IO String
doXlog = do
  h <- getEnv "HOME"
  let fp = h ++ "/.xmonad-status" 
  b <- fileExist h
  if b
     then do 
       var <- newMVar ""
       t <- forkIO (block $ readPipe var fp)
       threadDelay (5 * 100000)
       throwTo t (ExitException ExitSuccess)
       mb <- readMVar var
       return mb -- $ fromMaybe "" mb
     else return []

readPipe :: MVar String -> FilePath -> IO ()
readPipe var fp = do
  catch (unblock go) (const $ return ())
  where go = do
          fh <- openFile fp ReadMode
          str <- hGetLine fh
          modifyMVar_ var (\_ -> return str)
          hClose fh


More information about the Xmonad mailing list