diff options
| author | Adam Vogt <vogt.adam@gmail.com> | 2014-02-25 01:27:03 -0500 | 
|---|---|---|
| committer | Adam Vogt <vogt.adam@gmail.com> | 2014-02-25 12:29:04 -0500 | 
| commit | dc670b15ba8b279e1119ac895dd681feab4e3939 (patch) | |
| tree | 59ac3f96a4ab84bf43af7d88dc256d4353d258d1 /src/Plugins | |
| parent | b739857ed4d2282e80a8908165ffda82fcc3ecdc (diff) | |
| download | xmobar-dc670b15ba8b279e1119ac895dd681feab4e3939.tar.gz xmobar-dc670b15ba8b279e1119ac895dd681feab4e3939.tar.bz2 | |
have disabled plugins still accept input
This change lets xmobar compiled without -fwith_inotify accept a config
that mentions the Mail plugin with a warning (and display an
Updating...).
Diffstat (limited to 'src/Plugins')
| -rw-r--r-- | src/Plugins/DateZone.hs | 28 | ||||
| -rw-r--r-- | src/Plugins/MBox.hs | 13 | ||||
| -rw-r--r-- | src/Plugins/Mail.hs | 12 | 
3 files changed, 45 insertions, 8 deletions
| diff --git a/src/Plugins/DateZone.hs b/src/Plugins/DateZone.hs index 79596c9..f1737fb 100644 --- a/src/Plugins/DateZone.hs +++ b/src/Plugins/DateZone.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-}  {-# LANGUAGE DoAndIfThenElse #-}  -----------------------------------------------------------------------------  -- | @@ -23,30 +24,37 @@ module Plugins.DateZone (DateZone(..)) where  import Plugins -import Localize +#ifdef DATEZONE  import Control.Concurrent.STM +import System.IO.Unsafe + +import Localize  import Data.Time.LocalTime  import Data.Time.Format  import Data.Time.LocalTime.TimeZone.Olson  import Data.Time.LocalTime.TimeZone.Series -import System.IO.Unsafe  import System.Locale (TimeLocale) +#else +import System.IO +import Plugins.Date +#endif -{-# NOINLINE localeLock #-} --- ensures that only one plugin instance sets the locale -localeLock :: TMVar Bool -localeLock = unsafePerformIO (newTMVarIO False) -  data DateZone = DateZone String String String String Int      deriving (Read, Show)  instance Exec DateZone where      alias (DateZone _ _ _ a _) = a +#ifndef DATEZONE +    start (DateZone f _ _ a r) cb = do +      hPutStrLn stderr $ "Warning: DateZone plugin needs -fwith_datezone."++ +                  " Using Date plugin instead." +      start (Date f a r) cb +#else      start (DateZone f l z _ r) cb = do        lock <- atomically $ takeTMVar localeLock        setupTimeLocale l @@ -60,6 +68,11 @@ instance Exec DateZone where        where go func = func >>= cb >> tenthSeconds r >> go func +{-# NOINLINE localeLock #-} +-- ensures that only one plugin instance sets the locale +localeLock :: TMVar Bool +localeLock = unsafePerformIO (newTMVarIO False) +  date :: String -> TimeLocale -> IO String  date format loc = getZonedTime >>= return . formatTime loc format @@ -67,3 +80,4 @@ dateZone :: String -> TimeLocale -> TimeZoneSeries -> IO String  dateZone format loc timeZone = getZonedTime >>= return . formatTime loc format . utcToLocalTime' timeZone . zonedTimeToUTC  --   zonedTime <- getZonedTime  --   return $ formatTime loc format $ utcToLocalTime' timeZone $ zonedTimeToUTC zonedTime +#endif diff --git a/src/Plugins/MBox.hs b/src/Plugins/MBox.hs index c4335f7..d9a9765 100644 --- a/src/Plugins/MBox.hs +++ b/src/Plugins/MBox.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-}  -----------------------------------------------------------------------------  -- |  -- Module      :  Plugins.MBox @@ -16,6 +17,7 @@ module Plugins.MBox (MBox(..)) where  import Prelude  import Plugins +#ifdef INOTIFY  import Plugins.Utils (changeLoop, expandHome)  import Control.Monad (when) @@ -57,6 +59,10 @@ parseOptions args =      (o, _, []) -> return $ foldr id defaults o      (_, _, errs) -> ioError . userError $ concat errs +#else +import System.IO +#endif +  -- | A list of display names, paths to mbox files and display colours,  -- followed by a list of options.  data MBox = MBox [(String, FilePath, String)] [String] String @@ -64,8 +70,12 @@ data MBox = MBox [(String, FilePath, String)] [String] String  instance Exec MBox where    alias (MBox _ _ a) = a +#ifndef INOTIFY +  start _ _ = do +    hPutStrLn stderr $ "Warning: xmobar is not compiled with -fwith_inotify" ++ +          " but the MBox plugin requires it" +#else    start (MBox boxes args _) cb = do -      opts <- parseOptions args      let showAll = oAll opts          prefix = oPrefix opts @@ -109,3 +119,4 @@ handleNotification v _ =  do    (p, _) <- atomically $ readTVar v    n <- countMails p    atomically $ writeTVar v (p, n) +#endif diff --git a/src/Plugins/Mail.hs b/src/Plugins/Mail.hs index d146d17..d4abb0b 100644 --- a/src/Plugins/Mail.hs +++ b/src/Plugins/Mail.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-}  -----------------------------------------------------------------------------  -- |  -- Module      :  Plugins.Mail @@ -15,6 +16,7 @@  module Plugins.Mail where  import Plugins +#ifdef INOTIFY  import Plugins.Utils (expandHome, changeLoop)  import Control.Monad @@ -27,6 +29,10 @@ import System.INotify  import Data.List (isPrefixOf)  import Data.Set (Set)  import qualified Data.Set as S +#else +import System.IO +#endif +  -- | A list of mail box names and paths to maildirs.  data Mail = Mail [(String, FilePath)] String @@ -34,6 +40,11 @@ data Mail = Mail [(String, FilePath)] String  instance Exec Mail where      alias (Mail _ a) = a +#ifndef INOTIFY +    start _ _ = do +        hPutStrLn stderr $ "Warning: xmobar is not compiled with -fwith_inotify," +                        ++ " but the Mail plugin requires it." +#else      start (Mail ms _) cb = do          vs <- mapM (const $ newTVarIO S.empty) ms @@ -65,3 +76,4 @@ handle v e = atomically $ modifyTVar v $ case e of   where      delete = S.delete (filePath e)      create = S.insert (filePath e) +#endif | 
