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