Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data GhcMessage where
- data GhcMessageOpts = GhcMessageOpts {}
- data DriverMessage where
- DriverUnknownMessage :: UnknownDiagnostic (DiagnosticOpts DriverMessage) -> DriverMessage
- DriverPsHeaderMessage :: !PsMessage -> DriverMessage
- DriverMissingHomeModules :: UnitId -> [ModuleName] -> !BuildingCabalPackage -> DriverMessage
- DriverUnknownReexportedModules :: UnitId -> [ReexportedModule] -> DriverMessage
- DriverUnknownHiddenModules :: UnitId -> [ModuleName] -> DriverMessage
- DriverUnusedPackages :: [(UnitId, PackageName, Version, PackageArg)] -> DriverMessage
- DriverUnnecessarySourceImports :: !ModuleName -> DriverMessage
- DriverDuplicatedModuleDeclaration :: !Module -> [FilePath] -> DriverMessage
- DriverModuleNotFound :: !ModuleName -> DriverMessage
- DriverFileModuleNameMismatch :: !ModuleName -> !ModuleName -> DriverMessage
- DriverUnexpectedSignature :: !ModuleName -> !BuildingCabalPackage -> GenInstantiations UnitId -> DriverMessage
- DriverFileNotFound :: !FilePath -> DriverMessage
- DriverStaticPointersNotSupported :: DriverMessage
- DriverBackpackModuleNotFound :: !ModuleName -> DriverMessage
- DriverUserDefinedRuleIgnored :: !(RuleDecl GhcTc) -> DriverMessage
- DriverMixedSafetyImport :: !ModuleName -> DriverMessage
- DriverCannotLoadInterfaceFile :: !Module -> DriverMessage
- DriverInferredSafeModule :: !Module -> DriverMessage
- DriverMarkedTrustworthyButInferredSafe :: !Module -> DriverMessage
- DriverInferredSafeImport :: !Module -> DriverMessage
- DriverCannotImportUnsafeModule :: !Module -> DriverMessage
- DriverMissingSafeHaskellMode :: !Module -> DriverMessage
- DriverPackageNotTrusted :: !UnitState -> !UnitId -> DriverMessage
- DriverCannotImportFromUntrustedPackage :: !UnitState -> !Module -> DriverMessage
- DriverRedirectedNoMain :: !ModuleName -> DriverMessage
- DriverHomePackagesNotClosed :: ![UnitId] -> DriverMessage
- DriverInterfaceError :: !IfaceMessage -> DriverMessage
- DriverInconsistentDynFlags :: String -> DriverMessage
- DriverSafeHaskellIgnoredExtension :: !Extension -> DriverMessage
- DriverPackageTrustIgnored :: DriverMessage
- DriverUnrecognisedFlag :: String -> DriverMessage
- DriverDeprecatedFlag :: String -> String -> DriverMessage
- DriverModuleGraphCycle :: [ModuleGraphNode] -> DriverMessage
- DriverInstantiationNodeInDependencyGeneration :: InstantiatedUnit -> DriverMessage
- DriverNoConfiguredLLVMToolchain :: DriverMessage
- data DriverMessageOpts = DriverMessageOpts {}
- type DriverMessages = Messages DriverMessage
- data PsMessage = PsHeaderMessage !PsHeaderMessage
- type WarningMessages = Messages GhcMessage
- type ErrorMessages = Messages GhcMessage
- type WarnMsg = MsgEnvelope GhcMessage
- ghcUnknownMessage :: (DiagnosticOpts a ~ NoDiagnosticOpts, Diagnostic a, Typeable a) => a -> GhcMessage
- hoistTcRnMessage :: Monad m => m (Messages TcRnMessage, a) -> m (Messages GhcMessage, a)
- hoistDsMessage :: Monad m => m (Messages DsMessage, a) -> m (Messages GhcMessage, a)
- checkBuildingCabalPackage :: DynFlags -> BuildingCabalPackage
Documentation
data GhcMessage where Source #
The umbrella type that encompasses all the different messages that GHC might output during the different compilation stages. See Note [GhcMessage].
GhcPsMessage :: PsMessage -> GhcMessage | A message from the parsing phase. |
GhcTcRnMessage :: TcRnMessage -> GhcMessage | A message from typecheck/renaming phase. |
GhcDsMessage :: DsMessage -> GhcMessage | A message from the desugaring (HsToCore) phase. |
GhcDriverMessage :: DriverMessage -> GhcMessage | A message from the driver. |
GhcUnknownMessage :: UnknownDiagnostic (DiagnosticOpts GhcMessage) -> GhcMessage | An "escape" hatch which can be used when we don't know the source of
the message or if the message is not one of the typed ones. The
|
Instances
data DriverMessage where Source #
A message from the driver.
DriverUnknownMessage :: UnknownDiagnostic (DiagnosticOpts DriverMessage) -> DriverMessage | Simply wraps a generic |
DriverPsHeaderMessage :: !PsMessage -> DriverMessage | A parse error in parsing a Haskell file header during dependency analysis |
DriverMissingHomeModules :: UnitId -> [ModuleName] -> !BuildingCabalPackage -> DriverMessage | DriverMissingHomeModules is a warning (controlled with -Wmissing-home-modules) that arises when running GHC in --make mode when some modules needed for compilation are not included on the command line. For example, if A imports B, `ghc --make A.hs` will cause this warning, while `ghc --make A.hs B.hs` will not. Useful for cabal to ensure GHC won't pick up modules listed neither in 'exposed-modules' nor in 'other-modules'. Test case: warningsshould_compileMissingMod |
DriverUnknownReexportedModules :: UnitId -> [ReexportedModule] -> DriverMessage | DriverUnknown is a warning that arises when a user tries to reexport a module which isn't part of that unit. |
DriverUnknownHiddenModules :: UnitId -> [ModuleName] -> DriverMessage | DriverUnknownHiddenModules is a warning that arises when a user tries to hide a module which isn't part of that unit. |
DriverUnusedPackages :: [(UnitId, PackageName, Version, PackageArg)] -> DriverMessage | DriverUnusedPackages occurs when when package is requested on command line, but was never needed during compilation. Activated by -Wunused-packages. Test cases: warningsshould_compileUnusedPackages |
DriverUnnecessarySourceImports :: !ModuleName -> DriverMessage | DriverUnnecessarySourceImports (controlled with -Wunused-imports) occurs if there
are {-# SOURCE #-} imports which are not necessary. See Test cases: warningsshould_compileT10637 |
DriverDuplicatedModuleDeclaration :: !Module -> [FilePath] -> DriverMessage | DriverDuplicatedModuleDeclaration occurs if a module Test cases: None. |
DriverModuleNotFound :: !ModuleName -> DriverMessage | DriverModuleNotFound occurs if a module Test cases: None. |
DriverFileModuleNameMismatch :: !ModuleName -> !ModuleName -> DriverMessage | DriverFileModuleNameMismatch occurs if a module Test cases: modulemod178, driver/bug1677 |
DriverUnexpectedSignature :: !ModuleName -> !BuildingCabalPackage -> GenInstantiations UnitId -> DriverMessage | DriverUnexpectedSignature occurs when GHC encounters a module Example:
Test cases: driver/T12955 |
DriverFileNotFound :: !FilePath -> DriverMessage | DriverFileNotFound occurs when the input file (e.g. given on the command line) can't be found. Test cases: None. |
DriverStaticPointersNotSupported :: DriverMessage | DriverStaticPointersNotSupported occurs when the Test cases: ghciscriptsStaticPtr |
DriverBackpackModuleNotFound :: !ModuleName -> DriverMessage | DriverBackpackModuleNotFound occurs when Backpack can't find a particular module during its dependency analysis. Test cases: - |
DriverUserDefinedRuleIgnored :: !(RuleDecl GhcTc) -> DriverMessage | DriverUserDefinedRuleIgnored is a warning that occurs when user-defined rules are ignored. This typically happens when Safe Haskell. Test cases: testssafeHaskellsafeInfered/UnsafeWarn05 testssafeHaskellsafeInfered/UnsafeWarn06 testssafeHaskellsafeInfered/UnsafeWarn07 testssafeHaskellsafeInfered/UnsafeInfered11 testssafeHaskellsafeLanguage/SafeLang03 |
DriverMixedSafetyImport :: !ModuleName -> DriverMessage | DriverMixedSafetyImport is an error that occurs when a module is imported both as safe and unsafe. Test cases: testssafeHaskellsafeInfered/Mixed03 testssafeHaskellsafeInfered/Mixed02 |
DriverCannotLoadInterfaceFile :: !Module -> DriverMessage | DriverCannotLoadInterfaceFile is an error that occurs when we cannot load the interface file for a particular module. This can happen for example in the context of Safe Haskell, when we have to load a module to check if it can be safely imported. Test cases: None. |
DriverInferredSafeModule :: !Module -> DriverMessage | DriverInferredSafeImport is a warning (controlled by the Opt_WarnSafe flag) that occurs when a module is inferred safe. Test cases: None. |
DriverMarkedTrustworthyButInferredSafe :: !Module -> DriverMessage | DriverMarkedTrustworthyButInferredSafe is a warning (controlled by the Opt_WarnTrustworthySafe flag) that occurs when a module is marked trustworthy in SafeHaskell but it has been inferred safe. Test cases: testssafeHaskellsafeInfered/TrustworthySafe02 testssafeHaskellsafeInfered/TrustworthySafe03 |
DriverInferredSafeImport :: !Module -> DriverMessage | DriverInferredSafeImport is a warning (controlled by the Opt_WarnInferredSafeImports flag) that occurs when a safe-inferred module is imported from a safe module. Test cases: None. |
DriverCannotImportUnsafeModule :: !Module -> DriverMessage | DriverCannotImportUnsafeModule is an error that occurs when an usafe module is being imported from a safe one. Test cases: None. |
DriverMissingSafeHaskellMode :: !Module -> DriverMessage | DriverMissingSafeHaskellMode is a warning (controlled by the Opt_WarnMissingSafeHaskellMode flag) that occurs when a module is using SafeHaskell features but SafeHaskell mode is not enabled. Test cases: None. |
DriverPackageNotTrusted :: !UnitState -> !UnitId -> DriverMessage | DriverPackageNotTrusted is an error that occurs when a package is required to be trusted but it isn't. Test cases: testssafeHaskellcheck/Check01 testssafeHaskellcheck/Check08 testssafeHaskellcheck/Check06 testssafeHaskellcheckpkg01ImpSafeOnly09 testssafeHaskellcheckpkg01ImpSafe03 testssafeHaskellcheckpkg01ImpSafeOnly07 testssafeHaskellcheckpkg01ImpSafeOnly08 |
DriverCannotImportFromUntrustedPackage :: !UnitState -> !Module -> DriverMessage | DriverCannotImportFromUntrustedPackage is an error that occurs in the context of Safe Haskell when trying to import a module coming from an untrusted package. Test cases: testssafeHaskellcheck/Check09 testssafeHaskellcheckpkg01ImpSafe01 testssafeHaskellcheckpkg01ImpSafe04 testssafeHaskellcheckpkg01ImpSafeOnly03 testssafeHaskellcheckpkg01ImpSafeOnly05 testssafeHaskellflags/SafeFlags17 testssafeHaskellflags/SafeFlags22 testssafeHaskellflags/SafeFlags23 testssafeHaskellghci/p11 testssafeHaskellghci/p12 testssafeHaskellghci/p17 testssafeHaskellghci/p3 testssafeHaskellsafeInfered/UnsafeInfered01 testssafeHaskellsafeInfered/UnsafeInfered02 testssafeHaskellsafeInfered/UnsafeInfered02 testssafeHaskellsafeInfered/UnsafeInfered03 testssafeHaskellsafeInfered/UnsafeInfered05 testssafeHaskellsafeInfered/UnsafeInfered06 testssafeHaskellsafeInfered/UnsafeInfered09 testssafeHaskellsafeInfered/UnsafeInfered10 testssafeHaskellsafeInfered/UnsafeInfered11 testssafeHaskellsafeInfered/UnsafeWarn01 testssafeHaskellsafeInfered/UnsafeWarn03 testssafeHaskellsafeInfered/UnsafeWarn04 testssafeHaskellsafeInfered/UnsafeWarn05 testssafeHaskellunsafeLibs/BadImport01 testssafeHaskellunsafeLibs/BadImport06 testssafeHaskellunsafeLibs/BadImport07 testssafeHaskellunsafeLibs/BadImport08 testssafeHaskellunsafeLibs/BadImport09 testssafeHaskellunsafeLibs/Dep05 testssafeHaskellunsafeLibs/Dep06 testssafeHaskellunsafeLibs/Dep07 testssafeHaskellunsafeLibs/Dep08 testssafeHaskellunsafeLibs/Dep09 testssafeHaskellunsafeLibs/Dep10 |
DriverRedirectedNoMain :: !ModuleName -> DriverMessage | |
DriverHomePackagesNotClosed :: ![UnitId] -> DriverMessage | |
DriverInterfaceError :: !IfaceMessage -> DriverMessage | |
DriverInconsistentDynFlags :: String -> DriverMessage | |
DriverSafeHaskellIgnoredExtension :: !Extension -> DriverMessage | |
DriverPackageTrustIgnored :: DriverMessage | |
DriverUnrecognisedFlag :: String -> DriverMessage | |
DriverDeprecatedFlag :: String -> String -> DriverMessage | |
DriverModuleGraphCycle :: [ModuleGraphNode] -> DriverMessage | DriverModuleGraphCycle is an error that occurs if the module graph contains cyclic imports. Test cases: testsbackpackshould_fail/bkpfail51 testsdriverT20459 testsdriverT24196/T24196 testsdriverT24275/T24275 |
DriverInstantiationNodeInDependencyGeneration :: InstantiatedUnit -> DriverMessage | DriverInstantiationNodeInDependencyGeneration is an error that occurs
if the module graph used for dependency generation contains
Backpack |
DriverNoConfiguredLLVMToolchain :: DriverMessage | DriverNoConfiguredLLVMToolchain is an error that occurs if there is no LLVM toolchain configured but -fllvm is passed as an option to the compiler. Test cases: None. |
Instances
Diagnostic DriverMessage Source # | |||||
Defined in GHC.Driver.Errors.Ppr
| |||||
Generic DriverMessage Source # | |||||
Defined in GHC.Driver.Errors.Types
from :: DriverMessage -> Rep DriverMessage x # to :: Rep DriverMessage x -> DriverMessage # | |||||
type DiagnosticOpts DriverMessage Source # | |||||
Defined in GHC.Driver.Errors.Ppr | |||||
type Rep DriverMessage Source # | |||||
Defined in GHC.Driver.Errors.Types type Rep DriverMessage = D1 ('MetaData "DriverMessage" "GHC.Driver.Errors.Types" "ghc-9.13-inplace" 'False) (((((C1 ('MetaCons "DriverUnknownMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnknownDiagnostic (DiagnosticOpts DriverMessage)))) :+: C1 ('MetaCons "DriverPsHeaderMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsMessage))) :+: (C1 ('MetaCons "DriverMissingHomeModules" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BuildingCabalPackage))) :+: C1 ('MetaCons "DriverUnknownReexportedModules" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ReexportedModule])))) :+: ((C1 ('MetaCons "DriverUnknownHiddenModules" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName])) :+: C1 ('MetaCons "DriverUnusedPackages" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, PackageName, Version, PackageArg)]))) :+: (C1 ('MetaCons "DriverUnnecessarySourceImports" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModuleName)) :+: C1 ('MetaCons "DriverDuplicatedModuleDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Module) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]))))) :+: (((C1 ('MetaCons "DriverModuleNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModuleName)) :+: C1 ('MetaCons "DriverFileModuleNameMismatch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModuleName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModuleName))) :+: (C1 ('MetaCons "DriverUnexpectedSignature" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModuleName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BuildingCabalPackage) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GenInstantiations UnitId)))) :+: C1 ('MetaCons "DriverFileNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FilePath)))) :+: ((C1 ('MetaCons "DriverStaticPointersNotSupported" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DriverBackpackModuleNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModuleName))) :+: (C1 ('MetaCons "DriverUserDefinedRuleIgnored" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (RuleDecl GhcTc))) :+: (C1 ('MetaCons "DriverMixedSafetyImport" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModuleName)) :+: C1 ('MetaCons "DriverCannotLoadInterfaceFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Module))))))) :+: ((((C1 ('MetaCons "DriverInferredSafeModule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Module)) :+: C1 ('MetaCons "DriverMarkedTrustworthyButInferredSafe" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Module))) :+: (C1 ('MetaCons "DriverInferredSafeImport" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Module)) :+: C1 ('MetaCons "DriverCannotImportUnsafeModule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Module)))) :+: ((C1 ('MetaCons "DriverMissingSafeHaskellMode" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Module)) :+: C1 ('MetaCons "DriverPackageNotTrusted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitState) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitId))) :+: (C1 ('MetaCons "DriverCannotImportFromUntrustedPackage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitState) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Module)) :+: (C1 ('MetaCons "DriverRedirectedNoMain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModuleName)) :+: C1 ('MetaCons "DriverHomePackagesNotClosed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [UnitId])))))) :+: (((C1 ('MetaCons "DriverInterfaceError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IfaceMessage)) :+: C1 ('MetaCons "DriverInconsistentDynFlags" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "DriverSafeHaskellIgnoredExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Extension)) :+: C1 ('MetaCons "DriverPackageTrustIgnored" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DriverUnrecognisedFlag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "DriverDeprecatedFlag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "DriverModuleGraphCycle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleGraphNode])) :+: (C1 ('MetaCons "DriverInstantiationNodeInDependencyGeneration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InstantiatedUnit)) :+: C1 ('MetaCons "DriverNoConfiguredLLVMToolchain" 'PrefixI 'False) (U1 :: Type -> Type))))))) |
type DriverMessages = Messages DriverMessage Source #
A collection of driver messages
PsHeaderMessage !PsHeaderMessage | A group of parser messages emitted in |
Instances
Diagnostic PsMessage Source # | |||||
Defined in GHC.Parser.Errors.Ppr
| |||||
Generic PsMessage Source # | |||||
Defined in GHC.Parser.Errors.Types
| |||||
type DiagnosticOpts PsMessage Source # | |||||
Defined in GHC.Parser.Errors.Ppr | |||||
type Rep PsMessage Source # | |||||
Defined in GHC.Parser.Errors.Types type Rep PsMessage = D1 ('MetaData "PsMessage" "GHC.Parser.Errors.Types" "ghc-9.13-inplace" 'False) ((((((C1 ('MetaCons "PsUnknownMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnknownDiagnostic (DiagnosticOpts PsMessage)))) :+: (C1 ('MetaCons "PsHeaderMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsHeaderMessage)) :+: C1 ('MetaCons "PsWarnBidirectionalFormatChars" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (PsLoc, Char, String)))))) :+: ((C1 ('MetaCons "PsWarnTab" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)) :+: C1 ('MetaCons "PsWarnTransitionalLayout" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransLayoutReason))) :+: (C1 ('MetaCons "PsWarnUnrecognisedPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [String])) :+: C1 ('MetaCons "PsWarnMisplacedPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FileHeaderPragmaType))))) :+: ((C1 ('MetaCons "PsWarnHaddockInvalidPos" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PsWarnHaddockIgnoreMulti" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsWarnStarBinder" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PsWarnStarIsType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsWarnImportPreQualified" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PsWarnOperatorWhitespaceExtConflict" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OperatorWhitespaceSymbol)) :+: C1 ('MetaCons "PsWarnOperatorWhitespace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FastString) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OperatorWhitespaceOccurrence)))))) :+: (((C1 ('MetaCons "PsWarnViewPatternSignatures" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LPat GhcPs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LPat GhcPs))) :+: (C1 ('MetaCons "PsErrLambdaCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrEmptyLambda" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PsErrNumUnderscores" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumUnderscoreReason)) :+: C1 ('MetaCons "PsErrPrimStringInvalidChar" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PsErrMissingBlock" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrLexer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LexErr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LexErrKind))))) :+: (((C1 ('MetaCons "PsErrSuffixAT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrParse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsErrParseDetails))) :+: (C1 ('MetaCons "PsErrCmmLexer" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrUnsupportedBoxedSumExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SumOrTuple (HsExpr GhcPs)))))) :+: ((C1 ('MetaCons "PsErrUnsupportedBoxedSumPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SumOrTuple (PatBuilder GhcPs)))) :+: C1 ('MetaCons "PsErrUnexpectedQualifiedConstructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName))) :+: (C1 ('MetaCons "PsErrTupleSectionInPat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrIllegalBangPattern" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Pat GhcPs)))))))) :+: ((((C1 ('MetaCons "PsErrOpFewArgs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StarIsType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName)) :+: (C1 ('MetaCons "PsErrImportQualifiedTwice" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrImportPostQualified" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PsErrIllegalExplicitNamespace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrVarForTyCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName))) :+: (C1 ('MetaCons "PsErrIllegalPatSynExport" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrMalformedEntityString" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PsErrDotsInRecordUpdate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PsErrPrecedenceOutOfRange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "PsErrOverloadedRecordDotInvalid" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PsErrOverloadedRecordUpdateNotEnabled" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrOverloadedRecordUpdateNoQualifiedFields" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PsErrInvalidDataCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsType GhcPs))) :+: C1 ('MetaCons "PsErrInvalidInfixDataCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsType GhcPs)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsType GhcPs)))))))) :+: (((C1 ('MetaCons "PsErrIllegalPromotionQuoteDataCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName)) :+: (C1 ('MetaCons "PsErrUnpackDataCon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrUnexpectedKindAppInDataCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DataConBuilder) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsType GhcPs))))) :+: ((C1 ('MetaCons "PsErrInvalidRecordCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PatBuilder GhcPs))) :+: C1 ('MetaCons "PsErrIllegalUnboxedStringInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsLit GhcPs)))) :+: (C1 ('MetaCons "PsErrIllegalUnboxedFloatingLitInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsLit GhcPs))) :+: C1 ('MetaCons "PsErrDoNotationInPat" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "PsErrIfThenElseInPat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrLambdaInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HsLamVariant))) :+: (C1 ('MetaCons "PsErrCaseInPat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrLetInPat" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PsErrArrowExprInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsExpr GhcPs))) :+: C1 ('MetaCons "PsErrArrowCmdInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsCmd GhcPs)))) :+: (C1 ('MetaCons "PsErrArrowCmdInExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsCmd GhcPs))) :+: C1 ('MetaCons "PsErrOrPatInExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LPat GhcPs))))))))) :+: (((((C1 ('MetaCons "PsErrTypeAppWithoutSpace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: (C1 ('MetaCons "PsErrLazyPatWithoutSpace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: C1 ('MetaCons "PsErrBangPatWithoutSpace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))))) :+: ((C1 ('MetaCons "PsErrUnallowedPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsPragE GhcPs))) :+: C1 ('MetaCons "PsErrQualifiedDoInCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModuleName))) :+: (C1 ('MetaCons "PsErrInvalidInfixHole" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrSemiColonsInCondExpr" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsExpr GhcPs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsExpr GhcPs)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsExpr GhcPs)))))))) :+: ((C1 ('MetaCons "PsErrSemiColonsInCondCmd" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsExpr GhcPs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsCmd GhcPs)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsCmd GhcPs))))) :+: (C1 ('MetaCons "PsErrAtInPatPos" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrCaseCmdInFunAppCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsCmd GhcPs))))) :+: ((C1 ('MetaCons "PsErrLambdaCmdInFunAppCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HsLamVariant) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsCmd GhcPs))) :+: C1 ('MetaCons "PsErrIfCmdInFunAppCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsCmd GhcPs)))) :+: (C1 ('MetaCons "PsErrLetCmdInFunAppCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsCmd GhcPs))) :+: C1 ('MetaCons "PsErrDoCmdInFunAppCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsCmd GhcPs))))))) :+: (((C1 ('MetaCons "PsErrDoInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ModuleName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: (C1 ('MetaCons "PsErrMDoInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ModuleName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: C1 ('MetaCons "PsErrCaseInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))))) :+: ((C1 ('MetaCons "PsErrLambdaInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HsLamVariant) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: C1 ('MetaCons "PsErrLetInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs)))) :+: (C1 ('MetaCons "PsErrIfInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: C1 ('MetaCons "PsErrProcInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs)))))) :+: (((C1 ('MetaCons "PsErrMalformedTyOrClDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsType GhcPs))) :+: C1 ('MetaCons "PsErrIllegalWhereInDataDecl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PsErrIllegalDataTypeContext" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsContext GhcPs))) :+: C1 ('MetaCons "PsErrParseErrorOnInput" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OccName)))) :+: ((C1 ('MetaCons "PsErrMalformedDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName)) :+: C1 ('MetaCons "PsErrNotADataCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName))) :+: (C1 ('MetaCons "PsErrRecordSyntaxInPatSynDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LPat GhcPs))) :+: C1 ('MetaCons "PsErrEmptyWhereInPatSynDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName))))))) :+: ((((C1 ('MetaCons "PsErrInvalidWhereBindInPatSynDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsDecl GhcPs))) :+: (C1 ('MetaCons "PsErrNoSingleWhereBindInPatSynDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsDecl GhcPs))) :+: C1 ('MetaCons "PsErrDeclSpliceNotAtTopLevel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SpliceDecl GhcPs))))) :+: ((C1 ('MetaCons "PsErrInferredTypeVarNotAllowed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrMultipleNamesInStandaloneKindSignature" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LIdP GhcPs]))) :+: (C1 ('MetaCons "PsErrIllegalImportBundleForm" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrIllegalRoleName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FastString) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Role]))))) :+: (((C1 ('MetaCons "PsErrInvalidTypeSignature" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsInvalidTypeSignature) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: C1 ('MetaCons "PsErrUnexpectedTypeInDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsType GhcPs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LHsTypeArg GhcPs]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc))))) :+: (C1 ('MetaCons "PsErrExpectedHyphen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrSpaceInSCC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PsErrEmptyDoubleQuotes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "PsErrInvalidPackageName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FastString))) :+: (C1 ('MetaCons "PsErrInvalidRuleActivationMarker" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrLinearFunction" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PsErrMultiWayIf" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PsErrExplicitForall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "PsErrIllegalQualifiedDo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc)))) :+: ((C1 ('MetaCons "PsErrCmmParser" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CmmParserError)) :+: C1 ('MetaCons "PsErrIllegalTraditionalRecordSyntax" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc))) :+: (C1 ('MetaCons "PsErrParseErrorInCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc)) :+: C1 ('MetaCons "PsErrInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PatBuilder GhcPs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsErrInPatDetails))))) :+: (((C1 ('MetaCons "PsErrParseRightOpSectionInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PatBuilder GhcPs))) :+: C1 ('MetaCons "PsErrIllegalGadtRecordMultiplicity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsArrow GhcPs)))) :+: (C1 ('MetaCons "PsErrInvalidCApiImport" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrMultipleConForNewtype" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))) :+: ((C1 ('MetaCons "PsErrUnicodeCharLooksLike" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "PsErrInvalidPun" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsErrPunDetails))) :+: (C1 ('MetaCons "PsErrIllegalOrPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LPat GhcPs))) :+: C1 ('MetaCons "PsErrTypeSyntaxInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsErrTypeSyntaxDetails))))))))) |
type WarningMessages = Messages GhcMessage Source #
A collection of warning messages.
INVARIANT: Each GhcMessage
in the collection should have SevWarning
severity.
type ErrorMessages = Messages GhcMessage Source #
A collection of error messages.
INVARIANT: Each GhcMessage
in the collection should have SevError
severity.
type WarnMsg = MsgEnvelope GhcMessage Source #
A single warning message.
INVARIANT: It must have SevWarning
severity.
Constructors
ghcUnknownMessage :: (DiagnosticOpts a ~ NoDiagnosticOpts, Diagnostic a, Typeable a) => a -> GhcMessage Source #
Creates a new GhcMessage
out of any diagnostic. This function is also
provided to ease the integration of #18516 by allowing diagnostics to be
wrapped into the general (but structured) GhcMessage
type, so that the
conversion can happen gradually. This function should not be needed within
GHC, as it would typically be used by plugin or library authors (see
comment for the GhcUnknownMessage
type constructor)
Utility functions
hoistTcRnMessage :: Monad m => m (Messages TcRnMessage, a) -> m (Messages GhcMessage, a) Source #
Abstracts away the frequent pattern where we are calling ioMsgMaybe
on
the result of 'IO (Messages TcRnMessage, a)'.
hoistDsMessage :: Monad m => m (Messages DsMessage, a) -> m (Messages GhcMessage, a) Source #
Abstracts away the frequent pattern where we are calling ioMsgMaybe
on
the result of 'IO (Messages DsMessage, a)'.
checkBuildingCabalPackage :: DynFlags -> BuildingCabalPackage Source #
Checks if we are building a cabal package by consulting the DynFlags
.