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