ghc-9.13: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Types.Error.Codes

Description

Defines diagnostic codes for the diagnostics emitted by GHC.

A diagnostic code is a numeric unique identifier for a diagnostic. See Note [Diagnostic codes].

Synopsis

General diagnostic code infrastructure

class DiagnosticCodeNameSpace namespace Source #

A constraint for a namespace which has its own diagnostic codes.

See Note [Diagnostic code namespaces].

Associated Types

type NameSpaceTag namespace = (r :: Symbol) | r -> namespace Source #

The symbolic tag for a namespace.

type DiagnosticCodeFor namespace (c :: Symbol) :: Nat Source #

A diagnostic code in a given namespace.

type ConRecursIntoFor namespace (c :: Symbol) :: Maybe Type Source #

Specify that one should recur into an argument of a constructor in order to obtain a diagnostic code. See Note [Diagnostic codes].

Instances

Instances details
DiagnosticCodeNameSpace GHC Source # 
Instance details

Defined in GHC.Types.Error.Codes

Associated Types

type NameSpaceTag GHC 
Instance details

Defined in GHC.Types.Error.Codes

type NameSpaceTag GHC = "GHC"
type DiagnosticCodeFor GHC con 
Instance details

Defined in GHC.Types.Error.Codes

type ConRecursIntoFor GHC con 
Instance details

Defined in GHC.Types.Error.Codes

type Outdated (a :: k) = a Source #

Use this type synonym to mark a diagnostic code as outdated.

The presence of this type synonym is used by the codes test to determine which diagnostic codes to check for testsuite coverage.

constructorCode :: forall namespace diag. (Generic diag, GDiagnosticCode namespace (Rep diag)) => diag -> Maybe DiagnosticCode Source #

This function obtains a diagnostic code by looking up the constructor name using generics, and using the DiagnosticCode type family.

constructorCodes :: forall namespace diag. (Generic diag, GDiagnosticCodes namespace '[diag] (Rep diag)) => Map DiagnosticCode String Source #

This function computes all diagnostic codes that occur inside a given type using generics and the DiagnosticCode type family.

For example, if T = MkT1 | MkT2, GhcDiagnosticCode "MkT1" = 123 and GhcDiagnosticCode "MkT2" = 456, then we will get > constructorCodes GHC T = fromList [ (DiagnosticCode GHC 123, "MkT1"), (DiagnosticCode GHC 456, "MkT2") ]

GHC diagnostic codes

data GHC Source #

The GHC namespace for diagnostic codes.

Instances

Instances details
DiagnosticCodeNameSpace GHC Source # 
Instance details

Defined in GHC.Types.Error.Codes

Associated Types

type NameSpaceTag GHC 
Instance details

Defined in GHC.Types.Error.Codes

type NameSpaceTag GHC = "GHC"
type DiagnosticCodeFor GHC con 
Instance details

Defined in GHC.Types.Error.Codes

type ConRecursIntoFor GHC con 
Instance details

Defined in GHC.Types.Error.Codes

type NameSpaceTag GHC Source # 
Instance details

Defined in GHC.Types.Error.Codes

type NameSpaceTag GHC = "GHC"
type ConRecursIntoFor GHC con Source # 
Instance details

Defined in GHC.Types.Error.Codes

type DiagnosticCodeFor GHC con Source # 
Instance details

Defined in GHC.Types.Error.Codes

type family GhcDiagnosticCode (c :: Symbol) = (n :: Nat) | n -> c where ... Source #

Type family computing the numeric diagnostic code for a given error message constructor.

Its injectivity annotation ensures uniqueness of error codes.

Never remove a return value from this type family! Outdated error messages must still be tracked here to ensure uniqueness of diagnostic codes across GHC versions.

See Note [Diagnostic codes] in GHC.Types.Error.

Equations

GhcDiagnosticCode "DsEmptyEnumeration" = 10190 
GhcDiagnosticCode "DsIdentitiesFound" = 4214 
GhcDiagnosticCode "DsOverflowedLiterals" = 97441 
GhcDiagnosticCode "DsRedundantBangPatterns" = 38520 
GhcDiagnosticCode "DsOverlappingPatterns" = 53633 
GhcDiagnosticCode "DsInaccessibleRhs" = 94210 
GhcDiagnosticCode "DsMaxPmCheckModelsReached" = 61505 
GhcDiagnosticCode "DsNonExhaustivePatterns" = 62161 
GhcDiagnosticCode "DsTopLevelBindsNotAllowed" = 48099 
GhcDiagnosticCode "DsUselessSpecialiseForClassMethodSelector" = 93315 
GhcDiagnosticCode "DsUselessSpecialiseForNoInlineFunction" = 38524 
GhcDiagnosticCode "DsOrphanRule" = 58181 
GhcDiagnosticCode "DsRuleLhsTooComplicated" = 69441 
GhcDiagnosticCode "DsRuleIgnoredDueToConstructor" = 828 
GhcDiagnosticCode "DsRuleBindersNotBound" = 40548 
GhcDiagnosticCode "DsLazyPatCantBindVarsOfUnliftedType" = 17879 
GhcDiagnosticCode "DsNotYetHandledByTH" = 65904 
GhcDiagnosticCode "DsAggregatedViewExpressions" = 19551 
GhcDiagnosticCode "DsUnbangedStrictPatterns" = 21030 
GhcDiagnosticCode "DsCannotMixPolyAndUnliftedBindings" = 20036 
GhcDiagnosticCode "DsWrongDoBind" = 8838 
GhcDiagnosticCode "DsUnusedDoBind" = 81995 
GhcDiagnosticCode "DsRecBindsNotAllowedForUnliftedTys" = 20185 
GhcDiagnosticCode "DsRuleMightInlineFirst" = 95396 
GhcDiagnosticCode "DsAnotherRuleMightFireFirst" = 87502 
GhcDiagnosticCode "DsIncompleteRecordSelector" = 17335 
GhcDiagnosticCode "PsErrParseLanguagePragma" = 68686 
GhcDiagnosticCode "PsErrUnsupportedExt" = 46537 
GhcDiagnosticCode "PsErrParseOptionsPragma" = 24342 
GhcDiagnosticCode "PsErrUnknownOptionsPragma" = 4924 
GhcDiagnosticCode "PsWarnBidirectionalFormatChars" = 3272 
GhcDiagnosticCode "PsWarnTab" = 94817 
GhcDiagnosticCode "PsWarnTransitionalLayout" = 93617 
GhcDiagnosticCode "PsWarnOperatorWhitespaceExtConflict" = 47082 
GhcDiagnosticCode "PsWarnOperatorWhitespace" = 40798 
GhcDiagnosticCode "PsWarnHaddockInvalidPos" = 94458 
GhcDiagnosticCode "PsWarnHaddockIgnoreMulti" = 5641 
GhcDiagnosticCode "PsWarnStarBinder" = 21887 
GhcDiagnosticCode "PsWarnStarIsType" = 39567 
GhcDiagnosticCode "PsWarnUnrecognisedPragma" = 42044 
GhcDiagnosticCode "PsWarnMisplacedPragma" = 28007 
GhcDiagnosticCode "PsWarnImportPreQualified" = 7924 
GhcDiagnosticCode "PsWarnViewPatternSignatures" = 834 
GhcDiagnosticCode "PsErrLexer" = 21231 
GhcDiagnosticCode "PsErrCmmLexer" = 75725 
GhcDiagnosticCode "PsErrCmmParser" = 9848 
GhcDiagnosticCode "PsErrParse" = 58481 
GhcDiagnosticCode "PsErrTypeAppWithoutSpace" = 84077 
GhcDiagnosticCode "PsErrLazyPatWithoutSpace" = 27207 
GhcDiagnosticCode "PsErrBangPatWithoutSpace" = 95644 
GhcDiagnosticCode "PsErrInvalidInfixHole" = 45106 
GhcDiagnosticCode "PsErrExpectedHyphen" = 44524 
GhcDiagnosticCode "PsErrSpaceInSCC" = 76176 
GhcDiagnosticCode "PsErrEmptyDoubleQuotes" = 11861 
GhcDiagnosticCode "PsErrLambdaCase" = 51179 
GhcDiagnosticCode "PsErrEmptyLambda" = 71614 
GhcDiagnosticCode "PsErrLinearFunction" = 31574 
GhcDiagnosticCode "PsErrMultiWayIf" = 28985 
GhcDiagnosticCode "PsErrOverloadedRecordUpdateNotEnabled" = 82135 
GhcDiagnosticCode "PsErrNumUnderscores" = 62330 
GhcDiagnosticCode "PsErrIllegalBangPattern" = 79767 
GhcDiagnosticCode "PsErrOverloadedRecordDotInvalid" = 26832 
GhcDiagnosticCode "PsErrIllegalPatSynExport" = 89515 
GhcDiagnosticCode "PsErrOverloadedRecordUpdateNoQualifiedFields" = 94863 
GhcDiagnosticCode "PsErrExplicitForall" = 25955 
GhcDiagnosticCode "PsErrIllegalQualifiedDo" = 40280 
GhcDiagnosticCode "PsErrQualifiedDoInCmd" = 54089 
GhcDiagnosticCode "PsErrRecordSyntaxInPatSynDecl" = 28021 
GhcDiagnosticCode "PsErrEmptyWhereInPatSynDecl" = 13248 
GhcDiagnosticCode "PsErrInvalidWhereBindInPatSynDecl" = 24737 
GhcDiagnosticCode "PsErrNoSingleWhereBindInPatSynDecl" = 65536 
GhcDiagnosticCode "PsErrDeclSpliceNotAtTopLevel" = 8451 
GhcDiagnosticCode "PsErrMultipleNamesInStandaloneKindSignature" = 42569 
GhcDiagnosticCode "PsErrIllegalExplicitNamespace" = 47007 
GhcDiagnosticCode "PsErrUnallowedPragma" = 85314 
GhcDiagnosticCode "PsErrImportPostQualified" = 87491 
GhcDiagnosticCode "PsErrImportQualifiedTwice" = 5661 
GhcDiagnosticCode "PsErrIllegalImportBundleForm" = 81284 
GhcDiagnosticCode "PsErrInvalidRuleActivationMarker" = 50396 
GhcDiagnosticCode "PsErrMissingBlock" = 16849 
GhcDiagnosticCode "PsErrUnsupportedBoxedSumExpr" = 9550 
GhcDiagnosticCode "PsErrUnsupportedBoxedSumPat" = 16863 
GhcDiagnosticCode "PsErrUnexpectedQualifiedConstructor" = 73413 
GhcDiagnosticCode "PsErrTupleSectionInPat" = 9646 
GhcDiagnosticCode "PsErrOpFewArgs" = 24180 
GhcDiagnosticCode "PsErrVarForTyCon" = 18208 
GhcDiagnosticCode "PsErrMalformedEntityString" = 26204 
GhcDiagnosticCode "PsErrDotsInRecordUpdate" = 70712 
GhcDiagnosticCode "PsErrInvalidDataCon" = 46574 
GhcDiagnosticCode "PsErrInvalidInfixDataCon" = 30670 
GhcDiagnosticCode "PsErrIllegalPromotionQuoteDataCon" = 80236 
GhcDiagnosticCode "PsErrUnpackDataCon" = 40845 
GhcDiagnosticCode "PsErrUnexpectedKindAppInDataCon" = 83653 
GhcDiagnosticCode "PsErrInvalidRecordCon" = 8195 
GhcDiagnosticCode "PsErrIllegalUnboxedStringInPat" = 69925 
GhcDiagnosticCode "PsErrIllegalUnboxedFloatingLitInPat" = 76595 
GhcDiagnosticCode "PsErrDoNotationInPat" = 6446 
GhcDiagnosticCode "PsErrIfThenElseInPat" = 45696 
GhcDiagnosticCode "PsErrLambdaCaseInPat" = Outdated 7636 
GhcDiagnosticCode "PsErrCaseInPat" = 53786 
GhcDiagnosticCode "PsErrLetInPat" = 78892 
GhcDiagnosticCode "PsErrLambdaInPat" = 482 
GhcDiagnosticCode "PsErrArrowExprInPat" = 4584 
GhcDiagnosticCode "PsErrArrowCmdInPat" = 98980 
GhcDiagnosticCode "PsErrArrowCmdInExpr" = 66043 
GhcDiagnosticCode "PsErrViewPatInExpr" = Outdated 66228 
GhcDiagnosticCode "PsErrOrPatInExpr" = 66718 
GhcDiagnosticCode "PsErrLambdaCmdInFunAppCmd" = 12178 
GhcDiagnosticCode "PsErrCaseCmdInFunAppCmd" = 92971 
GhcDiagnosticCode "PsErrLambdaCaseCmdInFunAppCmd" = Outdated 47171 
GhcDiagnosticCode "PsErrIfCmdInFunAppCmd" = 97005 
GhcDiagnosticCode "PsErrLetCmdInFunAppCmd" = 70526 
GhcDiagnosticCode "PsErrDoCmdInFunAppCmd" = 77808 
GhcDiagnosticCode "PsErrDoInFunAppExpr" = 52095 
GhcDiagnosticCode "PsErrMDoInFunAppExpr" = 67630 
GhcDiagnosticCode "PsErrLambdaInFunAppExpr" = 6074 
GhcDiagnosticCode "PsErrCaseInFunAppExpr" = 25037 
GhcDiagnosticCode "PsErrLambdaCaseInFunAppExpr" = Outdated 77182 
GhcDiagnosticCode "PsErrLetInFunAppExpr" = 90355 
GhcDiagnosticCode "PsErrIfInFunAppExpr" = 1239 
GhcDiagnosticCode "PsErrProcInFunAppExpr" = 4807 
GhcDiagnosticCode "PsErrMalformedTyOrClDecl" = 47568 
GhcDiagnosticCode "PsErrIllegalWhereInDataDecl" = 36952 
GhcDiagnosticCode "PsErrIllegalDataTypeContext" = 87429 
GhcDiagnosticCode "PsErrPrimStringInvalidChar" = 43080 
GhcDiagnosticCode "PsErrSuffixAT" = 33856 
GhcDiagnosticCode "PsErrPrecedenceOutOfRange" = 25078 
GhcDiagnosticCode "PsErrSemiColonsInCondExpr" = 75254 
GhcDiagnosticCode "PsErrSemiColonsInCondCmd" = 18910 
GhcDiagnosticCode "PsErrAtInPatPos" = 8382 
GhcDiagnosticCode "PsErrParseErrorOnInput" = 66418 
GhcDiagnosticCode "PsErrMalformedDecl" = 85316 
GhcDiagnosticCode "PsErrNotADataCon" = 25742 
GhcDiagnosticCode "PsErrInferredTypeVarNotAllowed" = 57342 
GhcDiagnosticCode "PsErrIllegalTraditionalRecordSyntax" = 65719 
GhcDiagnosticCode "PsErrParseErrorInCmd" = 3790 
GhcDiagnosticCode "PsErrInPat" = 7626 
GhcDiagnosticCode "PsErrIllegalRoleName" = 9009 
GhcDiagnosticCode "PsErrInvalidTypeSignature" = 94426 
GhcDiagnosticCode "PsErrUnexpectedTypeInDecl" = 77878 
GhcDiagnosticCode "PsErrInvalidPackageName" = 21926 
GhcDiagnosticCode "PsErrParseRightOpSectionInPat" = 72516 
GhcDiagnosticCode "PsErrIllegalGadtRecordMultiplicity" = 37475 
GhcDiagnosticCode "PsErrInvalidCApiImport" = 72744 
GhcDiagnosticCode "PsErrMultipleConForNewtype" = 5380 
GhcDiagnosticCode "PsErrUnicodeCharLooksLike" = 31623 
GhcDiagnosticCode "PsErrInvalidPun" = 52943 
GhcDiagnosticCode "PsErrIllegalOrPat" = 29847 
GhcDiagnosticCode "PsErrTypeSyntaxInPat" = 32181 
GhcDiagnosticCode "DriverMissingHomeModules" = 32850 
GhcDiagnosticCode "DriverUnknownHiddenModules" = 38189 
GhcDiagnosticCode "DriverUnknownReexportedModules" = 68286 
GhcDiagnosticCode "DriverUnusedPackages" = 42258 
GhcDiagnosticCode "DriverUnnecessarySourceImports" = 88907 
GhcDiagnosticCode "DriverDuplicatedModuleDeclaration" = 29235 
GhcDiagnosticCode "DriverModuleNotFound" = 82272 
GhcDiagnosticCode "DriverFileModuleNameMismatch" = 28623 
GhcDiagnosticCode "DriverUnexpectedSignature" = 66004 
GhcDiagnosticCode "DriverFileNotFound" = 49196 
GhcDiagnosticCode "DriverStaticPointersNotSupported" = 77799 
GhcDiagnosticCode "DriverBackpackModuleNotFound" = 19971 
GhcDiagnosticCode "DriverUserDefinedRuleIgnored" = 56147 
GhcDiagnosticCode "DriverMixedSafetyImport" = 70172 
GhcDiagnosticCode "DriverCannotLoadInterfaceFile" = 37141 
GhcDiagnosticCode "DriverInferredSafeModule" = 58656 
GhcDiagnosticCode "DriverMarkedTrustworthyButInferredSafe" = 19244 
GhcDiagnosticCode "DriverInferredSafeImport" = 82658 
GhcDiagnosticCode "DriverCannotImportUnsafeModule" = 44360 
GhcDiagnosticCode "DriverMissingSafeHaskellMode" = 29747 
GhcDiagnosticCode "DriverPackageNotTrusted" = 8674 
GhcDiagnosticCode "DriverCannotImportFromUntrustedPackage" = 75165 
GhcDiagnosticCode "DriverRedirectedNoMain" = 95379 
GhcDiagnosticCode "DriverHomePackagesNotClosed" = 3271 
GhcDiagnosticCode "DriverInconsistentDynFlags" = 74335 
GhcDiagnosticCode "DriverSafeHaskellIgnoredExtension" = 98887 
GhcDiagnosticCode "DriverPackageTrustIgnored" = 83552 
GhcDiagnosticCode "DriverUnrecognisedFlag" = 93741 
GhcDiagnosticCode "DriverDeprecatedFlag" = 53692 
GhcDiagnosticCode "DriverModuleGraphCycle" = 92213 
GhcDiagnosticCode "DriverInstantiationNodeInDependencyGeneration" = 74284 
GhcDiagnosticCode "DriverNoConfiguredLLVMToolchain" = 66599 
GhcDiagnosticCode "BadTelescope" = 97739 
GhcDiagnosticCode "UserTypeError" = 64725 
GhcDiagnosticCode "UnsatisfiableError" = 22250 
GhcDiagnosticCode "ReportHoleError" = 88464 
GhcDiagnosticCode "FixedRuntimeRepError" = 55287 
GhcDiagnosticCode "BlockedEquality" = 6200 
GhcDiagnosticCode "ExpectingMoreArguments" = 81325 
GhcDiagnosticCode "UnboundImplicitParams" = 91416 
GhcDiagnosticCode "AmbiguityPreventsSolvingCt" = 78125 
GhcDiagnosticCode "CannotResolveInstance" = 39999 
GhcDiagnosticCode "OverlappingInstances" = 43085 
GhcDiagnosticCode "UnsafeOverlap" = 36705 
GhcDiagnosticCode "MultiplicityCoercionsNotSupported" = 59840 
GhcDiagnosticCode "BasicMismatch" = 18872 
GhcDiagnosticCode "KindMismatch" = 89223 
GhcDiagnosticCode "TypeEqMismatch" = 83865 
GhcDiagnosticCode "CouldNotDeduce" = 5617 
GhcDiagnosticCode "CannotUnifyWithPolytype" = 91028 
GhcDiagnosticCode "OccursCheck" = 27958 
GhcDiagnosticCode "SkolemEscape" = 46956 
GhcDiagnosticCode "DifferentTyVars" = 25897 
GhcDiagnosticCode "RepresentationalEq" = 10283 
GhcDiagnosticCode "TcRnSolverDepthError" = 40404 
GhcDiagnosticCode "TcRnRedundantConstraints" = 30606 
GhcDiagnosticCode "TcRnInaccessibleCode" = 40564 
GhcDiagnosticCode "TcRnInaccessibleCoAxBranch" = 28129 
GhcDiagnosticCode "TcRnTypeDoesNotHaveFixedRuntimeRep" = 18478 
GhcDiagnosticCode "TcRnImplicitLift" = 846 
GhcDiagnosticCode "TcRnUnusedPatternBinds" = 61367 
GhcDiagnosticCode "TcRnDodgyExports" = 75356 
GhcDiagnosticCode "TcRnMissingImportList" = 77037 
GhcDiagnosticCode "TcRnUnsafeDueToPlugin" = 1687 
GhcDiagnosticCode "TcRnModMissingRealSrcSpan" = 84170 
GhcDiagnosticCode "TcRnIdNotExportedFromModuleSig" = 44188 
GhcDiagnosticCode "TcRnIdNotExportedFromLocalSig" = 50058 
GhcDiagnosticCode "TcRnShadowedName" = 63397 
GhcDiagnosticCode "TcRnInvalidWarningCategory" = 53573 
GhcDiagnosticCode "TcRnDuplicateWarningDecls" = 711 
GhcDiagnosticCode "TcRnSimplifierTooManyIterations" = 95822 
GhcDiagnosticCode "TcRnIllegalPatSynDecl" = 82077 
GhcDiagnosticCode "TcRnLinearPatSyn" = 15172 
GhcDiagnosticCode "TcRnEmptyRecordUpdate" = 20825 
GhcDiagnosticCode "TcRnIllegalFieldPunning" = 44287 
GhcDiagnosticCode "TcRnIllegalWildcardsInRecord" = 37132 
GhcDiagnosticCode "TcRnIllegalWildcardInType" = 65507 
GhcDiagnosticCode "TcRnIllegalNamedWildcardInTypeArgument" = 93411 
GhcDiagnosticCode "TcRnIllegalImplicitTyVarInTypeArgument" = 80557 
GhcDiagnosticCode "TcRnDuplicateFieldName" = 85524 
GhcDiagnosticCode "TcRnIllegalViewPattern" = 22406 
GhcDiagnosticCode "TcRnCharLiteralOutOfRange" = 17268 
GhcDiagnosticCode "TcRnIllegalWildcardsInConstructor" = 47217 
GhcDiagnosticCode "TcRnIgnoringAnnotations" = 66649 
GhcDiagnosticCode "TcRnAnnotationInSafeHaskell" = 68934 
GhcDiagnosticCode "TcRnInvalidTypeApplication" = 95781 
GhcDiagnosticCode "TcRnTagToEnumMissingValArg" = 36495 
GhcDiagnosticCode "TcRnTagToEnumUnspecifiedResTy" = 8522 
GhcDiagnosticCode "TcRnTagToEnumResTyNotAnEnum" = 49356 
GhcDiagnosticCode "TcRnTagToEnumResTyTypeData" = 96189 
GhcDiagnosticCode "TcRnArrowIfThenElsePredDependsOnResultTy" = 55868 
GhcDiagnosticCode "TcRnIllegalHsBootOrSigDecl" = 58195 
GhcDiagnosticCode "TcRnRecursivePatternSynonym" = 72489 
GhcDiagnosticCode "TcRnPartialTypeSigTyVarMismatch" = 88793 
GhcDiagnosticCode "TcRnPartialTypeSigBadQuantifier" = 94185 
GhcDiagnosticCode "TcRnMissingSignature" = 38417 
GhcDiagnosticCode "TcRnPolymorphicBinderMissingSig" = 64414 
GhcDiagnosticCode "TcRnOverloadedSig" = 16675 
GhcDiagnosticCode "TcRnTupleConstraintInst" = 69012 
GhcDiagnosticCode "TcRnUserTypeError" = 47403 
GhcDiagnosticCode "TcRnConstraintInKind" = 1259 
GhcDiagnosticCode "TcRnUnboxedTupleOrSumTypeFuncArg" = 19590 
GhcDiagnosticCode "TcRnLinearFuncInKind" = 13218 
GhcDiagnosticCode "TcRnForAllEscapeError" = 31147 
GhcDiagnosticCode "TcRnVDQInTermType" = 51580 
GhcDiagnosticCode "TcRnBadQuantPredHead" = 2550 
GhcDiagnosticCode "TcRnIllegalTupleConstraint" = 77539 
GhcDiagnosticCode "TcRnNonTypeVarArgInConstraint" = 80003 
GhcDiagnosticCode "TcRnIllegalImplicitParam" = 75863 
GhcDiagnosticCode "TcRnIllegalConstraintSynonymOfKind" = 75844 
GhcDiagnosticCode "TcRnOversaturatedVisibleKindArg" = 45474 
GhcDiagnosticCode "TcRnForAllRankErr" = 91510 
GhcDiagnosticCode "TcRnMonomorphicBindings" = 55524 
GhcDiagnosticCode "TcRnOrphanInstance" = 90177 
GhcDiagnosticCode "TcRnFunDepConflict" = 46208 
GhcDiagnosticCode "TcRnDupInstanceDecls" = 59692 
GhcDiagnosticCode "TcRnConflictingFamInstDecls" = 34447 
GhcDiagnosticCode "TcRnFamInstNotInjective" = 5175 
GhcDiagnosticCode "TcRnBangOnUnliftedType" = 55666 
GhcDiagnosticCode "TcRnLazyBangOnUnliftedType" = 71444 
GhcDiagnosticCode "TcRnPatSynBundledWithNonDataCon" = 66775 
GhcDiagnosticCode "TcRnPatSynBundledWithWrongType" = 66025 
GhcDiagnosticCode "TcRnDupeModuleExport" = 51876 
GhcDiagnosticCode "TcRnExportedModNotImported" = 90973 
GhcDiagnosticCode "TcRnNullExportedModule" = 64649 
GhcDiagnosticCode "TcRnMissingExportList" = 85401 
GhcDiagnosticCode "TcRnExportHiddenComponents" = 94558 
GhcDiagnosticCode "TcRnExportHiddenDefault" = 74775 
GhcDiagnosticCode "TcRnDuplicateExport" = 47854 
GhcDiagnosticCode "TcRnExportedParentChildMismatch" = 88993 
GhcDiagnosticCode "TcRnConflictingExports" = 69158 
GhcDiagnosticCode "TcRnDuplicateFieldExport" = 97219 
GhcDiagnosticCode "TcRnAmbiguousFieldInUpdate" = 56428 
GhcDiagnosticCode "TcRnAmbiguousRecordUpdate" = 2256 
GhcDiagnosticCode "TcRnMissingFields" = 20125 
GhcDiagnosticCode "TcRnFieldUpdateInvalidType" = 63055 
GhcDiagnosticCode "TcRnMissingStrictFields" = 95909 
GhcDiagnosticCode "TcRnStaticFormNotClosed" = 88431 
GhcDiagnosticCode "TcRnIllegalStaticExpression" = 23800 
GhcDiagnosticCode "TcRnUselessTypeable" = 90584 
GhcDiagnosticCode "TcRnDerivingDefaults" = 20042 
GhcDiagnosticCode "TcRnNonUnaryTypeclassConstraint" = 73993 
GhcDiagnosticCode "TcRnPartialTypeSignatures" = 60661 
GhcDiagnosticCode "TcRnLazyGADTPattern" = 87005 
GhcDiagnosticCode "TcRnArrowProcGADTPattern" = 64525 
GhcDiagnosticCode "TcRnTypeEqualityOutOfScope" = 12003 
GhcDiagnosticCode "TcRnTypeEqualityRequiresOperators" = 58520 
GhcDiagnosticCode "TcRnIllegalTypeOperator" = 62547 
GhcDiagnosticCode "TcRnGADTMonoLocalBinds" = 58008 
GhcDiagnosticCode "TcRnIncorrectNameSpace" = 31891 
GhcDiagnosticCode "TcRnNoRebindableSyntaxRecordDot" = 65945 
GhcDiagnosticCode "TcRnNoFieldPunsRecordDot" = 57365 
GhcDiagnosticCode "TcRnListComprehensionDuplicateBinding" = 81232 
GhcDiagnosticCode "TcRnLastStmtNotExpr" = 55814 
GhcDiagnosticCode "TcRnUnexpectedStatementInContext" = 42026 
GhcDiagnosticCode "TcRnSectionWithoutParentheses" = 95880 
GhcDiagnosticCode "TcRnIllegalImplicitParameterBindings" = 50730 
GhcDiagnosticCode "TcRnIllegalTupleSection" = 59155 
GhcDiagnosticCode "TcRnTermNameInType" = 37479 
GhcDiagnosticCode "TcRnUnexpectedKindVar" = 12875 
GhcDiagnosticCode "TcRnNegativeNumTypeLiteral" = 93632 
GhcDiagnosticCode "TcRnUnusedQuantifiedTypeVar" = 54180 
GhcDiagnosticCode "TcRnMissingRoleAnnotation" = 65490 
GhcDiagnosticCode "TcRnUntickedPromotedThing" = 49957 
GhcDiagnosticCode "TcRnIllegalBuiltinSyntax" = 39716 
GhcDiagnosticCode "TcRnForeignImportPrimExtNotSet" = 49692 
GhcDiagnosticCode "TcRnForeignImportPrimSafeAnn" = 26133 
GhcDiagnosticCode "TcRnForeignFunctionImportAsValue" = 76251 
GhcDiagnosticCode "TcRnFunPtrImportWithoutAmpersand" = 57989 
GhcDiagnosticCode "TcRnIllegalForeignDeclBackend" = 3355 
GhcDiagnosticCode "TcRnUnsupportedCallConv" = 1245 
GhcDiagnosticCode "TcRnInvalidCIdentifier" = 95774 
GhcDiagnosticCode "TcRnExpectedValueId" = 1570 
GhcDiagnosticCode "TcRnRecSelectorEscapedTyVar" = 55876 
GhcDiagnosticCode "TcRnPatSynNotBidirectional" = 16444 
GhcDiagnosticCode "TcRnIllegalDerivingItem" = 11913 
GhcDiagnosticCode "TcRnUnexpectedAnnotation" = 18932 
GhcDiagnosticCode "TcRnIllegalRecordSyntax" = 89246 
GhcDiagnosticCode "TcRnInvalidVisibleKindArgument" = 20967 
GhcDiagnosticCode "TcRnTooManyBinders" = 5989 
GhcDiagnosticCode "TcRnDifferentNamesForTyVar" = 17370 
GhcDiagnosticCode "TcRnDisconnectedTyVar" = 59738 
GhcDiagnosticCode "TcRnInvalidReturnKind" = 55233 
GhcDiagnosticCode "TcRnClassKindNotConstraint" = 80768 
GhcDiagnosticCode "TcRnMatchesHaveDiffNumArgs" = 91938 
GhcDiagnosticCode "TcRnCannotBindScopedTyVarInPatSig" = 46131 
GhcDiagnosticCode "TcRnCannotBindTyVarsInPatBind" = 48361 
GhcDiagnosticCode "TcRnTooManyTyArgsInConPattern" = 1629 
GhcDiagnosticCode "TcRnMultipleInlinePragmas" = 96665 
GhcDiagnosticCode "TcRnUnexpectedPragmas" = 88293 
GhcDiagnosticCode "TcRnNonOverloadedSpecialisePragma" = 35827 
GhcDiagnosticCode "TcRnSpecialiseNotVisible" = 85337 
GhcDiagnosticCode "TcRnDifferentExportWarnings" = 92878 
GhcDiagnosticCode "TcRnIncompleteExportWarnings" = 94721 
GhcDiagnosticCode "TcRnIllegalTypeOperatorDecl" = 50649 
GhcDiagnosticCode "TcRnOrPatBindsVariables" = 81303 
GhcDiagnosticCode "TcRnIllegalKind" = 64861 
GhcDiagnosticCode "TcRnUnexpectedPatSigType" = 74097 
GhcDiagnosticCode "TcRnIllegalKindSignature" = 91382 
GhcDiagnosticCode "TcRnDataKindsError" = 68567 
GhcDiagnosticCode "TcRnIllegalHsigDefaultMethods" = 93006 
GhcDiagnosticCode "TcRnHsigFixityMismatch" = 93007 
GhcDiagnosticCode "TcRnHsigMissingModuleExport" = 93011 
GhcDiagnosticCode "TcRnBadGenericMethod" = 59794 
GhcDiagnosticCode "TcRnWarningMinimalDefIncomplete" = 13511 
GhcDiagnosticCode "TcRnDefaultMethodForPragmaLacksBinding" = 28587 
GhcDiagnosticCode "TcRnIgnoreSpecialisePragmaOnDefMethod" = 72520 
GhcDiagnosticCode "TcRnBadMethodErr" = 46284 
GhcDiagnosticCode "TcRnIllegalTypeData" = 15013 
GhcDiagnosticCode "TcRnTypeDataForbids" = 67297 
GhcDiagnosticCode "TcRnUnsatisfiedMinimalDef" = 6201 
GhcDiagnosticCode "TcRnMisplacedInstSig" = 6202 
GhcDiagnosticCode "TcRnCapturedTermName" = 54201 
GhcDiagnosticCode "TcRnBindingOfExistingName" = 58805 
GhcDiagnosticCode "TcRnMultipleFixityDecls" = 50419 
GhcDiagnosticCode "TcRnIllegalPatternSynonymDecl" = 41507 
GhcDiagnosticCode "TcRnIllegalClassBinding" = 69248 
GhcDiagnosticCode "TcRnOrphanCompletePragma" = 93961 
GhcDiagnosticCode "TcRnEmptyCase" = 48010 
GhcDiagnosticCode "TcRnNonStdGuards" = 59119 
GhcDiagnosticCode "TcRnDuplicateSigDecl" = 31744 
GhcDiagnosticCode "TcRnMisplacedSigDecl" = 87866 
GhcDiagnosticCode "TcRnUnexpectedDefaultSig" = 40700 
GhcDiagnosticCode "TcRnDuplicateMinimalSig" = 85346 
GhcDiagnosticCode "TcRnLoopySuperclassSolve" = Outdated 36038 
GhcDiagnosticCode "TcRnUnexpectedStandaloneDerivingDecl" = 95159 
GhcDiagnosticCode "TcRnUnusedVariableInRuleDecl" = 65669 
GhcDiagnosticCode "TcRnUnexpectedStandaloneKindSig" = 45906 
GhcDiagnosticCode "TcRnIllegalRuleLhs" = 63294 
GhcDiagnosticCode "TcRnDuplicateRoleAnnot" = 97170 
GhcDiagnosticCode "TcRnDuplicateKindSig" = 43371 
GhcDiagnosticCode "TcRnIllegalDerivStrategy" = 87139 
GhcDiagnosticCode "TcRnIllegalMultipleDerivClauses" = 30281 
GhcDiagnosticCode "TcRnNoDerivStratSpecified" = 55631 
GhcDiagnosticCode "TcRnStupidThetaInGadt" = 18403 
GhcDiagnosticCode "TcRnShadowedTyVarNameInFamResult" = 99412 
GhcDiagnosticCode "TcRnIncorrectTyVarOnLhsOfInjCond" = 88333 
GhcDiagnosticCode "TcRnUnknownTyVarsOnRhsOfInjCond" = 48254 
GhcDiagnosticCode "TcRnBadlyStaged" = 28914 
GhcDiagnosticCode "TcRnBadlyStagedType" = 86357 
GhcDiagnosticCode "TcRnStageRestriction" = 18157 
GhcDiagnosticCode "TcRnTyThingUsedWrong" = 10969 
GhcDiagnosticCode "TcRnCannotDefaultKindVar" = 79924 
GhcDiagnosticCode "TcRnUninferrableTyVar" = 16220 
GhcDiagnosticCode "TcRnSkolemEscape" = 71451 
GhcDiagnosticCode "TcRnPatSynEscapedCoercion" = 88986 
GhcDiagnosticCode "TcRnPatSynExistentialInResult" = 33973 
GhcDiagnosticCode "TcRnPatSynArityMismatch" = 18365 
GhcDiagnosticCode "TcRnTyFamDepsDisabled" = 43991 
GhcDiagnosticCode "TcRnAbstractClosedTyFamDecl" = 60012 
GhcDiagnosticCode "TcRnPartialFieldSelector" = 82712 
GhcDiagnosticCode "TcRnHasFieldResolvedIncomplete" = 86894 
GhcDiagnosticCode "TcRnSuperclassCycle" = 29210 
GhcDiagnosticCode "TcRnDefaultSigMismatch" = 72771 
GhcDiagnosticCode "TcRnTyFamResultDisabled" = 44012 
GhcDiagnosticCode "TcRnCommonFieldResultTypeMismatch" = 31004 
GhcDiagnosticCode "TcRnCommonFieldTypeMismatch" = 91827 
GhcDiagnosticCode "TcRnDataConParentTypeMismatch" = 45219 
GhcDiagnosticCode "TcRnGADTsDisabled" = 23894 
GhcDiagnosticCode "TcRnExistentialQuantificationDisabled" = 25709 
GhcDiagnosticCode "TcRnGADTDataContext" = 61072 
GhcDiagnosticCode "TcRnMultipleConForNewtype" = 16409 
GhcDiagnosticCode "TcRnKindSignaturesDisabled" = 49378 
GhcDiagnosticCode "TcRnEmptyDataDeclsDisabled" = 32478 
GhcDiagnosticCode "TcRnRoleMismatch" = 29178 
GhcDiagnosticCode "TcRnRoleCountMismatch" = 54298 
GhcDiagnosticCode "TcRnIllegalRoleAnnotation" = 77192 
GhcDiagnosticCode "TcRnRoleAnnotationsDisabled" = 17779 
GhcDiagnosticCode "TcRnIncoherentRoles" = 18273 
GhcDiagnosticCode "TcRnTypeSynonymCycle" = 97522 
GhcDiagnosticCode "TcRnSelfImport" = 43281 
GhcDiagnosticCode "TcRnNoExplicitImportList" = 16029 
GhcDiagnosticCode "TcRnSafeImportsDisabled" = 26971 
GhcDiagnosticCode "TcRnDeprecatedModule" = 15328 
GhcDiagnosticCode "TcRnCompatUnqualifiedImport" = Outdated 82347 
GhcDiagnosticCode "TcRnRedundantSourceImport" = 54478 
GhcDiagnosticCode "TcRnDuplicateDecls" = 29916 
GhcDiagnosticCode "TcRnPackageImportsDisabled" = 10032 
GhcDiagnosticCode "TcRnIllegalDataCon" = 78448 
GhcDiagnosticCode "TcRnNestedForallsContexts" = 71492 
GhcDiagnosticCode "TcRnRedundantRecordWildcard" = 15932 
GhcDiagnosticCode "TcRnUnusedRecordWildcard" = 83475 
GhcDiagnosticCode "TcRnUnusedName" = 40910 
GhcDiagnosticCode "TcRnQualifiedBinder" = 28329 
GhcDiagnosticCode "TcRnInvalidRecordField" = 53822 
GhcDiagnosticCode "TcRnTupleTooLarge" = 94803 
GhcDiagnosticCode "TcRnCTupleTooLarge" = 89347 
GhcDiagnosticCode "TcRnIllegalInferredTyVars" = 54832 
GhcDiagnosticCode "TcRnAmbiguousName" = 87543 
GhcDiagnosticCode "TcRnBindingNameConflict" = 10498 
GhcDiagnosticCode "NonCanonicalMonoid" = 50928 
GhcDiagnosticCode "NonCanonicalMonad" = 22705 
GhcDiagnosticCode "TcRnDefaultedExceptionContext" = 46235 
GhcDiagnosticCode "TcRnImplicitImportOfPrelude" = 20540 
GhcDiagnosticCode "TcRnMissingMain" = 67120 
GhcDiagnosticCode "TcRnGhciUnliftedBind" = 17999 
GhcDiagnosticCode "TcRnGhciMonadLookupFail" = 44990 
GhcDiagnosticCode "TcRnArityMismatch" = 27346 
GhcDiagnosticCode "TcRnSimplifiableConstraint" = 62412 
GhcDiagnosticCode "TcRnIllegalQuasiQuotes" = 77343 
GhcDiagnosticCode "TcRnImplicitRhsQuantification" = 16382 
GhcDiagnosticCode "TcRnBadTyConTelescope" = 87279 
GhcDiagnosticCode "TcRnPatersonCondFailure" = 22979 
GhcDiagnosticCode "TcRnDeprecatedInvisTyArgInConPat" = Outdated 69797 
GhcDiagnosticCode "TcRnInvalidDefaultedTyVar" = 45625 
GhcDiagnosticCode "TcRnIllegalTermLevelUse" = 1928 
GhcDiagnosticCode "TcRnNamespacedWarningPragmaWithoutFlag" = 14995 
GhcDiagnosticCode "TcRnInvisPatWithNoForAll" = 14964 
GhcDiagnosticCode "TcRnIllegalInvisibleTypePattern" = 78249 
GhcDiagnosticCode "TcRnNamespacedFixitySigWithoutFlag" = 78534 
GhcDiagnosticCode "TcRnOutOfArityTyVar" = 84925 
GhcDiagnosticCode "TcRnMisplacedInvisPat" = 11983 
GhcDiagnosticCode "TcRnIllformedTypePattern" = 88754 
GhcDiagnosticCode "TcRnIllegalTypePattern" = 70206 
GhcDiagnosticCode "TcRnIllformedTypeArgument" = 29092 
GhcDiagnosticCode "TcRnIllegalTypeExpr" = 35499 
GhcDiagnosticCode "TcRnUnexpectedTypeSyntaxInTerms" = 31244 
GhcDiagnosticCode "TypeApplication" = 23482 
GhcDiagnosticCode "TypeApplicationInPattern" = 17916 
GhcDiagnosticCode "PatSynNotInvertible" = 69317 
GhcDiagnosticCode "PatSynUnboundVar" = 28572 
GhcDiagnosticCode "LazyFieldsDisabled" = 81601 
GhcDiagnosticCode "UnpackWithoutStrictness" = 10107 
GhcDiagnosticCode "BackpackUnpackAbstractType" = 40091 
GhcDiagnosticCode "TyVarRoleMismatch" = 22221 
GhcDiagnosticCode "TyVarMissingInEnv" = 99991 
GhcDiagnosticCode "BadCoercionRole" = 92834 
GhcDiagnosticCode "MultiParamDisabled" = 28349 
GhcDiagnosticCode "FunDepsDisabled" = 15708 
GhcDiagnosticCode "ConstrainedClassMethodsDisabled" = 25079 
GhcDiagnosticCode "TyFamsDisabledFamily" = 39191 
GhcDiagnosticCode "TyFamsDisabledInstance" = 6206 
GhcDiagnosticCode "TcRnPrecedenceParsingError" = 88747 
GhcDiagnosticCode "TcRnSectionPrecedenceError" = 46878 
GhcDiagnosticCode "HsigShapeSortMismatch" = 93008 
GhcDiagnosticCode "HsigShapeNotUnifiable" = 93009 
GhcDiagnosticCode "TcRnIllegalInvisTyVarBndr" = 58589 
GhcDiagnosticCode "TcRnIllegalWildcardTyVarBndr" = 12211 
GhcDiagnosticCode "TcRnInvalidInvisTyVarBndr" = 57916 
GhcDiagnosticCode "TcRnInvisBndrWithoutSig" = 92337 
GhcDiagnosticCode "DoesNotHaveSingleField" = 23517 
GhcDiagnosticCode "IsNonLinear" = 38291 
GhcDiagnosticCode "IsGADT" = 89498 
GhcDiagnosticCode "HasConstructorContext" = 17440 
GhcDiagnosticCode "HasExistentialTyVar" = 7525 
GhcDiagnosticCode "HasStrictnessAnnotation" = 4049 
GhcDiagnosticCode "NoConstructorHasAllFields" = 14392 
GhcDiagnosticCode "MultiplePossibleParents" = 99339 
GhcDiagnosticCode "InvalidTyConParent" = 33238 
GhcDiagnosticCode "BadImportNotExported" = 61689 
GhcDiagnosticCode "BadImportAvailDataCon" = 35373 
GhcDiagnosticCode "BadImportNotExportedSubordinates" = 10237 
GhcDiagnosticCode "BadImportAvailTyCon" = 56449 
GhcDiagnosticCode "BadImportAvailVar" = 12112 
GhcDiagnosticCode "WarningTxt" = 63394 
GhcDiagnosticCode "DeprecatedTxt" = 68441 
GhcDiagnosticCode "IllegalOccName" = 55017 
GhcDiagnosticCode "SumAltArityExceeded" = 68444 
GhcDiagnosticCode "IllegalSumAlt" = 63966 
GhcDiagnosticCode "IllegalSumArity" = 97721 
GhcDiagnosticCode "MalformedType" = 28709 
GhcDiagnosticCode "IllegalLastStatement" = 47373 
GhcDiagnosticCode "KindSigsOnlyAllowedOnGADTs" = 40746 
GhcDiagnosticCode "IllegalDeclaration" = 23882 
GhcDiagnosticCode "CannotMixGADTConsWith98Cons" = 24104 
GhcDiagnosticCode "EmptyStmtListInDoBlock" = 34949 
GhcDiagnosticCode "NonVarInInfixExpr" = 99831 
GhcDiagnosticCode "MultiWayIfWithoutAlts" = 63930 
GhcDiagnosticCode "CasesExprWithoutAlts" = 91745 
GhcDiagnosticCode "ImplicitParamsWithOtherBinds" = 42974 
GhcDiagnosticCode "InvalidCCallImpent" = 60220 
GhcDiagnosticCode "RecGadtNoCons" = 18816 
GhcDiagnosticCode "GadtNoCons" = 38140 
GhcDiagnosticCode "InvalidTypeInstanceHeader" = 37056 
GhcDiagnosticCode "InvalidTyFamInstLHS" = 78486 
GhcDiagnosticCode "InvalidImplicitParamBinding" = 51603 
GhcDiagnosticCode "DefaultDataInstDecl" = 39639 
GhcDiagnosticCode "FunBindLacksEquations" = 52078 
GhcDiagnosticCode "EmptyGuard" = 45149 
GhcDiagnosticCode "EmptyParStmt" = 95595 
GhcDiagnosticCode "DodgyImportsEmptyParent" = 99623 
GhcDiagnosticCode "ImportLookupQualified" = 48795 
GhcDiagnosticCode "ImportLookupIllegal" = 14752 
GhcDiagnosticCode "ImportLookupAmbiguous" = 92057 
GhcDiagnosticCode "UnusedImportNone" = 66111 
GhcDiagnosticCode "UnusedImportSome" = 38856 
GhcDiagnosticCode "IllegalFamilyApplicationInInstance" = 73138 
GhcDiagnosticCode "IllegalSpecialClassInstance" = 97044 
GhcDiagnosticCode "IllegalInstanceFailsCoverageCondition" = 21572 
GhcDiagnosticCode "InstHeadAbstractClass" = 51758 
GhcDiagnosticCode "InstHeadNonClass" = 53946 
GhcDiagnosticCode "InstHeadTySynArgs" = 93557 
GhcDiagnosticCode "InstHeadNonTyVarArgs" = 48406 
GhcDiagnosticCode "InstHeadMultiParam" = 91901 
GhcDiagnosticCode "IllegalHasFieldInstanceNotATyCon" = 88994 
GhcDiagnosticCode "IllegalHasFieldInstanceFamilyTyCon" = 70743 
GhcDiagnosticCode "IllegalHasFieldInstanceTyConHasFields" = 43406 
GhcDiagnosticCode "IllegalHasFieldInstanceTyConHasField" = 30836 
GhcDiagnosticCode "NotAFamilyTyCon" = 6204 
GhcDiagnosticCode "NotAnOpenFamilyTyCon" = 6207 
GhcDiagnosticCode "FamilyCategoryMismatch" = 52347 
GhcDiagnosticCode "FamilyArityMismatch" = 12985 
GhcDiagnosticCode "TyFamNameMismatch" = 88221 
GhcDiagnosticCode "FamInstRHSOutOfScopeTyVars" = 53634 
GhcDiagnosticCode "FamInstLHSUnusedBoundTyVars" = 30337 
GhcDiagnosticCode "AssocInstanceMissing" = 8585 
GhcDiagnosticCode "AssocInstanceNotInAClass" = 6205 
GhcDiagnosticCode "AssocNotInThisClass" = 38351 
GhcDiagnosticCode "AssocNoClassTyVar" = 55912 
GhcDiagnosticCode "AssocTyVarsDontMatch" = 95424 
GhcDiagnosticCode "AssocDefaultNotAssoc" = 78822 
GhcDiagnosticCode "AssocMultipleDefaults" = 59128 
GhcDiagnosticCode "AssocDefaultNonTyVarArg" = 41522 
GhcDiagnosticCode "AssocDefaultDuplicateTyVars" = 48178 
GhcDiagnosticCode "NotADataType" = 31136 
GhcDiagnosticCode "NewtypeDataConNotInScope" = 72317 
GhcDiagnosticCode "UnliftedFFITypesNeeded" = 10964 
GhcDiagnosticCode "NotABoxedMarshalableTyCon" = 89401 
GhcDiagnosticCode "ForeignLabelNotAPtr" = 26070 
GhcDiagnosticCode "NotSimpleUnliftedType" = 43510 
GhcDiagnosticCode "NotBoxedKindAny" = 64097 
GhcDiagnosticCode "ForeignDynNotPtr" = 27555 
GhcDiagnosticCode "SafeHaskellMustBeInIO" = 57638 
GhcDiagnosticCode "IOResultExpected" = 41843 
GhcDiagnosticCode "UnexpectedNestedForall" = 92994 
GhcDiagnosticCode "LinearTypesNotAllowed" = 57396 
GhcDiagnosticCode "OneArgExpected" = 91490 
GhcDiagnosticCode "AtLeastOneArgExpected" = 7641 
GhcDiagnosticCode "BadSourceImport" = 64852 
GhcDiagnosticCode "HomeModError" = 58427 
GhcDiagnosticCode "DynamicHashMismatchError" = 54709 
GhcDiagnosticCode "CouldntFindInFiles" = 94559 
GhcDiagnosticCode "GenericMissing" = 87110 
GhcDiagnosticCode "MissingPackageFiles" = 22211 
GhcDiagnosticCode "MissingPackageWayFiles" = 88719 
GhcDiagnosticCode "ModuleSuggestion" = 61948 
GhcDiagnosticCode "MultiplePackages" = 45102 
GhcDiagnosticCode "NoUnitIdMatching" = 51294 
GhcDiagnosticCode "NotAModule" = 35235 
GhcDiagnosticCode "Can'tFindNameInInterface" = 83249 
GhcDiagnosticCode "CircularImport" = 75429 
GhcDiagnosticCode "HiModuleNameMismatchWarn" = 53693 
GhcDiagnosticCode "ExceptionOccurred" = 47808 
GhcDiagnosticCode "NotInScope" = 76037 
GhcDiagnosticCode "NotARecordField" = 22385 
GhcDiagnosticCode "NoExactName" = 97784 
GhcDiagnosticCode "SameName" = 81573 
GhcDiagnosticCode "MissingBinding" = 44432 
GhcDiagnosticCode "NoTopLevelBinding" = 10173 
GhcDiagnosticCode "UnknownSubordinate" = 54721 
GhcDiagnosticCode "NotInScopeTc" = 76329 
GhcDiagnosticCode "DerivErrNotWellKinded" = 62016 
GhcDiagnosticCode "DerivErrSafeHaskellGenericInst" = 7214 
GhcDiagnosticCode "DerivErrDerivingViaWrongKind" = 63174 
GhcDiagnosticCode "DerivErrNoEtaReduce" = 38996 
GhcDiagnosticCode "DerivErrBootFileFound" = 30903 
GhcDiagnosticCode "DerivErrDataConsNotAllInScope" = 54540 
GhcDiagnosticCode "DerivErrGNDUsedOnData" = 10333 
GhcDiagnosticCode "DerivErrNullaryClasses" = 4956 
GhcDiagnosticCode "DerivErrLastArgMustBeApp" = 28323 
GhcDiagnosticCode "DerivErrNoFamilyInstance" = 82614 
GhcDiagnosticCode "DerivErrNotStockDeriveable" = 158 
GhcDiagnosticCode "DerivErrHasAssociatedDatatypes" = 34611 
GhcDiagnosticCode "DerivErrNewtypeNonDeriveableClass" = 82023 
GhcDiagnosticCode "DerivErrCannotEtaReduceEnough" = 26557 
GhcDiagnosticCode "DerivErrOnlyAnyClassDeriveable" = 23244 
GhcDiagnosticCode "DerivErrNotDeriveable" = 38178 
GhcDiagnosticCode "DerivErrNotAClass" = 63388 
GhcDiagnosticCode "DerivErrNoConstructors" = 64560 
GhcDiagnosticCode "DerivErrLangExtRequired" = 86639 
GhcDiagnosticCode "DerivErrDunnoHowToDeriveForType" = 48959 
GhcDiagnosticCode "DerivErrMustBeEnumType" = 30750 
GhcDiagnosticCode "DerivErrMustHaveExactlyOneConstructor" = 37542 
GhcDiagnosticCode "DerivErrMustHaveSomeParameters" = 45539 
GhcDiagnosticCode "DerivErrMustNotHaveClassContext" = 16588 
GhcDiagnosticCode "DerivErrBadConstructor" = 16437 
GhcDiagnosticCode "DerivErrGenerics" = 30367 
GhcDiagnosticCode "DerivErrEnumOrProduct" = 58291 
GhcDiagnosticCode "LookupInstErrNotExact" = 10372 
GhcDiagnosticCode "LookupInstErrFlexiVar" = 10373 
GhcDiagnosticCode "LookupInstErrNotFound" = 10374 
GhcDiagnosticCode "TcRnMultipleDefaultDeclarations" = 99565 
GhcDiagnosticCode "TcRnIllegalDefaultClass" = 26555 
GhcDiagnosticCode "TcRnIllegalNamedDefault" = 55756 
GhcDiagnosticCode "TcRnBadDefaultType" = 88933 
GhcDiagnosticCode "TcRnWarnDefaulting" = 18042 
GhcDiagnosticCode "TcRnWarnClashingDefaultImports" = 77007 
GhcDiagnosticCode "EmptyStmtsGroupInParallelComp" = 41242 
GhcDiagnosticCode "EmptyStmtsGroupInTransformListComp" = 92693 
GhcDiagnosticCode "EmptyStmtsGroupInDoNotation" = 82311 
GhcDiagnosticCode "EmptyStmtsGroupInArrowNotation" = 19442 
GhcDiagnosticCode "MissingBootDefinition" = 63610 
GhcDiagnosticCode "MissingBootExport" = 91999 
GhcDiagnosticCode "MissingBootInstance" = 79857 
GhcDiagnosticCode "BadReexportedBootThing" = 12424 
GhcDiagnosticCode "BootMismatchedIdTypes" = 11890 
GhcDiagnosticCode "BootMismatchedTyCons" = 15843 
GhcDiagnosticCode "TypedTHWithPolyType" = 94642 
GhcDiagnosticCode "SplicePolymorphicLocalVar" = 6568 
GhcDiagnosticCode "SpliceThrewException" = 87897 
GhcDiagnosticCode "InvalidTopDecl" = 52886 
GhcDiagnosticCode "NonExactName" = 77923 
GhcDiagnosticCode "AddInvalidCorePlugin" = 86463 
GhcDiagnosticCode "AddDocToNonLocalDefn" = 67760 
GhcDiagnosticCode "FailedToLookupThInstName" = 49530 
GhcDiagnosticCode "CannotReifyInstance" = 30384 
GhcDiagnosticCode "CannotReifyOutOfScopeThing" = 24922 
GhcDiagnosticCode "CannotReifyThingNotInTypeEnv" = 79890 
GhcDiagnosticCode "NoRolesAssociatedWithThing" = 65923 
GhcDiagnosticCode "CannotRepresentType" = 75721 
GhcDiagnosticCode "ReportCustomQuasiError" = 39584 
GhcDiagnosticCode "MismatchedSpliceType" = 45108 
GhcDiagnosticCode "IllegalTHQuotes" = 62558 
GhcDiagnosticCode "IllegalTHSplice" = 26759 
GhcDiagnosticCode "NestedTHBrackets" = 59185 
GhcDiagnosticCode "AddTopDeclsUnexpectedDeclarationSplice" = 17599 
GhcDiagnosticCode "BadImplicitSplice" = 25277 
GhcDiagnosticCode "QuotedNameWrongStage" = 57695 
GhcDiagnosticCode "IllegalStaticFormInSplice" = 12219 
GhcDiagnosticCode "ZonkerCannotDefaultConcrete" = 52083 
GhcDiagnosticCode "ClassPE" = 86934 
GhcDiagnosticCode "TyConPE" = 85413 
GhcDiagnosticCode "PatSynPE" = 70349 
GhcDiagnosticCode "FamDataConPE" = 64578 
GhcDiagnosticCode "ConstrainedDataConPE" = 28374 
GhcDiagnosticCode "RecDataConPE" = 56753 
GhcDiagnosticCode "TermVariablePE" = 45510 
GhcDiagnosticCode "TypeVariablePE" = 47557 
GhcDiagnosticCode "TcRnIllegalInstanceHeadDecl" = Outdated 12222 
GhcDiagnosticCode "TcRnNoClassInstHead" = Outdated 56538 
GhcDiagnosticCode "TcRnNameByTemplateHaskellQuote" = Outdated 40027 
GhcDiagnosticCode "TcRnIllegalBindingOfBuiltIn" = Outdated 69639 
GhcDiagnosticCode "TcRnMixedSelectors" = Outdated 40887 
GhcDiagnosticCode "TcRnBadBootFamInstDecl" = Outdated 6203 
GhcDiagnosticCode "TcRnBindInBootFile" = Outdated 11247 
GhcDiagnosticCode "TcRnUnexpectedTypeSplice" = Outdated 39180 
GhcDiagnosticCode "PsErrUnexpectedTypeAppInDecl" = Outdated 45054 
GhcDiagnosticCode "TcRnUnpromotableThing" = Outdated 88634 
GhcDiagnosticCode "UntouchableVariable" = Outdated 34699 
GhcDiagnosticCode "TcRnBindVarAlreadyInScope" = Outdated 69710 
GhcDiagnosticCode "TcRnBindMultipleVariables" = Outdated 92957 
GhcDiagnosticCode "TcRnHsigNoIface" = Outdated 93010 
GhcDiagnosticCode "TcRnInterfaceLookupError" = Outdated 52243 
GhcDiagnosticCode "TcRnForallIdentifier" = Outdated 64088 

type family ConRecursInto (con :: Symbol) :: Maybe Type where ... Source #

Some constructors of diagnostic datatypes don't have corresponding error codes, because we recur inside them.

For example, we don't have an error code for the TcRnCannotDeriveInstance constructor of TcRnMessage, because we recur into the DeriveInstanceErrReason to obtain an error code.

This type family keeps track of such constructors.

Equations

ConRecursInto "GhcDriverMessage" = 'Just DriverMessage 
ConRecursInto "GhcPsMessage" = 'Just PsMessage 
ConRecursInto "GhcTcRnMessage" = 'Just TcRnMessage 
ConRecursInto "GhcDsMessage" = 'Just DsMessage 
ConRecursInto "GhcUnknownMessage" = 'Just (UnknownDiagnosticFor GhcMessage) 
ConRecursInto "DriverUnknownMessage" = 'Just (UnknownDiagnosticFor DriverMessage) 
ConRecursInto "DriverPsHeaderMessage" = 'Just PsMessage 
ConRecursInto "DriverInterfaceError" = 'Just IfaceMessage 
ConRecursInto "CantFindErr" = 'Just CantFindInstalled 
ConRecursInto "CantFindInstalledErr" = 'Just CantFindInstalled 
ConRecursInto "CantFindInstalled" = 'Just CantFindInstalledReason 
ConRecursInto "BadIfaceFile" = 'Just ReadInterfaceError 
ConRecursInto "FailedToLoadDynamicInterface" = 'Just ReadInterfaceError 
ConRecursInto "PsUnknownMessage" = 'Just (UnknownDiagnosticFor PsMessage) 
ConRecursInto "PsHeaderMessage" = 'Just PsHeaderMessage 
ConRecursInto "TcRnUnknownMessage" = 'Just (UnknownDiagnosticFor TcRnMessage) 
ConRecursInto "TcRnMessageWithInfo" = 'Just TcRnMessageDetailed 
ConRecursInto "TcRnMessageDetailed" = 'Just TcRnMessage 
ConRecursInto "TcRnWithHsDocContext" = 'Just TcRnMessage 
ConRecursInto "TcRnCannotDeriveInstance" = 'Just DeriveInstanceErrReason 
ConRecursInto "TcRnLookupInstance" = 'Just LookupInstanceErrReason 
ConRecursInto "TcRnPragmaWarning" = 'Just (WarningTxt GhcRn) 
ConRecursInto "TcRnNotInScope" = 'Just NotInScopeError 
ConRecursInto "TcRnIllegalNewtype" = 'Just IllegalNewtypeReason 
ConRecursInto "TcRnHsigShapeMismatch" = 'Just HsigShapeMismatchReason 
ConRecursInto "TcRnPatSynInvalidRhs" = 'Just PatSynInvalidRhsReason 
ConRecursInto "TcRnBadRecordUpdate" = 'Just BadRecordUpdateReason 
ConRecursInto "TcRnBadFieldAnnotation" = 'Just BadFieldAnnotationReason 
ConRecursInto "TcRnRoleValidationFailed" = 'Just RoleValidationFailedReason 
ConRecursInto "TcRnClassExtensionDisabled" = 'Just DisabledClassExtension 
ConRecursInto "TcRnTyFamsDisabled" = 'Just TyFamsDisabledReason 
ConRecursInto "TcRnDodgyImports" = 'Just DodgyImportsReason 
ConRecursInto "DodgyImportsHiding" = 'Just ImportLookupReason 
ConRecursInto "TcRnImportLookup" = 'Just ImportLookupReason 
ConRecursInto "TcRnUnusedImport" = 'Just UnusedImportReason 
ConRecursInto "TcRnNonCanonicalDefinition" = 'Just NonCanonicalDefinition 
ConRecursInto "TcRnIllegalInstance" = 'Just IllegalInstanceReason 
ConRecursInto "TcRnTypeApplicationsDisabled" = 'Just TypeApplication 
ConRecursInto "IllegalClassInstance" = 'Just IllegalClassInstanceReason 
ConRecursInto "IllegalFamilyInstance" = 'Just IllegalFamilyInstanceReason 
ConRecursInto "IllegalInstanceHead" = 'Just IllegalInstanceHeadReason 
ConRecursInto "IllegalHasFieldInstance" = 'Just IllegalHasFieldInstance 
ConRecursInto "InvalidAssoc" = 'Just InvalidAssoc 
ConRecursInto "InvalidAssocInstance" = 'Just InvalidAssocInstance 
ConRecursInto "InvalidAssocDefault" = 'Just InvalidAssocDefault 
ConRecursInto "AssocDefaultBadArgs" = 'Just AssocDefaultBadArgs 
ConRecursInto "TcRnTHError" = 'Just THError 
ConRecursInto "THSyntaxError" = 'Just THSyntaxError 
ConRecursInto "THNameError" = 'Just THNameError 
ConRecursInto "THReifyError" = 'Just THReifyError 
ConRecursInto "TypedTHError" = 'Just TypedTHError 
ConRecursInto "THSpliceFailed" = 'Just SpliceFailReason 
ConRecursInto "RunSpliceFailure" = 'Just RunSpliceFailReason 
ConRecursInto "ConversionFail" = 'Just ConversionFailReason 
ConRecursInto "AddTopDeclsError" = 'Just AddTopDeclsError 
ConRecursInto "AddTopDeclsRunSpliceFailure" = 'Just RunSpliceFailReason 
ConRecursInto "TcRnInterfaceError" = 'Just IfaceMessage 
ConRecursInto "Can'tFindInterface" = 'Just MissingInterfaceError 
ConRecursInto "TcRnBootMismatch" = 'Just BootMismatch 
ConRecursInto "MissingBootThing" = 'Just MissingBootThing 
ConRecursInto "BootMismatch" = 'Just BootMismatchWhat 
ConRecursInto "TcRnZonkerMessage" = 'Just ZonkerMessage 
ConRecursInto "TcRnIllegalForeignType" = 'Just IllegalForeignTypeReason 
ConRecursInto "TypeCannotBeMarshaled" = 'Just TypeCannotBeMarshaledReason 
ConRecursInto "TcRnSolverReport" = 'Just SolverReportWithCtxt 
ConRecursInto "SolverReportWithCtxt" = 'Just TcSolverReportMsg 
ConRecursInto "TcReportWithInfo" = 'Just TcSolverReportMsg 
ConRecursInto "CannotUnifyVariable" = 'Just CannotUnifyVariableReason 
ConRecursInto "Mismatch" = 'Just MismatchMsg 
ConRecursInto "TcRnEmptyStmtsGroup" = 'Just EmptyStatementGroupErrReason 
ConRecursInto "DsUnknownMessage" = 'Just (UnknownDiagnosticFor DsMessage) 
ConRecursInto "ImportLookupBad" = 'Just BadImportKind 
ConRecursInto "TcRnUnpromotableThing" = 'Just PromotionErr 
ConRecursInto _1 = 'Nothing :: Maybe Type