Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- 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
- | SuggestDefaultDeclaration TyCon [Type]
- | SuggestExplicitDerivingClauseStrategies (Map AssumedDerivingStrategy [LHsSigType GhcRn])
- | SuggestExplicitStandaloneDerivingStrategy AssumedDerivingStrategy (LHsSigWcType GhcRn)
- | SuggestParenthesizePatternRHS
- data AvailableBindings
- data InstantiationSuggestion = InstantiationSuggestion !ModuleName !Module
- data LanguageExtensionHint
- data ImportSuggestion
- data HowInScope
- data SimilarName
- data StarIsType
- data UntickedPromotedThing
- data AssumedDerivingStrategy
- pprUntickedConstructor :: LexicalFixity -> Name -> SDoc
- isBareSymbol :: LexicalFixity -> Name -> Bool
- 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
- noStarIsTypeHints :: StarIsType -> RdrName -> [GhcHint]
Documentation
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) = .... |
SuggestDefaultDeclaration TyCon [Type] | Suggest a default declaration; e.g |
SuggestExplicitDerivingClauseStrategies | Suggest using explicit deriving strategies for a deriving clause. Triggered by: See comment of |
| |
SuggestExplicitStandaloneDerivingStrategy | Suggest using an explicit deriving strategy for a standalone deriving instance. Triggered by: See comment of |
| |
SuggestParenthesizePatternRHS | Suggest add parens to pattern `e -> p :: t` |
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 InstantiationSuggestion Source #
An InstantiationSuggestion
for a '.hsig' file. This is generated
by GHC in case of a DriverUnexpectedSignature
and suggests a way
to instantiate a particular signature, where the first argument is
the signature name and the second is the module where the signature
was defined.
Example:
src/MyStr.hsig:2:11: error: Unexpected signature: ‘MyStr’ (Try passing -instantiated-with="MyStr=MyStr" replacing MyStr as necessary.)
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 |
data ImportSuggestion Source #
Suggest how to fix an import.
CouldImportFrom (NonEmpty (Module, ImportedModsVal)) | Some module exports what we want, but we aren't explicitly importing it. |
CouldUnhideFrom (NonEmpty (Module, ImportedModsVal)) | Some module exports what we want, but we are explicitly hiding it. |
CouldRemoveTypeKeyword ModuleName | The module exports what we want, but it isn't a type. |
CouldAddTypeKeyword ModuleName | The module exports what we want, but it's a type and we have |
ImportDataCon | Suggest importing a data constructor to bring it into scope |
|
data HowInScope Source #
Explain how something is in scope.
LocallyBoundAt SrcSpan | It was locally bound at this particular source location. |
ImportedBy ImpDeclSpec | It was imported by this particular import declaration. |
data UntickedPromotedThing Source #
Something is promoted to the type-level without a promotion tick.
data AssumedDerivingStrategy Source #
The deriving strategy that was assumed when not explicitly listed in the
source. This is used solely by the missing-deriving-strategies warning.
There's no Via
case because we never assume that.
Instances
pprUntickedConstructor :: LexicalFixity -> Name -> SDoc Source #
isBareSymbol :: LexicalFixity -> Name -> Bool Source #
Whether a constructor name is printed out as a bare symbol, e.g. :
.
True for symbolic names in infix position.
Used for pretty-printing.
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.
noStarIsTypeHints :: StarIsType -> RdrName -> [GhcHint] Source #
Display info about the treatment of *
under NoStarIsType.
With StarIsType, three properties of *
hold:
(a) it is not an infix operator (b) it is always in scope (c) it is a synonym for Data.Kind.Type
However, the user might not know that they are working on a module with NoStarIsType and write code that still assumes (a), (b), and (c), which actually do not hold in that module.
Violation of (a) shows up in the parser. For instance, in the following
examples, we have *
not applied to enough arguments:
data A :: * data F :: * -> *
Violation of (b) or (c) show up in the renamer and the typechecker respectively. For instance:
type K = Either * Bool
This will parse differently depending on whether StarIsType is enabled, but it will parse nonetheless. With NoStarIsType it is parsed as a type operator, thus we have ((*) Either Bool). Now there are two cases to consider:
- There is no definition of (*) in scope. In this case the renamer will fail to look it up. This is a violation of assumption (b).
- There is a definition of the (*) type operator in scope (for example coming from GHC.TypeNats). In this case the user will get a kind mismatch error. This is a violation of assumption (c).
The user might unknowingly be working on a module with NoStarIsType
or use *
as Type
out of habit. So it is important to give a
hint whenever an assumption about *
is violated. Unfortunately, it is
somewhat difficult to deal with (c), so we limit ourselves to (a) and (b).
noStarIsTypeHints
returns appropriate hints to the user depending on the
extensions enabled in the module and the name that triggered the error.
That is, if we have NoStarIsType and the error is related to *
or its
Unicode variant, we will suggest using Type
; otherwise we won't
suggest anything.