module Development.IDE.GHC.Warnings(withWarnings) where
import GhcMonad
import ErrUtils
import GhcPlugins as GHC hiding (Var)
import Control.Concurrent.Extra
import Control.Monad.Extra
import qualified Data.Text as T
import Development.IDE.Types.Diagnostics
import Development.IDE.GHC.Util
import Development.IDE.GHC.Error
withWarnings :: GhcMonad m => T.Text -> ((ModSummary -> ModSummary) -> m a) -> m ([(WarnReason, FileDiagnostic)], a)
withWarnings diagSource action = do
warnings <- liftIO $ newVar []
oldFlags <- getDynFlags
let newAction :: DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> SDoc -> IO ()
newAction dynFlags wr _ loc style msg = do
let wr_d = fmap (wr,) $ diagFromErrMsg diagSource dynFlags $ mkWarnMsg dynFlags loc (queryQual style) msg
modifyVar_ warnings $ return . (wr_d:)
setLogAction newAction
res <- action $ \x -> x{ms_hspp_opts = (ms_hspp_opts x){log_action = newAction}}
setLogAction $ log_action oldFlags
warns <- liftIO $ readVar warnings
return (reverse $ concat warns, res)
setLogAction :: GhcMonad m => LogAction -> m ()
setLogAction act = void $ modifyDynFlags $ \dyn -> dyn{log_action = act}