X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fparser%2FLexer.x;h=a6f7224c97d3fcf72226a717d065d3a0aa99ce53;hb=2b4b74fba442bd07e14712846b3e4fc0145c851e;hp=753a9728ea3b51a352cad5285e5d9cc3c9584731;hpb=f109a0b2d927a8c7fe5cc9881f0dfdae3e34f399;p=ghc-hetmet.git diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index 753a972..a6f7224 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -28,7 +28,7 @@ module Lexer ( getMessages, popContext, pushCurrentContext, setLastToken, setSrcLoc, getLexState, popLexState, pushLexState, - extension, glaExtsEnabled, bangPatEnabled + extension, standaloneDerivingEnabled, bangPatEnabled ) where #include "HsVersions.h" @@ -202,7 +202,7 @@ $tab+ { warn Opt_WarnTabs (text "Tab character") } -- generate a matching '}' token. () { do_layout_left } -<0,option_prags,glaexts> \n { begin bol } +<0,option_prags> \n { begin bol } "{-#" $whitechar* (line|LINE) { begin line_prag2 } @@ -220,15 +220,16 @@ $tab+ { warn Opt_WarnTabs (text "Tab character") } -- NOTE: accept -} at the end of a LINE pragma, for compatibility -- with older versions of GHC which generated these. --- We only want RULES pragmas to be picked up when -fglasgow-exts --- is on, because the contents of the pragma is always written using --- glasgow-exts syntax (using forall etc.), so if glasgow exts are not --- enabled, we're sure to get a parse error. +-- We only want RULES pragmas to be picked up when explicit forall +-- syntax is enabled is on, because the contents of the pragma always +-- uses it. If it's not on then we're sure to get a parse error. -- (ToDo: we should really emit a warning when ignoring pragmas) - - "{-#" $whitechar* (RULES|rules) { token ITrules_prag } +-- XXX Now that we can enable this without the -fglasgow-exts hammer, +-- is it better just to let the parse error happen? +<0> + "{-#" $whitechar* (RULES|rules) / { ifExtension explicitForallEnabled } { token ITrules_prag } -<0,option_prags,glaexts> { +<0,option_prags> { "{-#" $whitechar* (INLINE|inline) { token (ITinline_prag True) } "{-#" $whitechar* (NO(T?)INLINE|no(t?)inline) { token (ITinline_prag False) } @@ -265,29 +266,28 @@ $tab+ { warn Opt_WarnTabs (text "Tab character") } "{-#" $whitechar* (INCLUDE|include) { lex_string_prag ITinclude_prag } } -<0,option_prags,glaexts> { +<0,option_prags> { -- This is to catch things like {-# OPTIONS OPTIONS_HUGS ... "{-#" $whitechar* $idchar+ { nested_comment lexToken } } -- '0' state: ordinary lexemes --- 'glaexts' state: glasgow extensions (postfix '#', etc.) -- Haddock comments -<0,glaexts> { +<0> { "-- " $docsym / { ifExtension haddockEnabled } { multiline_doc_comment } "{-" \ ? $docsym / { ifExtension haddockEnabled } { nested_doc_comment } } -- "special" symbols -<0,glaexts> { +<0> { "[:" / { ifExtension parrEnabled } { token ITopabrack } ":]" / { ifExtension parrEnabled } { token ITcpabrack } } -<0,glaexts> { +<0> { "[|" / { ifExtension thEnabled } { token ITopenExpQuote } "[e|" / { ifExtension thEnabled } { token ITopenExpQuote } "[p|" / { ifExtension thEnabled } { token ITopenPatQuote } @@ -298,24 +298,29 @@ $tab+ { warn Opt_WarnTabs (text "Tab character") } "$(" / { ifExtension thEnabled } { token ITparenEscape } } -<0,glaexts> { +<0> { "(|" / { ifExtension arrowsEnabled `alexAndPred` notFollowedBySymbol } { special IToparenbar } "|)" / { ifExtension arrowsEnabled } { special ITcparenbar } } -<0,glaexts> { +<0> { \? @varid / { ifExtension ipEnabled } { skip_one_varid ITdupipvarid } } - { - "(#" / { notFollowedBySymbol } { token IToubxparen } - "#)" { token ITcubxparen } - "{|" { token ITocurlybar } - "|}" { token ITccurlybar } +<0> { + "(#" / { ifExtension unboxedTuplesEnabled `alexAndPred` notFollowedBySymbol } + { token IToubxparen } + "#)" / { ifExtension unboxedTuplesEnabled } + { token ITcubxparen } } -<0,option_prags,glaexts> { +<0> { + "{|" / { ifExtension genericsEnabled } { token ITocurlybar } + "|}" / { ifExtension genericsEnabled } { token ITccurlybar } +} + +<0,option_prags> { \( { special IToparen } \) { special ITcparen } \[ { special ITobrack } @@ -328,7 +333,7 @@ $tab+ { warn Opt_WarnTabs (text "Tab character") } \} { close_brace } } -<0,option_prags,glaexts> { +<0,option_prags> { @qual @varid { check_qvarid } @qual @conid { idtoken qconid } @varid { varid } @@ -342,7 +347,7 @@ $tab+ { warn Opt_WarnTabs (text "Tab character") } @qual @conid { pop_and (idtoken qconid) } } -<0,glaexts> { +<0> { @qual @varid "#"+ / { ifExtension magicHashEnabled } { idtoken qvarid } @qual @conid "#"+ / { ifExtension magicHashEnabled } { idtoken qconid } @varid "#"+ / { ifExtension magicHashEnabled } { varid } @@ -351,7 +356,7 @@ $tab+ { warn Opt_WarnTabs (text "Tab character") } -- ToDo: M.(,,,) -<0,glaexts> { +<0> { @qual @varsym { idtoken qvarsym } @qual @consym { idtoken qconsym } @varsym { varsym } @@ -360,7 +365,7 @@ $tab+ { warn Opt_WarnTabs (text "Tab character") } -- For the normal boxed literals we need to be careful -- when trying to be close to Haskell98 -<0,glaexts> { +<0> { -- Normal integral literals (:: Num a => a, from Integer) @decimal { tok_num positive 0 0 decimal } 0[oO] @octal { tok_num positive 2 2 octal } @@ -370,28 +375,28 @@ $tab+ { warn Opt_WarnTabs (text "Tab character") } @floating_point { strtoken tok_float } } - { +<0> { -- Unboxed ints (:: Int#) -- It's simpler (and faster?) to give separate cases to the negatives, -- especially considering octal/hexadecimal prefixes. - @decimal \# { tok_primint positive 0 1 decimal } - 0[oO] @octal \# { tok_primint positive 2 3 octal } - 0[xX] @hexadecimal \# { tok_primint positive 2 3 hexadecimal } - @negative @decimal \# { tok_primint negative 1 2 decimal } - @negative 0[oO] @octal \# { tok_primint negative 3 4 octal } - @negative 0[xX] @hexadecimal \# { tok_primint negative 3 4 hexadecimal } + @decimal \# / { ifExtension magicHashEnabled } { tok_primint positive 0 1 decimal } + 0[oO] @octal \# / { ifExtension magicHashEnabled } { tok_primint positive 2 3 octal } + 0[xX] @hexadecimal \# / { ifExtension magicHashEnabled } { tok_primint positive 2 3 hexadecimal } + @negative @decimal \# / { ifExtension magicHashEnabled } { tok_primint negative 1 2 decimal } + @negative 0[oO] @octal \# / { ifExtension magicHashEnabled } { tok_primint negative 3 4 octal } + @negative 0[xX] @hexadecimal \# / { ifExtension magicHashEnabled } { tok_primint negative 3 4 hexadecimal } -- Unboxed floats and doubles (:: Float#, :: Double#) -- prim_{float,double} work with signed literals - @signed @floating_point \# { init_strtoken 1 tok_primfloat } - @signed @floating_point \# \# { init_strtoken 2 tok_primdouble } + @signed @floating_point \# / { ifExtension magicHashEnabled } { init_strtoken 1 tok_primfloat } + @signed @floating_point \# \# / { ifExtension magicHashEnabled } { init_strtoken 2 tok_primdouble } } -- Strings and chars are lexed by hand-written code. The reason is -- that even if we recognise the string or char here in the regex -- lexer, we would still have to parse the string afterward in order -- to convert it to a String. -<0,glaexts> { +<0> { \' { lex_char_tok } \" { lex_string_tok } } @@ -651,9 +656,7 @@ reservedSymsFM = listToUFM $ ,("!", ITbang, always) -- For data T (a::*) = MkT - ,("*", ITstar, \i -> glaExtsEnabled i || - kindSigsEnabled i || - tyFamEnabled i) + ,("*", ITstar, \i -> kindSigsEnabled i || tyFamEnabled i) -- For 'forall a . t' ,(".", ITdot, explicitForallEnabled) @@ -1106,8 +1109,8 @@ lex_string s = do Just ('"',i) -> do setInput i - glaexts <- extension glaExtsEnabled - if glaexts + magicHash <- extension magicHashEnabled + if magicHash then do i <- getInput case alexGetChar' i of @@ -1191,9 +1194,9 @@ lex_char_tok span buf len = do -- We've seen ' finish_char_tok :: SrcLoc -> Char -> P (Located Token) finish_char_tok loc ch -- We've already seen the closing quote -- Just need to check for trailing # - = do glaexts <- extension glaExtsEnabled + = do magicHash <- extension magicHashEnabled i@(AI end _ _) <- getInput - if glaexts then do + if magicHash then do case alexGetChar' i of Just ('#',i@(AI end _ _)) -> do setInput i @@ -1509,8 +1512,8 @@ getLexState = P $ \s@PState{ lex_state=ls:l } -> POk s ls -- -fglasgow-exts or -fparr) are represented by a bitmap stored in an unboxed -- integer -glaExtsBit, ffiBit, parrBit :: Int -glaExtsBit = 0 +genericsBit, ffiBit, parrBit :: Int +genericsBit = 0 -- {| and |} ffiBit = 1 parrBit = 2 arrowsBit = 4 @@ -1525,10 +1528,12 @@ magicHashBit = 11 -- # in both functions and operators kindSigsBit = 12 -- Kind signatures on type variables recursiveDoBit = 13 -- mdo unicodeSyntaxBit = 14 -- the forall symbol, arrow symbols, etc +unboxedTuplesBit = 15 -- (# and #) +standaloneDerivingBit = 16 -- standalone instance deriving declarations -glaExtsEnabled, ffiEnabled, parrEnabled :: Int -> Bool +genericsEnabled, ffiEnabled, parrEnabled :: Int -> Bool always _ = True -glaExtsEnabled flags = testBit flags glaExtsBit +genericsEnabled flags = testBit flags genericsBit ffiEnabled flags = testBit flags ffiBit parrEnabled flags = testBit flags parrBit arrowsEnabled flags = testBit flags arrowsBit @@ -1542,6 +1547,8 @@ magicHashEnabled flags = testBit flags magicHashBit kindSigsEnabled flags = testBit flags kindSigsBit recursiveDoEnabled flags = testBit flags recursiveDoBit unicodeSyntaxEnabled flags = testBit flags unicodeSyntaxBit +unboxedTuplesEnabled flags = testBit flags unboxedTuplesBit +standaloneDerivingEnabled flags = testBit flags standaloneDerivingBit -- PState for parsing options pragmas -- @@ -1579,11 +1586,11 @@ mkPState buf loc flags = loc = loc, extsBitmap = fromIntegral bitmap, context = [], - lex_state = [bol, if glaExtsEnabled bitmap then glaexts else 0] + lex_state = [bol, 0] -- we begin in the layout state if toplev_layout is set } where - bitmap = glaExtsBit `setBitIf` dopt Opt_GlasgowExts flags + bitmap = genericsBit `setBitIf` dopt Opt_Generics flags .|. ffiBit `setBitIf` dopt Opt_FFI flags .|. parrBit `setBitIf` dopt Opt_PArr flags .|. arrowsBit `setBitIf` dopt Opt_Arrows flags @@ -1591,6 +1598,9 @@ mkPState buf loc flags = .|. ipBit `setBitIf` dopt Opt_ImplicitParams flags .|. explicitForallBit `setBitIf` dopt Opt_ScopedTypeVariables flags .|. explicitForallBit `setBitIf` dopt Opt_PolymorphicComponents flags + .|. explicitForallBit `setBitIf` dopt Opt_ExistentialQuantification flags + .|. explicitForallBit `setBitIf` dopt Opt_Rank2Types flags + .|. explicitForallBit `setBitIf` dopt Opt_RankNTypes flags .|. bangPatBit `setBitIf` dopt Opt_BangPatterns flags .|. tyFamBit `setBitIf` dopt Opt_TypeFamilies flags .|. haddockBit `setBitIf` dopt Opt_Haddock flags @@ -1598,6 +1608,8 @@ mkPState buf loc flags = .|. kindSigsBit `setBitIf` dopt Opt_KindSignatures flags .|. recursiveDoBit `setBitIf` dopt Opt_RecursiveDo flags .|. unicodeSyntaxBit `setBitIf` dopt Opt_UnicodeSyntax flags + .|. unboxedTuplesBit `setBitIf` dopt Opt_UnboxedTuples flags + .|. standaloneDerivingBit `setBitIf` dopt Opt_StandaloneDeriving flags -- setBitIf :: Int -> Bool -> Int b `setBitIf` cond | cond = bit b