ghc-9.4.3: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Types.Error

Synopsis

Messages

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 Source #

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

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

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

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

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

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

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

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

toList :: Messages a -> [a] Source #

null :: Messages a -> Bool Source #

length :: Messages a -> Int Source #

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

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

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

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

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

Traversable Messages Source # 
Instance details

Defined in GHC.Types.Error

Methods

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

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

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

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

Functor Messages Source # 
Instance details

Defined in GHC.Types.Error

Methods

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

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

Monoid (Messages e) Source # 
Instance details

Defined in GHC.Types.Error

Semigroup (Messages e) Source # 
Instance details

Defined in GHC.Types.Error

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

Defined in GHC.Types.Error

Methods

ppr :: Messages e -> SDoc Source #

addMessage :: MsgEnvelope e -> Messages e -> Messages e Source #

Adds a Message to the input collection of messages. See Note [Discarding Messages].

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

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

unionManyMessages :: Foldable f => f (Messages e) -> Messages e Source #

Joins many Messagess together

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 Source #

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

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

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

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

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

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

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

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

toList :: MsgEnvelope a -> [a] Source #

null :: MsgEnvelope a -> Bool Source #

length :: MsgEnvelope a -> Int Source #

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

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

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

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

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

Traversable MsgEnvelope Source # 
Instance details

Defined in GHC.Types.Error

Methods

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

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

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

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

Functor MsgEnvelope Source # 
Instance details

Defined in GHC.Types.Error

Methods

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

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

Show (MsgEnvelope DiagnosticMessage) Source # 
Instance details

Defined in GHC.Types.Error

Classifying Messages

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

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.

Instances

Instances details
Show MessageClass Source # 
Instance details

Defined in GHC.Types.Error

ToJson MessageClass Source # 
Instance details

Defined in GHC.Types.Error

Eq MessageClass Source # 
Instance details

Defined in GHC.Types.Error

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

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. See also Note [Rendering Messages].

Instances

Instances details
Diagnostic DriverMessage Source # 
Instance details

Defined in GHC.Driver.Errors.Ppr

Diagnostic GhcMessage Source # 
Instance details

Defined in GHC.Driver.Errors.Ppr

Diagnostic DsMessage Source # 
Instance details

Defined in GHC.HsToCore.Errors.Ppr

Diagnostic PsMessage Source # 
Instance details

Defined in GHC.Parser.Errors.Ppr

Diagnostic TcRnMessage Source # 
Instance details

Defined in GHC.Tc.Errors.Ppr

Diagnostic DiagnosticMessage Source # 
Instance details

Defined in GHC.Types.Error

data DiagnosticMessage Source #

A generic Diagnostic message, without any further classification or provenance: By looking at a DiagnosticMessage we don't know neither where it was generated nor how to intepret its payload (as it's just a structured document). All we can do is to print it out and look at its DiagnosticReason.

data DiagnosticReason Source #

The reason why a Diagnostic was emitted in the first place. Diagnostic messages are born within GHC with a very precise reason, which can be completely statically-computed (i.e. this is an error or a warning no matter what), or influenced by the specific state of the DynFlags at the moment of the creation of a new Diagnostic. For example, a parsing error is always going to be an error, whereas a 'WarningWithoutFlag Opt_WarnUnusedImports' might turn into an error due to '-Werror' or '-Werror=warn-unused-imports'. Interpreting a DiagnosticReason together with its associated Severity gives us the full picture.

Constructors

WarningWithoutFlag

Born as a warning.

WarningWithFlag !WarningFlag

Warning was enabled with the flag.

ErrorWithoutFlag

Born as an error.

data DiagnosticHint Source #

A generic Hint message, to be used with DiagnosticMessage.

Constructors

DiagnosticHint !SDoc 

Instances

Instances details
Outputable DiagnosticHint Source # 
Instance details

Defined in GHC.Types.Error

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

Hints and refactoring actions

data GhcHint Source #

A type for hints emitted by GHC. A hint suggests a possible way to deal with a particular warning or error.

Constructors

forall a.(Outputable a, Typeable a) => UnknownHint a

An "unknown" hint. This type constructor allows arbitrary -- hints to be embedded. The typical use case would be GHC plugins -- willing to emit hints alongside their custom diagnostics.

SuggestExtension !LanguageExtensionHint

Suggests adding a particular language extension. GHC will do its best trying to guess when the user is using the syntax of a particular language extension without having the relevant extension enabled.

Example: If the user uses the keyword "mdo" (and we are in a monadic block), but the relevant extension is not enabled, GHC will emit a 'SuggestExtension RecursiveDo'.

Test case(s): parsershould_failT12429, parsershould_failT8501c, parsershould_failT18251e, ... (and many more)

SuggestMissingDo

Suggests that a monadic code block is probably missing a "do" keyword.

Example: main = putStrLn "hello" putStrLn "world"

Test case(s): parsershould_failT8501a, parsershould_failreadFail007, parsershould_failInfixAppPatErr, parsershould_failT984

SuggestLetInDo

Suggests that a "let" expression is needed in a "do" block.

Test cases: None (that explicitly test this particular hint is emitted).

SuggestAddSignatureCabalFile !ModuleName

Suggests to add an ".hsig" signature file to the Cabal manifest.

Triggered by: DriverUnexpectedSignature, if Cabal is being used.

Example: See comment of DriverUnexpectedSignature.

Test case(s): driver/T12955

SuggestSignatureInstantiations !ModuleName [InstantiationSuggestion]

Suggests to explicitly list the instantiations for the signatures in the GHC invocation command.

Triggered by: DriverUnexpectedSignature, if Cabal is not being used.

Example: See comment of DriverUnexpectedSignature.

Test case(s): driver/T12955

SuggestUseSpaces

Suggests to use spaces instead of tabs.

Triggered by: PsWarnTab.

Examples: None Test Case(s): None

SuggestUseWhitespaceAfter !OperatorWhitespaceSymbol

Suggests adding a whitespace after the given symbol.

Examples: None Test Case(s): parsershould_compileT18834a.hs

SuggestUseWhitespaceAround !String !OperatorWhitespaceOccurrence

Suggests adding a whitespace around the given operator symbol, as it might be repurposed as special syntax by a future language extension. The second parameter is how such operator occurred, if in a prefix, suffix or tight infix position.

Triggered by: PsWarnOperatorWhitespace.

Example: h a b = a+b -- not OK, no spaces around +.

Test Case(s): parsershould_compileT18834b.hs

SuggestParentheses

Suggests wrapping an expression in parentheses

Examples: None Test Case(s): None

SuggestIncreaseMaxPmCheckModels

Suggests to increase the -fmax-pmcheck-models limit for the pattern match checker.

Triggered by: DsMaxPmCheckModelsReached

Test case(s): pmcheckshould_compileTooManyDeltas pmcheckshould_compileTooManyDeltas pmcheckshould_compileT11822

SuggestAddTypeSignatures AvailableBindings

Suggests adding a type signature, typically to resolve ambiguity or help GHC inferring types.

SuggestBindToWildcard !(LHsExpr GhcTc)

Suggests to explicitly discard the result of a monadic action by binding the result to the '_' wilcard.

Example: main = do _ <- getCurrentTime

SuggestAddInlineOrNoInlinePragma !Var !Activation 
SuggestAddPhaseToCompetingRule !RuleName 
SuggestAddToHSigExportList !Name !(Maybe Module)

Suggests adding an identifier to the export list of a signature.

SuggestIncreaseSimplifierIterations

Suggests increasing the limit for the number of iterations in the simplifier.

SuggestUseTypeFromDataKind (Maybe RdrName)

Suggests to explicitly import Type from the Kind module, because using "*" to mean Type relies on the StarIsType extension, which will become deprecated in the future.

Triggered by: PsWarnStarIsType Example: None Test case(s): wcompat-warnings/WCompatWarningsOn.hs

SuggestQualifiedAfterModuleName

Suggests placing the qualified keyword after the module name.

Triggered by: PsWarnImportPreQualified Example: None Test case(s): module/mod184.hs

SuggestThQuotationSyntax

Suggests using TemplateHaskell quotation syntax.

Triggered by: PsErrEmptyDoubleQuotes only if TemplateHaskell is enabled. Example: None Test case(s): parsershould_failT13450TH.hs

SuggestRoles [Role]

Suggests alternative roles in case we found an illegal one.

Triggered by: PsErrIllegalRoleName Example: None Test case(s): rolesshould_failRoles7.hs

SuggestQualifyStarOperator

Suggests qualifying the * operator in modules where StarIsType is enabled.

Triggered by: PsWarnStarBinder Test case(s): warningsshould_compileStarBinder.hs

SuggestTypeSignatureForm

Suggests that a type signature should have form variable :: type in order to be accepted by GHC.

Triggered by: PsErrInvalidTypeSignature Test case(s): parsershould_failT3811

SuggestFixOrphanInstance

Suggests to move an orphan instance or to newtype-wrap it.

Triggered by: TcRnOrphanInstance Test cases(s): warningsshould_compileT9178 typecheckshould_compileT4912

SuggestAddStandaloneDerivation

Suggests to use a standalone deriving declaration when GHC can't derive a typeclass instance in a trivial way.

Triggered by: DerivBadErrConstructor Test cases(s): typecheckshould_failtcfail086

SuggestFillInWildcardConstraint

Suggests the user to fill in the wildcard constraint to disambiguate which constraint that is.

Example: deriving instance _ => Eq (Foo f a)

Triggered by: DerivBadErrConstructor Test cases(s): partial-sigsshould_failT13324_fail2

SuggestRenameForall

Suggests to use an identifier other than forall Triggered by: TcRnForallIdentifier

SuggestAppropriateTHTick NameSpace

Suggests to use the appropriate Template Haskell tick: a single tick for a term-level NameSpace, or a double tick for a type-level NameSpace.

Triggered by: TcRnIncorrectNameSpace.

SuggestDumpSlices

Suggests enabling -ddump-splices to help debug an issue when a Name is not in scope or is used in multiple different namespaces (e.g. both as a data constructor and a type constructor).

Concomitant with NoExactName or SameName errors, see e.g. "GHC.Rename.Env.lookupExactOcc_either". Test cases: T5971, T7241, T13937.

SuggestAddTick UntickedPromotedThing

Suggests adding a tick to refer to something which has been promoted to the type level, e.g. a data constructor.

Test cases: T9778, T19984.

SuggestMoveToDeclarationSite

Something is split off from its corresponding declaration. For example, a datatype is given a role declaration in a different module.

Test cases: T495, T8485, T2713, T5533.

Fields

  • SDoc

    fixity declaration, role annotation, type signature, ...

  • RdrName

    the RdrName for the declaration site

SuggestSimilarNames RdrName (NonEmpty SimilarName)

Suggest a similar name that the user might have meant, e.g. suggest traverse when the user has written travrese.

Test case: mod73.

RemindFieldSelectorSuppressed

Remind the user that the field selector has been suppressed because of -XNoFieldSelectors.

Test cases: NFSSuppressed, records-nofieldselectors.

ImportSuggestion ImportSuggestion

Suggest importing from a module, removing a hiding clause, or explain to the user that we couldn't find a module with the given ModuleName.

Test cases: mod28, mod36, mod87, mod114, ...

SuggestImportingDataCon

Suggest importing a data constructor to bring it into scope Triggered by: TcRnTypeCannotBeMarshaled

Test cases: ccfail004

SuggestPlacePragmaInHeader 

Instances

Instances details
Outputable GhcHint Source # 
Instance details

Defined in GHC.Types.Hint.Ppr

Methods

ppr :: GhcHint -> SDoc Source #

data AvailableBindings Source #

The bindings we have available in scope when suggesting an explicit type signature.

Constructors

NamedBindings (NonEmpty Name) 
UnnamedBinding

An unknown binding (i.e. too complicated to turn into a Name)

data LanguageExtensionHint Source #

Constructors

SuggestSingleExtension !SDoc !Extension

Suggest to enable the input extension. This is the hint that GHC emits if this is not a "known" fix, i.e. this is GHC giving its best guess on what extension might be necessary to make a certain program compile. For example, GHC might suggests to enable BlockArguments when the user simply formatted incorrectly the input program, so GHC here is trying to be as helpful as possible. If the input SDoc is not empty, it will contain some extra information about the why the extension is required, but it's totally irrelevant/redundant for IDEs and other tools.

SuggestAnyExtension !SDoc [Extension]

Suggest to enable the input extensions. The list is to be intended as disjuctive i.e. the user is suggested to enable any of the extensions listed. If the input SDoc is not empty, it will contain some extra information about the why the extensions are required, but it's totally irrelevant/redundant for IDEs and other tools.

SuggestExtensions !SDoc [Extension]

Suggest to enable the input extensions. The list is to be intended as conjunctive i.e. the user is suggested to enable all the extensions listed. If the input SDoc is not empty, it will contain some extra information about the why the extensions are required, but it's totally irrelevant/redundant for IDEs and other tools.

SuggestExtensionInOrderTo !SDoc !Extension

Suggest to enable the input extension in order to fix a certain problem. This is the suggestion that GHC emits when is more-or-less clear "what's going on". For example, if both DeriveAnyClass and GeneralizedNewtypeDeriving are turned on, the right thing to do is to enabled DerivingStrategies, so in contrast to SuggestSingleExtension GHC will be a bit more "imperative" (i.e. "Use X Y Z in order to ... "). If the input SDoc is not empty, it will contain some extra information about the why the extensions are required, but it's totally irrelevant/redundant for IDEs and other tools.

suggestExtension :: Extension -> GhcHint Source #

Suggests a single extension without extra user info.

suggestExtensionWithInfo :: SDoc -> Extension -> GhcHint Source #

Like suggestExtension but allows supplying extra info for the user.

suggestExtensions :: [Extension] -> GhcHint Source #

Suggests to enable every extension in the list.

suggestExtensionsWithInfo :: SDoc -> [Extension] -> GhcHint Source #

Like suggestExtensions but allows supplying extra info for the user.

suggestAnyExtension :: [Extension] -> GhcHint Source #

Suggests to enable any extension in the list.

suggestAnyExtensionWithInfo :: SDoc -> [Extension] -> GhcHint Source #

Like suggestAnyExtension but allows supplying extra info for the user.

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.

Rendering Messages

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

Show SDoc Source # 
Instance details

Defined in GHC.CmmToAsm.AArch64.Regs

Outputable SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: SDoc -> SDoc Source #

Eq SDoc Source # 
Instance details

Defined in GHC.CmmToAsm.AArch64.Regs

Methods

(==) :: SDoc -> SDoc -> Bool #

(/=) :: SDoc -> SDoc -> Bool #

OutputableP env SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

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

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.

mkDecorated :: [SDoc] -> DecoratedSDoc Source #

Creates a new DecoratedSDoc out of a list of SDoc.

mkSimpleDecorated :: SDoc -> DecoratedSDoc Source #

Creates a new DecoratedSDoc out of a single SDoc

unionDecoratedSDoc :: DecoratedSDoc -> DecoratedSDoc -> DecoratedSDoc Source #

Joins two DecoratedSDoc together. The resulting DecoratedSDoc will have a number of entries which is the sum of the lengths of the input.

mapDecoratedSDoc :: (SDoc -> SDoc) -> DecoratedSDoc -> DecoratedSDoc Source #

Apply a transformation function to all elements of a DecoratedSDoc.

mkLocMessage :: MessageClass -> SrcSpan -> SDoc -> SDoc Source #

Make an unannotated error message with location info.

mkLocMessageAnn Source #

Arguments

:: Maybe String

optional annotation

-> MessageClass

What kind of message?

-> SrcSpan

location

-> SDoc

message

-> SDoc 

Make a possibly annotated error message with location info.

Queries

isIntrinsicErrorMessage :: Diagnostic e => MsgEnvelope e -> Bool Source #

Returns True if this is, intrinsically, a failure. See Note [Intrinsic And Extrinsic Failures].

isExtrinsicErrorMessage :: MsgEnvelope e -> Bool Source #

Returns True if the envelope contains a message that will stop compilation: either an intrinsic error or a fatal (-Werror) warning

partitionMessages :: Diagnostic e => Messages e -> (Messages e, Messages e) Source #

Partitions the Messages and returns a tuple which first element are the warnings, and the second the errors.

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.

errorsOrFatalWarningsFound :: Messages e -> Bool Source #

Are there any errors or -Werror warnings here?