[Xmonad] Can I use xmobar with DynamicLog?

Spencer Janssen sjanssen at cse.unl.edu
Wed Sep 26 01:44:45 EDT 2007


On Monday 24 September 2007 15:55:25 Andrea Rossato wrote:
> 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

Here's a hack that seems to work.  Run with "xmonad | xmobar".

I'll comment tomorrow on how we might accomplish this without unsafePerformIO
hacks.


Cheers,
Spencer Janssen

-------------- 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 Control.Concurrent
import Foreign (unsafePerformIO)

import Plugins

data XLog = XLog
    deriving (Read)

instance Exec XLog where
    rate XLog = 10
    alias XLog = "xlog"
    run XLog = readMVar reading

reading :: MVar String
reading = unsafePerformIO $ do
    m <- newMVar ""
    let loop = do
                l <- getLine
                tryTakeMVar m
                putMVar m l
                loop
    forkIO loop
    return m
{-# NOINLINE reading #-}


More information about the Xmonad mailing list