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

GHC.Types.Hint

Synopsis

Documentation

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)

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: 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 
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

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

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 disjunctive 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.

data ImportSuggestion Source #

Suggest how to fix an import.

Constructors

CouldImportFrom (NonEmpty (Module, ImportedModsVal)) OccName

Some module exports what we want, but we aren't explicitly importing it.

CouldUnhideFrom (NonEmpty (Module, ImportedModsVal)) OccName

Some module exports what we want, but we are explicitly hiding it.

data HowInScope Source #

Explain how something is in scope.

Constructors

LocallyBoundAt SrcSpan

It was locally bound at this particular source location.

ImportedBy ImpDeclSpec

It was imported by this particular import declaration.

data StarIsType Source #

Whether * is a synonym for Type.

Constructors

StarIsNotType 
StarIsType 

data UntickedPromotedThing Source #

Something is promoted to the type-level without a promotion tick.

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:

  1. 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).
  2. 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.