summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authorJose Antonio Ortega Ruiz <jao@gnu.org>2010-12-11 21:41:08 +0100
committerJose Antonio Ortega Ruiz <jao@gnu.org>2010-12-11 21:41:08 +0100
commit4b26940ed310b9d7119eaf83c18526eb5ec38cd5 (patch)
tree2f9be0ff20806b9330d2125cbeae9afac5101cd3
parent643b9235844d730aa9f0340da2a290a3c42bbccc (diff)
downloadxmobar-4b26940ed310b9d7119eaf83c18526eb5ec38cd5.tar.gz
xmobar-4b26940ed310b9d7119eaf83c18526eb5ec38cd5.tar.bz2
MBox: support for ~ paths and skipping non-existing mboxes
-rw-r--r--NEWS3
-rw-r--r--Plugins/MBox.hs22
-rw-r--r--Plugins/Mail.hs16
-rw-r--r--Plugins/Utils.hs39
-rw-r--r--README10
5 files changed, 56 insertions, 34 deletions
diff --git a/NEWS b/NEWS
index 295a99f..10038c3 100644
--- a/NEWS
+++ b/NEWS
@@ -33,6 +33,8 @@ _New features_
present CPUs (Ben Boeckel).
- CpuFreq monitor uses just one decimal digit for GHz values (Petr
Rockai).
+ - Mail plugin expands paths starting with "~/" (Ben Boeckel). Ditto
+ MBox.
- New compilation flag, `all_extensions`.
- Documentation and website updates.
@@ -46,6 +48,7 @@ _Bug fixes_
boxes in monitors (Norbert Zeh).
- TopMem and TopProc now use the `-L` and `-H` options correctly for
memory template fields.
+ - MBox skips non-existent mbox paths instead of hanging.
[issue 23]: http://code.google.com/p/xmobar/issues/detail?id=23
[issue 24]: http://code.google.com/p/xmobar/issues/detail?id=24
diff --git a/Plugins/MBox.hs b/Plugins/MBox.hs
index 265e860..f24fa1c 100644
--- a/Plugins/MBox.hs
+++ b/Plugins/MBox.hs
@@ -16,6 +16,7 @@ module Plugins.MBox (MBox(..)) where
import Prelude hiding (catch)
import Plugins
+import Plugins.Utils (changeLoop, expandHome)
import Control.Monad
import Control.Concurrent.STM
@@ -65,7 +66,6 @@ data MBox = MBox [(String, FilePath, String)] [String] String
instance Exec MBox where
alias (MBox _ _ a) = a
start (MBox ms args _) cb = do
- vs <- mapM (const $ newTVarIO ("", 0 :: Int)) ms
opts <- parseOptions args -- $ words args
let dir = oDir opts
@@ -76,24 +76,26 @@ instance Exec MBox where
dirExists <- doesDirectoryExist dir
let ts = map (\(t, _, _) -> t) ms
- sec = \(_, f, _) -> f
+ sec (_, f, _) = f
md = if dirExists then (dir </>) . sec else sec
fs = map md ms
cs = map (\(_, _, c) -> c) ms
ev = [CloseWrite]
+ xfs <- mapM expandHome fs
+ vs <- replicateM (length xfs) (newTVarIO ("", 0 :: Int))
i <- initINotify
- zipWithM_ (\f v -> addWatch i ev f (handleNotification v)) fs vs
- forM_ (zip fs vs) $ \(f, v) -> do
+ forM_ (zip xfs vs) $ \(f, v) -> do
exists <- doesFileExist f
n <- if exists then countMails f else return 0
atomically $ writeTVar v (f, n)
+ when exists $ addWatch i ev f (handleNotification v) >> return ()
changeLoop (mapM (fmap snd . readTVar) vs) $ \ns ->
let s = unwords [ showC uniq m n c | (m, n, c) <- zip3 ts ns cs
, allb || n /= 0 ]
- in cb (if length s == 0 then "" else pref ++ s ++ suff)
+ in cb (if null s then "" else pref ++ s ++ suff)
showC :: Bool -> String -> Int -> String -> String
showC u m n c =
@@ -112,13 +114,3 @@ handleNotification v _ = do
(p, _) <- atomically $ readTVar v
n <- countMails p
atomically $ writeTVar v (p, n)
-
-changeLoop :: Eq a => STM a -> (a -> IO ()) -> IO ()
-changeLoop s f = atomically s >>= go
- where
- go old = do
- f old
- go =<< atomically (do
- new <- s
- guard (new /= old)
- return new)
diff --git a/Plugins/Mail.hs b/Plugins/Mail.hs
index 89cac30..38cdaae 100644
--- a/Plugins/Mail.hs
+++ b/Plugins/Mail.hs
@@ -16,12 +16,12 @@ module Plugins.Mail where
import Prelude hiding (catch)
import Plugins
+import Plugins.Utils (expandHome, changeLoop)
import Control.Monad
import Control.Concurrent.STM
import System.Directory
-import System.Environment
import System.FilePath
import System.INotify
@@ -58,10 +58,6 @@ instance Exec Mail where
modifyTVar :: TVar a -> (a -> a) -> STM ()
modifyTVar v f = readTVar v >>= writeTVar v . f
-expandHome :: FilePath -> IO FilePath
-expandHome ('~':'/':path) = fmap (</> path) (getEnv "HOME")
-expandHome p = return p
-
handle :: TVar (Set String) -> Event -> IO ()
handle v e = atomically $ modifyTVar v $ case e of
Created {} -> create
@@ -72,13 +68,3 @@ handle v e = atomically $ modifyTVar v $ case e of
where
delete = S.delete (filePath e)
create = S.insert (filePath e)
-
-changeLoop :: Eq a => STM a -> (a -> IO ()) -> IO ()
-changeLoop s f = atomically s >>= go
- where
- go old = do
- f old
- go =<< atomically (do
- new <- s
- guard (new /= old)
- return new)
diff --git a/Plugins/Utils.hs b/Plugins/Utils.hs
new file mode 100644
index 0000000..1dbcd40
--- /dev/null
+++ b/Plugins/Utils.hs
@@ -0,0 +1,39 @@
+------------------------------------------------------------------------------
+-- |
+-- Module: Plugins.Utils
+-- Copyright: (c) 2010 Jose Antonio Ortega Ruiz
+-- License: BSD3-style (see LICENSE)
+--
+-- Maintainer: Jose A Ortega Ruiz <jao@gnu.org>
+-- Stability: unstable
+-- Portability: unportable
+-- Created: Sat Dec 11, 2010 20:55
+--
+--
+-- Miscellaneous utility functions
+--
+------------------------------------------------------------------------------
+
+
+module Plugins.Utils (expandHome, changeLoop) where
+
+import Control.Monad
+import Control.Concurrent.STM
+
+import System.Environment
+import System.FilePath
+
+
+expandHome :: FilePath -> IO FilePath
+expandHome ('~':'/':path) = fmap (</> path) (getEnv "HOME")
+expandHome p = return p
+
+changeLoop :: Eq a => STM a -> (a -> IO ()) -> IO ()
+changeLoop s f = atomically s >>= go
+ where
+ go old = do
+ f old
+ go =<< atomically (do
+ new <- s
+ guard (new /= old)
+ return new)
diff --git a/README b/README
index 5201334..132e44a 100644
--- a/README
+++ b/README
@@ -546,11 +546,12 @@ Monitors have default aliases.
`Mail Args`
- aliases to `Mail`
-- Args: list of maildirs in form `[("name1","path1"),("name2","path2")]`
+- Args: list of maildirs in form
+ `[("name1","path1"),("name2","path2")]`. Paths may start with a '~'
+ to expand to the user's home directory.
- This plugin requires inotify support in your linux kernel and the
[hinotify] package. To activate, pass `--flags="with_inotify"`
during compilation.
-- Paths may start with a '~' to expand to the user's home directory.
`MBox Mboxes Opts Alias`
@@ -566,15 +567,16 @@ Monitors have default aliases.
of displayed mail coints
-s suffix --suffix suffix a string giving a suffix for the list
of displayed mail coints
+- Paths may start with a '~' to expand to the user's home directory.
- This plugin requires inotify support in your linux kernel and the
[hinotify] package. To activate, pass `--flags="with_inotify"`
during compilation.
- Example. The following command look for mails in `/var/mail/inbox`
- and `/foo/mbox`, and will put a space in front of the printed string
+ and `~/foo/mbox`, and will put a space in front of the printed string
(when it's not empty); it can be used in the template with the alias
`mbox`:
- Run MBox [("I ", "inbox", "red"), ("O ", "/foo/mbox", "")]
+ Run MBox [("I ", "inbox", "red"), ("O ", "~/foo/mbox", "")]
["-d", "/var/mail/", "-p", " "] "mbox"
## Monitor Plugins Commands Arguments