summaryrefslogtreecommitdiffhomepage
path: root/Plugins/MBox.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Plugins/MBox.hs')
-rw-r--r--Plugins/MBox.hs22
1 files changed, 7 insertions, 15 deletions
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)