summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
-rw-r--r--Plugins/MBox.hs43
-rw-r--r--Plugins/Monitors/MPD.hs10
-rw-r--r--README21
3 files changed, 58 insertions, 16 deletions
diff --git a/Plugins/MBox.hs b/Plugins/MBox.hs
index 3f7b70c..ce153e1 100644
--- a/Plugins/MBox.hs
+++ b/Plugins/MBox.hs
@@ -23,19 +23,52 @@ import Control.Exception (SomeException, handle, evaluate)
import System.Directory
import System.FilePath
+import System.Console.GetOpt
import System.INotify
+
import qualified Data.ByteString.Lazy.Char8 as B
+data Options = Options
+ { oAll :: Bool
+ , oDir :: FilePath
+ , oPrefix :: String
+ , oSuffix :: String
+ }
+
+defaults :: Options
+defaults = Options { oAll = False, oDir = "", oPrefix = "", oSuffix = "" }
+
+options :: [OptDescr (Options -> Options)]
+options =
+ [ Option "a" ["all"] (NoArg (\o -> o { oAll = True })) ""
+ , Option "d" ["dir"] (ReqArg (\x o -> o { oDir = x }) "") ""
+ , Option "p" ["prefix"] (ReqArg (\x o -> o { oPrefix = x }) "") ""
+ , Option "s" ["suffix"] (ReqArg (\x o -> o { oSuffix = x }) "") ""
+ ]
+
+parseOptions :: [String] -> IO Options
+parseOptions args =
+ case getOpt Permute options args of
+ (o, _, []) -> return $ foldr id defaults o
+ (_, _, errs) -> ioError . userError $ concat errs
+
-- | A list of display names, paths to mbox files and display colours,
--- followed by a directory to resolve relative path names (can be "")
-data MBox = MBox [(String, FilePath, String)] FilePath
+-- followed by a list of options.
+data MBox = MBox [(String, FilePath, String)] [String] String
deriving (Read, Show)
instance Exec MBox where
- start (MBox ms dir) cb = do
+ 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
+ allb = oAll opts
+ pref = oPrefix opts
+ suff = oSuffix opts
+
dirExists <- doesDirectoryExist dir
let ts = map (\(t, _, _) -> t) ms
sec = \(_, f, _) -> f
@@ -53,7 +86,9 @@ instance Exec MBox where
atomically $ writeTVar v (f, n)
changeLoop (mapM (fmap snd . readTVar) vs) $ \ns ->
- cb . unwords $ [ showC m n c | (m, n, c) <- zip3 ts ns cs, n /= 0 ]
+ let s = unwords [ showC m n c | (m, n, c) <- zip3 ts ns cs
+ , allb || n /= 0 ]
+ in cb (if length s == 0 then "" else pref ++ s ++ suff)
showC :: String -> Int -> String -> String
showC m n c =
diff --git a/Plugins/Monitors/MPD.hs b/Plugins/Monitors/MPD.hs
index 410662d..72b73d6 100644
--- a/Plugins/Monitors/MPD.hs
+++ b/Plugins/Monitors/MPD.hs
@@ -33,9 +33,9 @@ defaultOpts = MOpts { mPlaying = ">>", mStopped = "><", mPaused = "||" }
options :: [OptDescr (MOpts -> MOpts)]
options =
- [ Option ['P'] ["playing"] (ReqArg (\x o -> o { mPlaying = x }) "") ""
- , Option ['S'] ["stopped"] (ReqArg (\x o -> o { mStopped = x }) "") ""
- , Option ['Z'] ["paused"] (ReqArg (\x o -> o { mPaused = x }) "") ""
+ [ Option "P" ["playing"] (ReqArg (\x o -> o { mPlaying = x }) "") ""
+ , Option "S" ["stopped"] (ReqArg (\x o -> o { mStopped = x }) "") ""
+ , Option "Z" ["paused"] (ReqArg (\x o -> o { mPaused = x }) "") ""
]
runMPD :: [String] -> Monitor String
@@ -53,7 +53,7 @@ mopts argv =
(o, _, []) -> return $ foldr id defaultOpts o
(_, _, errs) -> ioError . userError $ concat errs
-parseMPD :: (M.Response M.Status) -> (M.Response (Maybe M.Song)) -> MOpts
+parseMPD :: M.Response M.Status -> M.Response (Maybe M.Song) -> MOpts
-> (Float, [String])
parseMPD (Left e) _ _ = (0, show e:repeat "")
parseMPD (Right st) song opts = (b, [ss, si, vol, len, lap, plen] ++ sf)
@@ -74,7 +74,7 @@ stateGlyph s o =
M.Paused -> mPaused o
M.Stopped -> mStopped o
-parseSong :: (M.Response (Maybe M.Song)) -> [String]
+parseSong :: M.Response (Maybe M.Song) -> [String]
parseSong (Left _) = repeat ""
parseSong (Right Nothing) = repeat ""
parseSong (Right (Just s)) =
diff --git a/README b/README
index 5d0a8ba..af979c9 100644
--- a/README
+++ b/README
@@ -473,22 +473,29 @@ Monitors have default aliases.
To activate, pass --flags="with_inotify" to "runhaskell Setup configure"
or to "cabal install".
-`MBox Mboxes BaseDir`
+`MBox Mboxes Opts Alias`
-- aliases to `MBox`
- Mboxes a list of mbox files of the form [("name", "path", "color")],
where name is the displayed name, path the absolute or relative (to
BaseDir) path of the mbox file, and color the color to use to display
the mail count (use an empty string for the default).
-- BaseDir is a string giving the base directory where mbox files with
- a relative path live. It can be empty if all your paths are
- absolute.
+- Opts is a possibly empty list of options, as flags. Possible values:
+ -a --all (no arg) Show all mailboxes, even if empty.
+ -d dir --dir dir a string giving the base directory where mbox files with
+ a relative path live.
+ -p prefix --prefix prefix a string giving a prefix for the list
+ of displayed mail coints
+ -s suffix --suffix suffix a string giving a suffix for the list
+ of displayed mail coints
- This plugin requires INOTIFY support in Linux kernel and hinotify library.
To activate, pass --flags="with_inotify" to "runhaskell Setup
configure" or to "cabal install".
- Example:
- `Run MBox [("I ", "inbox", "red"), ("O ", "/foo/mbox", "")] "/var/mail/"`
- will look for mails in /var/mail/inbox and /foo/mbox.
+ `Run MBox [("I ", "inbox", "red"), ("O ", "/foo/mbox", "")]
+ ["-d", "/var/mail/", "-p", " "] "mbox"`
+ will look for mails in `/var/mail/inbox` 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`.
### Monitor Plugins Commands Arguments