summaryrefslogtreecommitdiff
path: root/compiler/GHC/Parser/Errors.hs
blob: 83812f7673d4b2ae5a4b99488ec6e2c8ce9c2cbd (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
module GHC.Parser.Errors
   ( PsWarning(..)
   , TransLayoutReason(..)
   , OperatorWhitespaceSymbol(..)
   , OperatorWhitespaceOccurrence(..)
   , NumUnderscoreReason(..)
   , PsError(..)
   , PsErrorDesc(..)
   , LexErr(..)
   , CmmParserError(..)
   , LexErrKind(..)
   , Hint(..)
   , StarIsType (..)
   )
where

import GHC.Prelude
import GHC.Types.SrcLoc
import GHC.Types.Name.Reader (RdrName)
import GHC.Types.Name.Occurrence (OccName)
import GHC.Parser.Types
import Language.Haskell.Syntax.Extension
import GHC.Hs.Extension
import GHC.Hs.Expr
import GHC.Hs.Pat
import GHC.Hs.Type
import GHC.Hs.Lit
import GHC.Hs.Decls
import GHC.Core.Coercion.Axiom (Role)
import GHC.Utils.Outputable (SDoc)
import GHC.Data.FastString
import GHC.Unit.Module.Name

-- | A warning that might arise during parsing.
data PsWarning

     -- | Warn when tabulations are found
   = PsWarnTab
      { tabFirst :: !SrcSpan -- ^ First occurrence of a tab
      , tabCount :: !Word    -- ^ Number of other occurrences
      }

   | PsWarnTransitionalLayout !SrcSpan !TransLayoutReason
      -- ^ Transitional layout warnings

   | PsWarnUnrecognisedPragma !SrcSpan
      -- ^ Unrecognised pragma

   | PsWarnHaddockInvalidPos !SrcSpan
      -- ^ Invalid Haddock comment position

   | PsWarnHaddockIgnoreMulti !SrcSpan
      -- ^ Multiple Haddock comment for the same entity

   | PsWarnStarBinder !SrcSpan
      -- ^ Found binding occurrence of "*" while StarIsType is enabled

   | PsWarnStarIsType !SrcSpan
      -- ^ Using "*" for "Type" without StarIsType enabled

   | PsWarnImportPreQualified !SrcSpan
      -- ^ Pre qualified import with 'WarnPrepositiveQualifiedModule' enabled

   | PsWarnOperatorWhitespaceExtConflict !SrcSpan !OperatorWhitespaceSymbol
   | PsWarnOperatorWhitespace !SrcSpan !FastString !OperatorWhitespaceOccurrence

-- | The operator symbol in the 'WarnOperatorWhitespaceExtConflict' warning.
data OperatorWhitespaceSymbol
   = OperatorWhitespaceSymbol_PrefixPercent
   | OperatorWhitespaceSymbol_PrefixDollar
   | OperatorWhitespaceSymbol_PrefixDollarDollar

-- | The operator occurrence type in the 'WarnOperatorWhitespace' warning.
data OperatorWhitespaceOccurrence
   = OperatorWhitespaceOccurrence_Prefix
   | OperatorWhitespaceOccurrence_Suffix
   | OperatorWhitespaceOccurrence_TightInfix

data TransLayoutReason
   = TransLayout_Where -- ^ "`where' clause at the same depth as implicit layout block"
   | TransLayout_Pipe  -- ^ "`|' at the same depth as implicit layout block")

data PsError = PsError
   { errDesc  :: !PsErrorDesc   -- ^ Error description
   , errHints :: ![Hint]      -- ^ Hints
   , errLoc   :: !SrcSpan     -- ^ Error position
   }

data PsErrorDesc
   = PsErrLambdaCase
      -- ^ LambdaCase syntax used without the extension enabled

   | PsErrNumUnderscores !NumUnderscoreReason
      -- ^ Underscores in literals without the extension enabled

   | PsErrPrimStringInvalidChar
      -- ^ Invalid character in primitive string

   | PsErrMissingBlock
      -- ^ Missing block

   | PsErrLexer !LexErr !LexErrKind
      -- ^ Lexer error

   | PsErrSuffixAT
      -- ^ Suffix occurrence of `@`

   | PsErrParse !String
      -- ^ Parse errors

   | PsErrCmmLexer
      -- ^ Cmm lexer error

   | PsErrUnsupportedBoxedSumExpr !(SumOrTuple (HsExpr GhcPs))
      -- ^ Unsupported boxed sum in expression

   | PsErrUnsupportedBoxedSumPat !(SumOrTuple (PatBuilder GhcPs))
      -- ^ Unsupported boxed sum in pattern

   | PsErrUnexpectedQualifiedConstructor !RdrName
      -- ^ Unexpected qualified constructor

   | PsErrTupleSectionInPat
      -- ^ Tuple section in pattern context

   | PsErrIllegalBangPattern !(Pat GhcPs)
      -- ^ Bang-pattern without BangPattterns enabled

   | PsErrOpFewArgs !StarIsType !RdrName
      -- ^ Operator applied to too few arguments

   | PsErrImportQualifiedTwice
      -- ^ Import: multiple occurrences of 'qualified'

   | PsErrImportPostQualified
      -- ^ Post qualified import without 'ImportQualifiedPost'

   | PsErrIllegalExplicitNamespace
      -- ^ Explicit namespace keyword without 'ExplicitNamespaces'

   | PsErrVarForTyCon !RdrName
      -- ^ Expecting a type constructor but found a variable

   | PsErrIllegalPatSynExport
      -- ^ Illegal export form allowed by PatternSynonyms

   | PsErrMalformedEntityString
      -- ^ Malformed entity string

   | PsErrDotsInRecordUpdate
      -- ^ Dots used in record update

   | PsErrPrecedenceOutOfRange !Int
      -- ^ Precedence out of range

   | PsErrOverloadedRecordDotInvalid
      -- ^ Invalid use of record dot syntax `.'

   | PsErrOverloadedRecordUpdateNotEnabled
      -- ^ `OverloadedRecordUpdate` is not enabled.

   | PsErrOverloadedRecordUpdateNoQualifiedFields
      -- ^ Can't use qualified fields when OverloadedRecordUpdate is enabled.

   | PsErrInvalidDataCon !(HsType GhcPs)
      -- ^ Cannot parse data constructor in a data/newtype declaration

   | PsErrInvalidInfixDataCon !(HsType GhcPs) !RdrName !(HsType GhcPs)
      -- ^ Cannot parse data constructor in a data/newtype declaration

   | PsErrUnpackDataCon
      -- ^ UNPACK applied to a data constructor

   | PsErrUnexpectedKindAppInDataCon !DataConBuilder !(HsType GhcPs)
      -- ^ Unexpected kind application in data/newtype declaration

   | PsErrInvalidRecordCon !(PatBuilder GhcPs)
      -- ^ Not a record constructor

   | PsErrIllegalUnboxedStringInPat !(HsLit GhcPs)
      -- ^ Illegal unboxed string literal in pattern

   | PsErrDoNotationInPat
      -- ^ Do-notation in pattern

   | PsErrIfTheElseInPat
      -- ^ If-then-else syntax in pattern

   | PsErrLambdaCaseInPat
      -- ^ Lambda-case in pattern

   | PsErrCaseInPat
      -- ^ case..of in pattern

   | PsErrLetInPat
      -- ^ let-syntax in pattern

   | PsErrLambdaInPat
      -- ^ Lambda-syntax in pattern

   | PsErrArrowExprInPat !(HsExpr GhcPs)
      -- ^ Arrow expression-syntax in pattern

   | PsErrArrowCmdInPat !(HsCmd GhcPs)
      -- ^ Arrow command-syntax in pattern

   | PsErrArrowCmdInExpr !(HsCmd GhcPs)
      -- ^ Arrow command-syntax in expression

   | PsErrViewPatInExpr !(LHsExpr GhcPs) !(LHsExpr GhcPs)
      -- ^ View-pattern in expression

   | PsErrTypeAppWithoutSpace !RdrName !(LHsExpr GhcPs)
      -- ^ Type-application without space before '@'

   | PsErrLazyPatWithoutSpace !(LHsExpr GhcPs)
      -- ^ Lazy-pattern ('~') without space after it

   | PsErrBangPatWithoutSpace !(LHsExpr GhcPs)
      -- ^ Bang-pattern ('!') without space after it

   | PsErrUnallowedPragma !(HsPragE GhcPs)
      -- ^ Pragma not allowed in this position

   | PsErrQualifiedDoInCmd !ModuleName
      -- ^ Qualified do block in command

   | PsErrInvalidInfixHole
      -- ^ Invalid infix hole, expected an infix operator

   | PsErrSemiColonsInCondExpr
      -- ^ Unexpected semi-colons in conditional expression
         !(HsExpr GhcPs) -- ^ conditional expr
         !Bool           -- ^ "then" semi-colon?
         !(HsExpr GhcPs) -- ^ "then" expr
         !Bool           -- ^ "else" semi-colon?
         !(HsExpr GhcPs) -- ^ "else" expr

   | PsErrSemiColonsInCondCmd
      -- ^ Unexpected semi-colons in conditional command
         !(HsExpr GhcPs) -- ^ conditional expr
         !Bool           -- ^ "then" semi-colon?
         !(HsCmd GhcPs)  -- ^ "then" expr
         !Bool           -- ^ "else" semi-colon?
         !(HsCmd GhcPs)  -- ^ "else" expr

   | PsErrAtInPatPos
      -- ^ @-operator in a pattern position

   | PsErrLambdaCmdInFunAppCmd !(LHsCmd GhcPs)
      -- ^ Unexpected lambda command in function application

   | PsErrCaseCmdInFunAppCmd !(LHsCmd GhcPs)
      -- ^ Unexpected case command in function application

   | PsErrIfCmdInFunAppCmd !(LHsCmd GhcPs)
      -- ^ Unexpected if command in function application

   | PsErrLetCmdInFunAppCmd !(LHsCmd GhcPs)
      -- ^ Unexpected let command in function application

   | PsErrDoCmdInFunAppCmd !(LHsCmd GhcPs)
      -- ^ Unexpected do command in function application

   | PsErrDoInFunAppExpr !(Maybe ModuleName) !(LHsExpr GhcPs)
      -- ^ Unexpected do block in function application

   | PsErrMDoInFunAppExpr !(Maybe ModuleName) !(LHsExpr GhcPs)
      -- ^ Unexpected mdo block in function application

   | PsErrLambdaInFunAppExpr !(LHsExpr GhcPs)
      -- ^ Unexpected lambda expression in function application

   | PsErrCaseInFunAppExpr !(LHsExpr GhcPs)
      -- ^ Unexpected case expression in function application

   | PsErrLambdaCaseInFunAppExpr !(LHsExpr GhcPs)
      -- ^ Unexpected lambda-case expression in function application

   | PsErrLetInFunAppExpr !(LHsExpr GhcPs)
      -- ^ Unexpected let expression in function application

   | PsErrIfInFunAppExpr !(LHsExpr GhcPs)
      -- ^ Unexpected if expression in function application

   | PsErrProcInFunAppExpr !(LHsExpr GhcPs)
      -- ^ Unexpected proc expression in function application

   | PsErrMalformedTyOrClDecl !(LHsType GhcPs)
      -- ^ Malformed head of type or class declaration

   | PsErrIllegalWhereInDataDecl
      -- ^ Illegal 'where' keyword in data declaration

   | PsErrIllegalDataTypeContext !(LHsContext GhcPs)
      -- ^ Illegal datatyp context

   | PsErrParseErrorOnInput !OccName
      -- ^ Parse error on input

   | PsErrMalformedDecl !SDoc !RdrName
      -- ^ Malformed ... declaration for ...

   | PsErrUnexpectedTypeAppInDecl !(LHsType GhcPs) !SDoc !RdrName
      -- ^ Unexpected type application in a declaration

   | PsErrNotADataCon !RdrName
      -- ^ Not a data constructor

   | PsErrRecordSyntaxInPatSynDecl !(LPat GhcPs)
      -- ^ Record syntax used in pattern synonym declaration

   | PsErrEmptyWhereInPatSynDecl !RdrName
      -- ^ Empty 'where' clause in pattern-synonym declaration

   | PsErrInvalidWhereBindInPatSynDecl !RdrName !(HsDecl GhcPs)
      -- ^ Invalid binding name in 'where' clause of pattern-synonym declaration

   | PsErrNoSingleWhereBindInPatSynDecl !RdrName !(HsDecl GhcPs)
      -- ^ Multiple bindings in 'where' clause of pattern-synonym declaration

   | PsErrDeclSpliceNotAtTopLevel !(SpliceDecl GhcPs)
      -- ^ Declaration splice not a top-level

   | PsErrInferredTypeVarNotAllowed
      -- ^ Inferred type variables not allowed here

   | PsErrMultipleNamesInStandaloneKindSignature [LIdP GhcPs]
      -- ^ Multiple names in standalone kind signatures

   | PsErrIllegalImportBundleForm
      -- ^ Illegal import bundle form

   | PsErrIllegalRoleName !FastString [Role]
      -- ^ Illegal role name

   | PsErrInvalidTypeSignature !(LHsExpr GhcPs)
      -- ^ Invalid type signature

   | PsErrUnexpectedTypeInDecl !(LHsType GhcPs) !SDoc !RdrName [LHsTypeArg GhcPs] !SDoc
      -- ^ Unexpected type in declaration

   | PsErrExpectedHyphen
      -- ^ Expected a hyphen

   | PsErrSpaceInSCC
      -- ^ Found a space in a SCC

   | PsErrEmptyDoubleQuotes !Bool-- Is TH on?
      -- ^ Found two single quotes

   | PsErrInvalidPackageName !FastString
      -- ^ Invalid package name

   | PsErrInvalidRuleActivationMarker
      -- ^ Invalid rule activation marker

   | PsErrLinearFunction
      -- ^ Linear function found but LinearTypes not enabled

   | PsErrMultiWayIf
      -- ^ Multi-way if-expression found but MultiWayIf not enabled

   | PsErrExplicitForall !Bool -- is Unicode forall?
      -- ^ Explicit forall found but no extension allowing it is enabled

   | PsErrIllegalQualifiedDo !SDoc
      -- ^ Found qualified-do without QualifiedDo enabled

   | PsErrCmmParser !CmmParserError
      -- ^ Cmm parser error

   | PsErrIllegalTraditionalRecordSyntax !SDoc
      -- ^ Illegal traditional record syntax
      --
      -- TODO: distinguish errors without using SDoc

   | PsErrParseErrorInCmd !SDoc
      -- ^ Parse error in command
      --
      -- TODO: distinguish errors without using SDoc

   | PsErrParseErrorInPat !SDoc
      -- ^ Parse error in pattern
      --
      -- TODO: distinguish errors without using SDoc


newtype StarIsType = StarIsType Bool

data NumUnderscoreReason
   = NumUnderscore_Integral
   | NumUnderscore_Float
   deriving (Show,Eq,Ord)

data Hint
   = SuggestTH
   | SuggestRecursiveDo
   | SuggestDo
   | SuggestMissingDo
   | SuggestLetInDo
   | SuggestPatternSynonyms
   | SuggestInfixBindMaybeAtPat !RdrName
   | TypeApplicationsInPatternsOnlyDataCons -- ^ Type applications in patterns are only allowed on data constructors


data LexErrKind
   = LexErrKind_EOF        -- ^ End of input
   | LexErrKind_UTF8       -- ^ UTF-8 decoding error
   | LexErrKind_Char !Char -- ^ Error at given character
   deriving (Show,Eq,Ord)

data LexErr
   = LexError               -- ^ Lexical error
   | LexUnknownPragma       -- ^ Unknown pragma
   | LexErrorInPragma       -- ^ Lexical error in pragma
   | LexNumEscapeRange      -- ^ Numeric escape sequence out of range
   | LexStringCharLit       -- ^ Llexical error in string/character literal
   | LexStringCharLitEOF    -- ^ Unexpected end-of-file in string/character literal
   | LexUnterminatedComment -- ^ Unterminated `{-'
   | LexUnterminatedOptions -- ^ Unterminated OPTIONS pragma
   | LexUnterminatedQQ      -- ^ Unterminated quasiquotation

-- | Errors from the Cmm parser
data CmmParserError
   = CmmUnknownPrimitive    !FastString -- ^ Unknown Cmm primitive
   | CmmUnknownMacro        !FastString -- ^ Unknown macro
   | CmmUnknownCConv        !String     -- ^ Unknown calling convention
   | CmmUnrecognisedSafety  !String     -- ^ Unrecognised safety
   | CmmUnrecognisedHint    !String     -- ^ Unrecognised hint