Implement -XUnicodeSyntax
[ghc-hetmet.git] / compiler / parser / Lexer.x
1 -----------------------------------------------------------------------------
2 -- (c) The University of Glasgow, 2006
3 --
4 -- GHC's lexer.
5 --
6 -- This is a combination of an Alex-generated lexer from a regex
7 -- definition, with some hand-coded bits.
8 --
9 -- Completely accurate information about token-spans within the source
10 -- file is maintained.  Every token has a start and end SrcLoc attached to it.
11 --
12 -----------------------------------------------------------------------------
13
14 --   ToDo / known bugs:
15 --    - Unicode
16 --    - parsing integers is a bit slow
17 --    - readRational is a bit slow
18 --
19 --   Known bugs, that were also in the previous version:
20 --    - M... should be 3 tokens, not 1.
21 --    - pragma-end should be only valid in a pragma
22
23 {
24 module Lexer (
25    Token(..), lexer, pragState, mkPState, PState(..),
26    P(..), ParseResult(..), getSrcLoc, 
27    failLocMsgP, failSpanMsgP, srcParseFail,
28    getMessages,
29    popContext, pushCurrentContext, setLastToken, setSrcLoc,
30    getLexState, popLexState, pushLexState,
31    extension, glaExtsEnabled, bangPatEnabled
32   ) where
33
34 #include "HsVersions.h"
35
36 import Bag
37 import ErrUtils
38 import Outputable
39 import StringBuffer
40 import FastString
41 import FastTypes
42 import SrcLoc
43 import UniqFM
44 import DynFlags
45 import Ctype
46 import Util             ( maybePrefixMatch, readRational )
47
48 import Control.Monad
49 import Data.Bits
50 import Data.Char        ( chr, isSpace )
51 import Data.Ratio
52 import Debug.Trace
53
54 #if __GLASGOW_HASKELL__ >= 605
55 import Data.Char        ( GeneralCategory(..), generalCategory, isPrint, isUpper )
56 #else
57 import Compat.Unicode   ( GeneralCategory(..), generalCategory, isPrint, isUpper )
58 #endif
59 }
60
61 $unispace    = \x05 -- Trick Alex into handling Unicode. See alexGetChar.
62 $whitechar   = [\ \n\r\f\v\xa0 $unispace]
63 $white_no_nl = $whitechar # \n
64 $tab         = \t
65
66 $ascdigit  = 0-9
67 $unidigit  = \x03 -- Trick Alex into handling Unicode. See alexGetChar.
68 $decdigit  = $ascdigit -- for now, should really be $digit (ToDo)
69 $digit     = [$ascdigit $unidigit]
70
71 $special   = [\(\)\,\;\[\]\`\{\}]
72 $ascsymbol = [\!\#\$\%\&\*\+\.\/\<\=\>\?\@\\\^\|\-\~ \xa1-\xbf \xd7 \xf7]
73 $unisymbol = \x04 -- Trick Alex into handling Unicode. See alexGetChar.
74 $symbol    = [$ascsymbol $unisymbol] # [$special \_\:\"\']
75
76 $unilarge  = \x01 -- Trick Alex into handling Unicode. See alexGetChar.
77 $asclarge  = [A-Z \xc0-\xd6 \xd8-\xde]
78 $large     = [$asclarge $unilarge]
79
80 $unismall  = \x02 -- Trick Alex into handling Unicode. See alexGetChar.
81 $ascsmall  = [a-z \xdf-\xf6 \xf8-\xff]
82 $small     = [$ascsmall $unismall \_]
83
84 $unigraphic = \x06 -- Trick Alex into handling Unicode. See alexGetChar.
85 $graphic   = [$small $large $symbol $digit $special $unigraphic \:\"\']
86
87 $octit     = 0-7
88 $hexit     = [$decdigit A-F a-f]
89 $symchar   = [$symbol \:]
90 $nl        = [\n\r]
91 $idchar    = [$small $large $digit \']
92
93 $docsym    = [\| \^ \* \$]
94
95 @varid     = $small $idchar*
96 @conid     = $large $idchar*
97
98 @varsym    = $symbol $symchar*
99 @consym    = \: $symchar*
100
101 @decimal     = $decdigit+
102 @octal       = $octit+
103 @hexadecimal = $hexit+
104 @exponent    = [eE] [\-\+]? @decimal
105
106 -- we support the hierarchical module name extension:
107 @qual = (@conid \.)+
108
109 @floating_point = @decimal \. @decimal @exponent? | @decimal @exponent
110
111 -- normal signed numerical literals can only be explicitly negative,
112 -- not explicitly positive (contrast @exponent)
113 @negative = \-
114 @signed = @negative ?
115
116 haskell :-
117
118 -- everywhere: skip whitespace and comments
119 $white_no_nl+                           ;
120 $tab+         { warn Opt_WarnTabs (text "Tab character") }
121
122 -- Everywhere: deal with nested comments.  We explicitly rule out
123 -- pragmas, "{-#", so that we don't accidentally treat them as comments.
124 -- (this can happen even though pragmas will normally take precedence due to
125 -- longest-match, because pragmas aren't valid in every state, but comments
126 -- are). We also rule out nested Haddock comments, if the -haddock flag is
127 -- set.
128
129 "{-" / { isNormalComment } { nested_comment lexToken }
130
131 -- Single-line comments are a bit tricky.  Haskell 98 says that two or
132 -- more dashes followed by a symbol should be parsed as a varsym, so we
133 -- have to exclude those.
134
135 -- Since Haddock comments aren't valid in every state, we need to rule them
136 -- out here.  
137
138 -- The following two rules match comments that begin with two dashes, but
139 -- continue with a different character. The rules test that this character
140 -- is not a symbol (in which case we'd have a varsym), and that it's not a
141 -- space followed by a Haddock comment symbol (docsym) (in which case we'd
142 -- have a Haddock comment). The rules then munch the rest of the line.
143
144 "-- " ~$docsym .* ;
145 "--" [^$symbol : \ ] .* ;
146
147 -- Next, match Haddock comments if no -haddock flag
148
149 "-- " $docsym .* / { ifExtension (not . haddockEnabled) } ;
150
151 -- Now, when we've matched comments that begin with 2 dashes and continue
152 -- with a different character, we need to match comments that begin with three
153 -- or more dashes (which clearly can't be Haddock comments). We only need to
154 -- make sure that the first non-dash character isn't a symbol, and munch the
155 -- rest of the line.
156
157 "---"\-* [^$symbol :] .* ;
158
159 -- Since the previous rules all match dashes followed by at least one
160 -- character, we also need to match a whole line filled with just dashes.
161
162 "--"\-* / { atEOL } ;
163
164 -- We need this rule since none of the other single line comment rules
165 -- actually match this case.
166
167 "-- " / { atEOL } ;
168
169 -- 'bol' state: beginning of a line.  Slurp up all the whitespace (including
170 -- blank lines) until we find a non-whitespace character, then do layout
171 -- processing.
172 --
173 -- One slight wibble here: what if the line begins with {-#? In
174 -- theory, we have to lex the pragma to see if it's one we recognise,
175 -- and if it is, then we backtrack and do_bol, otherwise we treat it
176 -- as a nested comment.  We don't bother with this: if the line begins
177 -- with {-#, then we'll assume it's a pragma we know about and go for do_bol.
178 <bol> {
179   \n                                    ;
180   ^\# (line)?                           { begin line_prag1 }
181   ^\# pragma .* \n                      ; -- GCC 3.3 CPP generated, apparently
182   ^\# \! .* \n                          ; -- #!, for scripts
183   ()                                    { do_bol }
184 }
185
186 -- after a layout keyword (let, where, do, of), we begin a new layout
187 -- context if the curly brace is missing.
188 -- Careful! This stuff is quite delicate.
189 <layout, layout_do> {
190   \{ / { notFollowedBy '-' }            { pop_and open_brace }
191         -- we might encounter {-# here, but {- has been handled already
192   \n                                    ;
193   ^\# (line)?                           { begin line_prag1 }
194 }
195
196 -- do is treated in a subtly different way, see new_layout_context
197 <layout>    ()                          { new_layout_context True }
198 <layout_do> ()                          { new_layout_context False }
199
200 -- after a new layout context which was found to be to the left of the
201 -- previous context, we have generated a '{' token, and we now need to
202 -- generate a matching '}' token.
203 <layout_left>  ()                       { do_layout_left }
204
205 <0,option_prags,glaexts> \n                             { begin bol }
206
207 "{-#" $whitechar* (line|LINE)           { begin line_prag2 }
208
209 -- single-line line pragmas, of the form
210 --    # <line> "<file>" <extra-stuff> \n
211 <line_prag1> $decdigit+                 { setLine line_prag1a }
212 <line_prag1a> \" [$graphic \ ]* \"      { setFile line_prag1b }
213 <line_prag1b> .*                        { pop }
214
215 -- Haskell-style line pragmas, of the form
216 --    {-# LINE <line> "<file>" #-}
217 <line_prag2> $decdigit+                 { setLine line_prag2a }
218 <line_prag2a> \" [$graphic \ ]* \"      { setFile line_prag2b }
219 <line_prag2b> "#-}"|"-}"                { pop }
220    -- NOTE: accept -} at the end of a LINE pragma, for compatibility
221    -- with older versions of GHC which generated these.
222
223 -- We only want RULES pragmas to be picked up when -fglasgow-exts
224 -- is on, because the contents of the pragma is always written using
225 -- glasgow-exts syntax (using forall etc.), so if glasgow exts are not
226 -- enabled, we're sure to get a parse error.
227 -- (ToDo: we should really emit a warning when ignoring pragmas)
228 <glaexts>
229   "{-#" $whitechar* (RULES|rules)       { token ITrules_prag }
230
231 <0,option_prags,glaexts> {
232   "{-#" $whitechar* (INLINE|inline)     { token (ITinline_prag True) }
233   "{-#" $whitechar* (NO(T?)INLINE|no(t?)inline)
234                                         { token (ITinline_prag False) }
235   "{-#" $whitechar* (SPECIALI[SZ]E|speciali[sz]e)
236                                         { token ITspec_prag }
237   "{-#" $whitechar* (SPECIALI[SZ]E|speciali[sz]e)
238         $whitechar* (INLINE|inline)     { token (ITspec_inline_prag True) }
239   "{-#" $whitechar* (SPECIALI[SZ]E|speciali[sz]e)
240         $whitechar* (NO(T?)INLINE|no(t?)inline)
241                                         { token (ITspec_inline_prag False) }
242   "{-#" $whitechar* (SOURCE|source)     { token ITsource_prag }
243   "{-#" $whitechar* (DEPRECATED|deprecated)
244                                         { token ITdeprecated_prag }
245   "{-#" $whitechar* (SCC|scc)           { token ITscc_prag }
246   "{-#" $whitechar* (GENERATED|generated)
247                                         { token ITgenerated_prag }
248   "{-#" $whitechar* (CORE|core)         { token ITcore_prag }
249   "{-#" $whitechar* (UNPACK|unpack)     { token ITunpack_prag }
250
251   "{-#" $whitechar* (DOCOPTIONS|docoptions)
252   / { ifExtension haddockEnabled }     { lex_string_prag ITdocOptions }
253
254  "{-#"                                 { nested_comment lexToken }
255
256   -- ToDo: should only be valid inside a pragma:
257   "#-}"                                 { token ITclose_prag}
258 }
259
260 <option_prags> {
261   "{-#" $whitechar* (OPTIONS|options)   { lex_string_prag IToptions_prag }
262   "{-#" $whitechar* (OPTIONS_GHC|options_ghc)
263                                         { lex_string_prag IToptions_prag }
264   "{-#" $whitechar* (LANGUAGE|language) { token ITlanguage_prag }
265   "{-#" $whitechar* (INCLUDE|include)   { lex_string_prag ITinclude_prag }
266 }
267
268 <0,option_prags,glaexts> {
269         -- This is to catch things like {-# OPTIONS OPTIONS_HUGS ... 
270   "{-#" $whitechar* $idchar+            { nested_comment lexToken }
271 }
272
273 -- '0' state: ordinary lexemes
274 -- 'glaexts' state: glasgow extensions (postfix '#', etc.)
275
276 -- Haddock comments
277
278 <0,glaexts> {
279   "-- " $docsym    / { ifExtension haddockEnabled } { multiline_doc_comment }
280   "{-" \ ? $docsym / { ifExtension haddockEnabled } { nested_doc_comment }
281 }
282
283 -- "special" symbols
284
285 <0,glaexts> {
286   "[:" / { ifExtension parrEnabled }    { token ITopabrack }
287   ":]" / { ifExtension parrEnabled }    { token ITcpabrack }
288 }
289   
290 <0,glaexts> {
291   "[|"      / { ifExtension thEnabled } { token ITopenExpQuote }
292   "[e|"     / { ifExtension thEnabled } { token ITopenExpQuote }
293   "[p|"     / { ifExtension thEnabled } { token ITopenPatQuote }
294   "[d|"     / { ifExtension thEnabled } { layout_token ITopenDecQuote }
295   "[t|"     / { ifExtension thEnabled } { token ITopenTypQuote }
296   "|]"      / { ifExtension thEnabled } { token ITcloseQuote }
297   \$ @varid / { ifExtension thEnabled } { skip_one_varid ITidEscape }
298   "$("      / { ifExtension thEnabled } { token ITparenEscape }
299 }
300
301 <0,glaexts> {
302   "(|" / { ifExtension arrowsEnabled `alexAndPred` notFollowedBySymbol }
303                                         { special IToparenbar }
304   "|)" / { ifExtension arrowsEnabled }  { special ITcparenbar }
305 }
306
307 <0,glaexts> {
308   \? @varid / { ifExtension ipEnabled } { skip_one_varid ITdupipvarid }
309 }
310
311 <glaexts> {
312   "(#" / { notFollowedBySymbol }        { token IToubxparen }
313   "#)"                                  { token ITcubxparen }
314   "{|"                                  { token ITocurlybar }
315   "|}"                                  { token ITccurlybar }
316 }
317
318 <0,option_prags,glaexts> {
319   \(                                    { special IToparen }
320   \)                                    { special ITcparen }
321   \[                                    { special ITobrack }
322   \]                                    { special ITcbrack }
323   \,                                    { special ITcomma }
324   \;                                    { special ITsemi }
325   \`                                    { special ITbackquote }
326                                 
327   \{                                    { open_brace }
328   \}                                    { close_brace }
329 }
330
331 <0,option_prags,glaexts> {
332   @qual @varid                  { check_qvarid }
333   @qual @conid                  { idtoken qconid }
334   @varid                        { varid }
335   @conid                        { idtoken conid }
336 }
337
338 -- after an illegal qvarid, such as 'M.let', 
339 -- we back up and try again in the bad_qvarid state:
340 <bad_qvarid> {
341   @conid                        { pop_and (idtoken conid) }
342   @qual @conid                  { pop_and (idtoken qconid) }
343 }
344
345 <0,glaexts> {
346   @qual @varid "#"+ / { ifExtension magicHashEnabled } { idtoken qvarid }
347   @qual @conid "#"+ / { ifExtension magicHashEnabled } { idtoken qconid }
348   @varid "#"+       / { ifExtension magicHashEnabled } { varid }
349   @conid "#"+       / { ifExtension magicHashEnabled } { idtoken conid }
350 }
351
352 -- ToDo: M.(,,,)
353
354 <0,glaexts> {
355   @qual @varsym                 { idtoken qvarsym }
356   @qual @consym                 { idtoken qconsym }
357   @varsym                       { varsym }
358   @consym                       { consym }
359 }
360
361 -- For the normal boxed literals we need to be careful
362 -- when trying to be close to Haskell98
363 <0,glaexts> {
364   -- Normal integral literals (:: Num a => a, from Integer)
365   @decimal                      { tok_num positive 0 0 decimal }
366   0[oO] @octal                  { tok_num positive 2 2 octal }
367   0[xX] @hexadecimal            { tok_num positive 2 2 hexadecimal }
368
369   -- Normal rational literals (:: Fractional a => a, from Rational)
370   @floating_point               { strtoken tok_float }
371 }
372
373 <glaexts> {
374   -- Unboxed ints (:: Int#)
375   -- It's simpler (and faster?) to give separate cases to the negatives,
376   -- especially considering octal/hexadecimal prefixes.
377   @decimal \#                   { tok_primint positive 0 1 decimal }
378   0[oO] @octal \#               { tok_primint positive 2 3 octal }
379   0[xX] @hexadecimal \#         { tok_primint positive 2 3 hexadecimal }
380   @negative @decimal \#                 { tok_primint negative 1 2 decimal }
381   @negative 0[oO] @octal \#             { tok_primint negative 3 4 octal }
382   @negative 0[xX] @hexadecimal \#       { tok_primint negative 3 4 hexadecimal }
383
384   -- Unboxed floats and doubles (:: Float#, :: Double#)
385   -- prim_{float,double} work with signed literals
386   @signed @floating_point \#            { init_strtoken 1 tok_primfloat }
387   @signed @floating_point \# \#         { init_strtoken 2 tok_primdouble }
388 }
389
390 -- Strings and chars are lexed by hand-written code.  The reason is
391 -- that even if we recognise the string or char here in the regex
392 -- lexer, we would still have to parse the string afterward in order
393 -- to convert it to a String.
394 <0,glaexts> {
395   \'                            { lex_char_tok }
396   \"                            { lex_string_tok }
397 }
398
399 {
400 -- -----------------------------------------------------------------------------
401 -- The token type
402
403 data Token
404   = ITas                        -- Haskell keywords
405   | ITcase
406   | ITclass
407   | ITdata
408   | ITdefault
409   | ITderiving
410   | ITderive
411   | ITdo
412   | ITelse
413   | IThiding
414   | ITif
415   | ITimport
416   | ITin
417   | ITinfix
418   | ITinfixl
419   | ITinfixr
420   | ITinstance
421   | ITlet
422   | ITmodule
423   | ITnewtype
424   | ITof
425   | ITqualified
426   | ITthen
427   | ITtype
428   | ITwhere
429   | ITscc                       -- ToDo: remove (we use {-# SCC "..." #-} now)
430
431   | ITforall                    -- GHC extension keywords
432   | ITforeign
433   | ITexport
434   | ITlabel
435   | ITdynamic
436   | ITsafe
437   | ITthreadsafe
438   | ITunsafe
439   | ITstdcallconv
440   | ITccallconv
441   | ITdotnet
442   | ITmdo
443   | ITfamily
444
445         -- Pragmas
446   | ITinline_prag Bool          -- True <=> INLINE, False <=> NOINLINE
447   | ITspec_prag                 -- SPECIALISE   
448   | ITspec_inline_prag Bool     -- SPECIALISE INLINE (or NOINLINE)
449   | ITsource_prag
450   | ITrules_prag
451   | ITdeprecated_prag
452   | ITline_prag
453   | ITscc_prag
454   | ITgenerated_prag
455   | ITcore_prag                 -- hdaume: core annotations
456   | ITunpack_prag
457   | ITclose_prag
458   | IToptions_prag String
459   | ITinclude_prag String
460   | ITlanguage_prag
461
462   | ITdotdot                    -- reserved symbols
463   | ITcolon
464   | ITdcolon
465   | ITequal
466   | ITlam
467   | ITvbar
468   | ITlarrow
469   | ITrarrow
470   | ITat
471   | ITtilde
472   | ITdarrow
473   | ITminus
474   | ITbang
475   | ITstar
476   | ITdot
477
478   | ITbiglam                    -- GHC-extension symbols
479
480   | ITocurly                    -- special symbols
481   | ITccurly
482   | ITocurlybar                 -- {|, for type applications
483   | ITccurlybar                 -- |}, for type applications
484   | ITvocurly
485   | ITvccurly
486   | ITobrack
487   | ITopabrack                  -- [:, for parallel arrays with -fparr
488   | ITcpabrack                  -- :], for parallel arrays with -fparr
489   | ITcbrack
490   | IToparen
491   | ITcparen
492   | IToubxparen
493   | ITcubxparen
494   | ITsemi
495   | ITcomma
496   | ITunderscore
497   | ITbackquote
498
499   | ITvarid   FastString        -- identifiers
500   | ITconid   FastString
501   | ITvarsym  FastString
502   | ITconsym  FastString
503   | ITqvarid  (FastString,FastString)
504   | ITqconid  (FastString,FastString)
505   | ITqvarsym (FastString,FastString)
506   | ITqconsym (FastString,FastString)
507
508   | ITdupipvarid   FastString   -- GHC extension: implicit param: ?x
509
510   | ITpragma StringBuffer
511
512   | ITchar       Char
513   | ITstring     FastString
514   | ITinteger    Integer
515   | ITrational   Rational
516
517   | ITprimchar   Char
518   | ITprimstring FastString
519   | ITprimint    Integer
520   | ITprimfloat  Rational
521   | ITprimdouble Rational
522
523   -- MetaHaskell extension tokens
524   | ITopenExpQuote              --  [| or [e|
525   | ITopenPatQuote              --  [p|
526   | ITopenDecQuote              --  [d|
527   | ITopenTypQuote              --  [t|         
528   | ITcloseQuote                --  |]
529   | ITidEscape   FastString     --  $x
530   | ITparenEscape               --  $( 
531   | ITvarQuote                  --  '
532   | ITtyQuote                   --  ''
533
534   -- Arrow notation extension
535   | ITproc
536   | ITrec
537   | IToparenbar                 --  (|
538   | ITcparenbar                 --  |)
539   | ITlarrowtail                --  -<
540   | ITrarrowtail                --  >-
541   | ITLarrowtail                --  -<<
542   | ITRarrowtail                --  >>-
543
544   | ITunknown String            -- Used when the lexer can't make sense of it
545   | ITeof                       -- end of file token
546
547   -- Documentation annotations
548   | ITdocCommentNext  String     -- something beginning '-- |'
549   | ITdocCommentPrev  String     -- something beginning '-- ^'
550   | ITdocCommentNamed String     -- something beginning '-- $'
551   | ITdocSection      Int String -- a section heading
552   | ITdocOptions      String     -- doc options (prune, ignore-exports, etc)
553
554 #ifdef DEBUG
555   deriving Show -- debugging
556 #endif
557
558 isSpecial :: Token -> Bool
559 -- If we see M.x, where x is a keyword, but
560 -- is special, we treat is as just plain M.x, 
561 -- not as a keyword.
562 isSpecial ITas          = True
563 isSpecial IThiding      = True
564 isSpecial ITderive      = True
565 isSpecial ITqualified   = True
566 isSpecial ITforall      = True
567 isSpecial ITexport      = True
568 isSpecial ITlabel       = True
569 isSpecial ITdynamic     = True
570 isSpecial ITsafe        = True
571 isSpecial ITthreadsafe  = True
572 isSpecial ITunsafe      = True
573 isSpecial ITccallconv   = True
574 isSpecial ITstdcallconv = True
575 isSpecial ITmdo         = True
576 isSpecial ITfamily      = True
577 isSpecial _             = False
578
579 -- the bitmap provided as the third component indicates whether the
580 -- corresponding extension keyword is valid under the extension options
581 -- provided to the compiler; if the extension corresponding to *any* of the
582 -- bits set in the bitmap is enabled, the keyword is valid (this setup
583 -- facilitates using a keyword in two different extensions that can be
584 -- activated independently)
585 --
586 reservedWordsFM = listToUFM $
587         map (\(x, y, z) -> (mkFastString x, (y, z)))
588        [( "_",          ITunderscore,   0 ),
589         ( "as",         ITas,           0 ),
590         ( "case",       ITcase,         0 ),     
591         ( "class",      ITclass,        0 ),    
592         ( "data",       ITdata,         0 ),     
593         ( "default",    ITdefault,      0 ),  
594         ( "deriving",   ITderiving,     0 ), 
595         ( "derive",     ITderive,       0 ), 
596         ( "do",         ITdo,           0 ),       
597         ( "else",       ITelse,         0 ),     
598         ( "hiding",     IThiding,       0 ),
599         ( "if",         ITif,           0 ),       
600         ( "import",     ITimport,       0 ),   
601         ( "in",         ITin,           0 ),       
602         ( "infix",      ITinfix,        0 ),    
603         ( "infixl",     ITinfixl,       0 ),   
604         ( "infixr",     ITinfixr,       0 ),   
605         ( "instance",   ITinstance,     0 ), 
606         ( "let",        ITlet,          0 ),      
607         ( "module",     ITmodule,       0 ),   
608         ( "newtype",    ITnewtype,      0 ),  
609         ( "of",         ITof,           0 ),       
610         ( "qualified",  ITqualified,    0 ),
611         ( "then",       ITthen,         0 ),     
612         ( "type",       ITtype,         0 ),     
613         ( "where",      ITwhere,        0 ),
614         ( "_scc_",      ITscc,          0 ),            -- ToDo: remove
615
616         ( "forall",     ITforall,        bit tvBit),
617         ( "mdo",        ITmdo,           bit recursiveDoBit),
618         ( "family",     ITfamily,        bit tyFamBit),
619
620         ( "foreign",    ITforeign,       bit ffiBit),
621         ( "export",     ITexport,        bit ffiBit),
622         ( "label",      ITlabel,         bit ffiBit),
623         ( "dynamic",    ITdynamic,       bit ffiBit),
624         ( "safe",       ITsafe,          bit ffiBit),
625         ( "threadsafe", ITthreadsafe,    bit ffiBit),
626         ( "unsafe",     ITunsafe,        bit ffiBit),
627         ( "stdcall",    ITstdcallconv,   bit ffiBit),
628         ( "ccall",      ITccallconv,     bit ffiBit),
629         ( "dotnet",     ITdotnet,        bit ffiBit),
630
631         ( "rec",        ITrec,           bit arrowsBit),
632         ( "proc",       ITproc,          bit arrowsBit)
633      ]
634
635 reservedSymsFM :: UniqFM (Token, Int -> Bool)
636 reservedSymsFM = listToUFM $
637     map (\ (x,y,z) -> (mkFastString x,(y,z)))
638       [ ("..",  ITdotdot,   always)
639         -- (:) is a reserved op, meaning only list cons
640        ,(":",   ITcolon,    always)
641        ,("::",  ITdcolon,   always)
642        ,("=",   ITequal,    always)
643        ,("\\",  ITlam,      always)
644        ,("|",   ITvbar,     always)
645        ,("<-",  ITlarrow,   always)
646        ,("->",  ITrarrow,   always)
647        ,("@",   ITat,       always)
648        ,("~",   ITtilde,    always)
649        ,("=>",  ITdarrow,   always)
650        ,("-",   ITminus,    always)
651        ,("!",   ITbang,     always)
652
653         -- For data T (a::*) = MkT
654        ,("*", ITstar, \i -> glaExtsEnabled i ||
655                             kindSigsEnabled i ||
656                             tyFamEnabled i)
657         -- For 'forall a . t'
658        ,(".", ITdot, tvEnabled)
659
660        ,("-<",  ITlarrowtail, arrowsEnabled)
661        ,(">-",  ITrarrowtail, arrowsEnabled)
662        ,("-<<", ITLarrowtail, arrowsEnabled)
663        ,(">>-", ITRarrowtail, arrowsEnabled)
664
665 #if __GLASGOW_HASKELL__ >= 605
666        ,("∷",   ITdcolon, unicodeSyntaxEnabled)
667        ,("⇒",   ITdarrow, unicodeSyntaxEnabled)
668        ,("∀",   ITforall, \i -> unicodeSyntaxEnabled i && tvEnabled i)
669        ,("→",   ITrarrow, unicodeSyntaxEnabled)
670        ,("←",   ITlarrow, unicodeSyntaxEnabled)
671        ,("⋯",   ITdotdot, unicodeSyntaxEnabled)
672         -- ToDo: ideally, → and ∷ should be "specials", so that they cannot
673         -- form part of a large operator.  This would let us have a better
674         -- syntax for kinds: ɑ∷*→* would be a legal kind signature. (maybe).
675 #endif
676        ]
677
678 -- -----------------------------------------------------------------------------
679 -- Lexer actions
680
681 type Action = SrcSpan -> StringBuffer -> Int -> P (Located Token)
682
683 special :: Token -> Action
684 special tok span _buf len = return (L span tok)
685
686 token, layout_token :: Token -> Action
687 token t span buf len = return (L span t)
688 layout_token t span buf len = pushLexState layout >> return (L span t)
689
690 idtoken :: (StringBuffer -> Int -> Token) -> Action
691 idtoken f span buf len = return (L span $! (f buf len))
692
693 skip_one_varid :: (FastString -> Token) -> Action
694 skip_one_varid f span buf len 
695   = return (L span $! f (lexemeToFastString (stepOn buf) (len-1)))
696
697 strtoken :: (String -> Token) -> Action
698 strtoken f span buf len = 
699   return (L span $! (f $! lexemeToString buf len))
700
701 init_strtoken :: Int -> (String -> Token) -> Action
702 -- like strtoken, but drops the last N character(s)
703 init_strtoken drop f span buf len = 
704   return (L span $! (f $! lexemeToString buf (len-drop)))
705
706 begin :: Int -> Action
707 begin code _span _str _len = do pushLexState code; lexToken
708
709 pop :: Action
710 pop _span _buf _len = do popLexState; lexToken
711
712 pop_and :: Action -> Action
713 pop_and act span buf len = do popLexState; act span buf len
714
715 {-# INLINE nextCharIs #-}
716 nextCharIs buf p = not (atEnd buf) && p (currentChar buf)
717
718 notFollowedBy char _ _ _ (AI _ _ buf) 
719   = nextCharIs buf (/=char)
720
721 notFollowedBySymbol _ _ _ (AI _ _ buf)
722   = nextCharIs buf (`notElem` "!#$%&*+./<=>?@\\^|-~")
723
724 -- We must reject doc comments as being ordinary comments everywhere.
725 -- In some cases the doc comment will be selected as the lexeme due to
726 -- maximal munch, but not always, because the nested comment rule is
727 -- valid in all states, but the doc-comment rules are only valid in
728 -- the non-layout states.
729 isNormalComment bits _ _ (AI _ _ buf)
730   | haddockEnabled bits = notFollowedByDocOrPragma
731   | otherwise           = nextCharIs buf (/='#')
732   where
733     notFollowedByDocOrPragma
734        = not $ spaceAndP buf (`nextCharIs` (`elem` "|^*$#"))
735
736 spaceAndP buf p = p buf || nextCharIs buf (==' ') && p (snd (nextChar buf))
737
738 haddockDisabledAnd p bits _ _ (AI _ _ buf)
739   = if haddockEnabled bits then False else (p buf)
740
741 atEOL _ _ _ (AI _ _ buf) = atEnd buf || currentChar buf == '\n'
742
743 ifExtension pred bits _ _ _ = pred bits
744
745 multiline_doc_comment :: Action
746 multiline_doc_comment span buf _len = withLexedDocType (worker "")
747   where
748     worker commentAcc input docType oneLine = case alexGetChar input of
749       Just ('\n', input') 
750         | oneLine -> docCommentEnd input commentAcc docType buf span
751         | otherwise -> case checkIfCommentLine input' of
752           Just input -> worker ('\n':commentAcc) input docType False
753           Nothing -> docCommentEnd input commentAcc docType buf span
754       Just (c, input) -> worker (c:commentAcc) input docType oneLine
755       Nothing -> docCommentEnd input commentAcc docType buf span
756       
757     checkIfCommentLine input = check (dropNonNewlineSpace input)
758       where
759         check input = case alexGetChar input of
760           Just ('-', input) -> case alexGetChar input of
761             Just ('-', input) -> case alexGetChar input of
762               Just (c, _) | c /= '-' -> Just input
763               _ -> Nothing
764             _ -> Nothing
765           _ -> Nothing
766
767         dropNonNewlineSpace input = case alexGetChar input of
768           Just (c, input') 
769             | isSpace c && c /= '\n' -> dropNonNewlineSpace input'
770             | otherwise -> input
771           Nothing -> input
772
773 {-
774   nested comments require traversing by hand, they can't be parsed
775   using regular expressions.
776 -}
777 nested_comment :: P (Located Token) -> Action
778 nested_comment cont span _str _len = do
779   input <- getInput
780   go 1 input
781   where
782     go 0 input = do setInput input; cont
783     go n input = case alexGetChar input of
784       Nothing -> errBrace input span
785       Just ('-',input) -> case alexGetChar input of
786         Nothing  -> errBrace input span
787         Just ('\125',input) -> go (n-1) input
788         Just (c,_)          -> go n input
789       Just ('\123',input) -> case alexGetChar input of
790         Nothing  -> errBrace input span
791         Just ('-',input) -> go (n+1) input
792         Just (c,_)       -> go n input
793       Just (c,input) -> go n input
794
795 nested_doc_comment :: Action
796 nested_doc_comment span buf _len = withLexedDocType (go "")
797   where
798     go commentAcc input docType _ = case alexGetChar input of
799       Nothing -> errBrace input span
800       Just ('-',input) -> case alexGetChar input of
801         Nothing -> errBrace input span
802         Just ('\125',input@(AI end _ buf2)) ->
803           docCommentEnd input commentAcc docType buf span
804         Just (c,_) -> go ('-':commentAcc) input docType False
805       Just ('\123', input) -> case alexGetChar input of
806         Nothing  -> errBrace input span
807         Just ('-',input) -> do
808           setInput input
809           let cont = do input <- getInput; go commentAcc input docType False
810           nested_comment cont span buf _len
811         Just (c,_) -> go ('\123':commentAcc) input docType False
812       Just (c,input) -> go (c:commentAcc) input docType False
813
814 withLexedDocType lexDocComment = do
815   input@(AI _ _ buf) <- getInput
816   case prevChar buf ' ' of
817     '|' -> lexDocComment input ITdocCommentNext False
818     '^' -> lexDocComment input ITdocCommentPrev False
819     '$' -> lexDocComment input ITdocCommentNamed False
820     '*' -> lexDocSection 1 input 
821  where 
822     lexDocSection n input = case alexGetChar input of 
823       Just ('*', input) -> lexDocSection (n+1) input
824       Just (c, _) -> lexDocComment input (ITdocSection n) True
825       Nothing -> do setInput input; lexToken -- eof reached, lex it normally
826
827 -- docCommentEnd
828 -------------------------------------------------------------------------------
829 -- This function is quite tricky. We can't just return a new token, we also
830 -- need to update the state of the parser. Why? Because the token is longer
831 -- than what was lexed by Alex, and the lexToken function doesn't know this, so 
832 -- it writes the wrong token length to the parser state. This function is
833 -- called afterwards, so it can just update the state. 
834
835 -- This is complicated by the fact that Haddock tokens can span multiple lines, 
836 -- which is something that the original lexer didn't account for. 
837 -- I have added last_line_len in the parser state which represents the length 
838 -- of the part of the token that is on the last line. It is now used for layout 
839 -- calculation in pushCurrentContext instead of last_len. last_len is, like it 
840 -- was before, the full length of the token, and it is now only used for error
841 -- messages. /Waern 
842
843 docCommentEnd :: AlexInput -> String -> (String -> Token) -> StringBuffer ->
844                  SrcSpan -> P (Located Token) 
845 docCommentEnd input commentAcc docType buf span = do
846   setInput input
847   let (AI loc last_offs nextBuf) = input
848       comment = reverse commentAcc
849       span' = mkSrcSpan (srcSpanStart span) loc
850       last_len = byteDiff buf nextBuf
851       
852       last_line_len = if (last_offs - last_len < 0) 
853         then last_offs
854         else last_len  
855   
856   span `seq` setLastToken span' last_len last_line_len
857   return (L span' (docType comment))
858  
859 errBrace (AI end _ _) span = failLocMsgP (srcSpanStart span) end "unterminated `{-'"
860  
861 open_brace, close_brace :: Action
862 open_brace span _str _len = do 
863   ctx <- getContext
864   setContext (NoLayout:ctx)
865   return (L span ITocurly)
866 close_brace span _str _len = do 
867   popContext
868   return (L span ITccurly)
869
870 -- We have to be careful not to count M.<varid> as a qualified name
871 -- when <varid> is a keyword.  We hack around this by catching 
872 -- the offending tokens afterward, and re-lexing in a different state.
873 check_qvarid span buf len = do
874   case lookupUFM reservedWordsFM var of
875         Just (keyword,exts)
876           | not (isSpecial keyword) ->
877           if exts == 0 
878              then try_again
879              else do
880                 b <- extension (\i -> exts .&. i /= 0)
881                 if b then try_again
882                      else return token
883         _other -> return token
884   where
885         (mod,var) = splitQualName buf len
886         token     = L span (ITqvarid (mod,var))
887
888         try_again = do
889                 (AI _ offs _) <- getInput       
890                 setInput (AI (srcSpanStart span) (offs-len) buf)
891                 pushLexState bad_qvarid
892                 lexToken
893
894 qvarid buf len = ITqvarid $! splitQualName buf len
895 qconid buf len = ITqconid $! splitQualName buf len
896
897 splitQualName :: StringBuffer -> Int -> (FastString,FastString)
898 -- takes a StringBuffer and a length, and returns the module name
899 -- and identifier parts of a qualified name.  Splits at the *last* dot,
900 -- because of hierarchical module names.
901 splitQualName orig_buf len = split orig_buf orig_buf
902   where
903     split buf dot_buf
904         | orig_buf `byteDiff` buf >= len  = done dot_buf
905         | c == '.'                        = found_dot buf'
906         | otherwise                       = split buf' dot_buf
907       where
908        (c,buf') = nextChar buf
909   
910     -- careful, we might get names like M....
911     -- so, if the character after the dot is not upper-case, this is
912     -- the end of the qualifier part.
913     found_dot buf -- buf points after the '.'
914         | isUpper c    = split buf' buf
915         | otherwise    = done buf
916       where
917        (c,buf') = nextChar buf
918
919     done dot_buf =
920         (lexemeToFastString orig_buf (qual_size - 1),
921          lexemeToFastString dot_buf (len - qual_size))
922       where
923         qual_size = orig_buf `byteDiff` dot_buf
924
925 varid span buf len = 
926   case lookupUFM reservedWordsFM fs of
927         Just (keyword,0)    -> do
928                 maybe_layout keyword
929                 return (L span keyword)
930         Just (keyword,exts) -> do
931                 b <- extension (\i -> exts .&. i /= 0)
932                 if b then do maybe_layout keyword
933                              return (L span keyword)
934                      else return (L span (ITvarid fs))
935         _other -> return (L span (ITvarid fs))
936   where
937         fs = lexemeToFastString buf len
938
939 conid buf len = ITconid fs
940   where fs = lexemeToFastString buf len
941
942 qvarsym buf len = ITqvarsym $! splitQualName buf len
943 qconsym buf len = ITqconsym $! splitQualName buf len
944
945 varsym = sym ITvarsym
946 consym = sym ITconsym
947
948 sym con span buf len = 
949   case lookupUFM reservedSymsFM fs of
950         Just (keyword,exts) -> do
951                 b <- extension exts
952                 if b then return (L span keyword)
953                      else return (L span $! con fs)
954         _other -> return (L span $! con fs)
955   where
956         fs = lexemeToFastString buf len
957
958 -- Variations on the integral numeric literal.
959 tok_integral :: (Integer -> Token)
960      -> (Integer -> Integer)
961  --    -> (StringBuffer -> StringBuffer) -> (Int -> Int)
962      -> Int -> Int
963      -> (Integer, (Char->Int)) -> Action
964 tok_integral itint transint transbuf translen (radix,char_to_int) span buf len =
965   return $ L span $ itint $! transint $ parseUnsignedInteger
966      (offsetBytes transbuf buf) (subtract translen len) radix char_to_int
967
968 -- some conveniences for use with tok_integral
969 tok_num = tok_integral ITinteger
970 tok_primint = tok_integral ITprimint
971 positive = id
972 negative = negate
973 decimal = (10,octDecDigit)
974 octal = (8,octDecDigit)
975 hexadecimal = (16,hexDigit)
976
977 -- readRational can understand negative rationals, exponents, everything.
978 tok_float        str = ITrational   $! readRational str
979 tok_primfloat    str = ITprimfloat  $! readRational str
980 tok_primdouble   str = ITprimdouble $! readRational str
981
982 -- -----------------------------------------------------------------------------
983 -- Layout processing
984
985 -- we're at the first token on a line, insert layout tokens if necessary
986 do_bol :: Action
987 do_bol span _str _len = do
988         pos <- getOffside
989         case pos of
990             LT -> do
991                 --trace "layout: inserting '}'" $ do
992                 popContext
993                 -- do NOT pop the lex state, we might have a ';' to insert
994                 return (L span ITvccurly)
995             EQ -> do
996                 --trace "layout: inserting ';'" $ do
997                 popLexState
998                 return (L span ITsemi)
999             GT -> do
1000                 popLexState
1001                 lexToken
1002
1003 -- certain keywords put us in the "layout" state, where we might
1004 -- add an opening curly brace.
1005 maybe_layout ITdo       = pushLexState layout_do
1006 maybe_layout ITmdo      = pushLexState layout_do
1007 maybe_layout ITof       = pushLexState layout
1008 maybe_layout ITlet      = pushLexState layout
1009 maybe_layout ITwhere    = pushLexState layout
1010 maybe_layout ITrec      = pushLexState layout
1011 maybe_layout _          = return ()
1012
1013 -- Pushing a new implicit layout context.  If the indentation of the
1014 -- next token is not greater than the previous layout context, then
1015 -- Haskell 98 says that the new layout context should be empty; that is
1016 -- the lexer must generate {}.
1017 --
1018 -- We are slightly more lenient than this: when the new context is started
1019 -- by a 'do', then we allow the new context to be at the same indentation as
1020 -- the previous context.  This is what the 'strict' argument is for.
1021 --
1022 new_layout_context strict span _buf _len = do
1023     popLexState
1024     (AI _ offset _) <- getInput
1025     ctx <- getContext
1026     case ctx of
1027         Layout prev_off : _  | 
1028            (strict     && prev_off >= offset  ||
1029             not strict && prev_off > offset) -> do
1030                 -- token is indented to the left of the previous context.
1031                 -- we must generate a {} sequence now.
1032                 pushLexState layout_left
1033                 return (L span ITvocurly)
1034         other -> do
1035                 setContext (Layout offset : ctx)
1036                 return (L span ITvocurly)
1037
1038 do_layout_left span _buf _len = do
1039     popLexState
1040     pushLexState bol  -- we must be at the start of a line
1041     return (L span ITvccurly)
1042
1043 -- -----------------------------------------------------------------------------
1044 -- LINE pragmas
1045
1046 setLine :: Int -> Action
1047 setLine code span buf len = do
1048   let line = parseUnsignedInteger buf len 10 octDecDigit
1049   setSrcLoc (mkSrcLoc (srcSpanFile span) (fromIntegral line - 1) 0)
1050         -- subtract one: the line number refers to the *following* line
1051   popLexState
1052   pushLexState code
1053   lexToken
1054
1055 setFile :: Int -> Action
1056 setFile code span buf len = do
1057   let file = lexemeToFastString (stepOn buf) (len-2)
1058   setSrcLoc (mkSrcLoc file (srcSpanEndLine span) (srcSpanEndCol span))
1059   popLexState
1060   pushLexState code
1061   lexToken
1062
1063
1064 -- -----------------------------------------------------------------------------
1065 -- Options, includes and language pragmas.
1066
1067 lex_string_prag :: (String -> Token) -> Action
1068 lex_string_prag mkTok span buf len
1069     = do input <- getInput
1070          start <- getSrcLoc
1071          tok <- go [] input
1072          end <- getSrcLoc
1073          return (L (mkSrcSpan start end) tok)
1074     where go acc input
1075               = if isString input "#-}"
1076                    then do setInput input
1077                            return (mkTok (reverse acc))
1078                    else case alexGetChar input of
1079                           Just (c,i) -> go (c:acc) i
1080                           Nothing -> err input
1081           isString i [] = True
1082           isString i (x:xs)
1083               = case alexGetChar i of
1084                   Just (c,i') | c == x    -> isString i' xs
1085                   _other -> False
1086           err (AI end _ _) = failLocMsgP (srcSpanStart span) end "unterminated options pragma"
1087
1088
1089 -- -----------------------------------------------------------------------------
1090 -- Strings & Chars
1091
1092 -- This stuff is horrible.  I hates it.
1093
1094 lex_string_tok :: Action
1095 lex_string_tok span buf len = do
1096   tok <- lex_string ""
1097   end <- getSrcLoc 
1098   return (L (mkSrcSpan (srcSpanStart span) end) tok)
1099
1100 lex_string :: String -> P Token
1101 lex_string s = do
1102   i <- getInput
1103   case alexGetChar' i of
1104     Nothing -> lit_error
1105
1106     Just ('"',i)  -> do
1107         setInput i
1108         glaexts <- extension glaExtsEnabled
1109         if glaexts
1110           then do
1111             i <- getInput
1112             case alexGetChar' i of
1113               Just ('#',i) -> do
1114                    setInput i
1115                    if any (> '\xFF') s
1116                     then failMsgP "primitive string literal must contain only characters <= \'\\xFF\'"
1117                     else let s' = mkZFastString (reverse s) in
1118                          return (ITprimstring s')
1119                         -- mkZFastString is a hack to avoid encoding the
1120                         -- string in UTF-8.  We just want the exact bytes.
1121               _other ->
1122                 return (ITstring (mkFastString (reverse s)))
1123           else
1124                 return (ITstring (mkFastString (reverse s)))
1125
1126     Just ('\\',i)
1127         | Just ('&',i) <- next -> do 
1128                 setInput i; lex_string s
1129         | Just (c,i) <- next, is_space c -> do 
1130                 setInput i; lex_stringgap s
1131         where next = alexGetChar' i
1132
1133     Just (c, i) -> do
1134         c' <- lex_char c i
1135         lex_string (c':s)
1136
1137 lex_stringgap s = do
1138   c <- getCharOrFail
1139   case c of
1140     '\\' -> lex_string s
1141     c | is_space c -> lex_stringgap s
1142     _other -> lit_error
1143
1144
1145 lex_char_tok :: Action
1146 -- Here we are basically parsing character literals, such as 'x' or '\n'
1147 -- but, when Template Haskell is on, we additionally spot
1148 -- 'x and ''T, returning ITvarQuote and ITtyQuote respectively, 
1149 -- but WIHTOUT CONSUMING the x or T part  (the parser does that).
1150 -- So we have to do two characters of lookahead: when we see 'x we need to
1151 -- see if there's a trailing quote
1152 lex_char_tok span buf len = do  -- We've seen '
1153    i1 <- getInput       -- Look ahead to first character
1154    let loc = srcSpanStart span
1155    case alexGetChar' i1 of
1156         Nothing -> lit_error 
1157
1158         Just ('\'', i2@(AI end2 _ _)) -> do     -- We've seen ''
1159                   th_exts <- extension thEnabled
1160                   if th_exts then do
1161                         setInput i2
1162                         return (L (mkSrcSpan loc end2)  ITtyQuote)
1163                    else lit_error
1164
1165         Just ('\\', i2@(AI end2 _ _)) -> do     -- We've seen 'backslash 
1166                   setInput i2
1167                   lit_ch <- lex_escape
1168                   mc <- getCharOrFail   -- Trailing quote
1169                   if mc == '\'' then finish_char_tok loc lit_ch
1170                                 else do setInput i2; lit_error 
1171
1172         Just (c, i2@(AI end2 _ _)) 
1173                 | not (isAny c) -> lit_error
1174                 | otherwise ->
1175
1176                 -- We've seen 'x, where x is a valid character
1177                 --  (i.e. not newline etc) but not a quote or backslash
1178            case alexGetChar' i2 of      -- Look ahead one more character
1179                 Nothing -> lit_error
1180                 Just ('\'', i3) -> do   -- We've seen 'x'
1181                         setInput i3 
1182                         finish_char_tok loc c
1183                 _other -> do            -- We've seen 'x not followed by quote
1184                                         -- If TH is on, just parse the quote only
1185                         th_exts <- extension thEnabled  
1186                         let (AI end _ _) = i1
1187                         if th_exts then return (L (mkSrcSpan loc end) ITvarQuote)
1188                                    else do setInput i2; lit_error
1189
1190 finish_char_tok :: SrcLoc -> Char -> P (Located Token)
1191 finish_char_tok loc ch  -- We've already seen the closing quote
1192                         -- Just need to check for trailing #
1193   = do  glaexts <- extension glaExtsEnabled
1194         i@(AI end _ _) <- getInput
1195         if glaexts then do
1196                 case alexGetChar' i of
1197                         Just ('#',i@(AI end _ _)) -> do
1198                                 setInput i
1199                                 return (L (mkSrcSpan loc end) (ITprimchar ch))
1200                         _other ->
1201                                 return (L (mkSrcSpan loc end) (ITchar ch))
1202                 else do
1203                    return (L (mkSrcSpan loc end) (ITchar ch))
1204
1205 lex_char :: Char -> AlexInput -> P Char
1206 lex_char c inp = do
1207   case c of
1208       '\\' -> do setInput inp; lex_escape
1209       c | isAny c -> do setInput inp; return c
1210       _other -> lit_error
1211
1212 isAny c | c > '\xff' = isPrint c
1213         | otherwise  = is_any c
1214
1215 lex_escape :: P Char
1216 lex_escape = do
1217   c <- getCharOrFail
1218   case c of
1219         'a'   -> return '\a'
1220         'b'   -> return '\b'
1221         'f'   -> return '\f'
1222         'n'   -> return '\n'
1223         'r'   -> return '\r'
1224         't'   -> return '\t'
1225         'v'   -> return '\v'
1226         '\\'  -> return '\\'
1227         '"'   -> return '\"'
1228         '\''  -> return '\''
1229         '^'   -> do c <- getCharOrFail
1230                     if c >= '@' && c <= '_'
1231                         then return (chr (ord c - ord '@'))
1232                         else lit_error
1233
1234         'x'   -> readNum is_hexdigit 16 hexDigit
1235         'o'   -> readNum is_octdigit  8 octDecDigit
1236         x | is_digit x -> readNum2 is_digit 10 octDecDigit (octDecDigit x)
1237
1238         c1 ->  do
1239            i <- getInput
1240            case alexGetChar' i of
1241             Nothing -> lit_error
1242             Just (c2,i2) -> 
1243               case alexGetChar' i2 of
1244                 Nothing -> do setInput i2; lit_error
1245                 Just (c3,i3) -> 
1246                    let str = [c1,c2,c3] in
1247                    case [ (c,rest) | (p,c) <- silly_escape_chars,
1248                                      Just rest <- [maybePrefixMatch p str] ] of
1249                           (escape_char,[]):_ -> do
1250                                 setInput i3
1251                                 return escape_char
1252                           (escape_char,_:_):_ -> do
1253                                 setInput i2
1254                                 return escape_char
1255                           [] -> lit_error
1256
1257 readNum :: (Char -> Bool) -> Int -> (Char -> Int) -> P Char
1258 readNum is_digit base conv = do
1259   i <- getInput
1260   c <- getCharOrFail
1261   if is_digit c 
1262         then readNum2 is_digit base conv (conv c)
1263         else do setInput i; lit_error
1264
1265 readNum2 is_digit base conv i = do
1266   input <- getInput
1267   read i input
1268   where read i input = do
1269           case alexGetChar' input of
1270             Just (c,input') | is_digit c -> do
1271                 read (i*base + conv c) input'
1272             _other -> do
1273                 if i >= 0 && i <= 0x10FFFF
1274                    then do setInput input; return (chr i)
1275                    else lit_error
1276
1277 silly_escape_chars = [
1278         ("NUL", '\NUL'),
1279         ("SOH", '\SOH'),
1280         ("STX", '\STX'),
1281         ("ETX", '\ETX'),
1282         ("EOT", '\EOT'),
1283         ("ENQ", '\ENQ'),
1284         ("ACK", '\ACK'),
1285         ("BEL", '\BEL'),
1286         ("BS", '\BS'),
1287         ("HT", '\HT'),
1288         ("LF", '\LF'),
1289         ("VT", '\VT'),
1290         ("FF", '\FF'),
1291         ("CR", '\CR'),
1292         ("SO", '\SO'),
1293         ("SI", '\SI'),
1294         ("DLE", '\DLE'),
1295         ("DC1", '\DC1'),
1296         ("DC2", '\DC2'),
1297         ("DC3", '\DC3'),
1298         ("DC4", '\DC4'),
1299         ("NAK", '\NAK'),
1300         ("SYN", '\SYN'),
1301         ("ETB", '\ETB'),
1302         ("CAN", '\CAN'),
1303         ("EM", '\EM'),
1304         ("SUB", '\SUB'),
1305         ("ESC", '\ESC'),
1306         ("FS", '\FS'),
1307         ("GS", '\GS'),
1308         ("RS", '\RS'),
1309         ("US", '\US'),
1310         ("SP", '\SP'),
1311         ("DEL", '\DEL')
1312         ]
1313
1314 -- before calling lit_error, ensure that the current input is pointing to
1315 -- the position of the error in the buffer.  This is so that we can report
1316 -- a correct location to the user, but also so we can detect UTF-8 decoding
1317 -- errors if they occur.
1318 lit_error = lexError "lexical error in string/character literal"
1319
1320 getCharOrFail :: P Char
1321 getCharOrFail =  do
1322   i <- getInput
1323   case alexGetChar' i of
1324         Nothing -> lexError "unexpected end-of-file in string/character literal"
1325         Just (c,i)  -> do setInput i; return c
1326
1327 -- -----------------------------------------------------------------------------
1328 -- Warnings
1329
1330 warn :: DynFlag -> SDoc -> Action
1331 warn option warning span _buf _len = do
1332     addWarning option (mkWarnMsg span alwaysQualify warning)
1333     lexToken
1334
1335 -- -----------------------------------------------------------------------------
1336 -- The Parse Monad
1337
1338 data LayoutContext
1339   = NoLayout
1340   | Layout !Int
1341   deriving Show
1342
1343 data ParseResult a
1344   = POk PState a
1345   | PFailed 
1346         SrcSpan         -- The start and end of the text span related to
1347                         -- the error.  Might be used in environments which can 
1348                         -- show this span, e.g. by highlighting it.
1349         Message         -- The error message
1350
1351 data PState = PState { 
1352         buffer     :: StringBuffer,
1353     dflags     :: DynFlags,
1354     messages   :: Messages,
1355         last_loc   :: SrcSpan,  -- pos of previous token
1356         last_offs  :: !Int,     -- offset of the previous token from the
1357                                 -- beginning of  the current line.
1358                                 -- \t is equal to 8 spaces.
1359         last_len   :: !Int,     -- len of previous token
1360   last_line_len :: !Int,
1361         loc        :: SrcLoc,   -- current loc (end of prev token + 1)
1362         extsBitmap :: !Int,     -- bitmap that determines permitted extensions
1363         context    :: [LayoutContext],
1364         lex_state  :: [Int]
1365      }
1366         -- last_loc and last_len are used when generating error messages,
1367         -- and in pushCurrentContext only.  Sigh, if only Happy passed the
1368         -- current token to happyError, we could at least get rid of last_len.
1369         -- Getting rid of last_loc would require finding another way to 
1370         -- implement pushCurrentContext (which is only called from one place).
1371
1372 newtype P a = P { unP :: PState -> ParseResult a }
1373
1374 instance Monad P where
1375   return = returnP
1376   (>>=) = thenP
1377   fail = failP
1378
1379 returnP :: a -> P a
1380 returnP a = P $ \s -> POk s a
1381
1382 thenP :: P a -> (a -> P b) -> P b
1383 (P m) `thenP` k = P $ \ s ->
1384         case m s of
1385                 POk s1 a         -> (unP (k a)) s1
1386                 PFailed span err -> PFailed span err
1387
1388 failP :: String -> P a
1389 failP msg = P $ \s -> PFailed (last_loc s) (text msg)
1390
1391 failMsgP :: String -> P a
1392 failMsgP msg = P $ \s -> PFailed (last_loc s) (text msg)
1393
1394 failLocMsgP :: SrcLoc -> SrcLoc -> String -> P a
1395 failLocMsgP loc1 loc2 str = P $ \s -> PFailed (mkSrcSpan loc1 loc2) (text str)
1396
1397 failSpanMsgP :: SrcSpan -> String -> P a
1398 failSpanMsgP span msg = P $ \s -> PFailed span (text msg)
1399
1400 extension :: (Int -> Bool) -> P Bool
1401 extension p = P $ \s -> POk s (p $! extsBitmap s)
1402
1403 getExts :: P Int
1404 getExts = P $ \s -> POk s (extsBitmap s)
1405
1406 setSrcLoc :: SrcLoc -> P ()
1407 setSrcLoc new_loc = P $ \s -> POk s{loc=new_loc} ()
1408
1409 getSrcLoc :: P SrcLoc
1410 getSrcLoc = P $ \s@(PState{ loc=loc }) -> POk s loc
1411
1412 setLastToken :: SrcSpan -> Int -> Int -> P ()
1413 setLastToken loc len line_len = P $ \s -> POk s { 
1414   last_loc=loc, 
1415   last_len=len,
1416   last_line_len=line_len 
1417 } ()
1418
1419 data AlexInput = AI SrcLoc {-#UNPACK#-}!Int StringBuffer
1420
1421 alexInputPrevChar :: AlexInput -> Char
1422 alexInputPrevChar (AI _ _ buf) = prevChar buf '\n'
1423
1424 alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
1425 alexGetChar (AI loc ofs s) 
1426   | atEnd s   = Nothing
1427   | otherwise = adj_c `seq` loc' `seq` ofs' `seq` s' `seq` 
1428                 --trace (show (ord c)) $
1429                 Just (adj_c, (AI loc' ofs' s'))
1430   where (c,s') = nextChar s
1431         loc'   = advanceSrcLoc loc c
1432         ofs'   = advanceOffs c ofs
1433
1434         non_graphic     = '\x0'
1435         upper           = '\x1'
1436         lower           = '\x2'
1437         digit           = '\x3'
1438         symbol          = '\x4'
1439         space           = '\x5'
1440         other_graphic   = '\x6'
1441
1442         adj_c 
1443           | c <= '\x06' = non_graphic
1444           | c <= '\xff' = c
1445           -- Alex doesn't handle Unicode, so when Unicode
1446           -- character is encoutered we output these values
1447           -- with the actual character value hidden in the state.
1448           | otherwise = 
1449                 case generalCategory c of
1450                   UppercaseLetter       -> upper
1451                   LowercaseLetter       -> lower
1452                   TitlecaseLetter       -> upper
1453                   ModifierLetter        -> other_graphic
1454                   OtherLetter           -> other_graphic
1455                   NonSpacingMark        -> other_graphic
1456                   SpacingCombiningMark  -> other_graphic
1457                   EnclosingMark         -> other_graphic
1458                   DecimalNumber         -> digit
1459                   LetterNumber          -> other_graphic
1460                   OtherNumber           -> other_graphic
1461                   ConnectorPunctuation  -> other_graphic
1462                   DashPunctuation       -> other_graphic
1463                   OpenPunctuation       -> other_graphic
1464                   ClosePunctuation      -> other_graphic
1465                   InitialQuote          -> other_graphic
1466                   FinalQuote            -> other_graphic
1467                   OtherPunctuation      -> other_graphic
1468                   MathSymbol            -> symbol
1469                   CurrencySymbol        -> symbol
1470                   ModifierSymbol        -> symbol
1471                   OtherSymbol           -> symbol
1472                   Space                 -> space
1473                   _other                -> non_graphic
1474
1475 -- This version does not squash unicode characters, it is used when
1476 -- lexing strings.
1477 alexGetChar' :: AlexInput -> Maybe (Char,AlexInput)
1478 alexGetChar' (AI loc ofs s) 
1479   | atEnd s   = Nothing
1480   | otherwise = c `seq` loc' `seq` ofs' `seq` s' `seq` 
1481                 --trace (show (ord c)) $
1482                 Just (c, (AI loc' ofs' s'))
1483   where (c,s') = nextChar s
1484         loc'   = advanceSrcLoc loc c
1485         ofs'   = advanceOffs c ofs
1486
1487 advanceOffs :: Char -> Int -> Int
1488 advanceOffs '\n' offs = 0
1489 advanceOffs '\t' offs = (offs `quot` 8 + 1) * 8
1490 advanceOffs _    offs = offs + 1
1491
1492 getInput :: P AlexInput
1493 getInput = P $ \s@PState{ loc=l, last_offs=o, buffer=b } -> POk s (AI l o b)
1494
1495 setInput :: AlexInput -> P ()
1496 setInput (AI l o b) = P $ \s -> POk s{ loc=l, last_offs=o, buffer=b } ()
1497
1498 pushLexState :: Int -> P ()
1499 pushLexState ls = P $ \s@PState{ lex_state=l } -> POk s{lex_state=ls:l} ()
1500
1501 popLexState :: P Int
1502 popLexState = P $ \s@PState{ lex_state=ls:l } -> POk s{ lex_state=l } ls
1503
1504 getLexState :: P Int
1505 getLexState = P $ \s@PState{ lex_state=ls:l } -> POk s ls
1506
1507 -- for reasons of efficiency, flags indicating language extensions (eg,
1508 -- -fglasgow-exts or -fparr) are represented by a bitmap stored in an unboxed
1509 -- integer
1510
1511 glaExtsBit, ffiBit, parrBit :: Int
1512 glaExtsBit = 0
1513 ffiBit     = 1
1514 parrBit    = 2
1515 arrowsBit  = 4
1516 thBit      = 5
1517 ipBit      = 6
1518 tvBit      = 7  -- Scoped type variables enables 'forall' keyword
1519 bangPatBit = 8  -- Tells the parser to understand bang-patterns
1520                 -- (doesn't affect the lexer)
1521 tyFamBit   = 9  -- indexed type families: 'family' keyword and kind sigs
1522 haddockBit = 10 -- Lex and parse Haddock comments
1523 magicHashBit = 11 -- # in both functions and operators
1524 kindSigsBit = 12 -- Kind signatures on type variables
1525 recursiveDoBit = 13 -- mdo
1526 unicodeSyntaxBit = 14 -- the forall symbol, arrow symbols, etc
1527
1528 glaExtsEnabled, ffiEnabled, parrEnabled :: Int -> Bool
1529 always           _     = True
1530 glaExtsEnabled   flags = testBit flags glaExtsBit
1531 ffiEnabled       flags = testBit flags ffiBit
1532 parrEnabled      flags = testBit flags parrBit
1533 arrowsEnabled    flags = testBit flags arrowsBit
1534 thEnabled        flags = testBit flags thBit
1535 ipEnabled        flags = testBit flags ipBit
1536 tvEnabled        flags = testBit flags tvBit
1537 bangPatEnabled   flags = testBit flags bangPatBit
1538 tyFamEnabled     flags = testBit flags tyFamBit
1539 haddockEnabled   flags = testBit flags haddockBit
1540 magicHashEnabled flags = testBit flags magicHashBit
1541 kindSigsEnabled  flags = testBit flags kindSigsBit
1542 recursiveDoEnabled flags = testBit flags recursiveDoBit
1543 unicodeSyntaxEnabled flags = testBit flags unicodeSyntaxBit
1544
1545 -- PState for parsing options pragmas
1546 --
1547 pragState :: StringBuffer -> SrcLoc -> PState
1548 pragState buf loc  = 
1549   PState {
1550       buffer          = buf,
1551       messages      = emptyMessages,
1552       -- XXX defaultDynFlags is not right, but we don't have a real
1553       -- dflags handy
1554       dflags        = defaultDynFlags,
1555       last_loc      = mkSrcSpan loc loc,
1556       last_offs     = 0,
1557       last_len      = 0,
1558       last_line_len = 0,
1559       loc           = loc,
1560       extsBitmap    = 0,
1561       context       = [],
1562       lex_state     = [bol, option_prags, 0]
1563     }
1564
1565
1566 -- create a parse state
1567 --
1568 mkPState :: StringBuffer -> SrcLoc -> DynFlags -> PState
1569 mkPState buf loc flags  = 
1570   PState {
1571       buffer          = buf,
1572       dflags        = flags,
1573       messages      = emptyMessages,
1574       last_loc      = mkSrcSpan loc loc,
1575       last_offs     = 0,
1576       last_len      = 0,
1577       last_line_len = 0,
1578       loc           = loc,
1579       extsBitmap    = fromIntegral bitmap,
1580       context       = [],
1581       lex_state     = [bol, if glaExtsEnabled bitmap then glaexts else 0]
1582         -- we begin in the layout state if toplev_layout is set
1583     }
1584     where
1585       bitmap =     glaExtsBit `setBitIf` dopt Opt_GlasgowExts  flags
1586                .|. ffiBit       `setBitIf` dopt Opt_FFI          flags
1587                .|. parrBit      `setBitIf` dopt Opt_PArr         flags
1588                .|. arrowsBit    `setBitIf` dopt Opt_Arrows       flags
1589                .|. thBit        `setBitIf` dopt Opt_TH           flags
1590                .|. ipBit        `setBitIf` dopt Opt_ImplicitParams flags
1591                .|. tvBit        `setBitIf` dopt Opt_ScopedTypeVariables flags
1592                .|. bangPatBit   `setBitIf` dopt Opt_BangPatterns flags
1593                .|. tyFamBit     `setBitIf` dopt Opt_TypeFamilies flags
1594                .|. haddockBit   `setBitIf` dopt Opt_Haddock      flags
1595                .|. magicHashBit `setBitIf` dopt Opt_MagicHash    flags
1596                .|. kindSigsBit  `setBitIf` dopt Opt_KindSignatures flags
1597                .|. recursiveDoBit `setBitIf` dopt Opt_RecursiveDo flags
1598                .|. unicodeSyntaxBit `setBitIf` dopt Opt_UnicodeSyntax flags
1599       --
1600       setBitIf :: Int -> Bool -> Int
1601       b `setBitIf` cond | cond      = bit b
1602                         | otherwise = 0
1603
1604 addWarning :: DynFlag -> WarnMsg -> P ()
1605 addWarning option w
1606  = P $ \s@PState{messages=(ws,es), dflags=d} ->
1607        let ws' = if dopt option d then ws `snocBag` w else ws
1608        in POk s{messages=(ws', es)} ()
1609
1610 getMessages :: PState -> Messages
1611 getMessages PState{messages=ms} = ms
1612
1613 getContext :: P [LayoutContext]
1614 getContext = P $ \s@PState{context=ctx} -> POk s ctx
1615
1616 setContext :: [LayoutContext] -> P ()
1617 setContext ctx = P $ \s -> POk s{context=ctx} ()
1618
1619 popContext :: P ()
1620 popContext = P $ \ s@(PState{ buffer = buf, context = ctx, 
1621                            loc = loc, last_len = len, last_loc = last_loc }) ->
1622   case ctx of
1623         (_:tl) -> POk s{ context = tl } ()
1624         []     -> PFailed last_loc (srcParseErr buf len)
1625
1626 -- Push a new layout context at the indentation of the last token read.
1627 -- This is only used at the outer level of a module when the 'module'
1628 -- keyword is missing.
1629 pushCurrentContext :: P ()
1630 pushCurrentContext = P $ \ s@PState{ last_offs=offs, last_line_len=len, context=ctx } -> 
1631     POk s{context = Layout (offs-len) : ctx} ()
1632 --trace ("off: " ++ show offs ++ ", len: " ++ show len) $ POk s{context = Layout (offs-len) : ctx} ()
1633
1634 getOffside :: P Ordering
1635 getOffside = P $ \s@PState{last_offs=offs, context=stk} ->
1636                 let ord = case stk of
1637                         (Layout n:_) -> compare offs n
1638                         _            -> GT
1639                 in POk s ord
1640
1641 -- ---------------------------------------------------------------------------
1642 -- Construct a parse error
1643
1644 srcParseErr
1645   :: StringBuffer       -- current buffer (placed just after the last token)
1646   -> Int                -- length of the previous token
1647   -> Message
1648 srcParseErr buf len
1649   = hcat [ if null token 
1650              then ptext SLIT("parse error (possibly incorrect indentation)")
1651              else hcat [ptext SLIT("parse error on input "),
1652                         char '`', text token, char '\'']
1653     ]
1654   where token = lexemeToString (offsetBytes (-len) buf) len
1655
1656 -- Report a parse failure, giving the span of the previous token as
1657 -- the location of the error.  This is the entry point for errors
1658 -- detected during parsing.
1659 srcParseFail :: P a
1660 srcParseFail = P $ \PState{ buffer = buf, last_len = len,       
1661                             last_loc = last_loc } ->
1662     PFailed last_loc (srcParseErr buf len)
1663
1664 -- A lexical error is reported at a particular position in the source file,
1665 -- not over a token range.
1666 lexError :: String -> P a
1667 lexError str = do
1668   loc <- getSrcLoc
1669   i@(AI end _ buf) <- getInput
1670   reportLexError loc end buf str
1671
1672 -- -----------------------------------------------------------------------------
1673 -- This is the top-level function: called from the parser each time a
1674 -- new token is to be read from the input.
1675
1676 lexer :: (Located Token -> P a) -> P a
1677 lexer cont = do
1678   tok@(L span tok__) <- lexToken
1679 --  trace ("token: " ++ show tok__) $ do
1680   cont tok
1681
1682 lexToken :: P (Located Token)
1683 lexToken = do
1684   inp@(AI loc1 _ buf) <- getInput
1685   sc <- getLexState
1686   exts <- getExts
1687   case alexScanUser exts inp sc of
1688     AlexEOF -> do let span = mkSrcSpan loc1 loc1
1689                   setLastToken span 0 0
1690                   return (L span ITeof)
1691     AlexError (AI loc2 _ buf) -> do 
1692         reportLexError loc1 loc2 buf "lexical error"
1693     AlexSkip inp2 _ -> do
1694         setInput inp2
1695         lexToken
1696     AlexToken inp2@(AI end _ buf2) len t -> do
1697     setInput inp2
1698     let span = mkSrcSpan loc1 end
1699     let bytes = byteDiff buf buf2
1700     span `seq` setLastToken span bytes bytes
1701     t span buf bytes
1702
1703 reportLexError loc1 loc2 buf str
1704   | atEnd buf = failLocMsgP loc1 loc2 (str ++ " at end of input")
1705   | otherwise =
1706   let 
1707         c = fst (nextChar buf)
1708   in
1709   if c == '\0' -- decoding errors are mapped to '\0', see utf8DecodeChar#
1710     then failLocMsgP loc2 loc2 (str ++ " (UTF-8 decoding error)")
1711     else failLocMsgP loc1 loc2 (str ++ " at character " ++ show c)
1712 }