annotate C-- calls that do not return
[ghc-hetmet.git] / compiler / cmm / CmmLex.x
1 -----------------------------------------------------------------------------
2 --
3 -- (c) The University of Glasgow, 2004-2006
4 --
5 -- Lexer for concrete Cmm.  We try to stay close to the C-- spec, but there
6 -- are a few minor differences:
7 --
8 --   * extra keywords for our macros, and float32/float64 types
9 --   * global registers (Sp,Hp, etc.)
10 --
11 -----------------------------------------------------------------------------
12
13 {
14 module CmmLex (
15    CmmToken(..), cmmlex,
16   ) where
17
18 #include "HsVersions.h"
19
20 import Cmm
21 import Lexer
22
23 import SrcLoc
24 import UniqFM
25 import StringBuffer
26 import FastString
27 import Ctype
28 import Util
29 --import TRACE
30 }
31
32 $whitechar   = [\ \t\n\r\f\v\xa0] -- \xa0 is Unicode no-break space
33 $white_no_nl = $whitechar # \n
34
35 $ascdigit  = 0-9
36 $unidigit  = \x01 -- Trick Alex into handling Unicode. See alexGetChar.
37 $digit     = [$ascdigit $unidigit]
38 $octit     = 0-7
39 $hexit     = [$digit A-F a-f]
40
41 $unilarge  = \x03 -- Trick Alex into handling Unicode. See alexGetChar.
42 $asclarge  = [A-Z \xc0-\xd6 \xd8-\xde]
43 $large     = [$asclarge $unilarge]
44
45 $unismall  = \x04 -- Trick Alex into handling Unicode. See alexGetChar.
46 $ascsmall  = [a-z \xdf-\xf6 \xf8-\xff]
47 $small     = [$ascsmall $unismall \_]
48
49 $namebegin = [$large $small \. \$ \@]
50 $namechar  = [$namebegin $digit]
51
52 @decimal     = $digit+
53 @octal       = $octit+
54 @hexadecimal = $hexit+
55 @exponent    = [eE] [\-\+]? @decimal
56
57 @floating_point = @decimal \. @decimal @exponent? | @decimal @exponent
58
59 @escape      = \\ ([abfnrt\\\'\"\?] | x $hexit{1,2} | $octit{1,3})
60 @strchar     = ($printable # [\"\\]) | @escape
61
62 cmm :-
63
64 $white_no_nl+           ;
65 ^\# pragma .* \n        ; -- Apple GCC 3.3 CPP generates pragmas in its output
66
67 ^\# (line)?             { begin line_prag }
68
69 -- single-line line pragmas, of the form
70 --    # <line> "<file>" <extra-stuff> \n
71 <line_prag> $digit+                     { setLine line_prag1 }
72 <line_prag1> \" ($printable # \")* \"   { setFile line_prag2 }
73 <line_prag2> .*                         { pop }
74
75 <0> {
76   \n                    ;
77
78   [\:\;\{\}\[\]\(\)\=\`\~\/\*\%\-\+\&\^\|\>\<\,\!]      { special_char }
79   
80   ".."                  { kw CmmT_DotDot }
81   "::"                  { kw CmmT_DoubleColon }
82   ">>"                  { kw CmmT_Shr }
83   "<<"                  { kw CmmT_Shl }
84   ">="                  { kw CmmT_Ge }
85   "<="                  { kw CmmT_Le }
86   "=="                  { kw CmmT_Eq }
87   "!="                  { kw CmmT_Ne }
88   "&&"                  { kw CmmT_BoolAnd }
89   "||"                  { kw CmmT_BoolOr }
90   
91   R@decimal             { global_regN VanillaReg }
92   F@decimal             { global_regN FloatReg }
93   D@decimal             { global_regN DoubleReg }
94   L@decimal             { global_regN LongReg }
95   Sp                    { global_reg Sp }
96   SpLim                 { global_reg SpLim }
97   Hp                    { global_reg Hp }
98   HpLim                 { global_reg HpLim }
99   CurrentTSO            { global_reg CurrentTSO }
100   CurrentNursery        { global_reg CurrentNursery }
101   HpAlloc               { global_reg HpAlloc }
102   BaseReg               { global_reg BaseReg }
103   
104   $namebegin $namechar* { name }
105   
106   0 @octal              { tok_octal }
107   @decimal              { tok_decimal }
108   0[xX] @hexadecimal    { tok_hexadecimal }
109   @floating_point       { strtoken tok_float }
110   
111   \" @strchar* \"       { strtoken tok_string }
112 }
113
114 {
115 data CmmToken
116   = CmmT_SpecChar  Char
117   | CmmT_DotDot
118   | CmmT_DoubleColon
119   | CmmT_Shr
120   | CmmT_Shl
121   | CmmT_Ge
122   | CmmT_Le
123   | CmmT_Eq
124   | CmmT_Ne
125   | CmmT_BoolAnd
126   | CmmT_BoolOr
127   | CmmT_CLOSURE
128   | CmmT_INFO_TABLE
129   | CmmT_INFO_TABLE_RET
130   | CmmT_INFO_TABLE_FUN
131   | CmmT_INFO_TABLE_CONSTR
132   | CmmT_INFO_TABLE_SELECTOR
133   | CmmT_else
134   | CmmT_export
135   | CmmT_section
136   | CmmT_align
137   | CmmT_goto
138   | CmmT_if
139   | CmmT_jump
140   | CmmT_foreign
141   | CmmT_never
142   | CmmT_prim
143   | CmmT_return
144   | CmmT_returns
145   | CmmT_import
146   | CmmT_switch
147   | CmmT_case
148   | CmmT_default
149   | CmmT_bits8
150   | CmmT_bits16
151   | CmmT_bits32
152   | CmmT_bits64
153   | CmmT_float32
154   | CmmT_float64
155   | CmmT_GlobalReg GlobalReg
156   | CmmT_Name      FastString
157   | CmmT_String    String
158   | CmmT_Int       Integer
159   | CmmT_Float     Rational
160   | CmmT_EOF
161 #ifdef DEBUG
162   deriving (Show)
163 #endif
164
165 -- -----------------------------------------------------------------------------
166 -- Lexer actions
167
168 type Action = SrcSpan -> StringBuffer -> Int -> P (Located CmmToken)
169
170 begin :: Int -> Action
171 begin code _span _str _len = do pushLexState code; lexToken
172
173 pop :: Action
174 pop _span _buf _len = do popLexState; lexToken
175
176 special_char :: Action
177 special_char span buf len = return (L span (CmmT_SpecChar (currentChar buf)))
178
179 kw :: CmmToken -> Action
180 kw tok span buf len = return (L span tok)
181
182 global_regN :: (Int -> GlobalReg) -> Action
183 global_regN con span buf len 
184   = return (L span (CmmT_GlobalReg (con (fromIntegral n))))
185   where buf' = stepOn buf
186         n = parseUnsignedInteger buf' (len-1) 10 octDecDigit
187
188 global_reg :: GlobalReg -> Action
189 global_reg r span buf len = return (L span (CmmT_GlobalReg r))
190
191 strtoken :: (String -> CmmToken) -> Action
192 strtoken f span buf len = 
193   return (L span $! (f $! lexemeToString buf len))
194
195 name :: Action
196 name span buf len = 
197   case lookupUFM reservedWordsFM fs of
198         Just tok -> return (L span tok)
199         Nothing  -> return (L span (CmmT_Name fs))
200   where
201         fs = lexemeToFastString buf len
202
203 reservedWordsFM = listToUFM $
204         map (\(x, y) -> (mkFastString x, y)) [
205         ( "CLOSURE",            CmmT_CLOSURE ),
206         ( "INFO_TABLE",         CmmT_INFO_TABLE ),
207         ( "INFO_TABLE_RET",     CmmT_INFO_TABLE_RET ),
208         ( "INFO_TABLE_FUN",     CmmT_INFO_TABLE_FUN ),
209         ( "INFO_TABLE_CONSTR",  CmmT_INFO_TABLE_CONSTR ),
210         ( "INFO_TABLE_SELECTOR",CmmT_INFO_TABLE_SELECTOR ),
211         ( "else",               CmmT_else ),
212         ( "export",             CmmT_export ),
213         ( "section",            CmmT_section ),
214         ( "align",              CmmT_align ),
215         ( "goto",               CmmT_goto ),
216         ( "if",                 CmmT_if ),
217         ( "jump",               CmmT_jump ),
218         ( "foreign",            CmmT_foreign ),
219         ( "never",              CmmT_never ),
220         ( "prim",               CmmT_prim ),
221         ( "return",             CmmT_return ),
222         ( "returns",            CmmT_returns ),
223         ( "import",             CmmT_import ),
224         ( "switch",             CmmT_switch ),
225         ( "case",               CmmT_case ),
226         ( "default",            CmmT_default ),
227         ( "bits8",              CmmT_bits8 ),
228         ( "bits16",             CmmT_bits16 ),
229         ( "bits32",             CmmT_bits32 ),
230         ( "bits64",             CmmT_bits64 ),
231         ( "float32",            CmmT_float32 ),
232         ( "float64",            CmmT_float64 )
233         ]
234
235 tok_decimal span buf len 
236   = return (L span (CmmT_Int  $! parseUnsignedInteger buf len 10 octDecDigit))
237
238 tok_octal span buf len 
239   = return (L span (CmmT_Int  $! parseUnsignedInteger (offsetBytes 1 buf) (len-1) 8 octDecDigit))
240
241 tok_hexadecimal span buf len 
242   = return (L span (CmmT_Int  $! parseUnsignedInteger (offsetBytes 2 buf) (len-2) 16 hexDigit))
243
244 tok_float str = CmmT_Float $! readRational str
245
246 tok_string str = CmmT_String (read str)
247                  -- urk, not quite right, but it'll do for now
248
249 -- -----------------------------------------------------------------------------
250 -- Line pragmas
251
252 setLine :: Int -> Action
253 setLine code span buf len = do
254   let line = parseUnsignedInteger buf len 10 octDecDigit
255   setSrcLoc (mkSrcLoc (srcSpanFile span) (fromIntegral line - 1) 0)
256         -- subtract one: the line number refers to the *following* line
257   -- trace ("setLine "  ++ show line) $ do
258   popLexState
259   pushLexState code
260   lexToken
261
262 setFile :: Int -> Action
263 setFile code span buf len = do
264   let file = lexemeToFastString (stepOn buf) (len-2)
265   setSrcLoc (mkSrcLoc file (srcSpanEndLine span) (srcSpanEndCol span))
266   popLexState
267   pushLexState code
268   lexToken
269
270 -- -----------------------------------------------------------------------------
271 -- This is the top-level function: called from the parser each time a
272 -- new token is to be read from the input.
273
274 cmmlex :: (Located CmmToken -> P a) -> P a
275 cmmlex cont = do
276   tok@(L _ tok__) <- lexToken
277   --trace ("token: " ++ show tok__) $ do
278   cont tok
279
280 lexToken :: P (Located CmmToken)
281 lexToken = do
282   inp@(loc1,buf) <- getInput
283   sc <- getLexState
284   case alexScan inp sc of
285     AlexEOF -> do let span = mkSrcSpan loc1 loc1
286                   setLastToken span 0 0
287                   return (L span CmmT_EOF)
288     AlexError (loc2,_) -> do failLocMsgP loc1 loc2 "lexical error"
289     AlexSkip inp2 _ -> do
290         setInput inp2
291         lexToken
292     AlexToken inp2@(end,buf2) len t -> do
293         setInput inp2
294         let span = mkSrcSpan loc1 end
295         span `seq` setLastToken span len len
296         t span buf len
297
298 -- -----------------------------------------------------------------------------
299 -- Monad stuff
300
301 -- Stuff that Alex needs to know about our input type:
302 type AlexInput = (SrcLoc,StringBuffer)
303
304 alexInputPrevChar :: AlexInput -> Char
305 alexInputPrevChar (_,s) = prevChar s '\n'
306
307 alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
308 alexGetChar (loc,s) 
309   | atEnd s   = Nothing
310   | otherwise = c `seq` loc' `seq` s' `seq` Just (c, (loc', s'))
311   where c = currentChar s
312         loc' = advanceSrcLoc loc c
313         s'   = stepOn s
314
315 getInput :: P AlexInput
316 getInput = P $ \s@PState{ loc=l, buffer=b } -> POk s (l,b)
317
318 setInput :: AlexInput -> P ()
319 setInput (l,b) = P $ \s -> POk s{ loc=l, buffer=b } ()
320 }