summaryrefslogtreecommitdiffhomepage
path: root/src/Xmobar/System
diff options
context:
space:
mode:
Diffstat (limited to 'src/Xmobar/System')
-rw-r--r--src/Xmobar/System/DBus.hs10
-rw-r--r--src/Xmobar/System/Environment.hs9
2 files changed, 11 insertions, 8 deletions
diff --git a/src/Xmobar/System/DBus.hs b/src/Xmobar/System/DBus.hs
index 103a5a9..90bee2a 100644
--- a/src/Xmobar/System/DBus.hs
+++ b/src/Xmobar/System/DBus.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE ScopedTypeVariables #-}
-----------------------------------------------------------------------------
-- |
-- Module : DBus
@@ -17,9 +18,10 @@ module Xmobar.System.DBus (runIPC) where
import DBus
import DBus.Client hiding (interfaceName)
import qualified DBus.Client as DC
+import DBus.Socket
import Data.Maybe (isNothing)
import Control.Concurrent.STM
-import Control.Exception (handle)
+import Control.Exception
import System.IO (stderr, hPutStrLn)
import Control.Monad.IO.Class (liftIO)
@@ -35,10 +37,10 @@ interfaceName :: InterfaceName
interfaceName = interfaceName_ "org.Xmobar.Control"
runIPC :: TMVar SignalType -> IO ()
-runIPC mvst = handle printException exportConnection
+runIPC mvst = exportConnection `catches` [
+ Handler(\ (ex :: ClientError) -> hPutStrLn stderr (clientErrorMessage ex)),
+ Handler(\ (ex :: SocketError) -> hPutStrLn stderr (socketErrorMessage ex))]
where
- printException :: ClientError -> IO ()
- printException = hPutStrLn stderr . clientErrorMessage
exportConnection = do
client <- connectSession
requestName client busName [ nameDoNotQueue ]
diff --git a/src/Xmobar/System/Environment.hs b/src/Xmobar/System/Environment.hs
index 25802fe..0491bcc 100644
--- a/src/Xmobar/System/Environment.hs
+++ b/src/Xmobar/System/Environment.hs
@@ -13,14 +13,14 @@
-----------------------------------------------------------------------------
module Xmobar.System.Environment(expandEnv) where
-import Data.Maybe (fromMaybe)
-import System.Environment (lookupEnv)
+import qualified Data.Maybe as M
+import qualified System.Environment as E
expandEnv :: String -> IO String
expandEnv "" = return ""
expandEnv (c:s) = case c of
'$' -> do
- envVar <- fromMaybe "" <$> lookupEnv e
+ envVar <- M.fromMaybe "" <$> E.lookupEnv e
remainder <- expandEnv s'
return $ envVar ++ remainder
where (e, s') = getVar s
@@ -36,12 +36,13 @@ expandEnv (c:s) = case c of
False -> do
remainder <- expandEnv $ drop 1 s
return $ escString s ++ remainder
- where escString s' = let (cc:_) = s' in
+ where escString (cc:_) =
case cc of
't' -> "\t"
'n' -> "\n"
'$' -> "$"
_ -> [cc]
+ escString [] = ""
_ -> do
remainder <- expandEnv s