withLogger handles errors.

This commit is contained in:
Kazu Yamamoto 2014-04-28 13:52:28 +09:00
parent 000076223f
commit fc570551a2
4 changed files with 23 additions and 27 deletions

View File

@ -5,7 +5,7 @@ module Language.Haskell.GhcMod.Check (
, expand , expand
) where ) where
import Exception (ghandle) import Control.Applicative ((<$>))
import GHC (Ghc) import GHC (Ghc)
import Language.Haskell.GhcMod.ErrMsg import Language.Haskell.GhcMod.ErrMsg
import Language.Haskell.GhcMod.GHCApi import Language.Haskell.GhcMod.GHCApi
@ -23,7 +23,7 @@ checkSyntax :: Options
checkSyntax _ _ [] = return "" checkSyntax _ _ [] = return ""
checkSyntax opt cradle files = withGHC sessionName $ do checkSyntax opt cradle files = withGHC sessionName $ do
initializeFlagsWithCradle opt cradle initializeFlagsWithCradle opt cradle
check opt files either id id <$> check opt files
where where
sessionName = case files of sessionName = case files of
[file] -> file [file] -> file
@ -35,9 +35,9 @@ checkSyntax opt cradle files = withGHC sessionName $ do
-- Warnings and errors are returned. -- Warnings and errors are returned.
check :: Options check :: Options
-> [FilePath] -- ^ The target files. -> [FilePath] -- ^ The target files.
-> Ghc String -> Ghc (Either String String)
check opt fileNames = ghandle (handleErrMsg opt) $ check opt fileNames = withLogger opt setAllWaringFlags $
withLogger opt setAllWaringFlags $ setTargetFiles fileNames setTargetFiles fileNames
---------------------------------------------------------------- ----------------------------------------------------------------
@ -49,7 +49,7 @@ expandTemplate :: Options
expandTemplate _ _ [] = return "" expandTemplate _ _ [] = return ""
expandTemplate opt cradle files = withGHC sessionName $ do expandTemplate opt cradle files = withGHC sessionName $ do
initializeFlagsWithCradle opt cradle initializeFlagsWithCradle opt cradle
expand opt files either id id <$> expand opt files
where where
sessionName = case files of sessionName = case files of
[file] -> file [file] -> file
@ -60,7 +60,6 @@ expandTemplate opt cradle files = withGHC sessionName $ do
-- | Expanding Haskell Template. -- | Expanding Haskell Template.
expand :: Options expand :: Options
-> [FilePath] -- ^ The target files. -> [FilePath] -- ^ The target files.
-> Ghc String -> Ghc (Either String String)
expand opt fileNames = ghandle (handleErrMsg opt) $ expand opt fileNames = withLogger opt (Gap.setDumpSplices . setNoWaringFlags) $
withDynFlags Gap.setDumpSplices $ setTargetFiles fileNames
withLogger opt setNoWaringFlags $ setTargetFiles fileNames

View File

@ -13,6 +13,7 @@ import CoreMonad (liftIO)
import Data.IORef (IORef, newIORef, readIORef, writeIORef, modifyIORef) import Data.IORef (IORef, newIORef, readIORef, writeIORef, modifyIORef)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import ErrUtils (ErrMsg, errMsgShortDoc, errMsgExtraInfo) import ErrUtils (ErrMsg, errMsgShortDoc, errMsgExtraInfo)
import Exception (ghandle)
import GHC (Ghc, DynFlags, SrcSpan, Severity(SevError)) import GHC (Ghc, DynFlags, SrcSpan, Severity(SevError))
import qualified GHC as G import qualified GHC as G
import HscTypes (SourceError, srcErrorMessages) import HscTypes (SourceError, srcErrorMessages)
@ -50,24 +51,24 @@ appendLogRef df (LogRef ref) _ sev src style msg = do
---------------------------------------------------------------- ----------------------------------------------------------------
withLogger :: Options -> (DynFlags -> DynFlags) -> Ghc () -> Ghc String withLogger :: Options -> (DynFlags -> DynFlags) -> Ghc () -> Ghc (Either String String)
withLogger opt setDF body = do withLogger opt setDF body = ghandle (handleErrMsg opt) $ do
logref <- liftIO $ newLogRef logref <- liftIO $ newLogRef
withDynFlags (setLogger logref . setDF) $ do withDynFlags (setLogger logref . setDF) $ do
body body
liftIO $ readAndClearLogRef opt logref liftIO $ Right <$> readAndClearLogRef opt logref
where where
setLogger logref df = Gap.setLogAction df $ appendLogRef df logref setLogger logref df = Gap.setLogAction df $ appendLogRef df logref
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Converting 'SourceError' to 'String'. -- | Converting 'SourceError' to 'String'.
handleErrMsg :: Options -> SourceError -> Ghc String handleErrMsg :: Options -> SourceError -> Ghc (Either String String)
handleErrMsg opt err = do handleErrMsg opt err = do
dflag <- G.getSessionDynFlags dflag <- G.getSessionDynFlags
style <- getStyle style <- getStyle
let ret = convert opt . errBagToStrList dflag style . srcErrorMessages $ err let ret = convert opt . errBagToStrList dflag style . srcErrorMessages $ err
return ret return (Left ret)
errBagToStrList :: DynFlags -> PprStyle -> Bag ErrMsg -> [String] errBagToStrList :: DynFlags -> PprStyle -> Bag ErrMsg -> [String]
errBagToStrList dflag style = map (ppErrMsg dflag style) . reverse . bagToList errBagToStrList dflag style = map (ppErrMsg dflag style) . reverse . bagToList

View File

@ -21,10 +21,10 @@ module Language.Haskell.GhcMod.Internal (
, getDynamicFlags , getDynamicFlags
-- * Initializing 'DynFlags' -- * Initializing 'DynFlags'
, initializeFlagsWithCradle , initializeFlagsWithCradle
-- * 'Ghc' Monad -- * Targets
, setTargetFiles , setTargetFiles
, addTargetFiles , addTargetFiles
, handleErrMsg -- * Logging
, withLogger , withLogger
, setNoWaringFlags , setNoWaringFlags
, setAllWaringFlags , setAllWaringFlags

View File

@ -168,16 +168,12 @@ checkStx :: Options
-> FilePath -> FilePath
-> Ghc (String, Bool, Set FilePath) -> Ghc (String, Bool, Set FilePath)
checkStx opt set file = do checkStx opt set file = do
GE.ghandle handler $ do
(set',add) <- removeMainTarget file set (set',add) <- removeMainTarget file set
let files = if add then [file] else [] let files = if add then [file] else []
ret <- withLogger opt setAllWaringFlags $ addTargetFiles files eret <- withLogger opt setAllWaringFlags $ addTargetFiles files
return (ret, True, set') case eret of
where Right ret -> return (ret, True, set')
handler :: SourceError -> Ghc (String, Bool, Set FilePath) Left ret -> return (ret, True, set) -- fxime: set
handler err = do
ret <- handleErrMsg opt err
return (ret, True, set)
removeMainTarget :: FilePath -> Set FilePath -> Ghc (Set FilePath, Bool) removeMainTarget :: FilePath -> Set FilePath -> Ghc (Set FilePath, Bool)
removeMainTarget file set = do removeMainTarget file set = do