----------------------------------------------------------------------------- -- | -- Module : Plugins.XMonadLog -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- 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