X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fparser%2FLexer.x;h=66f4fe51366d36d60087e99ef2b32eba25c2f8cb;hp=b9abf7a848174379cc63958db21504033bfed75a;hb=c0f542271da944d540faf91678c48ff856174b57;hpb=0c266d7ac54ae27e693ef04e4679220a32da0694 diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index b9abf7a..66f4fe5 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -31,6 +31,8 @@ -- Note that Alex itself generates code with with some unused bindings and -- without type signatures, so removing the flag might not be possible. +{-# OPTIONS_GHC -funbox-strict-fields #-} + module Lexer ( Token(..), lexer, pragState, mkPState, PState(..), P(..), ParseResult(..), getSrcLoc, @@ -225,16 +227,8 @@ $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 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) --- 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> { + "{-#" $whitechar* (RULES|rules) { token ITrules_prag } "{-#" $whitechar* (INLINE|inline) { token (ITinline_prag True) } "{-#" $whitechar* (NO(T?)INLINE|no(t?)inline) { token (ITinline_prag False) } @@ -246,6 +240,8 @@ $tab+ { warn Opt_WarnTabs (text "Tab character") } $whitechar* (NO(T?)INLINE|no(t?)inline) { token (ITspec_inline_prag False) } "{-#" $whitechar* (SOURCE|source) { token ITsource_prag } + "{-#" $whitechar* (WARNING|warning) + { token ITwarning_prag } "{-#" $whitechar* (DEPRECATED|deprecated) { token ITdeprecated_prag } "{-#" $whitechar* (SCC|scc) { token ITscc_prag } @@ -254,10 +250,13 @@ $tab+ { warn Opt_WarnTabs (text "Tab character") } "{-#" $whitechar* (CORE|core) { token ITcore_prag } "{-#" $whitechar* (UNPACK|unpack) { token ITunpack_prag } - "{-#" { nested_comment lexToken } + -- We ignore all these pragmas, but don't generate a warning for them + -- CFILES is a hugs-only thing. + "{-#" $whitechar* (OPTIONS_HUGS|options_hugs|OPTIONS_NHC98|options_nhc98|OPTIONS_JHC|options_jhc|CFILES|cfiles) + { nested_comment lexToken } -- ToDo: should only be valid inside a pragma: - "#-}" { token ITclose_prag} + "#-}" { endPrag } } { @@ -272,12 +271,18 @@ $tab+ { warn Opt_WarnTabs (text "Tab character") } } <0> { + -- In the "0" mode we ignore these pragmas + "{-#" $whitechar* (OPTIONS|options|OPTIONS_GHC|options_ghc|OPTIONS_HADDOCK|options_haddock|LANGUAGE|language|INCLUDE|include) + { nested_comment lexToken } +} + +<0> { "-- #" .* ; } <0,option_prags> { - -- This is to catch things like {-# OPTIONS OPTIONS_HUGS ... - "{-#" $whitechar* $idchar+ { nested_comment lexToken } + "{-#" { warnThen Opt_WarnUnrecognisedPragmas (text "Unrecognised pragma") + (nested_comment lexToken) } } -- '0' state: ordinary lexemes @@ -464,6 +469,7 @@ data Token | ITspec_inline_prag Bool -- SPECIALISE INLINE (or NOINLINE) | ITsource_prag | ITrules_prag + | ITwarning_prag | ITdeprecated_prag | ITline_prag | ITscc_prag @@ -635,7 +641,7 @@ reservedWordsFM = listToUFM $ ( "where", ITwhere, 0 ), ( "_scc_", ITscc, 0 ), -- ToDo: remove - ( "forall", ITforall, bit explicitForallBit), + ( "forall", ITforall, bit explicitForallBit .|. bit inRulePragBit), ( "mdo", ITmdo, bit recursiveDoBit), ( "family", ITfamily, bit tyFamBit), ( "group", ITgroup, bit transformComprehensionsBit), @@ -678,7 +684,7 @@ reservedSymsFM = listToUFM $ -- For data T (a::*) = MkT ,("*", ITstar, \i -> kindSigsEnabled i || tyFamEnabled i) -- For 'forall a . t' - ,(".", ITdot, explicitForallEnabled) + ,(".", ITdot, \i -> explicitForallEnabled i || inRulePrag i) ,("-<", ITlarrowtail, arrowsEnabled) ,(">-", ITrarrowtail, arrowsEnabled) @@ -851,6 +857,18 @@ withLexedDocType lexDocComment = do Just (_, _) -> lexDocComment input (ITdocSection n) True Nothing -> do setInput input; lexToken -- eof reached, lex it normally +-- RULES pragmas turn on the forall and '.' keywords, and we turn them +-- off again at the end of the pragma. +rulePrag :: Action +rulePrag span buf len = do + setExts (.|. inRulePragBit) + return (L span ITrules_prag) + +endPrag :: Action +endPrag span buf len = do + setExts (.&. complement (bit inRulePragBit)) + return (L span ITclose_prag) + -- docCommentEnd ------------------------------------------------------------------------------- -- This function is quite tricky. We can't just return a new token, we also @@ -1373,6 +1391,11 @@ warn option warning srcspan _buf _len = do addWarning option srcspan warning lexToken +warnThen :: DynFlag -> SDoc -> Action -> Action +warnThen option warning action srcspan buf len = do + addWarning option srcspan warning + action srcspan buf len + -- ----------------------------------------------------------------------------- -- The Parse Monad @@ -1444,6 +1467,9 @@ extension p = P $ \s -> POk s (p $! extsBitmap s) getExts :: P Int getExts = P $ \s -> POk s (extsBitmap s) +setExts :: (Int -> Int) -> P () +setExts f = P $ \s -> POk s{ extsBitmap = f (extsBitmap s) } () + setSrcLoc :: SrcLoc -> P () setSrcLoc new_loc = P $ \s -> POk s{loc=new_loc} () @@ -1561,7 +1587,7 @@ bangPatBit = 8 -- Tells the parser to understand bang-patterns -- (doesn't affect the lexer) tyFamBit = 9 -- indexed type families: 'family' keyword and kind sigs haddockBit = 10 -- Lex and parse Haddock comments -magicHashBit = 11 -- # in both functions and operators +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 @@ -1569,6 +1595,7 @@ unboxedTuplesBit = 15 -- (# and #) standaloneDerivingBit = 16 -- standalone instance deriving declarations transformComprehensionsBit = 17 qqBit = 18 -- enable quasiquoting +inRulePragBit = 19 genericsEnabled, ffiEnabled, parrEnabled :: Int -> Bool always _ = True @@ -1590,6 +1617,7 @@ unboxedTuplesEnabled flags = testBit flags unboxedTuplesBit standaloneDerivingEnabled flags = testBit flags standaloneDerivingBit transformComprehensionsEnabled flags = testBit flags transformComprehensionsBit qqEnabled flags = testBit flags qqBit +inRulePrag flags = testBit flags inRulePragBit -- PState for parsing options pragmas -- @@ -1637,6 +1665,7 @@ mkPState buf loc flags = .|. qqBit `setBitIf` dopt Opt_QuasiQuotes flags .|. ipBit `setBitIf` dopt Opt_ImplicitParams flags .|. explicitForallBit `setBitIf` dopt Opt_ScopedTypeVariables flags + .|. explicitForallBit `setBitIf` dopt Opt_LiberalTypeSynonyms flags .|. explicitForallBit `setBitIf` dopt Opt_PolymorphicComponents flags .|. explicitForallBit `setBitIf` dopt Opt_ExistentialQuantification flags .|. explicitForallBit `setBitIf` dopt Opt_Rank2Types flags