From 147dd90ee7e706364f5c96a66b4a1aead8bef930 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Daniel=20Gr=C3=B6ber?= Date: Tue, 19 Aug 2014 04:49:44 +0200 Subject: [PATCH] Remove dedicated exception handling in `check` completely Exceptions are already caught at the top level so this is unnecessary. --- Language/Haskell/GhcMod/Check.hs | 5 ++--- Language/Haskell/GhcMod/Types.hs | 3 --- Language/Haskell/GhcMod/Utils.hs | 13 ------------- src/GHCMod.hs | 2 -- 4 files changed, 2 insertions(+), 21 deletions(-) diff --git a/Language/Haskell/GhcMod/Check.hs b/Language/Haskell/GhcMod/Check.hs index 88ace61..c2ea2a4 100644 --- a/Language/Haskell/GhcMod/Check.hs +++ b/Language/Haskell/GhcMod/Check.hs @@ -12,7 +12,6 @@ import qualified GHC as G import Language.Haskell.GhcMod.Logger import Language.Haskell.GhcMod.Monad (IOish, GhcModT, overrideGhcUserOptions) import Language.Haskell.GhcMod.Target (setTargetFiles) -import Language.Haskell.GhcMod.Utils (liftExceptions) ---------------------------------------------------------------- @@ -22,7 +21,7 @@ checkSyntax :: IOish m => [FilePath] -- ^ The target files. -> GhcModT m String checkSyntax [] = return "" -checkSyntax files = liftExceptions $ either id id <$> check files +checkSyntax files = either id id <$> check files ---------------------------------------------------------------- @@ -47,7 +46,7 @@ expandTemplate :: IOish m => [FilePath] -- ^ The target files. -> GhcModT m String expandTemplate [] = return "" -expandTemplate files = liftExceptions $ either id id <$> expand files +expandTemplate files = either id id <$> expand files ---------------------------------------------------------------- diff --git a/Language/Haskell/GhcMod/Types.hs b/Language/Haskell/GhcMod/Types.hs index 8313aae..6f7dbe9 100644 --- a/Language/Haskell/GhcMod/Types.hs +++ b/Language/Haskell/GhcMod/Types.hs @@ -2,15 +2,12 @@ module Language.Haskell.GhcMod.Types where import Data.List (intercalate) import qualified Data.Map as M -import Control.Exception (SomeException) import Control.Monad.Error (Error(..)) import PackageConfig (PackageConfig) data GhcModError = GMENoMsg -- ^ Unknown error - | GMEException SomeException - -- ^ Regular exception lifted by 'liftExceptions' | GMEString { gmeMsg :: String } -- ^ Some Error with a message. These are produced mostly by -- 'fail' calls on GhcModT. diff --git a/Language/Haskell/GhcMod/Utils.hs b/Language/Haskell/GhcMod/Utils.hs index 30597f9..37a33b1 100644 --- a/Language/Haskell/GhcMod/Utils.hs +++ b/Language/Haskell/GhcMod/Utils.hs @@ -2,7 +2,6 @@ module Language.Haskell.GhcMod.Utils where import MonadUtils (MonadIO, liftIO) -import Exception (ExceptionMonad, gtry) import Control.Exception import Control.Monad.Error (MonadError(..), Error(..)) import System.Directory (getCurrentDirectory, setCurrentDirectory) @@ -10,7 +9,6 @@ import System.Process (readProcessWithExitCode) import System.Exit (ExitCode(..)) import System.IO (hPutStrLn, stderr) import System.IO.Error (tryIOError) -import Language.Haskell.GhcMod.Types -- dropWhileEnd is not provided prior to base 4.5.0.0. dropWhileEnd :: (a -> Bool) -> [a] -> [a] @@ -64,14 +62,3 @@ liftIOExceptions action = do Left e -> case show e of "" -> throwError $ noMsg msg -> throwError $ strMsg msg - --- | Exceptions thrown in the computation passed to this function will be --- converted to 'MonadError' failures using 'throwError'. -liftExceptions :: (MonadIO m, ExceptionMonad m, MonadError GhcModError m) - => m a - -> m a -liftExceptions action = do - res <- gtry action - case res of - Right a -> return a - Left e -> throwError $ GMEException e diff --git a/src/GHCMod.hs b/src/GHCMod.hs index 41e9e38..5d5b414 100644 --- a/src/GHCMod.hs +++ b/src/GHCMod.hs @@ -141,8 +141,6 @@ main = flip E.catches handlers $ do cmd -> E.throw (NoSuchCommand cmd) case res of Right s -> putStr s - Left (GMEException e) -> - hPutStrLn stderr $ "Exception: " ++ show e Left (GMENoMsg) -> hPutStrLn stderr "Unknown error" Left (GMEString msg) ->