summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authorJose Antonio Ortega Ruiz <jao@gnu.org>2013-02-04 01:15:40 +0100
committerJose Antonio Ortega Ruiz <jao@gnu.org>2013-02-04 01:15:40 +0100
commit2991a3c18b00bb41197e6a688c4ce07ad52057c0 (patch)
tree7e1b2314940b9c62ce474fd14901b6c24732195e
parentfdc91a62c37bd475440bee275e6b0329833f6af4 (diff)
downloadxmobar-2991a3c18b00bb41197e6a688c4ce07ad52057c0.tar.gz
xmobar-2991a3c18b00bb41197e6a688c4ce07ad52057c0.tar.bz2
Removing uneeded uses of hiding (catch)
-rw-r--r--src/IPC/DBus.hs8
-rw-r--r--src/Plugins/Mail.hs1
-rw-r--r--src/Plugins/Monitors/Volume.hs11
3 files changed, 10 insertions, 10 deletions
diff --git a/src/IPC/DBus.hs b/src/IPC/DBus.hs
index 60544a9..b95e59f 100644
--- a/src/IPC/DBus.hs
+++ b/src/IPC/DBus.hs
@@ -12,15 +12,13 @@
--
-----------------------------------------------------------------------------
-module IPC.DBus ( runIPC ) where
-
-import Prelude hiding (catch)
+module IPC.DBus (runIPC) where
import DBus
import DBus.Client
import Control.Monad (when)
import Control.Concurrent.STM
-import Control.Exception (catch)
+import Control.Exception (handle)
import System.IO (stderr, hPutStrLn)
import Signal
@@ -35,7 +33,7 @@ interfaceName :: InterfaceName
interfaceName = interfaceName_ "org.Xmobar.Control"
runIPC :: TMVar SignalType -> IO ()
-runIPC mvst = catch exportConnection printException
+runIPC mvst = handle printException exportConnection
where
printException :: ClientError -> IO ()
printException = hPutStrLn stderr . clientErrorMessage
diff --git a/src/Plugins/Mail.hs b/src/Plugins/Mail.hs
index b11b7ad..d146d17 100644
--- a/src/Plugins/Mail.hs
+++ b/src/Plugins/Mail.hs
@@ -14,7 +14,6 @@
module Plugins.Mail where
-import Prelude hiding (catch)
import Plugins
import Plugins.Utils (expandHome, changeLoop)
diff --git a/src/Plugins/Monitors/Volume.hs b/src/Plugins/Monitors/Volume.hs
index 23dc348..f3d0f4c 100644
--- a/src/Plugins/Monitors/Volume.hs
+++ b/src/Plugins/Monitors/Volume.hs
@@ -19,7 +19,7 @@ import Control.Monad ( join, liftM2, liftM3, mplus )
import Data.Traversable (sequenceA)
import Plugins.Monitors.Common
import Sound.ALSA.Mixer
-import Sound.ALSA.Exception ( catch )
+import qualified Sound.ALSA.Exception as AE
import System.Console.GetOpt
volumeConfig :: IO MConfig
@@ -124,10 +124,12 @@ runVolume mixerName controlName argv = do
where
volumeControl :: Maybe Control -> Maybe Volume
- volumeControl c = join $ (playback . volume <$> c) `mplus` (common . volume <$> c)
+ volumeControl c = join $
+ (playback . volume <$> c) `mplus` (common . volume <$> c)
switchControl :: Maybe Control -> Maybe Switch
- switchControl c = join $ (playback . switch <$> c) `mplus` (common . switch <$> c)
+ switchControl c = join $
+ (playback . switch <$> c) `mplus` (common . switch <$> c)
liftMaybe :: Maybe (IO (a,b)) -> IO (Maybe a, Maybe b)
liftMaybe = fmap (liftM2 (,) (fmap fst) (fmap snd)) . sequenceA
@@ -138,7 +140,8 @@ runVolume mixerName controlName argv = do
getDB :: Maybe Volume -> Monitor (Maybe Integer)
getDB Nothing = return Nothing
- getDB (Just v) = io $ catch (getChannel FrontLeft $ dB v) (const $ return $ Just 0)
+ getDB (Just v) = io $ AE.catch (getChannel FrontLeft $ dB v)
+ (const $ return $ Just 0)
getVal :: Maybe Volume -> Monitor (Maybe Integer)
getVal Nothing = return Nothing