-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathLexer.x
2995 lines (2619 loc) · 115 KB
/
Lexer.x
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
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
-----------------------------------------------------------------------------
-- (c) The University of Glasgow, 2006
--
-- GHC's lexer for Haskell 2010 [1].
--
-- This is a combination of an Alex-generated lexer [2] from a regex
-- definition, with some hand-coded bits. [3]
--
-- Completely accurate information about token-spans within the source
-- file is maintained. Every token has a start and end RealSrcLoc
-- attached to it.
--
-- References:
-- [1] https://www.haskell.org/onlinereport/haskell2010/haskellch2.html
-- [2] http://www.haskell.org/alex/
-- [3] https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/Parser
--
-----------------------------------------------------------------------------
-- ToDo / known bugs:
-- - parsing integers is a bit slow
-- - readRational is a bit slow
--
-- Known bugs, that were also in the previous version:
-- - M... should be 3 tokens, not 1.
-- - pragma-end should be only valid in a pragma
-- qualified operator NOTES.
--
-- - If M.(+) is a single lexeme, then..
-- - Probably (+) should be a single lexeme too, for consistency.
-- Otherwise ( + ) would be a prefix operator, but M.( + ) would not be.
-- - But we have to rule out reserved operators, otherwise (..) becomes
-- a different lexeme.
-- - Should we therefore also rule out reserved operators in the qualified
-- form? This is quite difficult to achieve. We don't do it for
-- qualified varids.
-- -----------------------------------------------------------------------------
-- Alex "Haskell code fragment top"
{
{-# LANGUAGE BangPatterns #-}
-- See Note [Warnings in code generated by Alex] in compiler/parser/Lexer.x
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
module Lexer (
Token(..), lexer, pragState, mkPState, mkPStatePure, PState(..),
P(..), ParseResult(..), mkParserFlags, ParserFlags(..), getSrcLoc,
getPState, extopt, withThisPackage,
failLocMsgP, failSpanMsgP, srcParseFail,
getMessages,
popContext, pushModuleContext, setLastToken, setSrcLoc,
activeContext, nextIsEOF,
getLexState, popLexState, pushLexState,
extension, bangPatEnabled, datatypeContextsEnabled,
traditionalRecordSyntaxEnabled,
explicitForallEnabled,
inRulePrag,
explicitNamespacesEnabled,
patternSynonymsEnabled,
sccProfilingOn, hpcEnabled,
addWarning,
lexTokenStream,
addAnnotation,AddAnn,addAnnsAt,mkParensApiAnn,
commentToAnnotation,
moveAnnotations
) where
-- base
import Control.Monad
#if __GLASGOW_HASKELL__ > 710
import Control.Monad.Fail
#endif
import Data.Bits
import Data.Char
import Data.List
import Data.Maybe
import Data.Word
import EnumSet (EnumSet)
import qualified EnumSet
-- ghc-boot
import qualified GHC.LanguageExtensions as LangExt
-- bytestring
import Data.ByteString (ByteString)
-- containers
import Data.Map (Map)
import qualified Data.Map as Map
-- compiler/utils
import Bag
import Outputable
import StringBuffer
import FastString
import UniqFM
import Util ( readRational )
-- compiler/main
import ErrUtils
import DynFlags
-- compiler/basicTypes
import SrcLoc
import Module
import BasicTypes ( InlineSpec(..), RuleMatchInfo(..),
IntegralLit(..), FractionalLit(..),
SourceText(..) )
-- compiler/parser
import Ctype
import ApiAnnotation
}
-- -----------------------------------------------------------------------------
-- Alex "Character set macros"
-- NB: The logic behind these definitions is also reflected in basicTypes/Lexeme.hs
-- Any changes here should likely be reflected there.
$unispace = \x05 -- Trick Alex into handling Unicode. See alexGetByte.
$nl = [\n\r\f]
$whitechar = [$nl\v\ $unispace]
$white_no_nl = $whitechar # \n -- TODO #8424
$tab = \t
$ascdigit = 0-9
$unidigit = \x03 -- Trick Alex into handling Unicode. See alexGetByte.
$decdigit = $ascdigit -- for now, should really be $digit (ToDo)
$digit = [$ascdigit $unidigit]
$special = [\(\)\,\;\[\]\`\{\}]
$ascsymbol = [\!\#\$\%\&\*\+\.\/\<\=\>\?\@\\\^\|\-\~\:]
$unisymbol = \x04 -- Trick Alex into handling Unicode. See alexGetByte.
$symbol = [$ascsymbol $unisymbol] # [$special \_\"\']
$unilarge = \x01 -- Trick Alex into handling Unicode. See alexGetByte.
$asclarge = [A-Z]
$large = [$asclarge $unilarge]
$unismall = \x02 -- Trick Alex into handling Unicode. See alexGetByte.
$ascsmall = [a-z]
$small = [$ascsmall $unismall \_]
$unigraphic = \x06 -- Trick Alex into handling Unicode. See alexGetByte.
$graphic = [$small $large $symbol $digit $special $unigraphic \"\']
$binit = 0-1
$octit = 0-7
$hexit = [$decdigit A-F a-f]
$uniidchar = \x07 -- Trick Alex into handling Unicode. See alexGetByte.
$idchar = [$small $large $digit $uniidchar \']
$pragmachar = [$small $large $digit]
$docsym = [\| \^ \* \$]
-- -----------------------------------------------------------------------------
-- Alex "Regular expression macros"
@varid = $small $idchar* -- variable identifiers
@conid = $large $idchar* -- constructor identifiers
@varsym = ($symbol # \:) $symbol* -- variable (operator) symbol
@consym = \: $symbol* -- constructor (operator) symbol
@decimal = $decdigit+
@binary = $binit+
@octal = $octit+
@hexadecimal = $hexit+
@exponent = [eE] [\-\+]? @decimal
@qual = (@conid \.)+
@qvarid = @qual @varid
@qconid = @qual @conid
@qvarsym = @qual @varsym
@qconsym = @qual @consym
@floating_point = @decimal \. @decimal @exponent? | @decimal @exponent
-- normal signed numerical literals can only be explicitly negative,
-- not explicitly positive (contrast @exponent)
@negative = \-
@signed = @negative ?
-- -----------------------------------------------------------------------------
-- Alex "Identifier"
haskell :-
-- -----------------------------------------------------------------------------
-- Alex "Rules"
-- everywhere: skip whitespace
$white_no_nl+ ;
$tab { warnTab }
-- Everywhere: deal with nested comments. We explicitly rule out
-- pragmas, "{-#", so that we don't accidentally treat them as comments.
-- (this can happen even though pragmas will normally take precedence due to
-- longest-match, because pragmas aren't valid in every state, but comments
-- are). We also rule out nested Haddock comments, if the -haddock flag is
-- set.
"{-" / { isNormalComment } { nested_comment lexToken }
-- Single-line comments are a bit tricky. Haskell 98 says that two or
-- more dashes followed by a symbol should be parsed as a varsym, so we
-- have to exclude those.
-- Since Haddock comments aren't valid in every state, we need to rule them
-- out here.
-- The following two rules match comments that begin with two dashes, but
-- continue with a different character. The rules test that this character
-- is not a symbol (in which case we'd have a varsym), and that it's not a
-- space followed by a Haddock comment symbol (docsym) (in which case we'd
-- have a Haddock comment). The rules then munch the rest of the line.
"-- " ~$docsym .* { lineCommentToken }
"--" [^$symbol \ ] .* { lineCommentToken }
-- Next, match Haddock comments if no -haddock flag
"-- " $docsym .* / { ifExtension (not . haddockEnabled) } { lineCommentToken }
-- Now, when we've matched comments that begin with 2 dashes and continue
-- with a different character, we need to match comments that begin with three
-- or more dashes (which clearly can't be Haddock comments). We only need to
-- make sure that the first non-dash character isn't a symbol, and munch the
-- rest of the line.
"---"\-* ~$symbol .* { lineCommentToken }
-- Since the previous rules all match dashes followed by at least one
-- character, we also need to match a whole line filled with just dashes.
"--"\-* / { atEOL } { lineCommentToken }
-- We need this rule since none of the other single line comment rules
-- actually match this case.
"-- " / { atEOL } { lineCommentToken }
-- 'bol' state: beginning of a line. Slurp up all the whitespace (including
-- blank lines) until we find a non-whitespace character, then do layout
-- processing.
--
-- One slight wibble here: what if the line begins with {-#? In
-- theory, we have to lex the pragma to see if it's one we recognise,
-- and if it is, then we backtrack and do_bol, otherwise we treat it
-- as a nested comment. We don't bother with this: if the line begins
-- with {-#, then we'll assume it's a pragma we know about and go for do_bol.
<bol> {
\n ;
^\# line { begin line_prag1 }
^\# / { followedByDigit } { begin line_prag1 }
^\# pragma .* \n ; -- GCC 3.3 CPP generated, apparently
^\# \! .* \n ; -- #!, for scripts
() { do_bol }
}
-- after a layout keyword (let, where, do, of), we begin a new layout
-- context if the curly brace is missing.
-- Careful! This stuff is quite delicate.
<layout, layout_do, layout_if> {
\{ / { notFollowedBy '-' } { hopefully_open_brace }
-- we might encounter {-# here, but {- has been handled already
\n ;
^\# (line)? { begin line_prag1 }
}
-- after an 'if', a vertical bar starts a layout context for MultiWayIf
<layout_if> {
\| / { notFollowedBySymbol } { new_layout_context True dontGenerateSemic ITvbar }
() { pop }
}
-- do is treated in a subtly different way, see new_layout_context
<layout> () { new_layout_context True generateSemic ITvocurly }
<layout_do> () { new_layout_context False generateSemic ITvocurly }
-- after a new layout context which was found to be to the left of the
-- previous context, we have generated a '{' token, and we now need to
-- generate a matching '}' token.
<layout_left> () { do_layout_left }
<0,option_prags> \n { begin bol }
"{-#" $whitechar* $pragmachar+ / { known_pragma linePrags }
{ dispatch_pragmas linePrags }
-- single-line line pragmas, of the form
-- # <line> "<file>" <extra-stuff> \n
<line_prag1> @decimal { setLine line_prag1a }
<line_prag1a> \" [$graphic \ ]* \" { setFile line_prag1b }
<line_prag1b> .* { pop }
-- Haskell-style line pragmas, of the form
-- {-# LINE <line> "<file>" #-}
<line_prag2> @decimal { setLine line_prag2a }
<line_prag2a> \" [$graphic \ ]* \" { setFile line_prag2b }
<line_prag2b> "#-}"|"-}" { pop }
-- NOTE: accept -} at the end of a LINE pragma, for compatibility
-- with older versions of GHC which generated these.
-- Haskell-style column pragmas, of the form
-- {-# COLUMN <column> #-}
<column_prag> @decimal $whitechar* "#-}" { setColumn }
<0,option_prags> {
"{-#" $whitechar* $pragmachar+
$whitechar+ $pragmachar+ / { known_pragma twoWordPrags }
{ dispatch_pragmas twoWordPrags }
"{-#" $whitechar* $pragmachar+ / { known_pragma oneWordPrags }
{ dispatch_pragmas oneWordPrags }
-- We ignore all these pragmas, but don't generate a warning for them
"{-#" $whitechar* $pragmachar+ / { known_pragma ignoredPrags }
{ dispatch_pragmas ignoredPrags }
-- ToDo: should only be valid inside a pragma:
"#-}" { endPrag }
}
<option_prags> {
"{-#" $whitechar* $pragmachar+ / { known_pragma fileHeaderPrags }
{ dispatch_pragmas fileHeaderPrags }
}
<0> {
-- In the "0" mode we ignore these pragmas
"{-#" $whitechar* $pragmachar+ / { known_pragma fileHeaderPrags }
{ nested_comment lexToken }
}
<0,option_prags> {
"{-#" { warnThen Opt_WarnUnrecognisedPragmas (text "Unrecognised pragma")
(nested_comment lexToken) }
}
-- '0' state: ordinary lexemes
-- Haddock comments
<0,option_prags> {
"-- " $docsym / { ifExtension haddockEnabled } { multiline_doc_comment }
"{-" \ ? $docsym / { ifExtension haddockEnabled } { nested_doc_comment }
}
-- "special" symbols
<0> {
"[:" / { ifExtension parrEnabled } { token ITopabrack }
":]" / { ifExtension parrEnabled } { token ITcpabrack }
}
<0> {
"[|" / { ifExtension thQuotesEnabled } { token (ITopenExpQuote NoE
NormalSyntax) }
"[||" / { ifExtension thQuotesEnabled } { token (ITopenTExpQuote NoE) }
"[e|" / { ifExtension thQuotesEnabled } { token (ITopenExpQuote HasE
NormalSyntax) }
"[e||" / { ifExtension thQuotesEnabled } { token (ITopenTExpQuote HasE) }
"[p|" / { ifExtension thQuotesEnabled } { token ITopenPatQuote }
"[d|" / { ifExtension thQuotesEnabled } { layout_token ITopenDecQuote }
"[t|" / { ifExtension thQuotesEnabled } { token ITopenTypQuote }
"|]" / { ifExtension thQuotesEnabled } { token (ITcloseQuote
NormalSyntax) }
"||]" / { ifExtension thQuotesEnabled } { token ITcloseTExpQuote }
\$ @varid / { ifExtension thEnabled } { skip_one_varid ITidEscape }
"$$" @varid / { ifExtension thEnabled } { skip_two_varid ITidTyEscape }
"$(" / { ifExtension thEnabled } { token ITparenEscape }
"$$(" / { ifExtension thEnabled } { token ITparenTyEscape }
"[" @varid "|" / { ifExtension qqEnabled }
{ lex_quasiquote_tok }
-- qualified quasi-quote (#5555)
"[" @qvarid "|" / { ifExtension qqEnabled }
{ lex_qquasiquote_tok }
$unigraphic -- ⟦
/ { ifCurrentChar '⟦' `alexAndPred`
ifExtension (\i -> unicodeSyntaxEnabled i && thQuotesEnabled i) }
{ token (ITopenExpQuote NoE UnicodeSyntax) }
$unigraphic -- ⟧
/ { ifCurrentChar '⟧' `alexAndPred`
ifExtension (\i -> unicodeSyntaxEnabled i && thQuotesEnabled i) }
{ token (ITcloseQuote UnicodeSyntax) }
}
-- See Note [Lexing type applications]
<0> {
[^ $idchar \) ] ^
"@"
/ { ifExtension typeApplicationEnabled `alexAndPred` notFollowedBySymbol }
{ token ITtypeApp }
}
<0> {
"(|" / { ifExtension arrowsEnabled `alexAndPred` notFollowedBySymbol }
{ special (IToparenbar NormalSyntax) }
"|)" / { ifExtension arrowsEnabled } { special (ITcparenbar NormalSyntax) }
$unigraphic -- ⦇
/ { ifCurrentChar '⦇' `alexAndPred`
ifExtension (\i -> unicodeSyntaxEnabled i && arrowsEnabled i) }
{ special (IToparenbar UnicodeSyntax) }
$unigraphic -- ⦈
/ { ifCurrentChar '⦈' `alexAndPred`
ifExtension (\i -> unicodeSyntaxEnabled i && arrowsEnabled i) }
{ special (ITcparenbar UnicodeSyntax) }
}
<0> {
\? @varid / { ifExtension ipEnabled } { skip_one_varid ITdupipvarid }
}
<0> {
"#" @varid / { ifExtension overloadedLabelsEnabled }
{ skip_one_varid ITlabelvarid }
}
<0> {
"(#" / { orExtensions unboxedTuplesEnabled unboxedSumsEnabled }
{ token IToubxparen }
"#)" / { orExtensions unboxedTuplesEnabled unboxedSumsEnabled }
{ token ITcubxparen }
}
<0,option_prags> {
\( { special IToparen }
\) { special ITcparen }
\[ { special ITobrack }
\] { special ITcbrack }
\, { special ITcomma }
\; { special ITsemi }
\` { special ITbackquote }
\{ { open_brace }
\} { close_brace }
}
<0,option_prags> {
@qvarid { idtoken qvarid }
@qconid { idtoken qconid }
@varid { varid }
@conid { idtoken conid }
}
<0> {
@qvarid "#"+ / { ifExtension magicHashEnabled } { idtoken qvarid }
@qconid "#"+ / { ifExtension magicHashEnabled } { idtoken qconid }
@varid "#"+ / { ifExtension magicHashEnabled } { varid }
@conid "#"+ / { ifExtension magicHashEnabled } { idtoken conid }
}
-- ToDo: - move `var` and (sym) into lexical syntax?
-- - remove backquote from $special?
<0> {
@qvarsym { idtoken qvarsym }
@qconsym { idtoken qconsym }
@varsym { varsym }
@consym { consym }
}
-- For the normal boxed literals we need to be careful
-- when trying to be close to Haskell98
<0> {
-- Normal integral literals (:: Num a => a, from Integer)
@decimal { tok_num positive 0 0 decimal }
0[bB] @binary / { ifExtension binaryLiteralsEnabled } { tok_num positive 2 2 binary }
0[oO] @octal { tok_num positive 2 2 octal }
0[xX] @hexadecimal { tok_num positive 2 2 hexadecimal }
@negative @decimal / { ifExtension negativeLiteralsEnabled } { tok_num negative 1 1 decimal }
@negative 0[bB] @binary / { ifExtension negativeLiteralsEnabled `alexAndPred`
ifExtension binaryLiteralsEnabled } { tok_num negative 3 3 binary }
@negative 0[oO] @octal / { ifExtension negativeLiteralsEnabled } { tok_num negative 3 3 octal }
@negative 0[xX] @hexadecimal / { ifExtension negativeLiteralsEnabled } { tok_num negative 3 3 hexadecimal }
-- Normal rational literals (:: Fractional a => a, from Rational)
@floating_point { strtoken tok_float }
@negative @floating_point / { ifExtension negativeLiteralsEnabled } { strtoken tok_float }
}
<0> {
-- Unboxed ints (:: Int#) and words (:: Word#)
-- It's simpler (and faster?) to give separate cases to the negatives,
-- especially considering octal/hexadecimal prefixes.
@decimal \# / { ifExtension magicHashEnabled } { tok_primint positive 0 1 decimal }
0[bB] @binary \# / { ifExtension magicHashEnabled `alexAndPred`
ifExtension binaryLiteralsEnabled } { tok_primint positive 2 3 binary }
0[oO] @octal \# / { ifExtension magicHashEnabled } { tok_primint positive 2 3 octal }
0[xX] @hexadecimal \# / { ifExtension magicHashEnabled } { tok_primint positive 2 3 hexadecimal }
@negative @decimal \# / { ifExtension magicHashEnabled } { tok_primint negative 1 2 decimal }
@negative 0[bB] @binary \# / { ifExtension magicHashEnabled `alexAndPred`
ifExtension binaryLiteralsEnabled } { tok_primint negative 3 4 binary }
@negative 0[oO] @octal \# / { ifExtension magicHashEnabled } { tok_primint negative 3 4 octal }
@negative 0[xX] @hexadecimal \# / { ifExtension magicHashEnabled } { tok_primint negative 3 4 hexadecimal }
@decimal \# \# / { ifExtension magicHashEnabled } { tok_primword 0 2 decimal }
0[bB] @binary \# \# / { ifExtension magicHashEnabled `alexAndPred`
ifExtension binaryLiteralsEnabled } { tok_primword 2 4 binary }
0[oO] @octal \# \# / { ifExtension magicHashEnabled } { tok_primword 2 4 octal }
0[xX] @hexadecimal \# \# / { ifExtension magicHashEnabled } { tok_primword 2 4 hexadecimal }
-- Unboxed floats and doubles (:: Float#, :: Double#)
-- prim_{float,double} work with signed literals
@signed @floating_point \# / { ifExtension magicHashEnabled } { init_strtoken 1 tok_primfloat }
@signed @floating_point \# \# / { ifExtension magicHashEnabled } { init_strtoken 2 tok_primdouble }
}
-- Strings and chars are lexed by hand-written code. The reason is
-- that even if we recognise the string or char here in the regex
-- lexer, we would still have to parse the string afterward in order
-- to convert it to a String.
<0> {
\' { lex_char_tok }
\" { lex_string_tok }
}
-- Note [Lexing type applications]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- The desired syntax for type applications is to prefix the type application
-- with '@', like this:
--
-- foo @Int @Bool baz bum
--
-- This, of course, conflicts with as-patterns. The conflict arises because
-- expressions and patterns use the same parser, and also because we want
-- to allow type patterns within expression patterns.
--
-- Disambiguation is accomplished by requiring *something* to appear between
-- type application and the preceding token. This something must end with
-- a character that cannot be the end of the variable bound in an as-pattern.
-- Currently (June 2015), this means that the something cannot end with a
-- $idchar or a close-paren. (The close-paren is necessary if the as-bound
-- identifier is symbolic.)
--
-- Note that looking for whitespace before the '@' is insufficient, because
-- of this pathological case:
--
-- foo {- hi -}@Int
--
-- This design is predicated on the fact that as-patterns are generally
-- whitespace-free, and also that this whole thing is opt-in, with the
-- TypeApplications extension.
-- -----------------------------------------------------------------------------
-- Alex "Haskell code fragment bottom"
{
-- -----------------------------------------------------------------------------
-- The token type
data Token
= ITas -- Haskell keywords
| ITcase
| ITclass
| ITdata
| ITdefault
| ITderiving
| ITdo
| ITelse
| IThiding
| ITforeign
| ITif
| ITimport
| ITin
| ITinfix
| ITinfixl
| ITinfixr
| ITinstance
| ITlet
| ITmodule
| ITnewtype
| ITof
| ITqualified
| ITthen
| ITtype
| ITwhere
| ITforall IsUnicodeSyntax -- GHC extension keywords
| ITexport
| ITlabel
| ITdynamic
| ITsafe
| ITinterruptible
| ITunsafe
| ITstdcallconv
| ITccallconv
| ITcapiconv
| ITprimcallconv
| ITjavascriptcallconv
| ITmdo
| ITfamily
| ITrole
| ITgroup
| ITby
| ITusing
| ITpattern
| ITstatic
| ITstock
| ITanyclass
-- Backpack tokens
| ITunit
| ITsignature
| ITdependency
| ITrequires
-- Pragmas, see note [Pragma source text] in BasicTypes
| ITinline_prag SourceText InlineSpec RuleMatchInfo
| ITspec_prag SourceText -- SPECIALISE
| ITspec_inline_prag SourceText Bool -- SPECIALISE INLINE (or NOINLINE)
| ITsource_prag SourceText
| ITrules_prag SourceText
| ITwarning_prag SourceText
| ITdeprecated_prag SourceText
| ITline_prag
| ITscc_prag SourceText
| ITgenerated_prag SourceText
| ITcore_prag SourceText -- hdaume: core annotations
| ITunpack_prag SourceText
| ITnounpack_prag SourceText
| ITann_prag SourceText
| ITcomplete_prag SourceText
| ITclose_prag
| IToptions_prag String
| ITinclude_prag String
| ITlanguage_prag
| ITvect_prag SourceText
| ITvect_scalar_prag SourceText
| ITnovect_prag SourceText
| ITminimal_prag SourceText
| IToverlappable_prag SourceText -- instance overlap mode
| IToverlapping_prag SourceText -- instance overlap mode
| IToverlaps_prag SourceText -- instance overlap mode
| ITincoherent_prag SourceText -- instance overlap mode
| ITctype SourceText
| ITdotdot -- reserved symbols
| ITcolon
| ITdcolon IsUnicodeSyntax
| ITequal
| ITlam
| ITlcase
| ITvbar
| ITlarrow IsUnicodeSyntax
| ITrarrow IsUnicodeSyntax
| ITat
| ITtilde
| ITtildehsh
| ITdarrow IsUnicodeSyntax
| ITminus
| ITbang
| ITdot
| ITbiglam -- GHC-extension symbols
| ITocurly -- special symbols
| ITccurly
| ITvocurly
| ITvccurly
| ITobrack
| ITopabrack -- [:, for parallel arrays with -XParallelArrays
| ITcpabrack -- :], for parallel arrays with -XParallelArrays
| ITcbrack
| IToparen
| ITcparen
| IToubxparen
| ITcubxparen
| ITsemi
| ITcomma
| ITunderscore
| ITbackquote
| ITsimpleQuote -- '
| ITvarid FastString -- identifiers
| ITconid FastString
| ITvarsym FastString
| ITconsym FastString
| ITqvarid (FastString,FastString)
| ITqconid (FastString,FastString)
| ITqvarsym (FastString,FastString)
| ITqconsym (FastString,FastString)
| ITdupipvarid FastString -- GHC extension: implicit param: ?x
| ITlabelvarid FastString -- Overloaded label: #x
| ITchar SourceText Char -- Note [Literal source text] in BasicTypes
| ITstring SourceText FastString -- Note [Literal source text] in BasicTypes
| ITinteger IntegralLit -- Note [Literal source text] in BasicTypes
| ITrational FractionalLit
| ITprimchar SourceText Char -- Note [Literal source text] in BasicTypes
| ITprimstring SourceText ByteString -- Note [Literal source text] @BasicTypes
| ITprimint SourceText Integer -- Note [Literal source text] in BasicTypes
| ITprimword SourceText Integer -- Note [Literal source text] in BasicTypes
| ITprimfloat FractionalLit
| ITprimdouble FractionalLit
-- Template Haskell extension tokens
| ITopenExpQuote HasE IsUnicodeSyntax -- [| or [e|
| ITopenPatQuote -- [p|
| ITopenDecQuote -- [d|
| ITopenTypQuote -- [t|
| ITcloseQuote IsUnicodeSyntax -- |]
| ITopenTExpQuote HasE -- [|| or [e||
| ITcloseTExpQuote -- ||]
| ITidEscape FastString -- $x
| ITparenEscape -- $(
| ITidTyEscape FastString -- $$x
| ITparenTyEscape -- $$(
| ITtyQuote -- ''
| ITquasiQuote (FastString,FastString,RealSrcSpan)
-- ITquasiQuote(quoter, quote, loc)
-- represents a quasi-quote of the form
-- [quoter| quote |]
| ITqQuasiQuote (FastString,FastString,FastString,RealSrcSpan)
-- ITqQuasiQuote(Qual, quoter, quote, loc)
-- represents a qualified quasi-quote of the form
-- [Qual.quoter| quote |]
-- Arrow notation extension
| ITproc
| ITrec
| IToparenbar IsUnicodeSyntax -- (|
| ITcparenbar IsUnicodeSyntax -- |)
| ITlarrowtail IsUnicodeSyntax -- -<
| ITrarrowtail IsUnicodeSyntax -- >-
| ITLarrowtail IsUnicodeSyntax -- -<<
| ITRarrowtail IsUnicodeSyntax -- >>-
-- type application '@' (lexed differently than as-pattern '@',
-- due to checking for preceding whitespace)
| ITtypeApp
| ITunknown String -- Used when the lexer can't make sense of it
| ITeof -- end of file token
-- Documentation annotations
| ITdocCommentNext String -- something beginning '-- |'
| ITdocCommentPrev String -- something beginning '-- ^'
| ITdocCommentNamed String -- something beginning '-- $'
| ITdocSection Int String -- a section heading
| ITdocOptions String -- doc options (prune, ignore-exports, etc)
| ITlineComment String -- comment starting by "--"
| ITblockComment String -- comment in {- -}
deriving Show
instance Outputable Token where
ppr x = text (show x)
-- the bitmap provided as the third component indicates whether the
-- corresponding extension keyword is valid under the extension options
-- provided to the compiler; if the extension corresponding to *any* of the
-- bits set in the bitmap is enabled, the keyword is valid (this setup
-- facilitates using a keyword in two different extensions that can be
-- activated independently)
--
reservedWordsFM :: UniqFM (Token, ExtsBitmap)
reservedWordsFM = listToUFM $
map (\(x, y, z) -> (mkFastString x, (y, z)))
[( "_", ITunderscore, 0 ),
( "as", ITas, 0 ),
( "case", ITcase, 0 ),
( "class", ITclass, 0 ),
( "data", ITdata, 0 ),
( "default", ITdefault, 0 ),
( "deriving", ITderiving, 0 ),
( "do", ITdo, 0 ),
( "else", ITelse, 0 ),
( "hiding", IThiding, 0 ),
( "if", ITif, 0 ),
( "import", ITimport, 0 ),
( "in", ITin, 0 ),
( "infix", ITinfix, 0 ),
( "infixl", ITinfixl, 0 ),
( "infixr", ITinfixr, 0 ),
( "instance", ITinstance, 0 ),
( "let", ITlet, 0 ),
( "module", ITmodule, 0 ),
( "newtype", ITnewtype, 0 ),
( "of", ITof, 0 ),
( "qualified", ITqualified, 0 ),
( "then", ITthen, 0 ),
( "type", ITtype, 0 ),
( "where", ITwhere, 0 ),
( "forall", ITforall NormalSyntax,
xbit ExplicitForallBit .|.
xbit InRulePragBit),
( "mdo", ITmdo, xbit RecursiveDoBit),
-- See Note [Lexing type pseudo-keywords]
( "family", ITfamily, 0 ),
( "role", ITrole, 0 ),
( "pattern", ITpattern, xbit PatternSynonymsBit),
( "static", ITstatic, 0 ),
( "stock", ITstock, 0 ),
( "anyclass", ITanyclass, 0 ),
( "group", ITgroup, xbit TransformComprehensionsBit),
( "by", ITby, xbit TransformComprehensionsBit),
( "using", ITusing, xbit TransformComprehensionsBit),
( "foreign", ITforeign, xbit FfiBit),
( "export", ITexport, xbit FfiBit),
( "label", ITlabel, xbit FfiBit),
( "dynamic", ITdynamic, xbit FfiBit),
( "safe", ITsafe, xbit FfiBit .|.
xbit SafeHaskellBit),
( "interruptible", ITinterruptible, xbit InterruptibleFfiBit),
( "unsafe", ITunsafe, xbit FfiBit),
( "stdcall", ITstdcallconv, xbit FfiBit),
( "ccall", ITccallconv, xbit FfiBit),
( "capi", ITcapiconv, xbit CApiFfiBit),
( "prim", ITprimcallconv, xbit FfiBit),
( "javascript", ITjavascriptcallconv, xbit FfiBit),
( "unit", ITunit, 0 ),
( "dependency", ITdependency, 0 ),
( "signature", ITsignature, 0 ),
( "rec", ITrec, xbit ArrowsBit .|.
xbit RecursiveDoBit),
( "proc", ITproc, xbit ArrowsBit)
]
{-----------------------------------
Note [Lexing type pseudo-keywords]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
One might think that we wish to treat 'family' and 'role' as regular old
varids whenever -XTypeFamilies and -XRoleAnnotations are off, respectively.
But, there is no need to do so. These pseudo-keywords are not stolen syntax:
they are only used after the keyword 'type' at the top-level, where varids are
not allowed. Furthermore, checks further downstream (TcTyClsDecls) ensure that
type families and role annotations are never declared without their extensions
on. In fact, by unconditionally lexing these pseudo-keywords as special, we
can get better error messages.
Also, note that these are included in the `varid` production in the parser --
a key detail to make all this work.
-------------------------------------}
reservedSymsFM :: UniqFM (Token, ExtsBitmap -> Bool)
reservedSymsFM = listToUFM $
map (\ (x,y,z) -> (mkFastString x,(y,z)))
[ ("..", ITdotdot, always)
-- (:) is a reserved op, meaning only list cons
,(":", ITcolon, always)
,("::", ITdcolon NormalSyntax, always)
,("=", ITequal, always)
,("\\", ITlam, always)
,("|", ITvbar, always)
,("<-", ITlarrow NormalSyntax, always)
,("->", ITrarrow NormalSyntax, always)
,("@", ITat, always)
,("~", ITtilde, always)
,("~#", ITtildehsh, magicHashEnabled)
,("=>", ITdarrow NormalSyntax, always)
,("-", ITminus, always)
,("!", ITbang, always)
-- For 'forall a . t'
,(".", ITdot, always) -- \i -> explicitForallEnabled i || inRulePrag i)
,("-<", ITlarrowtail NormalSyntax, arrowsEnabled)
,(">-", ITrarrowtail NormalSyntax, arrowsEnabled)
,("-<<", ITLarrowtail NormalSyntax, arrowsEnabled)
,(">>-", ITRarrowtail NormalSyntax, arrowsEnabled)
,("∷", ITdcolon UnicodeSyntax, unicodeSyntaxEnabled)
,("⇒", ITdarrow UnicodeSyntax, unicodeSyntaxEnabled)
,("∀", ITforall UnicodeSyntax, unicodeSyntaxEnabled)
,("→", ITrarrow UnicodeSyntax, unicodeSyntaxEnabled)
,("←", ITlarrow UnicodeSyntax, unicodeSyntaxEnabled)
,("⤙", ITlarrowtail UnicodeSyntax,
\i -> unicodeSyntaxEnabled i && arrowsEnabled i)
,("⤚", ITrarrowtail UnicodeSyntax,
\i -> unicodeSyntaxEnabled i && arrowsEnabled i)
,("⤛", ITLarrowtail UnicodeSyntax,
\i -> unicodeSyntaxEnabled i && arrowsEnabled i)
,("⤜", ITRarrowtail UnicodeSyntax,
\i -> unicodeSyntaxEnabled i && arrowsEnabled i)
-- ToDo: ideally, → and ∷ should be "specials", so that they cannot
-- form part of a large operator. This would let us have a better
-- syntax for kinds: ɑ∷*→* would be a legal kind signature. (maybe).
]
-- -----------------------------------------------------------------------------
-- Lexer actions
type Action = RealSrcSpan -> StringBuffer -> Int -> P (RealLocated Token)
special :: Token -> Action
special tok span _buf _len = return (L span tok)
token, layout_token :: Token -> Action
token t span _buf _len = return (L span t)
layout_token t span _buf _len = pushLexState layout >> return (L span t)
idtoken :: (StringBuffer -> Int -> Token) -> Action
idtoken f span buf len = return (L span $! (f buf len))
skip_one_varid :: (FastString -> Token) -> Action
skip_one_varid f span buf len
= return (L span $! f (lexemeToFastString (stepOn buf) (len-1)))
skip_two_varid :: (FastString -> Token) -> Action
skip_two_varid f span buf len
= return (L span $! f (lexemeToFastString (stepOn (stepOn buf)) (len-2)))
strtoken :: (String -> Token) -> Action
strtoken f span buf len =
return (L span $! (f $! lexemeToString buf len))
init_strtoken :: Int -> (String -> Token) -> Action
-- like strtoken, but drops the last N character(s)
init_strtoken drop f span buf len =
return (L span $! (f $! lexemeToString buf (len-drop)))
begin :: Int -> Action
begin code _span _str _len = do pushLexState code; lexToken
pop :: Action
pop _span _buf _len = do _ <- popLexState
lexToken
hopefully_open_brace :: Action
hopefully_open_brace span buf len
= do relaxed <- extension relaxedLayout
ctx <- getContext
(AI l _) <- getInput
let offset = srcLocCol l
isOK = relaxed ||
case ctx of
Layout prev_off _ : _ -> prev_off < offset
_ -> True
if isOK then pop_and open_brace span buf len
else failSpanMsgP (RealSrcSpan span) (text "Missing block")
pop_and :: Action -> Action
pop_and act span buf len = do _ <- popLexState
act span buf len
{-# INLINE nextCharIs #-}
nextCharIs :: StringBuffer -> (Char -> Bool) -> Bool
nextCharIs buf p = not (atEnd buf) && p (currentChar buf)
{-# INLINE nextCharIsNot #-}
nextCharIsNot :: StringBuffer -> (Char -> Bool) -> Bool
nextCharIsNot buf p = not (nextCharIs buf p)
notFollowedBy :: Char -> AlexAccPred ExtsBitmap
notFollowedBy char _ _ _ (AI _ buf)
= nextCharIsNot buf (== char)
notFollowedBySymbol :: AlexAccPred ExtsBitmap
notFollowedBySymbol _ _ _ (AI _ buf)
= nextCharIsNot buf (`elem` "!#$%&*+./<=>?@\\^|-~")
followedByDigit :: AlexAccPred ExtsBitmap
followedByDigit _ _ _ (AI _ buf)
= afterOptionalSpace buf (\b -> nextCharIs b (`elem` ['0'..'9']))
ifCurrentChar :: Char -> AlexAccPred ExtsBitmap
ifCurrentChar char _ (AI _ buf) _ _
= nextCharIs buf (== char)
-- We must reject doc comments as being ordinary comments everywhere.
-- In some cases the doc comment will be selected as the lexeme due to
-- maximal munch, but not always, because the nested comment rule is
-- valid in all states, but the doc-comment rules are only valid in
-- the non-layout states.
isNormalComment :: AlexAccPred ExtsBitmap
isNormalComment bits _ _ (AI _ buf)