{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -fno-warn-orphans #-} -- instance Diagnostic {DriverMessage, GhcMessage}

module GHC.Driver.Errors.Ppr (
  -- This module only exports Diagnostic instances.
  ) where

import GHC.Prelude

import GHC.Driver.Errors.Types
import GHC.Driver.Flags
import GHC.Driver.Session
import GHC.HsToCore.Errors.Ppr ()
import GHC.Parser.Errors.Ppr ()
import GHC.Tc.Errors.Ppr ()
import GHC.Types.Error
import GHC.Types.Error.Codes ( constructorCode )
import GHC.Unit.Types
import GHC.Utils.Outputable
import GHC.Unit.Module
import GHC.Unit.State
import GHC.Types.Hint
import GHC.Types.SrcLoc
import Data.Version

import Language.Haskell.Syntax.Decls (RuleDecl(..))

--
-- Suggestions
--

-- | Suggests a list of 'InstantiationSuggestion' for the '.hsig' file to the user.
suggestInstantiatedWith :: ModuleName -> GenInstantiations UnitId -> [InstantiationSuggestion]
suggestInstantiatedWith :: ModuleName -> GenInstantiations UnitId -> [InstantiationSuggestion]
suggestInstantiatedWith ModuleName
pi_mod_name GenInstantiations UnitId
insts =
  [ ModuleName -> Module -> InstantiationSuggestion
InstantiationSuggestion ModuleName
k Module
v | (ModuleName
k,Module
v) <- ((ModuleName
pi_mod_name, forall u. ModuleName -> GenModule (GenUnit u)
mkHoleModule ModuleName
pi_mod_name) forall a. a -> [a] -> [a]
: GenInstantiations UnitId
insts) ]


instance Diagnostic GhcMessage where
  diagnosticMessage :: GhcMessage -> DecoratedSDoc
diagnosticMessage = \case
    GhcPsMessage PsMessage
m
      -> forall a. Diagnostic a => a -> DecoratedSDoc
diagnosticMessage PsMessage
m
    GhcTcRnMessage TcRnMessage
m
      -> forall a. Diagnostic a => a -> DecoratedSDoc
diagnosticMessage TcRnMessage
m
    GhcDsMessage DsMessage
m
      -> forall a. Diagnostic a => a -> DecoratedSDoc
diagnosticMessage DsMessage
m
    GhcDriverMessage DriverMessage
m
      -> forall a. Diagnostic a => a -> DecoratedSDoc
diagnosticMessage DriverMessage
m
    GhcUnknownMessage UnknownDiagnostic
m
      -> forall a. Diagnostic a => a -> DecoratedSDoc
diagnosticMessage UnknownDiagnostic
m

  diagnosticReason :: GhcMessage -> DiagnosticReason
diagnosticReason = \case
    GhcPsMessage PsMessage
m
      -> forall a. Diagnostic a => a -> DiagnosticReason
diagnosticReason PsMessage
m
    GhcTcRnMessage TcRnMessage
m
      -> forall a. Diagnostic a => a -> DiagnosticReason
diagnosticReason TcRnMessage
m
    GhcDsMessage DsMessage
m
      -> forall a. Diagnostic a => a -> DiagnosticReason
diagnosticReason DsMessage
m
    GhcDriverMessage DriverMessage
m
      -> forall a. Diagnostic a => a -> DiagnosticReason
diagnosticReason DriverMessage
m
    GhcUnknownMessage UnknownDiagnostic
m
      -> forall a. Diagnostic a => a -> DiagnosticReason
diagnosticReason UnknownDiagnostic
m

  diagnosticHints :: GhcMessage -> [GhcHint]
diagnosticHints = \case
    GhcPsMessage PsMessage
m
      -> forall a. Diagnostic a => a -> [GhcHint]
diagnosticHints PsMessage
m
    GhcTcRnMessage TcRnMessage
m
      -> forall a. Diagnostic a => a -> [GhcHint]
diagnosticHints TcRnMessage
m
    GhcDsMessage DsMessage
m
      -> forall a. Diagnostic a => a -> [GhcHint]
diagnosticHints DsMessage
m
    GhcDriverMessage DriverMessage
m
      -> forall a. Diagnostic a => a -> [GhcHint]
diagnosticHints DriverMessage
m
    GhcUnknownMessage UnknownDiagnostic
m
      -> forall a. Diagnostic a => a -> [GhcHint]
diagnosticHints UnknownDiagnostic
m

  diagnosticCode :: GhcMessage -> Maybe DiagnosticCode
diagnosticCode = forall diag.
(Generic diag, GDiagnosticCode (Rep diag)) =>
diag -> Maybe DiagnosticCode
constructorCode

instance Diagnostic DriverMessage where
  diagnosticMessage :: DriverMessage -> DecoratedSDoc
diagnosticMessage = \case
    DriverUnknownMessage UnknownDiagnostic
m
      -> forall a. Diagnostic a => a -> DecoratedSDoc
diagnosticMessage UnknownDiagnostic
m
    DriverPsHeaderMessage PsMessage
m
      -> forall a. Diagnostic a => a -> DecoratedSDoc
diagnosticMessage PsMessage
m
    DriverMissingHomeModules [ModuleName]
missing BuildingCabalPackage
buildingCabalPackage
      -> let msg :: SDoc
msg | BuildingCabalPackage
buildingCabalPackage forall a. Eq a => a -> a -> Bool
== BuildingCabalPackage
YesBuildingCabalPackage
                 = SDoc -> Int -> SDoc -> SDoc
hang
                     (String -> SDoc
text String
"These modules are needed for compilation but not listed in your .cabal file's other-modules: ")
                     Int
4
                     ([SDoc] -> SDoc
sep (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [ModuleName]
missing))
                 | Bool
otherwise
                 =
                   SDoc -> Int -> SDoc -> SDoc
hang
                     (String -> SDoc
text String
"Modules are not listed in command line but needed for compilation: ")
                     Int
4
                     ([SDoc] -> SDoc
sep (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [ModuleName]
missing))
         in SDoc -> DecoratedSDoc
mkSimpleDecorated SDoc
msg
    DriverUnknownHiddenModules [ModuleName]
missing
      -> let msg :: SDoc
msg = SDoc -> Int -> SDoc -> SDoc
hang
                     (String -> SDoc
text String
"Modules are listened as hidden but not part of the unit: ")
                     Int
4
                     ([SDoc] -> SDoc
sep (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [ModuleName]
missing))
         in SDoc -> DecoratedSDoc
mkSimpleDecorated SDoc
msg
    DriverUnknownReexportedModules [ModuleName]
missing
      -> let msg :: SDoc
msg = SDoc -> Int -> SDoc -> SDoc
hang
                     (String -> SDoc
text String
"Modules are listened as reexported but can't be found in any dependency: ")
                     Int
4
                     ([SDoc] -> SDoc
sep (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [ModuleName]
missing))
         in SDoc -> DecoratedSDoc
mkSimpleDecorated SDoc
msg
    DriverUnusedPackages [(UnitId, PackageName, Version, PackageArg)]
unusedArgs
      -> let msg :: SDoc
msg = [SDoc] -> SDoc
vcat [ String -> SDoc
text String
"The following packages were specified" SDoc -> SDoc -> SDoc
<+>
                          String -> SDoc
text String
"via -package or -package-id flags,"
                        , String -> SDoc
text String
"but were not needed for compilation:"
                        , Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
vcat (forall a b. (a -> b) -> [a] -> [b]
map (SDoc -> SDoc
withDash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a} {a}. Outputable a => (a, a, Version, PackageArg) -> SDoc
displayOneUnused) [(UnitId, PackageName, Version, PackageArg)]
unusedArgs))
                        ]
         in SDoc -> DecoratedSDoc
mkSimpleDecorated SDoc
msg
         where
            withDash :: SDoc -> SDoc
            withDash :: SDoc -> SDoc
withDash = SDoc -> SDoc -> SDoc
(<+>) (String -> SDoc
text String
"-")

            displayOneUnused :: (a, a, Version, PackageArg) -> SDoc
displayOneUnused (a
_uid, a
pn , Version
v, PackageArg
f) =
              forall a. Outputable a => a -> SDoc
ppr a
pn SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"-"  SDoc -> SDoc -> SDoc
<> String -> SDoc
text (Version -> String
showVersion Version
v)
                     SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (PackageArg -> SDoc
suffix PackageArg
f)

            suffix :: PackageArg -> SDoc
suffix PackageArg
f = String -> SDoc
text String
"exposed by flag" SDoc -> SDoc -> SDoc
<+> PackageArg -> SDoc
pprUnusedArg PackageArg
f

            pprUnusedArg :: PackageArg -> SDoc
            pprUnusedArg :: PackageArg -> SDoc
pprUnusedArg (PackageArg String
str) = String -> SDoc
text String
"-package" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
str
            pprUnusedArg (UnitIdArg Unit
uid) = String -> SDoc
text String
"-package-id" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Unit
uid

    DriverUnnecessarySourceImports ModuleName
mod
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated (String -> SDoc
text String
"{-# SOURCE #-} unnecessary in import of " SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr ModuleName
mod))
    DriverDuplicatedModuleDeclaration Module
mod [String]
files
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$
           String -> SDoc
text String
"module" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr Module
mod) SDoc -> SDoc -> SDoc
<+>
           String -> SDoc
text String
"is defined in multiple files:" SDoc -> SDoc -> SDoc
<+>
           [SDoc] -> SDoc
sep (forall a b. (a -> b) -> [a] -> [b]
map String -> SDoc
text [String]
files)
    DriverModuleNotFound ModuleName
mod
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated (String -> SDoc
text String
"module" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr ModuleName
mod) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"cannot be found locally")
    DriverFileModuleNameMismatch ModuleName
actual ModuleName
expected
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$
           String -> SDoc
text String
"File name does not match module name:"
           SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
"Saw     :" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr ModuleName
actual)
           SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
"Expected:" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr ModuleName
expected)

    DriverUnexpectedSignature ModuleName
pi_mod_name BuildingCabalPackage
_buildingCabalPackage GenInstantiations UnitId
_instantiations
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"Unexpected signature:" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr ModuleName
pi_mod_name)
    DriverFileNotFound String
hsFilePath
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated (String -> SDoc
text String
"Can't find" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
hsFilePath)
    DriverMessage
DriverStaticPointersNotSupported
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated (String -> SDoc
text String
"StaticPointers is not supported in GHCi interactive expressions.")
    DriverBackpackModuleNotFound ModuleName
modname
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated (String -> SDoc
text String
"module" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr ModuleName
modname SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"was not found")
    DriverUserDefinedRuleIgnored (HsRule { rd_name :: forall pass. RuleDecl pass -> XRec pass FastString
rd_name = XRec GhcTc FastString
n })
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$
            String -> SDoc
text String
"Rule \"" SDoc -> SDoc -> SDoc
<> FastString -> SDoc
ftext (forall l e. GenLocated l e -> e
unLoc XRec GhcTc FastString
n) SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"\" ignored" SDoc -> SDoc -> SDoc
$+$
            String -> SDoc
text String
"Defining user rules is disabled under Safe Haskell"
    DriverMixedSafetyImport ModuleName
modName
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$
           String -> SDoc
text String
"Module" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr ModuleName
modName SDoc -> SDoc -> SDoc
<+> String -> SDoc
text (String
"is imported both as a safe and unsafe import!")
    DriverCannotLoadInterfaceFile Module
m
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$
           String -> SDoc
text String
"Can't load the interface file for" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Module
m
           SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
", to check that it can be safely imported"
    DriverInferredSafeModule Module
m
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$
           SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr forall a b. (a -> b) -> a -> b
$ forall unit. GenModule unit -> ModuleName
moduleName Module
m) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"has been inferred as safe!"
    DriverInferredSafeImport Module
m
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$
           [SDoc] -> SDoc
sep
             [ String -> SDoc
text String
"Importing Safe-Inferred module "
                 SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr (forall unit. GenModule unit -> ModuleName
moduleName Module
m)
                 SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
" from explicitly Safe module"
             ]
    DriverMarkedTrustworthyButInferredSafe Module
m
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$
           SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr forall a b. (a -> b) -> a -> b
$ forall unit. GenModule unit -> ModuleName
moduleName Module
m) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"is marked as Trustworthy but has been inferred as safe!"
    DriverCannotImportUnsafeModule Module
m
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$
           [SDoc] -> SDoc
sep [ forall a. Outputable a => a -> SDoc
ppr (forall unit. GenModule unit -> ModuleName
moduleName Module
m)
                   SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
": Can't be safely imported!"
               , String -> SDoc
text String
"The module itself isn't safe." ]
    DriverMissingSafeHaskellMode Module
modName
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$
           forall a. Outputable a => a -> SDoc
ppr Module
modName SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"is missing Safe Haskell mode"
    DriverPackageNotTrusted UnitState
state UnitId
pkg
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$
           UnitState -> SDoc -> SDoc
pprWithUnitState UnitState
state
             forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"The package ("
                SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr UnitId
pkg
                SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
") is required to be trusted but it isn't!"
    DriverCannotImportFromUntrustedPackage UnitState
state Module
m
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$
           [SDoc] -> SDoc
sep [ forall a. Outputable a => a -> SDoc
ppr (forall unit. GenModule unit -> ModuleName
moduleName Module
m)
                   SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
": Can't be safely imported!"
               , String -> SDoc
text String
"The package ("
                   SDoc -> SDoc -> SDoc
<> (UnitState -> SDoc -> SDoc
pprWithUnitState UnitState
state forall a b. (a -> b) -> a -> b
$ forall a. Outputable a => a -> SDoc
ppr (forall unit. GenModule unit -> unit
moduleUnit Module
m))
                   SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
") the module resides in isn't trusted."
               ]
    DriverRedirectedNoMain ModuleName
mod_name
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$ (String -> SDoc
text
                       (String
"Output was redirected with -o, " forall a. [a] -> [a] -> [a]
++
                       String
"but no output will be generated.") SDoc -> SDoc -> SDoc
$$
                       (String -> SDoc
text String
"There is no module named" SDoc -> SDoc -> SDoc
<+>
                       SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr ModuleName
mod_name) SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"."))
    DriverHomePackagesNotClosed [UnitId]
needed_unit_ids
      -> SDoc -> DecoratedSDoc
mkSimpleDecorated forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat ([String -> SDoc
text String
"Home units are not closed."
                                  , String -> SDoc
text String
"It is necessary to also load the following units:" ]
                                  forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map (\UnitId
uid -> String -> SDoc
text String
"-" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr UnitId
uid) [UnitId]
needed_unit_ids)

  diagnosticReason :: DriverMessage -> DiagnosticReason
diagnosticReason = \case
    DriverUnknownMessage UnknownDiagnostic
m
      -> forall a. Diagnostic a => a -> DiagnosticReason
diagnosticReason UnknownDiagnostic
m
    DriverPsHeaderMessage {}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverMissingHomeModules{}
      -> WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnMissingHomeModules
    DriverUnknownHiddenModules {}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverUnknownReexportedModules {}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverUnusedPackages{}
      -> WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnUnusedPackages
    DriverUnnecessarySourceImports{}
      -> WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnUnusedImports
    DriverDuplicatedModuleDeclaration{}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverModuleNotFound{}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverFileModuleNameMismatch{}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverUnexpectedSignature{}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverFileNotFound{}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverMessage
DriverStaticPointersNotSupported
      -> DiagnosticReason
WarningWithoutFlag
    DriverBackpackModuleNotFound{}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverUserDefinedRuleIgnored{}
      -> DiagnosticReason
WarningWithoutFlag
    DriverMixedSafetyImport{}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverCannotLoadInterfaceFile{}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverInferredSafeModule{}
      -> WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnSafe
    DriverMarkedTrustworthyButInferredSafe{}
      ->WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnTrustworthySafe
    DriverInferredSafeImport{}
      -> WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnInferredSafeImports
    DriverCannotImportUnsafeModule{}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverMissingSafeHaskellMode{}
      -> WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnMissingSafeHaskellMode
    DriverPackageNotTrusted{}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverCannotImportFromUntrustedPackage{}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverRedirectedNoMain {}
      -> DiagnosticReason
ErrorWithoutFlag
    DriverHomePackagesNotClosed {}
      -> DiagnosticReason
ErrorWithoutFlag

  diagnosticHints :: DriverMessage -> [GhcHint]
diagnosticHints = \case
    DriverUnknownMessage UnknownDiagnostic
m
      -> forall a. Diagnostic a => a -> [GhcHint]
diagnosticHints UnknownDiagnostic
m
    DriverPsHeaderMessage PsMessage
psMsg
      -> forall a. Diagnostic a => a -> [GhcHint]
diagnosticHints PsMessage
psMsg
    DriverMissingHomeModules{}
      -> [GhcHint]
noHints
    DriverUnknownHiddenModules {}
      -> [GhcHint]
noHints
    DriverUnknownReexportedModules {}
      -> [GhcHint]
noHints
    DriverUnusedPackages{}
      -> [GhcHint]
noHints
    DriverUnnecessarySourceImports{}
      -> [GhcHint]
noHints
    DriverDuplicatedModuleDeclaration{}
      -> [GhcHint]
noHints
    DriverModuleNotFound{}
      -> [GhcHint]
noHints
    DriverFileModuleNameMismatch{}
      -> [GhcHint]
noHints
    DriverUnexpectedSignature ModuleName
pi_mod_name BuildingCabalPackage
buildingCabalPackage GenInstantiations UnitId
instantiations
      -> if BuildingCabalPackage
buildingCabalPackage forall a. Eq a => a -> a -> Bool
== BuildingCabalPackage
YesBuildingCabalPackage
           then [ModuleName -> GhcHint
SuggestAddSignatureCabalFile ModuleName
pi_mod_name]
           else [ModuleName -> [InstantiationSuggestion] -> GhcHint
SuggestSignatureInstantiations ModuleName
pi_mod_name (ModuleName -> GenInstantiations UnitId -> [InstantiationSuggestion]
suggestInstantiatedWith ModuleName
pi_mod_name GenInstantiations UnitId
instantiations)]
    DriverFileNotFound{}
      -> [GhcHint]
noHints
    DriverMessage
DriverStaticPointersNotSupported
      -> [GhcHint]
noHints
    DriverBackpackModuleNotFound{}
      -> [GhcHint]
noHints
    DriverUserDefinedRuleIgnored{}
      -> [GhcHint]
noHints
    DriverMixedSafetyImport{}
      -> [GhcHint]
noHints
    DriverCannotLoadInterfaceFile{}
      -> [GhcHint]
noHints
    DriverInferredSafeModule{}
      -> [GhcHint]
noHints
    DriverInferredSafeImport{}
      -> [GhcHint]
noHints
    DriverCannotImportUnsafeModule{}
      -> [GhcHint]
noHints
    DriverMissingSafeHaskellMode{}
      -> [GhcHint]
noHints
    DriverPackageNotTrusted{}
      -> [GhcHint]
noHints
    DriverMarkedTrustworthyButInferredSafe{}
      -> [GhcHint]
noHints
    DriverCannotImportFromUntrustedPackage{}
      -> [GhcHint]
noHints
    DriverRedirectedNoMain {}
      -> [GhcHint]
noHints
    DriverHomePackagesNotClosed {}
      -> [GhcHint]
noHints

  diagnosticCode :: DriverMessage -> Maybe DiagnosticCode
diagnosticCode = forall diag.
(Generic diag, GDiagnosticCode (Rep diag)) =>
diag -> Maybe DiagnosticCode
constructorCode