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

GHC.HsToCore.Errors.Types

Synopsis

Documentation

newtype MinBound Source #

Constructors

MinBound Integer 

newtype MaxBound Source #

Constructors

MaxBound Integer 

data DsMessage Source #

Diagnostics messages emitted during desugaring.

Constructors

DsUnknownMessage UnknownDiagnostic

Simply wraps a generic Diagnostic message.

DsEmptyEnumeration

DsEmptyEnumeration is a warning (controlled by the -Wempty-enumerations flag) that is emitted if an enumeration is empty.

Example(s):

main :: IO () main = do let enum = [5 .. 3] print enum

Here enum would yield an empty list, because 5 is greater than 3.

Test case(s): warningsshould_compileT10930 warningsshould_compileT18402 warningsshould_compileT10930b numericshould_compileT10929 numericshould_compileT7881 deSugarshould_runT18172

DsIdentitiesFound !Id !Type

DsIdentitiesFound is a warning (controlled by the -Widentities flag) that is emitted on uses of Prelude numeric conversions that are probably the identity (and hence could be omitted).

Example(s):

main :: IO () main = do let x = 10 print $ conv 10

where conv :: Int -> Int conv x = fromIntegral x

Here calling conv is essentially the identity function, and therefore can be omitted.

Test case(s): deSugarshould_compileT4488

DsOverflowedLiterals !Integer !Name !(Maybe (MinBound, MaxBound)) !NegLiteralExtEnabled 
DsRedundantBangPatterns !(HsMatchContext GhcRn) !SDoc 
DsOverlappingPatterns !(HsMatchContext GhcRn) !SDoc 
DsInaccessibleRhs !(HsMatchContext GhcRn) !SDoc 
DsMaxPmCheckModelsReached !MaxPmCheckModels 
DsNonExhaustivePatterns !(HsMatchContext GhcRn) !ExhaustivityCheckType !MaxUncoveredPatterns [Id] [Nabla] 
DsTopLevelBindsNotAllowed !BindsType !(HsBindLR GhcTc GhcTc) 
DsUselessSpecialiseForClassMethodSelector !Id 
DsUselessSpecialiseForNoInlineFunction !Id 
DsMultiplicityCoercionsNotSupported 
DsOrphanRule !CoreRule 
DsRuleLhsTooComplicated !CoreExpr !CoreExpr 
DsRuleIgnoredDueToConstructor !DataCon 
DsRuleBindersNotBound 

Fields

  • ![Var]

    The list of unbound binders

  • ![Var]

    The original binders

  • !CoreExpr

    The original LHS

  • !CoreExpr

    The optimised LHS

DsLazyPatCantBindVarsOfUnliftedType [Var] 
DsNotYetHandledByTH !ThRejectionReason 
DsAggregatedViewExpressions [[LHsExpr GhcTc]] 
DsUnbangedStrictPatterns !(HsBindLR GhcTc GhcTc) 
DsCannotMixPolyAndUnliftedBindings !(HsBindLR GhcTc GhcTc) 
DsWrongDoBind !(LHsExpr GhcTc) !Type 
DsUnusedDoBind !(LHsExpr GhcTc) !Type 
DsRecBindsNotAllowedForUnliftedTys ![LHsBindLR GhcTc GhcTc] 
DsRuleMightInlineFirst !RuleName !Var !Activation 
DsAnotherRuleMightFireFirst !RuleName !RuleName !Var 

Instances

Instances details
Generic DsMessage Source # 
Instance details

Defined in GHC.HsToCore.Errors.Types

Associated Types

type Rep DsMessage :: Type -> Type Source #

Diagnostic DsMessage Source # 
Instance details

Defined in GHC.HsToCore.Errors.Ppr

Associated Types

type DiagnosticOpts DsMessage Source #

type Rep DsMessage Source # 
Instance details

Defined in GHC.HsToCore.Errors.Types

type Rep DsMessage = D1 ('MetaData "DsMessage" "GHC.HsToCore.Errors.Types" "ghc" 'False) ((((C1 ('MetaCons "DsUnknownMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnknownDiagnostic)) :+: (C1 ('MetaCons "DsEmptyEnumeration" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DsIdentitiesFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Id) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Type)))) :+: (C1 ('MetaCons "DsOverflowedLiterals" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Name)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (MinBound, MaxBound))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NegLiteralExtEnabled))) :+: (C1 ('MetaCons "DsRedundantBangPatterns" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsMatchContext GhcRn)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc)) :+: C1 ('MetaCons "DsOverlappingPatterns" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsMatchContext GhcRn)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc))))) :+: ((C1 ('MetaCons "DsInaccessibleRhs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsMatchContext GhcRn)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc)) :+: (C1 ('MetaCons "DsMaxPmCheckModelsReached" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MaxPmCheckModels)) :+: C1 ('MetaCons "DsNonExhaustivePatterns" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsMatchContext GhcRn)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ExhaustivityCheckType)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MaxUncoveredPatterns) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Id]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Nabla])))))) :+: ((C1 ('MetaCons "DsTopLevelBindsNotAllowed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BindsType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsBindLR GhcTc GhcTc))) :+: C1 ('MetaCons "DsUselessSpecialiseForClassMethodSelector" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Id))) :+: (C1 ('MetaCons "DsUselessSpecialiseForNoInlineFunction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Id)) :+: C1 ('MetaCons "DsMultiplicityCoercionsNotSupported" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DsOrphanRule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CoreRule)) :+: (C1 ('MetaCons "DsRuleLhsTooComplicated" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CoreExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CoreExpr)) :+: C1 ('MetaCons "DsRuleIgnoredDueToConstructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DataCon)))) :+: ((C1 ('MetaCons "DsRuleBindersNotBound" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Var]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Var])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CoreExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CoreExpr))) :+: C1 ('MetaCons "DsLazyPatCantBindVarsOfUnliftedType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Var]))) :+: (C1 ('MetaCons "DsNotYetHandledByTH" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ThRejectionReason)) :+: C1 ('MetaCons "DsAggregatedViewExpressions" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[LHsExpr GhcTc]]))))) :+: ((C1 ('MetaCons "DsUnbangedStrictPatterns" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsBindLR GhcTc GhcTc))) :+: (C1 ('MetaCons "DsCannotMixPolyAndUnliftedBindings" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsBindLR GhcTc GhcTc))) :+: C1 ('MetaCons "DsWrongDoBind" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcTc)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Type)))) :+: ((C1 ('MetaCons "DsUnusedDoBind" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcTc)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Type)) :+: C1 ('MetaCons "DsRecBindsNotAllowedForUnliftedTys" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [LHsBindLR GhcTc GhcTc]))) :+: (C1 ('MetaCons "DsRuleMightInlineFirst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RuleName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Var) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Activation))) :+: C1 ('MetaCons "DsAnotherRuleMightFireFirst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RuleName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RuleName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Var))))))))
type DiagnosticOpts DsMessage Source # 
Instance details

Defined in GHC.HsToCore.Errors.Ppr

newtype DsArgNum Source #

Constructors

DsArgNum Int