[project @ 2001-05-22 13:43:14 by simonpj]
[ghc-hetmet.git] / ghc / compiler / parser / Lex.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[Lexical analysis]{Lexical analysis}
5
6 --------------------------------------------------------
7 [Jan 98]
8 There's a known bug in here:
9
10         If an interface file ends prematurely, Lex tries to
11         do headFS of an empty FastString.
12
13 An example that provokes the error is
14
15         f _:_ _forall_ [a] <<<END OF FILE>>>
16 --------------------------------------------------------
17
18 \begin{code}
19
20 module Lex (
21
22         ifaceParseErr, srcParseErr,
23
24         -- Monad for parser
25         Token(..), lexer, ParseResult(..), PState(..),
26         checkVersion, 
27         StringBuffer,
28
29         P, thenP, thenP_, returnP, mapP, failP, failMsgP,
30         getSrcLocP, setSrcLocP, getSrcFile,
31         layoutOn, layoutOff, pushContext, popContext
32     ) where
33
34 #include "HsVersions.h"
35
36 import Char             ( isSpace, toUpper )
37 import List             ( isSuffixOf )
38
39 import IdInfo           ( InlinePragInfo(..) )
40 import PrelNames        ( mkTupNameStr )
41 import CmdLineOpts      ( opt_HiVersion, opt_NoHiCheck )
42 import ForeignCall      ( Safety(..) )
43 import Demand           ( Demand(..) {- instance Read -} )
44 import UniqFM           ( listToUFM, lookupUFM )
45 import BasicTypes       ( NewOrData(..), Boxity(..) )
46 import SrcLoc           ( SrcLoc, incSrcLine, srcLocFile, srcLocLine,
47                           replaceSrcLine, mkSrcLoc )
48
49 import ErrUtils         ( Message )
50 import Outputable
51
52 import FastString
53 import StringBuffer
54 import GlaExts
55 import Ctype
56 import Char             ( chr, ord )
57 import PrelRead         ( readRational__ ) -- Glasgow non-std
58 \end{code}
59
60 %************************************************************************
61 %*                                                                      *
62 \subsection{Data types}
63 %*                                                                      *
64 %************************************************************************
65
66 The token data type, fairly un-interesting except from one
67 constructor, @ITidinfo@, which is used to lazily lex id info (arity,
68 strictness, unfolding etc).
69
70 The Idea/Observation here is that the renamer needs to scan through
71 all of an interface file before it can continue. But only a fraction
72 of the information contained in the file turns out to be useful, so
73 delaying as much as possible of the scanning and parsing of an
74 interface file Makes Sense (Heap profiles of the compiler 
75 show a reduction in heap usage by at least a factor of two,
76 post-renamer). 
77
78 Hence, the interface file lexer spots when value declarations are
79 being scanned and return the @ITidinfo@ and @ITtype@ constructors
80 for the type and any other id info for that binding (unfolding, strictness
81 etc). These constructors are applied to the result of lexing these sub-chunks.
82
83 The lexing of the type and id info is all done lazily, of course, so
84 the scanning (and subsequent parsing) will be done *only* on the ids the
85 renamer finds out that it is interested in. The rest will just be junked.
86 Laziness, you know it makes sense :-)
87
88 \begin{code}
89 data Token
90   = ITas                        -- Haskell keywords
91   | ITcase
92   | ITclass
93   | ITdata
94   | ITdefault
95   | ITderiving
96   | ITdo
97   | ITelse
98   | IThiding
99   | ITif
100   | ITimport
101   | ITin
102   | ITinfix
103   | ITinfixl
104   | ITinfixr
105   | ITinstance
106   | ITlet
107   | ITmodule
108   | ITnewtype
109   | ITof
110   | ITqualified
111   | ITthen
112   | ITtype
113   | ITwhere
114   | ITscc                       -- ToDo: remove (we use {-# SCC "..." #-} now)
115
116   | ITforall                    -- GHC extension keywords
117   | ITforeign
118   | ITexport
119   | ITlabel
120   | ITdynamic
121   | ITunsafe
122   | ITwith
123   | ITstdcallconv
124   | ITccallconv
125
126   | ITinterface                 -- interface keywords
127   | IT__export
128   | ITdepends
129   | IT__forall
130   | ITletrec 
131   | ITcoerce
132   | ITinlineMe
133   | ITinlineCall
134   | ITccall (Bool,Bool,Safety)  -- (is_dyn, is_casm, may_gc)
135   | ITdefaultbranch
136   | ITbottom
137   | ITinteger_lit 
138   | ITfloat_lit
139   | ITword_lit
140   | ITword64_lit
141   | ITint64_lit
142   | ITrational_lit
143   | ITaddr_lit
144   | ITlabel_lit
145   | ITlit_lit
146   | ITstring_lit
147   | ITtypeapp
148   | ITusage
149   | ITfuall
150   | ITarity 
151   | ITspecialise
152   | ITnocaf
153   | ITunfold InlinePragInfo
154   | ITstrict ([Demand], Bool)
155   | ITrules
156   | ITcprinfo
157   | ITdeprecated
158   | IT__scc
159   | ITsccAllCafs
160
161   | ITspecialise_prag           -- Pragmas
162   | ITsource_prag
163   | ITinline_prag
164   | ITnoinline_prag
165   | ITrules_prag
166   | ITdeprecated_prag
167   | ITline_prag
168   | ITscc_prag
169   | ITclose_prag
170
171   | ITdotdot                    -- reserved symbols
172   | ITdcolon
173   | ITequal
174   | ITlam
175   | ITvbar
176   | ITlarrow
177   | ITrarrow
178   | ITat
179   | ITtilde
180   | ITdarrow
181   | ITminus
182   | ITbang
183   | ITdot
184
185   | ITbiglam                    -- GHC-extension symbols
186
187   | ITocurly                    -- special symbols
188   | ITccurly
189   | ITocurlybar                 -- {|, for type applications
190   | ITccurlybar                 -- |}, for type applications
191   | ITvccurly
192   | ITobrack
193   | ITcbrack
194   | IToparen
195   | ITcparen
196   | IToubxparen
197   | ITcubxparen
198   | ITsemi
199   | ITcomma
200   | ITunderscore
201   | ITbackquote
202
203   | ITvarid   FAST_STRING       -- identifiers
204   | ITconid   FAST_STRING
205   | ITvarsym  FAST_STRING
206   | ITconsym  FAST_STRING
207   | ITqvarid  (FAST_STRING,FAST_STRING)
208   | ITqconid  (FAST_STRING,FAST_STRING)
209   | ITqvarsym (FAST_STRING,FAST_STRING)
210   | ITqconsym (FAST_STRING,FAST_STRING)
211
212   | ITipvarid FAST_STRING       -- GHC extension: implicit param: ?x
213
214   | ITpragma StringBuffer
215
216   | ITchar       Int
217   | ITstring     FAST_STRING
218   | ITinteger    Integer
219   | ITrational   Rational
220
221   | ITprimchar   Int
222   | ITprimstring FAST_STRING
223   | ITprimint    Integer
224   | ITprimfloat  Rational
225   | ITprimdouble Rational
226   | ITlitlit     FAST_STRING
227
228   | ITunknown String            -- Used when the lexer can't make sense of it
229   | ITeof                       -- end of file token
230   deriving Show -- debugging
231 \end{code}
232
233 -----------------------------------------------------------------------------
234 Keyword Lists
235
236 \begin{code}
237 pragmaKeywordsFM = listToUFM $
238       map (\ (x,y) -> (_PK_ x,y))
239        [( "SPECIALISE", ITspecialise_prag ),
240         ( "SPECIALIZE", ITspecialise_prag ),
241         ( "SOURCE",     ITsource_prag ),
242         ( "INLINE",     ITinline_prag ),
243         ( "NOINLINE",   ITnoinline_prag ),
244         ( "NOTINLINE",  ITnoinline_prag ),
245         ( "LINE",       ITline_prag ),
246         ( "RULES",      ITrules_prag ),
247         ( "RULEZ",      ITrules_prag ), -- american spelling :-)
248         ( "SCC",        ITscc_prag ),
249         ( "DEPRECATED", ITdeprecated_prag )
250         ]
251
252 haskellKeywordsFM = listToUFM $
253       map (\ (x,y) -> (_PK_ x,y))
254        [( "_",          ITunderscore ),
255         ( "as",         ITas ),
256         ( "case",       ITcase ),     
257         ( "class",      ITclass ),    
258         ( "data",       ITdata ),     
259         ( "default",    ITdefault ),  
260         ( "deriving",   ITderiving ), 
261         ( "do",         ITdo ),       
262         ( "else",       ITelse ),     
263         ( "hiding",     IThiding ),
264         ( "if",         ITif ),       
265         ( "import",     ITimport ),   
266         ( "in",         ITin ),       
267         ( "infix",      ITinfix ),    
268         ( "infixl",     ITinfixl ),   
269         ( "infixr",     ITinfixr ),   
270         ( "instance",   ITinstance ), 
271         ( "let",        ITlet ),      
272         ( "module",     ITmodule ),   
273         ( "newtype",    ITnewtype ),  
274         ( "of",         ITof ),       
275         ( "qualified",  ITqualified ),
276         ( "then",       ITthen ),     
277         ( "type",       ITtype ),     
278         ( "where",      ITwhere ),
279         ( "_scc_",      ITscc )         -- ToDo: remove
280      ]
281
282 isSpecial :: Token -> Bool
283 -- If we see M.x, where x is a keyword, but
284 -- is special, we treat is as just plain M.x, 
285 -- not as a keyword.
286 isSpecial ITas          = True
287 isSpecial IThiding      = True
288 isSpecial ITqualified   = True
289 isSpecial ITforall      = True
290 isSpecial ITexport      = True
291 isSpecial ITlabel       = True
292 isSpecial ITdynamic     = True
293 isSpecial ITunsafe      = True
294 isSpecial ITwith        = True
295 isSpecial ITccallconv   = True
296 isSpecial ITstdcallconv = True
297 isSpecial _             = False
298
299 -- IMPORTANT: Keep this in synch with ParseIface.y's var_fs production! (SUP)
300 ghcExtensionKeywordsFM = listToUFM $
301         map (\ (x,y) -> (_PK_ x,y))
302      [  ( "forall",     ITforall ),
303         ( "foreign",    ITforeign ),
304         ( "export",     ITexport ),
305         ( "label",      ITlabel ),
306         ( "dynamic",    ITdynamic ),
307         ( "unsafe",     ITunsafe ),
308         ( "with",       ITwith ),
309         ( "stdcall",    ITstdcallconv),
310         ( "ccall",      ITccallconv),
311         ("_ccall_",     ITccall (False, False, PlayRisky)),
312         ("_ccall_GC_",  ITccall (False, False, PlaySafe)),
313         ("_casm_",      ITccall (False, True,  PlayRisky)),
314         ("_casm_GC_",   ITccall (False, True,  PlaySafe)),
315
316         -- interface keywords
317         ("__interface",         ITinterface),
318         ("__export",            IT__export),
319         ("__depends",           ITdepends),
320         ("__forall",            IT__forall),
321         ("__letrec",            ITletrec),
322         ("__coerce",            ITcoerce),
323         ("__inline_me",         ITinlineMe),
324         ("__inline_call",       ITinlineCall),
325         ("__depends",           ITdepends),
326         ("__DEFAULT",           ITdefaultbranch),
327         ("__bot",               ITbottom),
328         ("__integer",           ITinteger_lit),
329         ("__float",             ITfloat_lit),
330         ("__int64",             ITint64_lit),
331         ("__word",              ITword_lit),
332         ("__word64",            ITword64_lit),
333         ("__rational",          ITrational_lit),
334         ("__addr",              ITaddr_lit),
335         ("__label",             ITlabel_lit),
336         ("__litlit",            ITlit_lit),
337         ("__string",            ITstring_lit),
338         ("__a",                 ITtypeapp),
339         ("__u",                 ITusage),
340         ("__fuall",             ITfuall),
341         ("__A",                 ITarity),
342         ("__P",                 ITspecialise),
343         ("__C",                 ITnocaf),
344         ("__R",                 ITrules),
345         ("__D",                 ITdeprecated),
346         ("__U",                 ITunfold NoInlinePragInfo),
347         
348         ("__ccall",             ITccall (False, False, PlayRisky)),
349         ("__ccall_GC",          ITccall (False, False, PlaySafe)),
350         ("__dyn_ccall",         ITccall (True,  False, PlayRisky)),
351         ("__dyn_ccall_GC",      ITccall (True,  False, PlaySafe)),
352         ("__casm",              ITccall (False, True,  PlayRisky)),
353         ("__dyn_casm",          ITccall (True,  True,  PlayRisky)),
354         ("__casm_GC",           ITccall (False, True,  PlaySafe)),
355         ("__dyn_casm_GC",       ITccall (True,  True,  PlaySafe)),
356
357         ("/\\",                 ITbiglam)
358      ]
359
360
361 haskellKeySymsFM = listToUFM $
362         map (\ (x,y) -> (_PK_ x,y))
363       [ ("..",          ITdotdot)
364        ,("::",          ITdcolon)
365        ,("=",           ITequal)
366        ,("\\",          ITlam)
367        ,("|",           ITvbar)
368        ,("<-",          ITlarrow)
369        ,("->",          ITrarrow)
370        ,("@",           ITat)
371        ,("~",           ITtilde)
372        ,("=>",          ITdarrow)
373        ,("-",           ITminus)
374        ,("!",           ITbang)
375        ,(".",           ITdot)          -- sadly, for 'forall a . t'
376        ]
377 \end{code}
378
379 -----------------------------------------------------------------------------
380 The lexical analyser
381
382 Lexer state:
383
384         - (glaexts) lexing an interface file or -fglasgow-exts
385         - (bol)   pointer to beginning of line (for column calculations)
386         - (buf)   pointer to beginning of token
387         - (buf)   pointer to current char
388         - (atbol) flag indicating whether we're at the beginning of a line
389
390 \begin{code}
391 lexer :: (Token -> P a) -> P a
392 lexer cont buf s@(PState{
393                     loc = loc,
394                     glasgow_exts = glaexts,
395                     bol = bol,
396                     atbol = atbol,
397                     context = ctx
398                 })
399
400         -- first, start a new lexeme and lose all the whitespace
401   =  _scc_ "Lexer" 
402   tab line bol atbol (stepOverLexeme buf)
403   where
404         line = srcLocLine loc
405
406         tab y bol atbol buf = -- trace ("tab: " ++ show (I# y) ++ " : " ++ show (currentChar buf)) $
407           case currentChar# buf of
408
409             '\NUL'# ->
410                    if bufferExhausted (stepOn buf)
411                         then cont ITeof buf s'
412                         else trace "lexer: misplaced NUL?" $ 
413                              tab y bol atbol (stepOn buf)
414
415             '\n'# -> let buf' = stepOn buf
416                      in tab (y +# 1#) (currentIndex# buf') 1# buf'
417
418                 -- find comments.  This got harder in Haskell 98.
419             '-'# ->  let trundle n = 
420                           let next = lookAhead# buf n in
421                           if next `eqChar#` '-'# then trundle (n +# 1#)
422                           else if is_symbol next || n <# 2#
423                                 then is_a_token
424                                 else tab y bol atbol 
425                                          (stepOnUntilChar# (stepOnBy# buf n) '\n'#)
426                     in trundle 1#
427
428                 -- comments and pragmas.  We deal with LINE pragmas here,
429                 -- and throw out any unrecognised pragmas as comments.  Any
430                 -- pragmas we know about are dealt with later (after any layout
431                 -- processing if necessary).
432             '{'# | lookAhead# buf 1# `eqChar#` '-'# ->
433                 if lookAhead# buf 2# `eqChar#` '#'# then
434                   if lookAhead# buf 3# `eqChar#` '#'# then is_a_token else
435                   case expandWhile# is_space (setCurrentPos# buf 3#) of { buf1->
436                   case expandWhile# is_ident (stepOverLexeme buf1)   of { buf2->
437                   let lexeme = mkFastString -- ToDo: too slow
438                                   (map toUpper (lexemeToString buf2)) in
439                   case lookupUFM pragmaKeywordsFM lexeme of
440                         Just ITline_prag -> 
441                            line_prag skip_to_end buf2 s'
442                         Just other -> is_a_token
443                         Nothing -> skip_to_end (stepOnBy# buf 2#) s'
444                   }}
445
446                 else skip_to_end (stepOnBy# buf 2#) s'
447                 where
448                     skip_to_end = nested_comment (lexer cont)
449
450                 -- special GHC extension: we grok cpp-style #line pragmas
451             '#'# | lexemeIndex buf ==# bol ->   -- the '#' must be in column 0
452                 case expandWhile# is_space (stepOn buf) of { buf1 ->
453                 if is_digit (currentChar# buf1) 
454                         then line_prag next_line buf1 s'
455                         else is_a_token
456                 }
457                 where
458                 next_line buf = lexer cont (stepOnUntilChar# buf '\n'#)
459
460                 -- tabs have been expanded beforehand
461             c | is_space c -> tab y bol atbol (stepOn buf)
462               | otherwise  -> is_a_token
463
464            where s' = s{loc = replaceSrcLine loc y, 
465                         bol = bol,
466                        atbol = atbol}
467
468                  is_a_token | atbol /=# 0# = lexBOL cont buf s'
469                             | otherwise    = lexToken cont glaexts buf s'
470
471 -- {-# LINE .. #-} pragmas.  yeuch.
472 line_prag cont buf s@PState{loc=loc} =
473   case expandWhile# is_space buf                of { buf1 ->
474   case scanNumLit 0 (stepOverLexeme buf1)       of { (line,buf2) ->
475   -- subtract one: the line number refers to the *following* line.
476   let real_line = line - 1 in
477   case fromInteger real_line                    of { i@(I# l) -> 
478         -- ToDo, if no filename then we skip the newline.... d'oh
479   case expandWhile# is_space buf2               of { buf3 ->
480   case currentChar# buf3                        of
481      '\"'#{-"-} -> 
482         case untilEndOfString# (stepOn (stepOverLexeme buf3)) of { buf4 ->
483         let 
484             file = lexemeToFastString buf4 
485             new_buf = stepOn (stepOverLexeme buf4)
486         in
487         if nullFastString file
488                 then cont new_buf s{loc = replaceSrcLine loc l}
489                 else cont new_buf s{loc = mkSrcLoc file i}
490         }
491      _other -> cont (stepOverLexeme buf3) s{loc = replaceSrcLine loc l}
492   }}}}
493
494 nested_comment :: P a -> P a
495 nested_comment cont buf = loop buf
496  where
497    loop buf = 
498      case currentChar# buf of
499         '\NUL'# | bufferExhausted (stepOn buf) -> 
500                 lexError "unterminated `{-'" buf -- -}
501         '-'# | lookAhead# buf 1# `eqChar#` '}'# ->
502                 cont (stepOnBy# buf 2#)
503
504         '{'# | lookAhead# buf 1# `eqChar#` '-'# ->
505               nested_comment (nested_comment cont) (stepOnBy# buf 2#)
506
507         '\n'# -> \ s@PState{loc=loc} ->
508                  let buf' = stepOn buf in
509                  nested_comment cont buf'
510                         s{loc = incSrcLine loc, bol = currentIndex# buf',
511                           atbol = 1#}
512
513         _   -> nested_comment cont (stepOn buf)
514
515 -- When we are lexing the first token of a line, check whether we need to
516 -- insert virtual semicolons or close braces due to layout.
517
518 lexBOL :: (Token -> P a) -> P a
519 lexBOL cont buf s@(PState{
520                     loc = loc,
521                     glasgow_exts = glaexts,
522                     bol = bol,
523                     atbol = atbol,
524                     context = ctx
525                   }) =
526         if need_close_curly then 
527                 --trace ("col = " ++ show (I# col) ++ ", layout: inserting '}'") $
528                 cont ITvccurly buf s{atbol = 1#, context = tail ctx}
529         else if need_semi_colon then
530                 --trace ("col = " ++ show (I# col) ++ ", layout: inserting ';'") $
531                 cont ITsemi buf s{atbol = 0#}
532         else
533                 lexToken cont glaexts buf s{atbol = 0#}
534   where
535         col = currentIndex# buf -# bol
536
537         need_close_curly =
538                 case ctx of
539                         [] -> False
540                         (i:_) -> case i of
541                                     NoLayout -> False
542                                     Layout n -> col <# n
543         need_semi_colon =
544                 case ctx of
545                         [] -> False
546                         (i:_) -> case i of
547                                     NoLayout -> False
548                                     Layout n -> col ==# n
549
550
551 lexToken :: (Token -> P a) -> Int# -> P a
552 lexToken cont glaexts buf =
553  -- trace "lexToken" $
554   case currentChar# buf of
555
556     -- special symbols ----------------------------------------------------
557     '('# | flag glaexts && lookAhead# buf 1# `eqChar#` '#'# 
558                 -> cont IToubxparen (setCurrentPos# buf 2#)
559          | otherwise
560                 -> cont IToparen (incLexeme buf)
561
562     ')'# -> cont ITcparen    (incLexeme buf)
563     '['# -> cont ITobrack    (incLexeme buf)
564     ']'# -> cont ITcbrack    (incLexeme buf)
565     ','# -> cont ITcomma     (incLexeme buf)
566     ';'# -> cont ITsemi      (incLexeme buf)
567     '}'# -> \ s@PState{context = ctx} ->
568             case ctx of 
569                 (_:ctx') -> cont ITccurly (incLexeme buf) s{context=ctx'}
570                 _        -> lexError "too many '}'s" buf s
571     '|'# -> case lookAhead# buf 1# of
572                  '}'#  | flag glaexts -> cont ITccurlybar 
573                                               (setCurrentPos# buf 2#)
574                  _                    -> lex_sym cont (incLexeme buf)
575
576                 
577     '#'# -> case lookAhead# buf 1# of
578                 ')'#  | flag glaexts -> cont ITcubxparen (setCurrentPos# buf 2#)
579                 '-'# -> case lookAhead# buf 2# of
580                            '}'# -> cont ITclose_prag (setCurrentPos# buf 3#)
581                            _    -> lex_sym cont (incLexeme buf)
582                 _    -> lex_sym cont (incLexeme buf)
583
584     '`'# | flag glaexts && lookAhead# buf 1# `eqChar#` '`'#
585                 -> lex_cstring cont (setCurrentPos# buf 2#)
586          | otherwise
587                 -> cont ITbackquote (incLexeme buf)
588
589     '{'# ->     -- look for "{-##" special iface pragma
590             case lookAhead# buf 1# of
591            '|'# | flag glaexts 
592                 -> cont ITocurlybar (setCurrentPos# buf 2#)
593            '-'# -> case lookAhead# buf 2# of
594                     '#'# -> case lookAhead# buf 3# of
595                                 '#'# -> 
596                                    let (lexeme, buf') 
597                                           = doDiscard 0# (stepOnBy# (stepOverLexeme buf) 4#) in
598                                             cont (ITpragma lexeme) buf'
599                                 _ -> lex_prag cont (setCurrentPos# buf 3#)
600                     _    -> cont ITocurly (incLexeme buf) 
601            _ -> (layoutOff `thenP_` cont ITocurly)  (incLexeme buf) 
602
603     -- strings/characters -------------------------------------------------
604     '\"'#{-"-} -> lex_string cont glaexts [] (incLexeme buf)
605     '\''#      -> lex_char (char_end cont) glaexts (incLexeme buf)
606
607     -- strictness and cpr pragmas and __scc treated specially.
608     '_'# | flag glaexts ->
609          case lookAhead# buf 1# of
610            '_'# -> case lookAhead# buf 2# of
611                     'S'# -> 
612                         lex_demand cont (stepOnUntil (not . isSpace) 
613                                         (stepOnBy# buf 3#)) -- past __S
614                     'M'# -> 
615                         cont ITcprinfo (stepOnBy# buf 3#)       -- past __M
616
617                     's'# -> 
618                         case prefixMatch (stepOnBy# buf 3#) "cc" of
619                                Just buf' -> lex_scc cont (stepOverLexeme buf')
620                                Nothing   -> lex_id cont glaexts buf
621                     _ -> lex_id cont glaexts buf
622            _    -> lex_id cont glaexts buf
623
624         -- Hexadecimal and octal constants
625     '0'# | (ch `eqChar#` 'x'# || ch `eqChar#` 'X'#) && is_hexdigit ch2
626                 -> readNum (after_lexnum cont glaexts) buf' is_hexdigit 16 hex
627          | (ch `eqChar#` 'o'# || ch `eqChar#` 'O'#) && is_octdigit ch2
628                 -> readNum (after_lexnum cont glaexts) buf' is_octdigit  8 oct_or_dec
629         where ch   = lookAhead# buf 1#
630               ch2  = lookAhead# buf 2#
631               buf' = setCurrentPos# buf 2#
632
633     '\NUL'# ->
634             if bufferExhausted (stepOn buf) then
635                cont ITeof buf
636             else
637                trace "lexIface: misplaced NUL?" $ 
638                cont (ITunknown "\NUL") (stepOn buf)
639
640     '?'# | flag glaexts && is_lower (lookAhead# buf 1#) ->
641             lex_ip cont (incLexeme buf)
642     c | is_digit  c -> lex_num cont glaexts 0 buf
643       | is_symbol c -> lex_sym cont buf
644       | is_upper  c -> lex_con cont glaexts buf
645       | is_ident  c -> lex_id  cont glaexts buf
646       | otherwise   -> lexError "illegal character" buf
647
648 -- Int# is unlifted, and therefore faster than Bool for flags.
649 {-# INLINE flag #-}
650 flag :: Int# -> Bool
651 flag 0# = False
652 flag _  = True
653
654 -------------------------------------------------------------------------------
655 -- Pragmas
656
657 lex_prag cont buf
658   = case expandWhile# is_space buf of { buf1 ->
659     case expandWhile# is_ident (stepOverLexeme buf1) of { buf2 -> 
660     let lexeme = mkFastString (map toUpper (lexemeToString buf2)) in
661     case lookupUFM pragmaKeywordsFM lexeme of
662         Just kw -> cont kw (mergeLexemes buf buf2)
663         Nothing -> panic "lex_prag"
664   }}
665
666 -------------------------------------------------------------------------------
667 -- Strings & Chars
668
669 lex_string cont glaexts s buf
670   = case currentChar# buf of
671         '"'#{-"-} -> 
672            let buf' = incLexeme buf
673                s' = mkFastStringNarrow (map chr (reverse s)) 
674            in case currentChar# buf' of
675                 '#'# | flag glaexts -> if all (<= 0xFF) s
676                     then cont (ITprimstring s') (incLexeme buf')
677                     else lexError "primitive string literal must contain only characters <= \'\\xFF\'" buf'
678                 _                   -> cont (ITstring s') buf'
679
680         -- ignore \& in a string, deal with string gaps
681         '\\'# | next_ch `eqChar#` '&'# 
682                 -> lex_string cont glaexts s buf'
683               | is_space next_ch
684                 -> lex_stringgap cont glaexts s (incLexeme buf)
685
686             where next_ch = lookAhead# buf 1#
687                   buf' = setCurrentPos# buf 2#
688
689         _ -> lex_char (lex_next_string cont s) glaexts buf
690
691 lex_stringgap cont glaexts s buf
692   = let buf' = incLexeme buf in
693     case currentChar# buf of
694         '\n'# -> \st@PState{loc = loc} -> lex_stringgap cont glaexts s buf' 
695                   st{loc = incSrcLine loc}
696         '\\'# -> lex_string cont glaexts s buf'
697         c | is_space c -> lex_stringgap cont glaexts s buf'
698         other -> charError buf'
699
700 lex_next_string cont s glaexts c buf = lex_string cont glaexts (c:s) buf
701
702 lex_char :: (Int# -> Int -> P a) -> Int# -> P a
703 lex_char cont glaexts buf
704   = case currentChar# buf of
705         '\\'# -> lex_escape (cont glaexts) (incLexeme buf)
706         c | is_any c -> cont glaexts (I# (ord# c)) (incLexeme buf)
707         other -> charError buf
708
709 char_end cont glaexts c buf
710   = case currentChar# buf of
711         '\''# -> let buf' = incLexeme buf in
712                  case currentChar# buf' of
713                         '#'# | flag glaexts 
714                                 -> cont (ITprimchar c) (incLexeme buf')
715                         _       -> cont (ITchar c) buf'
716         _     -> charError buf
717
718 lex_escape cont buf
719   = let buf' = incLexeme buf in
720     case currentChar# buf of
721         'a'#       -> cont (ord '\a') buf'
722         'b'#       -> cont (ord '\b') buf'
723         'f'#       -> cont (ord '\f') buf'
724         'n'#       -> cont (ord '\n') buf'
725         'r'#       -> cont (ord '\r') buf'
726         't'#       -> cont (ord '\t') buf'
727         'v'#       -> cont (ord '\v') buf'
728         '\\'#      -> cont (ord '\\') buf'
729         '"'#       -> cont (ord '\"') buf'
730         '\''#      -> cont (ord '\'') buf'
731         '^'#       -> let c = currentChar# buf' in
732                       if c `geChar#` '@'# && c `leChar#` '_'#
733                         then cont (I# (ord# c -# ord# '@'#)) (incLexeme buf')
734                         else charError buf'
735
736         'x'#      -> readNum (after_charnum cont) buf' is_hexdigit 16 hex
737         'o'#      -> readNum (after_charnum cont) buf' is_octdigit  8 oct_or_dec
738         x | is_digit x 
739                   -> readNum (after_charnum cont) buf is_digit    10 oct_or_dec
740
741         _          -> case [ (c,buf2) | (p,c) <- silly_escape_chars,
742                                        Just buf2 <- [prefixMatch buf p] ] of
743                             (c,buf2):_ -> cont (ord c) buf2
744                             [] -> charError buf'
745
746 after_charnum cont i buf
747   = if i >= 0 && i <= 0x10FFFF
748         then cont (fromInteger i) buf
749         else charError buf
750
751 readNum cont buf is_digit base conv = read buf 0
752   where read buf i 
753           = case currentChar# buf of { c ->
754             if is_digit c
755                 then read (incLexeme buf) (i*base + (toInteger (I# (conv c))))
756                 else cont i buf
757             }
758
759 is_hexdigit c 
760         =  is_digit c 
761         || (c `geChar#` 'a'# && c `leChar#` 'f'#)
762         || (c `geChar#` 'A'# && c `leChar#` 'F'#)
763
764 hex c | is_digit c = ord# c -# ord# '0'#
765       | otherwise  = ord# (to_lower c) -# ord# 'a'# +# 10#
766 oct_or_dec c = ord# c -# ord# '0'#
767
768 is_octdigit c = c `geChar#` '0'# && c `leChar#` '7'#
769
770 to_lower c 
771   | c `geChar#` 'A'# && c `leChar#` 'Z'#  
772         = chr# (ord# c -# (ord# 'A'# -# ord# 'a'#))
773   | otherwise = c
774
775 charError buf = lexError "error in character literal" buf
776
777 silly_escape_chars = [
778         ("NUL", '\NUL'),
779         ("SOH", '\SOH'),
780         ("STX", '\STX'),
781         ("ETX", '\ETX'),
782         ("EOT", '\EOT'),
783         ("ENQ", '\ENQ'),
784         ("ACK", '\ACK'),
785         ("BEL", '\BEL'),
786         ("BS", '\BS'),
787         ("HT", '\HT'),
788         ("LF", '\LF'),
789         ("VT", '\VT'),
790         ("FF", '\FF'),
791         ("CR", '\CR'),
792         ("SO", '\SO'),
793         ("SI", '\SI'),
794         ("DLE", '\DLE'),
795         ("DC1", '\DC1'),
796         ("DC2", '\DC2'),
797         ("DC3", '\DC3'),
798         ("DC4", '\DC4'),
799         ("NAK", '\NAK'),
800         ("SYN", '\SYN'),
801         ("ETB", '\ETB'),
802         ("CAN", '\CAN'),
803         ("EM", '\EM'),
804         ("SUB", '\SUB'),
805         ("ESC", '\ESC'),
806         ("FS", '\FS'),
807         ("GS", '\GS'),
808         ("RS", '\RS'),
809         ("US", '\US'),
810         ("SP", '\SP'),
811         ("DEL", '\DEL')
812         ]
813
814 -------------------------------------------------------------------------------
815
816 lex_demand cont buf = 
817  case read_em [] buf of { (ls,buf') -> 
818  case currentChar# buf' of
819    'B'# -> cont (ITstrict (ls, True )) (incLexeme buf')
820    _    -> cont (ITstrict (ls, False)) buf'
821  }
822  where
823    -- code snatched from Demand.lhs
824   read_em acc buf = 
825    case currentChar# buf of
826     'L'# -> read_em (WwLazy False : acc) (stepOn buf)
827     'A'# -> read_em (WwLazy True  : acc) (stepOn buf)
828     'S'# -> read_em (WwStrict     : acc) (stepOn buf)
829     'P'# -> read_em (WwPrim       : acc) (stepOn buf)
830     'E'# -> read_em (WwEnum       : acc) (stepOn buf)
831     ')'# -> (reverse acc, stepOn buf)
832     'U'# -> do_unpack DataType True  acc (stepOnBy# buf 2#)
833     'u'# -> do_unpack DataType False acc (stepOnBy# buf 2#)
834     'N'# -> do_unpack NewType True  acc (stepOnBy# buf 2#)
835     'n'# -> do_unpack NewType False acc (stepOnBy# buf 2#)
836     _    -> (reverse acc, buf)
837
838   do_unpack new_or_data wrapper_unpacks acc buf
839    = case read_em [] buf of
840       (stuff, rest) -> read_em (WwUnpack new_or_data wrapper_unpacks stuff : acc) rest
841
842
843 ------------------
844 lex_scc cont buf =
845  case currentChar# buf of
846   'C'# -> cont ITsccAllCafs (incLexeme buf)
847   other -> cont ITscc buf
848
849 -----------------------------------------------------------------------------
850 -- Numbers
851
852 lex_num :: (Token -> P a) -> Int# -> Integer -> P a
853 lex_num cont glaexts acc buf =
854  case scanNumLit acc buf of
855      (acc',buf') ->
856        case currentChar# buf' of
857          '.'# | is_digit (lookAhead# buf' 1#) ->
858              -- this case is not optimised at all, as the
859              -- presence of floating point numbers in interface
860              -- files is not that common. (ToDo)
861             case expandWhile# is_digit (incLexeme buf') of
862               buf2 -> -- points to first non digit char
863
864                 let l = case currentChar# buf2 of
865                           'E'# -> do_exponent
866                           'e'# -> do_exponent
867                           _ -> buf2
868
869                     do_exponent 
870                         = let buf3 = incLexeme buf2 in
871                           case currentChar# buf3 of
872                                 '-'# -> expandWhile# is_digit (incLexeme buf3)
873                                 '+'# -> expandWhile# is_digit (incLexeme buf3)
874                                 x | is_digit x -> expandWhile# is_digit buf3
875                                 _ -> buf2
876
877                     v = readRational__ (lexemeToString l)
878
879                 in case currentChar# l of -- glasgow exts only
880                       '#'# | flag glaexts -> let l' = incLexeme l in
881                               case currentChar# l' of
882                                 '#'# -> cont (ITprimdouble v) (incLexeme l')
883                                 _    -> cont (ITprimfloat  v) l'
884                       _ -> cont (ITrational v) l
885
886          _ -> after_lexnum cont glaexts acc' buf'
887                 
888 after_lexnum cont glaexts i buf
889   = case currentChar# buf of
890         '#'# | flag glaexts -> cont (ITprimint i) (incLexeme buf)
891         _    -> cont (ITinteger i) buf
892
893 -----------------------------------------------------------------------------
894 -- C "literal literal"s  (i.e. things like ``NULL'', ``stdout'' etc.)
895
896 -- we lexemeToFastString on the bit between the ``''s, but include the
897 -- quotes in the full lexeme.
898
899 lex_cstring cont buf =
900  case expandUntilMatch (stepOverLexeme buf) "\'\'" of
901    Just buf' -> cont (ITlitlit (lexemeToFastString 
902                                 (setCurrentPos# buf' (negateInt# 2#))))
903                    (mergeLexemes buf buf')
904    Nothing   -> lexError "unterminated ``" buf
905
906 -----------------------------------------------------------------------------
907 -- identifiers, symbols etc.
908
909 lex_ip cont buf =
910  case expandWhile# is_ident buf of
911    buf' -> cont (ITipvarid lexeme) buf'
912            where lexeme = lexemeToFastString buf'
913
914 lex_id cont glaexts buf =
915  let buf1 = expandWhile# is_ident buf in
916  seq buf1 $
917
918  case (if flag glaexts 
919         then expandWhile# (eqChar# '#'#) buf1 -- slurp trailing hashes
920         else buf1)                              of { buf' ->
921
922  let lexeme  = lexemeToFastString buf' in
923
924  case _scc_ "Lex.haskellKeyword" lookupUFM haskellKeywordsFM lexeme of {
925         Just kwd_token -> --trace ("hkeywd: "++_UNPK_(lexeme)) $
926                           cont kwd_token buf';
927         Nothing        -> 
928
929  let var_token = cont (ITvarid lexeme) buf' in
930
931  if not (flag glaexts)
932    then var_token
933    else
934
935  case lookupUFM ghcExtensionKeywordsFM lexeme of {
936         Just kwd_token -> cont kwd_token buf';
937         Nothing        -> var_token
938
939  }}}
940
941 lex_sym cont buf =
942  -- trace "lex_sym" $
943  case expandWhile# is_symbol buf of
944    buf' -> case lookupUFM haskellKeySymsFM lexeme of {
945                 Just kwd_token -> --trace ("keysym: "++unpackFS lexeme) $
946                                   cont kwd_token buf' ;
947                 Nothing        -> --trace ("sym: "++unpackFS lexeme) $
948                                   cont (mk_var_token lexeme) buf'
949            }
950         where lexeme = lexemeToFastString buf'
951
952
953 lex_con cont glaexts buf = 
954  -- trace ("con: "{-++unpackFS lexeme-}) $
955  case expandWhile# is_ident buf          of { buf1 ->
956  case slurp_trailing_hashes buf1 glaexts of { buf' ->
957
958  case currentChar# buf' of
959      '.'# -> munch
960      _    -> just_a_conid
961  
962    where
963     just_a_conid = cont (ITconid lexeme) buf'
964     lexeme = lexemeToFastString buf'
965     munch = lex_qid cont glaexts lexeme (incLexeme buf') just_a_conid
966  }}
967
968 lex_qid cont glaexts mod buf just_a_conid =
969  -- trace ("quid: "{-++unpackFS lexeme-}) $
970  case currentChar# buf of
971   '['# ->       -- Special case for []
972     case lookAhead# buf 1# of
973      ']'# -> cont (ITqconid  (mod,SLIT("[]"))) (setCurrentPos# buf 2#)
974      _    -> just_a_conid
975
976   '('# ->  -- Special case for (,,,)
977            -- This *is* necessary to deal with e.g. "instance C PrelBase.(,,)"
978     case lookAhead# buf 1# of
979      '#'# | flag glaexts -> case lookAhead# buf 2# of
980                 ','# -> lex_ubx_tuple cont mod (setCurrentPos# buf 3#) 
981                                 just_a_conid
982                 _    -> just_a_conid
983      ')'# -> cont (ITqconid (mod,SLIT("()"))) (setCurrentPos# buf 2#)
984      ','# -> lex_tuple cont mod (setCurrentPos# buf 2#) just_a_conid
985      _    -> just_a_conid
986
987   '-'# -> case lookAhead# buf 1# of
988             '>'# -> cont (ITqconid (mod,SLIT("(->)"))) (setCurrentPos# buf 2#)
989             _    -> lex_id3 cont glaexts mod buf just_a_conid
990   _    -> lex_id3 cont glaexts mod buf just_a_conid
991
992 lex_id3 cont glaexts mod buf just_a_conid
993   | is_symbol (currentChar# buf) =
994      let 
995         start_new_lexeme = stepOverLexeme buf
996      in
997      -- trace ("lex_id31 "{-++unpackFS lexeme-}) $
998      case expandWhile# is_symbol start_new_lexeme of { buf' ->
999      let
1000        lexeme  = lexemeToFastString buf'
1001         -- real lexeme is M.<sym>
1002        new_buf = mergeLexemes buf buf'
1003      in
1004      cont (mk_qvar_token mod lexeme) new_buf
1005         -- wrong, but arguably morally right: M... is now a qvarsym
1006      }
1007
1008   | otherwise   =
1009      let 
1010         start_new_lexeme = stepOverLexeme buf
1011      in
1012      -- trace ("lex_id32 "{-++unpackFS lexeme-}) $
1013      case expandWhile# is_ident start_new_lexeme of { buf1 ->
1014      if emptyLexeme buf1 
1015             then just_a_conid
1016             else
1017
1018      case slurp_trailing_hashes buf1 glaexts of { buf' ->
1019
1020      let
1021       lexeme      = lexemeToFastString buf'
1022       new_buf     = mergeLexemes buf buf'
1023       is_a_qvarid = cont (mk_qvar_token mod lexeme) new_buf
1024      in
1025      case _scc_ "Lex.haskellKeyword" lookupUFM haskellKeywordsFM lexeme of {
1026             Nothing          -> is_a_qvarid ;
1027
1028             Just kwd_token | isSpecial kwd_token   -- special ids (as, qualified, hiding) shouldn't be
1029                            -> is_a_qvarid          --  recognised as keywords here.
1030                            | otherwise
1031                            -> just_a_conid         -- avoid M.where etc.
1032      }}}
1033
1034 slurp_trailing_hashes buf glaexts
1035   | flag glaexts = expandWhile# (`eqChar#` '#'#) buf
1036   | otherwise    = buf
1037
1038
1039 mk_var_token pk_str
1040   | is_upper f          = ITconid pk_str
1041   | is_ident f          = ITvarid pk_str
1042   | f `eqChar#` ':'#    = ITconsym pk_str
1043   | otherwise           = ITvarsym pk_str
1044   where
1045       (C# f) = _HEAD_ pk_str
1046       -- tl     = _TAIL_ pk_str
1047
1048 mk_qvar_token m token =
1049 -- trace ("mk_qvar ") $ 
1050  case mk_var_token token of
1051    ITconid n  -> ITqconid  (m,n)
1052    ITvarid n  -> ITqvarid  (m,n)
1053    ITconsym n -> ITqconsym (m,n)
1054    ITvarsym n -> ITqvarsym (m,n)
1055    _          -> ITunknown (show token)
1056 \end{code}
1057
1058 ----------------------------------------------------------------------------
1059 Horrible stuff for dealing with M.(,,,)
1060
1061 \begin{code}
1062 lex_tuple cont mod buf back_off =
1063   go 2 buf
1064   where
1065    go n buf =
1066     case currentChar# buf of
1067       ','# -> go (n+1) (stepOn buf)
1068       ')'# -> cont (ITqconid (mod, snd (mkTupNameStr Boxed n))) (stepOn buf)
1069       _    -> back_off
1070
1071 lex_ubx_tuple cont mod buf back_off =
1072   go 2 buf
1073   where
1074    go n buf =
1075     case currentChar# buf of
1076       ','# -> go (n+1) (stepOn buf)
1077       '#'# -> case lookAhead# buf 1# of
1078                 ')'# -> cont (ITqconid (mod, snd (mkTupNameStr Unboxed n)))
1079                                  (stepOnBy# buf 2#)
1080                 _    -> back_off
1081       _    -> back_off
1082 \end{code}
1083
1084 -----------------------------------------------------------------------------
1085 doDiscard rips along really fast, looking for a '##-}', 
1086 indicating the end of the pragma we're skipping
1087
1088 \begin{code}
1089 doDiscard inStr buf =
1090  case currentChar# buf of
1091    '#'# | inStr ==# 0# ->
1092        case lookAhead# buf 1# of { '#'# -> 
1093        case lookAhead# buf 2# of { '-'# ->
1094        case lookAhead# buf 3# of { '}'# -> 
1095            (lexemeToBuffer buf, stepOverLexeme (setCurrentPos# buf 4#));
1096         _    -> doDiscard inStr (incLexeme buf) };
1097         _    -> doDiscard inStr (incLexeme buf) };
1098         _    -> doDiscard inStr (incLexeme buf) }
1099
1100    '"'# ->
1101        let
1102         odd_slashes buf flg i# =
1103           case lookAhead# buf i# of
1104            '\\'# -> odd_slashes buf (not flg) (i# -# 1#)
1105            _     -> flg
1106
1107         not_inStr = if inStr ==# 0# then 1# else 0#
1108        in
1109        case lookAhead# buf (negateInt# 1#) of --backwards, actually
1110          '\\'# -> -- escaping something..
1111            if odd_slashes buf True (negateInt# 2#) 
1112                 then  -- odd number of slashes, " is escaped.
1113                       doDiscard inStr (incLexeme buf)
1114                 else  -- even number of slashes, \ is escaped.
1115                       doDiscard not_inStr (incLexeme buf)
1116          _ -> doDiscard not_inStr (incLexeme buf)
1117
1118    '\''# | inStr ==# 0# ->
1119         case lookAhead# buf 1# of { '"'# ->
1120         case lookAhead# buf 2# of { '\''# ->
1121            doDiscard inStr (setCurrentPos# buf 3#);
1122         _ -> doDiscard inStr (incLexeme buf) };
1123         _ -> doDiscard inStr (incLexeme buf) }
1124
1125    _ -> doDiscard inStr (incLexeme buf)
1126
1127 \end{code}
1128
1129 -----------------------------------------------------------------------------
1130
1131 \begin{code}
1132 data LayoutContext
1133   = NoLayout
1134   | Layout Int#
1135
1136 data ParseResult a
1137   = POk PState a
1138   | PFailed Message
1139
1140 data PState = PState { 
1141         loc           :: SrcLoc,
1142         glasgow_exts  :: Int#,
1143         bol           :: Int#,
1144         atbol         :: Int#,
1145         context       :: [LayoutContext]
1146      }
1147
1148 type P a = StringBuffer         -- Input string
1149         -> PState
1150         -> ParseResult a
1151
1152 returnP   :: a -> P a
1153 returnP a buf s = POk s a
1154
1155 thenP      :: P a -> (a -> P b) -> P b
1156 m `thenP` k = \ buf s ->
1157         case m buf s of
1158                 POk s1 a -> k a buf s1
1159                 PFailed err  -> PFailed err
1160
1161 thenP_     :: P a -> P b -> P b
1162 m `thenP_` k = m `thenP` \_ -> k
1163
1164 mapP :: (a -> P b) -> [a] -> P [b]
1165 mapP f [] = returnP []
1166 mapP f (a:as) = 
1167      f a `thenP` \b ->
1168      mapP f as `thenP` \bs ->
1169      returnP (b:bs)
1170
1171 failP :: String -> P a
1172 failP msg buf s = PFailed (text msg)
1173
1174 failMsgP :: Message -> P a
1175 failMsgP msg buf s = PFailed msg
1176
1177 lexError :: String -> P a
1178 lexError str buf s@PState{ loc = loc } 
1179   = failMsgP (hcat [ppr loc, text ": ", text str]) buf s
1180
1181 getSrcLocP :: P SrcLoc
1182 getSrcLocP buf s@(PState{ loc = loc }) = POk s loc
1183
1184 -- use a temporary SrcLoc for the duration of the argument
1185 setSrcLocP :: SrcLoc -> P a -> P a
1186 setSrcLocP new_loc p buf s = 
1187   case p buf s{ loc=new_loc } of
1188       POk _ a   -> POk s a
1189       PFailed e -> PFailed e
1190   
1191 getSrcFile :: P FAST_STRING
1192 getSrcFile buf s@(PState{ loc = loc }) = POk s (srcLocFile loc)
1193
1194 pushContext :: LayoutContext -> P ()
1195 pushContext ctxt buf s@(PState{ context = ctx }) = POk s{context = ctxt:ctx} ()
1196
1197 {-
1198
1199 This special case in layoutOn is to handle layout contexts with are
1200 indented the same or less than the current context.  This is illegal
1201 according to the Haskell spec, so we have to arrange to close the
1202 current context.  eg.
1203
1204 class Foo a where
1205 class Bar a
1206
1207 after the first 'where', the sequence of events is:
1208
1209         - layout system inserts a ';' (column 0)
1210         - parser begins a new context at column 0
1211         - parser shifts ';' (legal empty declaration)
1212         - parser sees 'class': parse error (we're still in the inner context)
1213
1214 trouble is, by the time we know we need a new context, the lexer has
1215 already generated the ';'.  Hacky solution is as follows: since we
1216 know the column of the next token (it's the column number of the new
1217 context), we set the ACTUAL column number of the new context to this
1218 numer plus one.  Hence the next time the lexer is called, a '}' will
1219 be generated to close the new context straight away.  Furthermore, we
1220 have to set the atbol flag so that the ';' that the parser shifted as
1221 part of the new context is re-generated.
1222
1223 when the new context is *less* indented than the current one:
1224
1225 f = f where g = g where
1226 h = h
1227
1228         - current context: column 12.
1229         - on seeing 'h' (column 0), the layout system inserts '}'
1230         - parser starts a new context, column 0
1231         - parser sees '}', uses it to close new context
1232         - we still need to insert another '}' followed by a ';',
1233           hence the atbol trick.
1234
1235 There's also a special hack in here to deal with
1236
1237         do
1238            ....
1239            e $ do
1240            blah
1241
1242 i.e. the inner context is at the same indentation level as the outer
1243 context.  This is strictly illegal according to Haskell 98, but
1244 there's a lot of existing code using this style and it doesn't make
1245 any sense to disallow it, since empty 'do' lists don't make sense.
1246 -}
1247
1248 layoutOn :: Bool -> P ()
1249 layoutOn strict buf s@(PState{ bol = bol, context = ctx }) =
1250     let offset = lexemeIndex buf -# bol in
1251     case ctx of
1252         Layout prev_off : _ 
1253            | if strict then prev_off >=# offset else prev_off ># offset ->
1254                 --trace ("layout on, column: " ++  show (I# offset)) $
1255                 POk s{ context = Layout (offset +# 1#) : ctx, atbol = 1# } ()
1256         other -> 
1257                 --trace ("layout on, column: " ++  show (I# offset)) $
1258                 POk s{ context = Layout offset : ctx } ()
1259
1260 layoutOff :: P ()
1261 layoutOff buf s@(PState{ context = ctx }) =
1262     POk s{ context = NoLayout:ctx } ()
1263
1264 popContext :: P ()
1265 popContext = \ buf s@(PState{ context = ctx, loc = loc }) ->
1266   case ctx of
1267         (_:tl) -> POk s{ context = tl } ()
1268         []     -> PFailed (srcParseErr buf loc)
1269
1270 {- 
1271  Note that if the name of the file we're processing ends
1272  with `hi-boot', we accept it on faith as having the right
1273  version. This is done so that .hi-boot files that comes
1274  with hsc don't have to be updated before every release,
1275  *and* it allows us to share .hi-boot files with versions
1276  of hsc that don't have .hi version checking (e.g., ghc-2.10's)
1277
1278  If the version number is 0, the checking is also turned off.
1279  (needed to deal with GHC.hi only!)
1280
1281  Once we can assume we're compiling with a version of ghc that
1282  supports interface file checking, we can drop the special
1283  pleading
1284 -}
1285 checkVersion :: Maybe Integer -> P ()
1286 checkVersion mb@(Just v) buf s@(PState{loc = loc})
1287  | (v==0) || (v == fromInt opt_HiVersion) || opt_NoHiCheck = POk s ()
1288  | otherwise = PFailed (ifaceVersionErr mb loc ([]::[Token]){-Todo-})
1289 checkVersion mb@Nothing  buf s@(PState{loc = loc})
1290  | "hi-boot" `isSuffixOf` (_UNPK_ (srcLocFile loc)) = POk s ()
1291  | otherwise = PFailed (ifaceVersionErr mb loc ([]::[Token]){-Todo-})
1292
1293 -----------------------------------------------------------------
1294
1295 ifaceParseErr :: StringBuffer -> SrcLoc -> Message
1296 ifaceParseErr s l
1297   = hsep [ppr l, ptext SLIT("Interface file parse error; on input `"),
1298           text (lexemeToString s), char '\'']
1299
1300 ifaceVersionErr hi_vers l toks
1301   = hsep [ppr l, ptext SLIT("Interface file version error;"),
1302           ptext SLIT("Expected"), int opt_HiVersion, 
1303           ptext SLIT("found "), pp_version]
1304     where
1305      pp_version =
1306       case hi_vers of
1307         Nothing -> ptext SLIT("pre ghc-3.02 version")
1308         Just v  -> ptext SLIT("version") <+> integer v
1309
1310 -----------------------------------------------------------------------------
1311
1312 srcParseErr :: StringBuffer -> SrcLoc -> Message
1313 srcParseErr s l
1314   = hcat [ppr l, 
1315           if null token 
1316              then ptext SLIT(": parse error (possibly incorrect indentation)")
1317              else hcat [ptext SLIT(": parse error on input "),
1318                         char '`', text token, char '\'']
1319     ]
1320   where 
1321         token = lexemeToString s
1322
1323 \end{code}