Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data Messages e
- mkMessages :: Bag (MsgEnvelope e) -> Messages e
- getMessages :: Messages e -> Bag (MsgEnvelope e)
- emptyMessages :: Messages e
- isEmptyMessages :: Messages e -> Bool
- singleMessage :: MsgEnvelope e -> Messages e
- addMessage :: MsgEnvelope e -> Messages e -> Messages e
- unionMessages :: Messages e -> Messages e -> Messages e
- unionManyMessages :: Foldable f => f (Messages e) -> Messages e
- filterMessages :: (MsgEnvelope e -> Bool) -> Messages e -> Messages e
- data MsgEnvelope e = MsgEnvelope {}
- data MessageClass
- data Severity
- class HasDefaultDiagnosticOpts (DiagnosticOpts a) => Diagnostic a where
- type DiagnosticOpts a
- diagnosticMessage :: DiagnosticOpts a -> a -> DecoratedSDoc
- diagnosticReason :: a -> DiagnosticReason
- diagnosticHints :: a -> [GhcHint]
- diagnosticCode :: a -> Maybe DiagnosticCode
- data UnknownDiagnostic opts where
- UnknownDiagnostic :: forall a opts. (Diagnostic a, Typeable a) => (opts -> DiagnosticOpts a) -> a -> UnknownDiagnostic opts
- mkSimpleUnknownDiagnostic :: (Diagnostic a, Typeable a, DiagnosticOpts a ~ NoDiagnosticOpts) => a -> UnknownDiagnostic b
- mkUnknownDiagnostic :: (Typeable a, Diagnostic a) => a -> UnknownDiagnostic (DiagnosticOpts a)
- embedUnknownDiagnostic :: (Diagnostic a, Typeable a) => (opts -> DiagnosticOpts a) -> a -> UnknownDiagnostic opts
- data DiagnosticMessage = DiagnosticMessage {}
- data DiagnosticReason where
- newtype ResolvedDiagnosticReason = ResolvedDiagnosticReason {}
- data DiagnosticHint = DiagnosticHint !SDoc
- mkPlainDiagnostic :: DiagnosticReason -> [GhcHint] -> SDoc -> DiagnosticMessage
- mkPlainError :: [GhcHint] -> SDoc -> DiagnosticMessage
- mkDecoratedDiagnostic :: DiagnosticReason -> [GhcHint] -> [SDoc] -> DiagnosticMessage
- mkDecoratedError :: [GhcHint] -> [SDoc] -> DiagnosticMessage
- pprDiagnostic :: Diagnostic e => e -> SDoc
- class HasDefaultDiagnosticOpts opts where
- defaultOpts :: opts
- defaultDiagnosticOpts :: HasDefaultDiagnosticOpts (DiagnosticOpts opts) => DiagnosticOpts opts
- data NoDiagnosticOpts = NoDiagnosticOpts
- data GhcHint
- = (Outputable a, Typeable a) => UnknownHint a
- | SuggestExtension !LanguageExtensionHint
- | SuggestCorrectPragmaName ![String]
- | SuggestMissingDo
- | SuggestLetInDo
- | SuggestAddSignatureCabalFile !ModuleName
- | SuggestSignatureInstantiations !ModuleName [InstantiationSuggestion]
- | SuggestUseSpaces
- | SuggestUseWhitespaceAfter !OperatorWhitespaceSymbol
- | SuggestUseWhitespaceAround !String !OperatorWhitespaceOccurrence
- | SuggestParentheses
- | SuggestIncreaseMaxPmCheckModels
- | SuggestAddTypeSignatures AvailableBindings
- | SuggestBindToWildcard !(LHsExpr GhcTc)
- | SuggestAddInlineOrNoInlinePragma !Var !Activation
- | SuggestAddPhaseToCompetingRule !RuleName
- | SuggestAddToHSigExportList !Name !(Maybe Module)
- | SuggestIncreaseSimplifierIterations
- | SuggestUseTypeFromDataKind (Maybe RdrName)
- | SuggestQualifiedAfterModuleName
- | SuggestThQuotationSyntax
- | SuggestRoles [Role]
- | SuggestQualifyStarOperator
- | SuggestTypeSignatureRemoveQualifier
- | SuggestFixOrphanInst { }
- | SuggestAddStandaloneDerivation
- | SuggestAddStandaloneKindSignature Name
- | SuggestFillInWildcardConstraint
- | SuggestAppropriateTHTick NameSpace
- | SuggestDumpSlices
- | SuggestAddTick UntickedPromotedThing
- | SuggestMoveToDeclarationSite SDoc RdrName
- | SuggestSimilarNames RdrName (NonEmpty SimilarName)
- | RemindFieldSelectorSuppressed { }
- | ImportSuggestion OccName ImportSuggestion
- | SuggestPlacePragmaInHeader
- | SuggestPatternMatchingSyntax
- | SuggestSpecialiseVisibilityHints Name
- | SuggestRenameTypeVariable
- | SuggestExplicitBidiPatSyn Name (LPat GhcRn) [LIdP GhcRn]
- | SuggestSafeHaskell
- | SuggestRemoveRecordWildcard
- | SuggestMoveNonCanonicalDefinition Name Name String
- | SuggestIncreaseReductionDepth
- | SuggestRemoveNonCanonicalDefinition Name Name String
- | SuggestEtaReduceAbsDataTySyn TyCon
- | RemindRecordMissingField FastString Type Type
- | SuggestBindTyVarOnLhs RdrName
- | SuggestAnonymousWildcard
- | SuggestExplicitQuantification RdrName
- | SuggestBindTyVarExplicitly Name
- data AvailableBindings
- data LanguageExtensionHint
- suggestExtension :: Extension -> GhcHint
- suggestExtensionWithInfo :: SDoc -> Extension -> GhcHint
- suggestExtensions :: [Extension] -> GhcHint
- suggestExtensionsWithInfo :: SDoc -> [Extension] -> GhcHint
- suggestAnyExtension :: [Extension] -> GhcHint
- suggestAnyExtensionWithInfo :: SDoc -> [Extension] -> GhcHint
- useExtensionInOrderTo :: SDoc -> Extension -> GhcHint
- noHints :: [GhcHint]
- data SDoc
- data DecoratedSDoc
- mkDecorated :: [SDoc] -> DecoratedSDoc
- mkSimpleDecorated :: SDoc -> DecoratedSDoc
- unionDecoratedSDoc :: DecoratedSDoc -> DecoratedSDoc -> DecoratedSDoc
- mapDecoratedSDoc :: (SDoc -> SDoc) -> DecoratedSDoc -> DecoratedSDoc
- pprMessageBag :: Bag SDoc -> SDoc
- mkLocMessage :: MessageClass -> SrcSpan -> SDoc -> SDoc
- mkLocMessageWarningGroups :: Bool -> MessageClass -> SrcSpan -> SDoc -> SDoc
- getCaretDiagnostic :: MessageClass -> SrcSpan -> IO SDoc
- isIntrinsicErrorMessage :: Diagnostic e => MsgEnvelope e -> Bool
- isExtrinsicErrorMessage :: MsgEnvelope e -> Bool
- isWarningMessage :: Diagnostic e => MsgEnvelope e -> Bool
- getErrorMessages :: Diagnostic e => Messages e -> Bag (MsgEnvelope e)
- getWarningMessages :: Diagnostic e => Messages e -> Bag (MsgEnvelope e)
- partitionMessages :: Diagnostic e => Messages e -> (Messages e, Messages e)
- errorsFound :: Diagnostic e => Messages e -> Bool
- errorsOrFatalWarningsFound :: Messages e -> Bool
- data DiagnosticCode = DiagnosticCode {}
Messages
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
Functor Messages Source # | |
Foldable Messages Source # | |
Defined in GHC.Types.Error 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 # elem :: Eq a => a -> Messages a -> Bool # maximum :: Ord a => Messages a -> a # minimum :: Ord a => Messages a -> a # | |
Traversable Messages Source # | |
Diagnostic e => ToJson (Messages e) Source # | |
Diagnostic e => Outputable (Messages e) Source # | |
Monoid (Messages e) Source # | |
Semigroup (Messages e) Source # | |
mkMessages :: Bag (MsgEnvelope e) -> Messages e Source #
getMessages :: Messages e -> Bag (MsgEnvelope e) Source #
emptyMessages :: Messages e Source #
isEmptyMessages :: Messages e -> Bool Source #
singleMessage :: MsgEnvelope e -> Messages e 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 Messages
s together
filterMessages :: (MsgEnvelope e -> Bool) -> Messages e -> Messages e Source #
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
MsgEnvelope
s are aggregated into Messages
that are returned to the
user.
MsgEnvelope | |
|
Instances
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
.
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 ResolvedDiagnosticReason (Maybe DiagnosticCode) | Diagnostics from the compiler. This constructor is very powerful as
it allows the construction of a The |
Instances
ToJson MessageClass Source # | |
Defined in GHC.Types.Error json :: MessageClass -> JsonDoc 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
SevIgnore | Ignore this message, for example in case of suppression of warnings users don't want to see. See Note [Suppressing Messages] |
SevWarning | |
SevError |
class HasDefaultDiagnosticOpts (DiagnosticOpts a) => 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.
type DiagnosticOpts a Source #
Type of configuration options for the diagnostic.
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:
- The message might be from a plugin that does not supply codes.
- The message might not yet have been assigned a code. See the
Diagnostic
instance forDiagnosticMessage
.
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
data UnknownDiagnostic opts where Source #
An existential wrapper around an unknown diagnostic.
UnknownDiagnostic :: forall a opts. (Diagnostic a, Typeable a) => (opts -> DiagnosticOpts a) -> a -> UnknownDiagnostic opts |
Instances
HasDefaultDiagnosticOpts opts => Diagnostic (UnknownDiagnostic opts) Source # | |||||
Defined in GHC.Types.Error
diagnosticMessage :: DiagnosticOpts (UnknownDiagnostic opts) -> UnknownDiagnostic opts -> DecoratedSDoc Source # diagnosticReason :: UnknownDiagnostic opts -> DiagnosticReason Source # diagnosticHints :: UnknownDiagnostic opts -> [GhcHint] Source # diagnosticCode :: UnknownDiagnostic opts -> Maybe DiagnosticCode Source # | |||||
type DiagnosticOpts (UnknownDiagnostic opts) Source # | |||||
Defined in GHC.Types.Error |
mkSimpleUnknownDiagnostic :: (Diagnostic a, Typeable a, DiagnosticOpts a ~ NoDiagnosticOpts) => a -> UnknownDiagnostic b Source #
Make a "simple" unknown diagnostic which doesn't have any configuration options.
mkUnknownDiagnostic :: (Typeable a, Diagnostic a) => a -> UnknownDiagnostic (DiagnosticOpts a) Source #
Make an unknown diagnostic which uses the same options as the context it will be embedded into.
embedUnknownDiagnostic :: (Diagnostic a, Typeable a) => (opts -> DiagnosticOpts a) -> a -> UnknownDiagnostic opts Source #
Embed a more complicated diagnostic which requires a potentially different options type.
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 interpret its payload (as it's just a
structured document). All we can do is to print it out and look at its
DiagnosticReason
.
DiagnosticMessage | |
|
Instances
Diagnostic DiagnosticMessage Source # | |||||
Defined in GHC.Types.Error
| |||||
Show (MsgEnvelope DiagnosticMessage) Source # | |||||
Defined in GHC.Types.Error showsPrec :: Int -> MsgEnvelope DiagnosticMessage -> ShowS # show :: MsgEnvelope DiagnosticMessage -> String # showList :: [MsgEnvelope DiagnosticMessage] -> ShowS # | |||||
type DiagnosticOpts DiagnosticMessage Source # | |||||
Defined in GHC.Types.Error |
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.
WarningWithoutFlag | Born as a warning. |
WarningWithFlags !(NonEmpty WarningFlag) | Warning was enabled with the flag. |
WarningWithCategory !WarningCategory | Warning was enabled with a custom category. |
ErrorWithoutFlag | Born as an error. |
pattern WarningWithFlag :: WarningFlag -> DiagnosticReason | The single warning case |
Instances
Outputable DiagnosticReason Source # | |
Defined in GHC.Types.Error ppr :: DiagnosticReason -> SDoc Source # | |
Show DiagnosticReason Source # | |
Defined in GHC.Types.Error showsPrec :: Int -> DiagnosticReason -> ShowS # show :: DiagnosticReason -> String # showList :: [DiagnosticReason] -> ShowS # | |
Eq DiagnosticReason Source # | |
Defined in GHC.Types.Error (==) :: DiagnosticReason -> DiagnosticReason -> Bool # (/=) :: DiagnosticReason -> DiagnosticReason -> Bool # |
newtype ResolvedDiagnosticReason Source #
Like a DiagnosticReason
, but resolved against a specific set of DynFlags
to
work out which warning flag actually enabled this warning.
Instances
Outputable ResolvedDiagnosticReason Source # | |
Defined in GHC.Types.Error ppr :: ResolvedDiagnosticReason -> SDoc Source # |
data DiagnosticHint Source #
A generic Hint
message, to be used with DiagnosticMessage
.
Instances
Outputable DiagnosticHint Source # | |
Defined in GHC.Types.Error ppr :: DiagnosticHint -> SDoc Source # |
mkPlainDiagnostic :: DiagnosticReason -> [GhcHint] -> SDoc -> DiagnosticMessage Source #
mkPlainError :: [GhcHint] -> SDoc -> DiagnosticMessage Source #
Create an error DiagnosticMessage
holding just a single SDoc
mkDecoratedDiagnostic :: DiagnosticReason -> [GhcHint] -> [SDoc] -> DiagnosticMessage Source #
Create a DiagnosticMessage
from a list of bulleted SDocs and a DiagnosticReason
mkDecoratedError :: [GhcHint] -> [SDoc] -> DiagnosticMessage Source #
Create an error DiagnosticMessage
from a list of bulleted SDocs
pprDiagnostic :: Diagnostic e => e -> SDoc Source #
class HasDefaultDiagnosticOpts opts where Source #
defaultOpts :: opts Source #
Instances
HasDefaultDiagnosticOpts DriverMessageOpts Source # | |
Defined in GHC.Driver.Errors.Ppr | |
HasDefaultDiagnosticOpts GhcMessageOpts Source # | |
Defined in GHC.Driver.Errors.Ppr | |
HasDefaultDiagnosticOpts IfaceMessageOpts Source # | |
Defined in GHC.Iface.Errors.Ppr | |
HasDefaultDiagnosticOpts TcRnMessageOpts Source # | |
Defined in GHC.Tc.Errors.Ppr | |
HasDefaultDiagnosticOpts NoDiagnosticOpts Source # | |
Defined in GHC.Types.Error |
defaultDiagnosticOpts :: HasDefaultDiagnosticOpts (DiagnosticOpts opts) => DiagnosticOpts opts Source #
data NoDiagnosticOpts Source #
Instances
Hints and refactoring actions
A type for hints emitted by GHC. A hint suggests a possible way to deal with a particular warning or error.
(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) |
SuggestCorrectPragmaName ![String] | Suggests possible corrections of a misspelled pragma. Its argument represents all applicable suggestions. Example: {-# LNGUAGE BangPatterns #-} Test case(s): parsershould_compileT21589 |
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: Example: See comment of Test case(s): driver/T12955 |
SuggestSignatureInstantiations !ModuleName [InstantiationSuggestion] | Suggests to explicitly list the instantiations for the signatures in the GHC invocation command. Triggered by: Example: See comment of Test case(s): driver/T12955 |
SuggestUseSpaces | Suggests to use spaces instead of tabs. Triggered by: 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: 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: 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 Triggered by: |
SuggestQualifiedAfterModuleName | Suggests placing the Triggered by: |
SuggestThQuotationSyntax | Suggests using TemplateHaskell quotation syntax. Triggered by: |
SuggestRoles [Role] | Suggests alternative roles in case we found an illegal one. Triggered by: |
SuggestQualifyStarOperator | Suggests qualifying the Triggered by: |
SuggestTypeSignatureRemoveQualifier | Suggests that for a type signature 'M.x :: ...' the qualifier should be omitted in order to be accepted by GHC. Triggered by: |
SuggestFixOrphanInst | Suggests to move an orphan instance (for a typeclass or a type or data family), or to newtype-wrap it. Triggered by: |
SuggestAddStandaloneDerivation | Suggests to use a standalone deriving declaration when GHC can't derive a typeclass instance in a trivial way. Triggered by: |
SuggestAddStandaloneKindSignature Name | Suggests to add a standalone kind signature when GHC can't perform kind inference. Triggered by: |
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: |
SuggestAppropriateTHTick NameSpace | Suggests to use the appropriate Template Haskell tick:
a single tick for a term-level Triggered by: |
SuggestDumpSlices | Suggests enabling -ddump-splices to help debug an issue
when a Concomitant with |
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. |
SuggestSimilarNames RdrName (NonEmpty SimilarName) | Suggest a similar name that the user might have meant,
e.g. suggest Test case: mod73. |
RemindFieldSelectorSuppressed | Remind the user that the field selector has been suppressed because of -XNoFieldSelectors. Test cases: NFSSuppressed, records-nofieldselectors. |
ImportSuggestion OccName ImportSuggestion | Suggest importing from a module, removing a Test cases: mod28, mod36, mod87, mod114, ... |
SuggestPlacePragmaInHeader | Found a pragma in the body of a module, suggest placing it in the header. |
SuggestPatternMatchingSyntax | Suggest using pattern matching syntax for a non-bidirectional pattern synonym Test cases: patsynshould_failrecord-exquant typecheckshould_failT3176 |
SuggestSpecialiseVisibilityHints Name | Suggest tips for making a definition visible for the purpose of writing a SPECIALISE pragma for it in a different module. Test cases: none |
SuggestRenameTypeVariable | Suggest renaming implicitly quantified type variable in case it captures a term's name. |
SuggestExplicitBidiPatSyn Name (LPat GhcRn) [LIdP GhcRn] | |
SuggestSafeHaskell | Suggest enabling one of the SafeHaskell modes Safe, Unsafe or Trustworthy. |
SuggestRemoveRecordWildcard | Suggest removing a record wildcard from a pattern when it doesn't bind anything useful. |
SuggestMoveNonCanonicalDefinition | Suggest moving a method implementation to a different instance to its superclass that defines the canonical version of the method. |
SuggestIncreaseReductionDepth | Suggest to increase the solver maximum reduction depth |
SuggestRemoveNonCanonicalDefinition | Suggest removing a method implementation when a superclass defines the canonical version of that method. |
SuggestEtaReduceAbsDataTySyn TyCon | Suggest eta-reducing a type synonym used in the implementation of abstract data. |
RemindRecordMissingField FastString Type Type | Remind the user that there is no field of a type and name in the record, constructors are in the usual order $x$, $r$, $a$ |
SuggestBindTyVarOnLhs RdrName | Suggest binding the type variable on the LHS of the type declaration |
SuggestAnonymousWildcard | Suggest using an anonymous wildcard instead of a named wildcard |
SuggestExplicitQuantification RdrName | Suggest explicitly quantifying a type variable instead of relying on implicit quantification |
SuggestBindTyVarExplicitly Name | Suggest binding explicitly; e.g data T @k (a :: F k) = .... |
Instances
data AvailableBindings Source #
The bindings we have available in scope when suggesting an explicit type signature.
NamedBindings (NonEmpty Name) | |
UnnamedBinding | An unknown binding (i.e. too complicated to turn into a |
data LanguageExtensionHint Source #
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 |
SuggestAnyExtension !SDoc [Extension] | Suggest to enable the input extensions. The list
is to be intended as disjunctive i.e. the user is
suggested to enable any of the extensions listed. If
the input |
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 |
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 |
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.
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
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
JsRender SDoc Source # | |
IsDoc SDoc Source # | |
IsLine SDoc Source # | |
Defined in GHC.Utils.Outputable text :: String -> SDoc Source # ftext :: FastString -> SDoc Source # ztext :: FastZString -> SDoc Source # (<>) :: SDoc -> SDoc -> SDoc Source # (<+>) :: SDoc -> SDoc -> SDoc Source # sep :: [SDoc] -> SDoc Source # fsep :: [SDoc] -> SDoc Source # hcat :: [SDoc] -> SDoc Source # | |
IsOutput SDoc Source # | |
Defined in GHC.Utils.Outputable | |
Outputable SDoc Source # | |
IsString SDoc Source # | |
Defined in GHC.Utils.Outputable fromString :: String -> SDoc # | |
OutputableP env SDoc Source # | |
type Line SDoc Source # | |
Defined in GHC.Utils.Outputable |
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
.
:: MessageClass | What kind of message? |
-> SrcSpan | location |
-> SDoc | message |
-> SDoc |
mkLocMessageWarningGroups Source #
:: Bool | Print warning groups (if applicable)? |
-> MessageClass | What kind of message? |
-> SrcSpan | location |
-> SDoc | message |
-> SDoc |
Make an error message with location info, specifying whether to show warning groups (if applicable).
getCaretDiagnostic :: MessageClass -> SrcSpan -> IO SDoc Source #
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
isWarningMessage :: Diagnostic e => MsgEnvelope e -> Bool Source #
getErrorMessages :: Diagnostic e => Messages e -> Bag (MsgEnvelope e) Source #
getWarningMessages :: Diagnostic e => Messages e -> Bag (MsgEnvelope e) Source #
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?
Diagnostic codes
data DiagnosticCode Source #
A diagnostic code is a namespaced numeric identifier unique to the given diagnostic (error or warning).
All diagnostic codes defined within GHC are given the GHC namespace.
See Note [Diagnostic codes] in GHC.Types.Error.Codes.
DiagnosticCode | |
|
Instances
ToJson DiagnosticCode Source # | |
Defined in GHC.Types.Error json :: DiagnosticCode -> JsonDoc Source # | |
Outputable DiagnosticCode Source # | |
Defined in GHC.Types.Error ppr :: DiagnosticCode -> SDoc Source # | |
Show DiagnosticCode Source # | |
Defined in GHC.Types.Error showsPrec :: Int -> DiagnosticCode -> ShowS # show :: DiagnosticCode -> String # showList :: [DiagnosticCode] -> ShowS # | |
Eq DiagnosticCode Source # | |
Defined in GHC.Types.Error (==) :: DiagnosticCode -> DiagnosticCode -> Bool # (/=) :: DiagnosticCode -> DiagnosticCode -> Bool # | |
Ord DiagnosticCode Source # | |
Defined in GHC.Types.Error compare :: DiagnosticCode -> DiagnosticCode -> Ordering # (<) :: DiagnosticCode -> DiagnosticCode -> Bool # (<=) :: DiagnosticCode -> DiagnosticCode -> Bool # (>) :: DiagnosticCode -> DiagnosticCode -> Bool # (>=) :: DiagnosticCode -> DiagnosticCode -> Bool # max :: DiagnosticCode -> DiagnosticCode -> DiagnosticCode # min :: DiagnosticCode -> DiagnosticCode -> DiagnosticCode # |