{-# LANGUAGE CPP #-}
module Development.IDE.GHC.Compat.Outputable (
SDoc,
Outputable,
showSDoc,
showSDocUnsafe,
showSDocForUser,
ppr, pprPanic, text, vcat, (<+>), ($$), empty, hang, nest, punctuate,
printSDocQualifiedUnsafe,
printWithoutUniques,
mkPrintUnqualifiedDefault,
PrintUnqualified(..),
defaultUserStyle,
withPprStyle,
PsWarning,
PsError,
#if MIN_VERSION_ghc(9,5,0)
defaultDiagnosticOpts,
GhcMessage,
DriverMessage,
Messages,
initDiagOpts,
pprMessages,
#endif
#if MIN_VERSION_ghc(9,3,0)
DiagnosticReason(..),
renderDiagnosticMessageWithHints,
pprMsgEnvelopeBagWithLoc,
Error.getMessages,
renderWithContext,
defaultSDocContext,
errMsgDiagnostic,
unDecorated,
diagnosticMessage,
#else
pprWarning,
pprError,
#endif
DecoratedSDoc,
MsgEnvelope,
ErrMsg,
WarnMsg,
SourceError(..),
errMsgSpan,
errMsgSeverity,
formatErrorWithQual,
mkWarnMsg,
mkSrcErr,
srcErrorMessages,
textDoc,
) where
import GHC.Driver.Env
import GHC.Driver.Ppr
import GHC.Driver.Session
import qualified GHC.Types.Error as Error
#if MIN_VERSION_ghc(9,7,0)
import GHC.Types.Error (defaultDiagnosticOpts)
#endif
import GHC.Types.Name.Ppr
import GHC.Types.Name.Reader
import GHC.Types.SourceError
import GHC.Types.SrcLoc
import GHC.Unit.State
import GHC.Utils.Error hiding (mkWarnMsg)
import GHC.Utils.Outputable as Out
import GHC.Utils.Panic
#if !MIN_VERSION_ghc(9,3,0)
import GHC.Parser.Errors
import qualified GHC.Parser.Errors.Ppr as Ppr
#endif
#if MIN_VERSION_ghc(9,3,0)
import Data.Maybe
import GHC.Driver.Config.Diagnostic
import GHC.Parser.Errors.Types
#endif
#if MIN_VERSION_ghc(9,5,0)
import GHC.Driver.Errors.Types (DriverMessage, GhcMessage)
#endif
#if MIN_VERSION_ghc(9,5,0)
type PrintUnqualified = NamePprCtx
#endif
printWithoutUniques :: Outputable a => a -> String
printWithoutUniques :: forall a. Outputable a => a -> String
printWithoutUniques =
SDocContext -> SDoc -> String
renderWithContext (SDocContext
defaultSDocContext
{
sdocStyle :: PprStyle
sdocStyle = PprStyle
defaultUserStyle
, sdocSuppressUniques :: Bool
sdocSuppressUniques = Bool
True
, sdocCanUseUnicode :: Bool
sdocCanUseUnicode = Bool
True
}) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Outputable a => a -> SDoc
ppr
printSDocQualifiedUnsafe :: PrintUnqualified -> SDoc -> String
printSDocQualifiedUnsafe :: PrintUnqualified -> SDoc -> String
printSDocQualifiedUnsafe PrintUnqualified
unqual SDoc
doc =
SDocContext -> SDoc -> String
renderWithContext (SDocContext
defaultSDocContext { sdocStyle :: PprStyle
sdocStyle = PprStyle
sty }) SDoc
doc'
where
sty :: PprStyle
sty = PrintUnqualified -> Depth -> PprStyle
mkUserStyle PrintUnqualified
unqual Depth
AllTheWay
doc' :: SDoc
doc' = UnitState -> SDoc -> SDoc
pprWithUnitState UnitState
emptyUnitState SDoc
doc
#if !MIN_VERSION_ghc(9,3,0)
pprWarning :: PsWarning -> MsgEnvelope DecoratedSDoc
pprWarning :: PsWarning -> MsgEnvelope DecoratedSDoc
pprWarning =
PsWarning -> MsgEnvelope DecoratedSDoc
Ppr.pprWarning
pprError :: PsError -> MsgEnvelope DecoratedSDoc
pprError :: PsError -> MsgEnvelope DecoratedSDoc
pprError =
PsError -> MsgEnvelope DecoratedSDoc
Ppr.pprError
#endif
formatErrorWithQual :: DynFlags -> MsgEnvelope DecoratedSDoc -> String
formatErrorWithQual :: DynFlags -> MsgEnvelope DecoratedSDoc -> String
formatErrorWithQual DynFlags
dflags MsgEnvelope DecoratedSDoc
e =
DynFlags -> SDoc -> String
showSDoc DynFlags
dflags (forall e. RenderableDiagnostic e => MsgEnvelope e -> SDoc
pprNoLocMsgEnvelope MsgEnvelope DecoratedSDoc
e)
#if MIN_VERSION_ghc(9,3,0)
pprNoLocMsgEnvelope :: MsgEnvelope DecoratedSDoc -> SDoc
#else
pprNoLocMsgEnvelope :: Error.RenderableDiagnostic e => MsgEnvelope e -> SDoc
#endif
pprNoLocMsgEnvelope :: forall e. RenderableDiagnostic e => MsgEnvelope e -> SDoc
pprNoLocMsgEnvelope (MsgEnvelope { errMsgDiagnostic :: forall e. MsgEnvelope e -> e
errMsgDiagnostic = e
e
, errMsgContext :: forall e. MsgEnvelope e -> PrintUnqualified
errMsgContext = PrintUnqualified
unqual })
= (SDocContext -> SDoc) -> SDoc
sdocWithContext forall a b. (a -> b) -> a -> b
$ \SDocContext
_ctx ->
PrintUnqualified -> SDoc -> SDoc
withErrStyle PrintUnqualified
unqual forall a b. (a -> b) -> a -> b
$
#if MIN_VERSION_ghc(9,7,0)
(formatBulleted e)
#elif MIN_VERSION_ghc(9,3,0)
(formatBulleted _ctx $ e)
#else
(SDocContext -> DecoratedSDoc -> SDoc
formatBulleted SDocContext
_ctx forall a b. (a -> b) -> a -> b
$ forall a. RenderableDiagnostic a => a -> DecoratedSDoc
Error.renderDiagnostic e
e)
#endif
type ErrMsg = MsgEnvelope DecoratedSDoc
#if MIN_VERSION_ghc(9,3,0)
type WarnMsg = MsgEnvelope DecoratedSDoc
#endif
mkPrintUnqualifiedDefault :: HscEnv -> GlobalRdrEnv -> PrintUnqualified
#if MIN_VERSION_ghc(9,5,0)
mkPrintUnqualifiedDefault env =
mkNamePprCtx ptc (hsc_unit_env env)
where
ptc = initPromotionTickContext (hsc_dflags env)
#else
mkPrintUnqualifiedDefault :: HscEnv -> GlobalRdrEnv -> PrintUnqualified
mkPrintUnqualifiedDefault HscEnv
env =
UnitEnv -> GlobalRdrEnv -> PrintUnqualified
mkPrintUnqualified (HscEnv -> UnitEnv
hsc_unit_env HscEnv
env)
#endif
#if MIN_VERSION_ghc(9,3,0)
renderDiagnosticMessageWithHints :: forall a. Diagnostic a => a -> DecoratedSDoc
renderDiagnosticMessageWithHints a = Error.unionDecoratedSDoc
(diagnosticMessage
#if MIN_VERSION_ghc(9,5,0)
(defaultDiagnosticOpts @a)
#endif
a) (mkDecorated $ map ppr $ diagnosticHints a)
#endif
#if MIN_VERSION_ghc(9,3,0)
mkWarnMsg :: DynFlags -> Maybe DiagnosticReason -> b -> SrcSpan -> PrintUnqualified -> SDoc -> MsgEnvelope DecoratedSDoc
mkWarnMsg df reason _logFlags l st doc = fmap renderDiagnosticMessageWithHints $ mkMsgEnvelope (initDiagOpts df) l st (mkPlainDiagnostic (fromMaybe WarningWithoutFlag reason) [] doc)
#else
mkWarnMsg :: a -> b -> DynFlags -> SrcSpan -> PrintUnqualified -> SDoc -> MsgEnvelope DecoratedSDoc
mkWarnMsg :: forall a b.
a
-> b
-> DynFlags
-> SrcSpan
-> PrintUnqualified
-> SDoc
-> MsgEnvelope DecoratedSDoc
mkWarnMsg a
_ b
_ =
forall a b. a -> b -> a
const SrcSpan -> PrintUnqualified -> SDoc -> MsgEnvelope DecoratedSDoc
Error.mkWarnMsg
#endif
textDoc :: String -> SDoc
textDoc :: String -> SDoc
textDoc = String -> SDoc
text