ghc-mod/Language/Haskell/GhcMod/ErrMsg.hs

94 lines
3.2 KiB
Haskell
Raw Normal View History

2013-11-12 23:56:45 +00:00
{-# LANGUAGE BangPatterns, CPP #-}
2013-05-17 01:00:01 +00:00
module Language.Haskell.GhcMod.ErrMsg (
2011-08-24 07:50:26 +00:00
LogReader
, setLogger
, handleErrMsg
) where
2014-03-27 06:32:44 +00:00
import Bag (Bag, bagToList)
import Control.Applicative ((<$>))
import Data.IORef (IORef, newIORef, readIORef, writeIORef, modifyIORef)
import Data.Maybe (fromMaybe)
2014-03-27 11:54:18 +00:00
import DynFlags (dopt)
2014-03-27 06:32:44 +00:00
import ErrUtils (ErrMsg, errMsgShortDoc, errMsgExtraInfo)
2014-03-27 11:54:18 +00:00
import GHC (Ghc, DynFlags, SrcSpan, Severity(SevError))
2014-03-27 06:32:44 +00:00
import qualified GHC as G
import HscTypes (SourceError, srcErrorMessages)
import Language.Haskell.GhcMod.Doc (showPage, getStyle)
2013-05-17 01:00:01 +00:00
import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Types (Options, convert)
import Outputable (PprStyle, SDoc)
2013-03-05 06:18:57 +00:00
import System.FilePath (normalise)
2011-08-24 07:50:26 +00:00
----------------------------------------------------------------
2013-09-05 05:35:28 +00:00
-- | A means to read the log.
2014-04-21 05:04:58 +00:00
type LogReader = IO String
2011-08-24 07:50:26 +00:00
----------------------------------------------------------------
2014-03-18 03:38:04 +00:00
type Builder = [String] -> [String]
newtype LogRef = LogRef (IORef Builder)
newLogRef :: IO LogRef
newLogRef = LogRef <$> newIORef id
2014-04-21 05:04:58 +00:00
readAndClearLogRef :: Options -> LogRef -> IO String
readAndClearLogRef opt (LogRef ref) = do
2014-03-18 03:38:04 +00:00
b <- readIORef ref
writeIORef ref id
2014-04-21 05:04:58 +00:00
return $! convert opt (b [])
2014-03-18 03:38:04 +00:00
appendLogRef :: DynFlags -> LogRef -> DynFlags -> Severity -> SrcSpan -> PprStyle -> SDoc -> IO ()
appendLogRef df (LogRef ref) _ sev src style msg = do
let !l = ppMsg src sev df style msg
2014-03-18 03:38:04 +00:00
modifyIORef ref (\b -> b . (l:))
----------------------------------------------------------------
2014-04-21 05:04:58 +00:00
setLogger :: Bool -> DynFlags -> Options -> IO (DynFlags, LogReader)
2013-09-03 05:40:51 +00:00
setLogger False df _ = return (newdf, undefined)
2011-08-24 07:50:26 +00:00
where
newdf = Gap.setLogAction df $ \_ _ _ _ _ -> return ()
2014-04-21 05:04:58 +00:00
setLogger True df opt = do
2014-03-18 03:38:04 +00:00
logref <- newLogRef
let newdf = Gap.setLogAction df $ appendLogRef df logref
2014-04-21 05:04:58 +00:00
return (newdf, readAndClearLogRef opt logref)
2011-08-24 07:50:26 +00:00
----------------------------------------------------------------
2014-03-26 03:09:02 +00:00
-- | Converting 'SourceError' to 'String'.
2014-04-21 05:04:58 +00:00
handleErrMsg :: Options -> SourceError -> Ghc String
handleErrMsg opt err = do
2014-03-27 06:32:44 +00:00
dflag <- G.getSessionDynFlags
style <- getStyle
let ret = convert opt . errBagToStrList dflag style . srcErrorMessages $ err
2014-04-21 05:04:58 +00:00
return ret
2011-08-24 07:50:26 +00:00
errBagToStrList :: DynFlags -> PprStyle -> Bag ErrMsg -> [String]
errBagToStrList dflag style = map (ppErrMsg dflag style) . reverse . bagToList
2011-08-24 07:50:26 +00:00
----------------------------------------------------------------
ppErrMsg :: DynFlags -> PprStyle -> ErrMsg -> String
ppErrMsg dflag style err = ppMsg spn SevError dflag style msg ++ ext
2011-08-24 07:50:26 +00:00
where
2013-11-19 03:28:59 +00:00
spn = Gap.errorMsgSpan err
2013-11-13 00:10:25 +00:00
msg = errMsgShortDoc err
2014-04-21 07:12:30 +00:00
ext = showPage dflag style (errMsgExtraInfo err)
2011-08-24 07:50:26 +00:00
ppMsg :: SrcSpan -> Severity-> DynFlags -> PprStyle -> SDoc -> String
ppMsg spn sev dflag style msg = prefix ++ cts
2011-08-24 07:50:26 +00:00
where
2014-04-21 07:12:30 +00:00
cts = showPage dflag style msg
defaultPrefix
2014-03-27 11:54:18 +00:00
| dopt Gap.dumpSplicesFlag dflag = ""
| otherwise = "Dummy:0:0:Error:"
prefix = fromMaybe defaultPrefix $ do
(line,col,_,_) <- Gap.getSrcSpan spn
file <- normalise <$> Gap.getSrcFile spn
let severityCaption = Gap.showSeverityCaption sev
return $ file ++ ":" ++ show line ++ ":" ++ show col ++ ":" ++ severityCaption