diff options
Diffstat (limited to 'src')
| -rw-r--r-- | src/Environment.hs | 48 | ||||
| -rw-r--r-- | src/Plugins/BufferedPipeReader.hs | 4 | ||||
| -rw-r--r-- | src/Plugins/MarqueePipeReader.hs | 3 | ||||
| -rw-r--r-- | src/Plugins/PipeReader.hs | 3 | 
4 files changed, 55 insertions, 3 deletions
diff --git a/src/Environment.hs b/src/Environment.hs new file mode 100644 index 0000000..ebdf733 --- /dev/null +++ b/src/Environment.hs @@ -0,0 +1,48 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  XMobar.Environment +-- Copyright   :  (c) William Song +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Will Song <incertia@incertia.net> +-- Stability   :  stable +-- Portability :  portable +-- +-- A function to expand environment variables in strings +-- +----------------------------------------------------------------------------- +module Environment where + +import Data.Maybe           (fromMaybe) +import System.Environment   (lookupEnv) + +expandEnv :: String -> IO String +expandEnv "" = return "" +expandEnv (c:s) = case c of +  '$'       -> do +    envVar <- fromMaybe "" <$> lookupEnv e +    remainder <- expandEnv s' +    return $ envVar ++ remainder +    where (e, s') = getVar s +          getVar "" = ("", "") +          getVar ('{':s) = (takeUntil "}" s, drop 1 . dropUntil "}" $ s) +          getVar s = (takeUntil filterstr s, dropUntil filterstr s) +          filterstr = ",./? \t;:\"'~`!@#$%^&*()<>-+=\\|" +          takeUntil f = takeWhile (not . flip elem f) +          dropUntil f = dropWhile (not . flip elem f) + +  '\\' -> case s == "" of +    True  -> return "\\" +    False -> do +      remainder <- expandEnv $ drop 1 s +      return $ escString s ++ remainder +      where escString s = let (cc:ss) = s in +              case cc of +                't' -> "\t" +                'n' -> "\n" +                '$' -> "$" +                _   -> [cc] + +  _    -> do +    remainder <- expandEnv s +    return $ c : remainder diff --git a/src/Plugins/BufferedPipeReader.hs b/src/Plugins/BufferedPipeReader.hs index 9a7266e..b6cad9d 100644 --- a/src/Plugins/BufferedPipeReader.hs +++ b/src/Plugins/BufferedPipeReader.hs @@ -20,6 +20,7 @@ import Control.Concurrent.STM  import System.IO  import System.IO.Unsafe(unsafePerformIO) +import Environment  import Plugins  import Signal @@ -51,7 +52,8 @@ instance Exec BufferedPipeReader where          reader :: (Int, Bool, FilePath) -> TChan (Int, Bool, String) -> IO ()          reader p@(to, tg, fp) tc = do -            openFile fp ReadWriteMode >>= hGetLineSafe >>= \dt -> +            fp' <- expandEnv fp +            openFile fp' ReadWriteMode >>= hGetLineSafe >>= \dt ->                  atomically $ writeTChan tc (to, tg, dt)              reader p tc diff --git a/src/Plugins/MarqueePipeReader.hs b/src/Plugins/MarqueePipeReader.hs index 8120c84..0b3a710 100644 --- a/src/Plugins/MarqueePipeReader.hs +++ b/src/Plugins/MarqueePipeReader.hs @@ -15,6 +15,7 @@  module Plugins.MarqueePipeReader where  import System.IO (openFile, IOMode(ReadWriteMode), Handle) +import Environment  import Plugins (tenthSeconds, Exec(alias, start), hGetLineSafe)  import System.Posix.Files (getFileStatus, isNamedPipe)  import Control.Concurrent(forkIO, threadDelay) @@ -32,7 +33,7 @@ data MarqueePipeReader = MarqueePipeReader String (Length, Rate, Separator) Stri  instance Exec MarqueePipeReader where      alias (MarqueePipeReader _ _ a)    = a      start (MarqueePipeReader p (len, rate, sep) _) cb = do -        let (def, pipe) = split ':' p +        (def, pipe) <- split ':' <$> expandEnv p          unless (null def) (cb def)          checkPipe pipe          h <- openFile pipe ReadWriteMode diff --git a/src/Plugins/PipeReader.hs b/src/Plugins/PipeReader.hs index c3e491a..653a72d 100644 --- a/src/Plugins/PipeReader.hs +++ b/src/Plugins/PipeReader.hs @@ -16,6 +16,7 @@ module Plugins.PipeReader where  import System.IO  import Plugins +import Environment  import System.Posix.Files  import Control.Concurrent(threadDelay)  import Control.Exception @@ -27,7 +28,7 @@ data PipeReader = PipeReader String String  instance Exec PipeReader where      alias (PipeReader _ a)    = a      start (PipeReader p _) cb = do -        let (def, pipe) = split ':' p +        (def, pipe) <- split ':' <$> expandEnv p          unless (null def) (cb def)          checkPipe pipe          h <- openFile pipe ReadWriteMode  | 
