ghc-lib-parser-9.6.2.20230523: The GHC API, decoupled from GHC versions
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Utils.Error

Synopsis

Basic types

data Validity' a Source #

Constructors

IsValid

Everything is fine

NotValid a

A problem, and some indication of why

Instances

Instances details
Functor Validity' Source # 
Instance details

Defined in GHC.Utils.Error

Methods

fmap :: (a -> b) -> Validity' a -> Validity' b #

(<$) :: a -> Validity' b -> Validity' a #

type Validity = Validity' SDoc Source #

Monomorphic version of Validity' specialised for SDocs.

allValid :: [Validity' a] -> Validity' a Source #

If they aren't all valid, return the first

data Severity Source #

Used to describe warnings and errors o The message has a file/line/column heading, plus "warning:" or "error:", added by mkLocMessage o With SevIgnore the message is suppressed o Output is intended for end users

Constructors

SevIgnore

Ignore this message, for example in case of suppression of warnings users don't want to see. See Note [Suppressing Messages]

SevWarning 
SevError 

Instances

Instances details
Show Severity Source # 
Instance details

Defined in GHC.Types.Error

ToJson Severity Source # 
Instance details

Defined in GHC.Types.Error

Outputable Severity Source # 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: Severity -> SDoc Source #

Eq Severity Source # 
Instance details

Defined in GHC.Types.Error

Messages

class Diagnostic a where Source #

A class identifying a diagnostic. Dictionary.com defines a diagnostic as:

"a message output by a computer diagnosing an error in a computer program, computer system, or component device".

A Diagnostic carries the actual description of the message (which, in GHC's case, it can be an error or a warning) and the reason why such message was generated in the first place.

Associated Types

type DiagnosticOpts a Source #

Type of configuration options for the diagnostic.

Methods

defaultDiagnosticOpts :: DiagnosticOpts a Source #

diagnosticMessage :: DiagnosticOpts a -> a -> DecoratedSDoc Source #

Extract the error message text from a Diagnostic.

diagnosticReason :: a -> DiagnosticReason Source #

Extract the reason for this diagnostic. For warnings, a DiagnosticReason includes the warning flag.

diagnosticHints :: a -> [GhcHint] Source #

Extract any hints a user might use to repair their code to avoid this diagnostic.

diagnosticCode :: a -> Maybe DiagnosticCode Source #

Get the DiagnosticCode associated with this Diagnostic. This can return Nothing for at least two reasons:

  1. The message might be from a plugin that does not supply codes.
  2. The message might not yet have been assigned a code. See the Diagnostic instance for DiagnosticMessage.

Ideally, case (2) would not happen, but because some errors in GHC still use the old system of just writing the error message in-place (instead of using a dedicated error type and constructor), we do not have error codes for all errors. #18516 tracks our progress toward this goal.

Instances

Instances details
Diagnostic DriverMessage Source # 
Instance details

Defined in GHC.Driver.Errors.Ppr

Associated Types

type DiagnosticOpts DriverMessage Source #

Diagnostic GhcMessage Source # 
Instance details

Defined in GHC.Driver.Errors.Ppr

Associated Types

type DiagnosticOpts GhcMessage Source #

Diagnostic DsMessage Source # 
Instance details

Defined in GHC.HsToCore.Errors.Ppr

Associated Types

type DiagnosticOpts DsMessage Source #

Diagnostic PsMessage Source # 
Instance details

Defined in GHC.Parser.Errors.Ppr

Associated Types

type DiagnosticOpts PsMessage Source #

Diagnostic TcRnMessage Source # 
Instance details

Defined in GHC.Tc.Errors.Ppr

Associated Types

type DiagnosticOpts TcRnMessage Source #

Diagnostic DiagnosticMessage Source # 
Instance details

Defined in GHC.Types.Error

Diagnostic UnknownDiagnostic Source # 
Instance details

Defined in GHC.Types.Error

data MsgEnvelope e Source #

An envelope for GHC's facts about a running program, parameterised over the domain-specific (i.e. parsing, typecheck-renaming, etc) diagnostics.

To say things differently, GHC emits diagnostics about the running program, each of which is wrapped into a MsgEnvelope that carries specific information like where the error happened, etc. Finally, multiple MsgEnvelopes are aggregated into Messages that are returned to the user.

Constructors

MsgEnvelope 

Fields

Instances

Instances details
Foldable MsgEnvelope Source # 
Instance details

Defined in GHC.Types.Error

Methods

fold :: Monoid m => MsgEnvelope m -> m #

foldMap :: Monoid m => (a -> m) -> MsgEnvelope a -> m #

foldMap' :: Monoid m => (a -> m) -> MsgEnvelope a -> m #

foldr :: (a -> b -> b) -> b -> MsgEnvelope a -> b #

foldr' :: (a -> b -> b) -> b -> MsgEnvelope a -> b #

foldl :: (b -> a -> b) -> b -> MsgEnvelope a -> b #

foldl' :: (b -> a -> b) -> b -> MsgEnvelope a -> b #

foldr1 :: (a -> a -> a) -> MsgEnvelope a -> a #

foldl1 :: (a -> a -> a) -> MsgEnvelope a -> a #

toList :: MsgEnvelope a -> [a] #

null :: MsgEnvelope a -> Bool #

length :: MsgEnvelope a -> Int #

elem :: Eq a => a -> MsgEnvelope a -> Bool #

maximum :: Ord a => MsgEnvelope a -> a #

minimum :: Ord a => MsgEnvelope a -> a #

sum :: Num a => MsgEnvelope a -> a #

product :: Num a => MsgEnvelope a -> a #

Traversable MsgEnvelope Source # 
Instance details

Defined in GHC.Types.Error

Methods

traverse :: Applicative f => (a -> f b) -> MsgEnvelope a -> f (MsgEnvelope b) #

sequenceA :: Applicative f => MsgEnvelope (f a) -> f (MsgEnvelope a) #

mapM :: Monad m => (a -> m b) -> MsgEnvelope a -> m (MsgEnvelope b) #

sequence :: Monad m => MsgEnvelope (m a) -> m (MsgEnvelope a) #

Functor MsgEnvelope Source # 
Instance details

Defined in GHC.Types.Error

Methods

fmap :: (a -> b) -> MsgEnvelope a -> MsgEnvelope b #

(<$) :: a -> MsgEnvelope b -> MsgEnvelope a #

Show (MsgEnvelope DiagnosticMessage) Source # 
Instance details

Defined in GHC.Types.Error

data MessageClass Source #

The class for a diagnostic message. The main purpose is to classify a message within GHC, to distinguish it from a debug/dump message vs a proper diagnostic, for which we include a DiagnosticReason.

Constructors

MCOutput 
MCFatal 
MCInteractive 
MCDump

Log message intended for compiler developers No file/line/column stuff

MCInfo

Log messages intended for end users. No file/line/column stuff.

MCDiagnostic Severity DiagnosticReason (Maybe DiagnosticCode)

Diagnostics from the compiler. This constructor is very powerful as it allows the construction of a MessageClass with a completely arbitrary permutation of Severity and DiagnosticReason. As such, users are encouraged to use the mkMCDiagnostic smart constructor instead. Use this constructor directly only if you need to construct and manipulate diagnostic messages directly, for example inside Error. In all the other circumstances, especially when emitting compiler diagnostics, use the smart constructor.

The Maybe DiagnosticCode field carries a code (if available) for this diagnostic. If you are creating a message not tied to any error-message type, then use Nothing. In the long run, this really should always have a DiagnosticCode. See Note [Diagnostic codes].

Instances

Instances details
ToJson MessageClass Source # 
Instance details

Defined in GHC.Types.Error

data SDoc Source #

Represents a pretty-printable document.

To display an SDoc, use printSDoc, printSDocLn, bufLeftRenderSDoc, or renderWithContext. Avoid calling runSDoc directly as it breaks the abstraction layer.

Instances

Instances details
IsString SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

fromString :: String -> SDoc #

IsDoc SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Associated Types

type Line SDoc = (r :: Type) Source #

IsLine SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

IsOutput SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: SDoc -> SDoc Source #

OutputableP env SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> SDoc -> SDoc Source #

type Line SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

type Line SDoc = SDoc

data DecoratedSDoc Source #

A DecoratedSDoc is isomorphic to a '[SDoc]' but it carries the invariant that the input '[SDoc]' needs to be rendered decorated into its final form, where the typical case would be adding bullets between each elements of the list. The type of decoration depends on the formatting function used, but in practice GHC uses the formatBulleted.

data Messages e Source #

A collection of messages emitted by GHC during error reporting. A diagnostic message is typically a warning or an error. See Note [Messages].

INVARIANT: All the messages in this collection must be relevant, i.e. their Severity should not be SevIgnore. The smart constructor mkMessages will filter out any message which Severity is SevIgnore.

Instances

Instances details
Foldable Messages Source # 
Instance details

Defined in GHC.Types.Error

Methods

fold :: Monoid m => Messages m -> m #

foldMap :: Monoid m => (a -> m) -> Messages a -> m #

foldMap' :: Monoid m => (a -> m) -> Messages a -> m #

foldr :: (a -> b -> b) -> b -> Messages a -> b #

foldr' :: (a -> b -> b) -> b -> Messages a -> b #

foldl :: (b -> a -> b) -> b -> Messages a -> b #

foldl' :: (b -> a -> b) -> b -> Messages a -> b #

foldr1 :: (a -> a -> a) -> Messages a -> a #

foldl1 :: (a -> a -> a) -> Messages a -> a #

toList :: Messages a -> [a] #

null :: Messages a -> Bool #

length :: Messages a -> Int #

elem :: Eq a => a -> Messages a -> Bool #

maximum :: Ord a => Messages a -> a #

minimum :: Ord a => Messages a -> a #

sum :: Num a => Messages a -> a #

product :: Num a => Messages a -> a #

Traversable Messages Source # 
Instance details

Defined in GHC.Types.Error

Methods

traverse :: Applicative f => (a -> f b) -> Messages a -> f (Messages b) #

sequenceA :: Applicative f => Messages (f a) -> f (Messages a) #

mapM :: Monad m => (a -> m b) -> Messages a -> m (Messages b) #

sequence :: Monad m => Messages (m a) -> m (Messages a) #

Functor Messages Source # 
Instance details

Defined in GHC.Types.Error

Methods

fmap :: (a -> b) -> Messages a -> Messages b #

(<$) :: a -> Messages b -> Messages a #

Monoid (Messages e) Source # 
Instance details

Defined in GHC.Types.Error

Methods

mempty :: Messages e #

mappend :: Messages e -> Messages e -> Messages e #

mconcat :: [Messages e] -> Messages e #

Semigroup (Messages e) Source # 
Instance details

Defined in GHC.Types.Error

Methods

(<>) :: Messages e -> Messages e -> Messages e #

sconcat :: NonEmpty (Messages e) -> Messages e #

stimes :: Integral b => b -> Messages e -> Messages e #

Diagnostic e => Outputable (Messages e) Source # 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: Messages e -> SDoc Source #

unionMessages :: Messages e -> Messages e -> Messages e Source #

Joins two collections of messages together. See Note [Discarding Messages].

errorsFound :: Diagnostic e => Messages e -> Bool Source #

Are there any hard errors here? -Werror warnings are not detected. If you want to check for -Werror warnings, use errorsOrFatalWarningsFound.

Formatting

pprMsgEnvelopeBagWithLocDefault :: forall e. Diagnostic e => Bag (MsgEnvelope e) -> [SDoc] Source #

Print the messages with the suitable default configuration, usually not what you want but sometimes you don't really care about what the configuration is (for example, if the message is in a panic).

formatBulleted :: SDocContext -> DecoratedSDoc -> SDoc Source #

Formats the input list of structured document, where each element of the list gets a bullet.

Construction

data DiagOpts Source #

Constructors

DiagOpts 

Fields

mkDecorated :: [SDoc] -> DecoratedSDoc Source #

Creates a new DecoratedSDoc out of a list of SDoc.

mkLocMessage Source #

Arguments

:: MessageClass

What kind of message?

-> SrcSpan

location

-> SDoc

message

-> SDoc 

mkMsgEnvelope :: Diagnostic e => DiagOpts -> SrcSpan -> NamePprCtx -> e -> MsgEnvelope e Source #

Wrap a Diagnostic in a MsgEnvelope, recording its location. If you know your Diagnostic is an error, consider using mkErrorMsgEnvelope, which does not require looking at the DiagOpts

mkPlainMsgEnvelope :: Diagnostic e => DiagOpts -> SrcSpan -> e -> MsgEnvelope e Source #

Variant that doesn't care about qualified/unqualified names.

mkPlainErrorMsgEnvelope :: Diagnostic e => SrcSpan -> e -> MsgEnvelope e Source #

Variant of mkPlainMsgEnvelope which can be used when we are sure we are constructing a diagnostic with a ErrorWithoutFlag reason.

mkErrorMsgEnvelope :: Diagnostic e => SrcSpan -> NamePprCtx -> e -> MsgEnvelope e Source #

Wrap a Diagnostic in a MsgEnvelope, recording its location. Precondition: the diagnostic is, in fact, an error. That is, diagnosticReason msg == ErrorWithoutFlag.

errorDiagnostic :: MessageClass Source #

Varation of mkMCDiagnostic which can be used when we are sure the input DiagnosticReason is ErrorWithoutFlag and there is no diagnostic code.

diagReasonSeverity :: DiagOpts -> DiagnosticReason -> Severity Source #

Computes the right Severity for the input DiagnosticReason out of the 'DiagOpts. This function has to be called when a diagnostic is constructed, i.e. with a 'DiagOpts "snapshot" taken as close as possible to where a particular diagnostic message is built, otherwise the computed Severity might not be correct, due to the mutable nature of the DynFlags in GHC.

mkPlainError :: [GhcHint] -> SDoc -> DiagnosticMessage Source #

Create an error DiagnosticMessage holding just a single SDoc

mkDecoratedError :: [GhcHint] -> [SDoc] -> DiagnosticMessage Source #

Create an error DiagnosticMessage from a list of bulleted SDocs

noHints :: [GhcHint] Source #

Helper function to use when no hints can be provided. Currently this function can be used to construct plain DiagnosticMessage and add hints to them, but once #18516 will be fully executed, the main usage of this function would be in the implementation of the diagnosticHints typeclass method, to report the fact that a particular Diagnostic has no hints.

Utilities

Issuing messages during compilation

putMsg :: Logger -> SDoc -> IO () Source #

logOutput :: Logger -> SDoc -> IO () Source #

Like logInfo but with SevOutput rather then SevInfo

withTiming Source #

Arguments

:: MonadIO m 
=> Logger 
-> SDoc

The name of the phase

-> (a -> ())

A function to force the result (often either const () or rnf)

-> m a

The body of the phase to be timed

-> m a 

Time a compilation phase.

When timings are enabled (e.g. with the -v2 flag), the allocations and CPU time used by the phase will be reported to stderr. Consider a typical usage: withTiming getDynFlags (text "simplify") force PrintTimings pass. When timings are enabled the following costs are included in the produced accounting,

  • The cost of executing pass to a result r in WHNF
  • The cost of evaluating force r to WHNF (e.g. ())

The choice of the force function depends upon the amount of forcing desired; the goal here is to ensure that the cost of evaluating the result is, to the greatest extent possible, included in the accounting provided by withTiming. Often the pass already sufficiently forces its result during construction; in this case const () is a reasonable choice. In other cases, it is necessary to evaluate the result to normal form, in which case something like Control.DeepSeq.rnf is appropriate.

To avoid adversely affecting compiler performance when timings are not requested, the result is only forced when timings are enabled.

See Note [withTiming] for more.

withTimingSilent Source #

Arguments

:: MonadIO m 
=> Logger 
-> SDoc

The name of the phase

-> (a -> ())

A function to force the result (often either const () or rnf)

-> m a

The body of the phase to be timed

-> m a 

Same as withTiming, but doesn't print timings in the console (when given -vN, N >= 2 or -ddump-timings).

See Note [withTiming] for more.

ghcExit :: Logger -> Int -> IO () Source #

traceCmd :: Logger -> String -> String -> IO a -> IO a Source #

Trace a command (when verbosity level >= 3)

traceSystoolCommand :: Logger -> String -> IO a -> IO a Source #

Record in the eventlog when the given tool command starts and finishes, prepending the given String with "systool:", to easily be able to collect and process all the systool events.

For those events to show up in the eventlog, you need to run GHC with -v2 or -ddump-timings.