Add an extension for GHC's layout-rule relaxations
[ghc-hetmet.git] / compiler / parser / Lexer.x
index cadd56d..e52880b 100644 (file)
@@ -32,6 +32,7 @@
 
 {
 -- XXX The above flags turn off warnings in the generated code:
+{-# LANGUAGE BangPatterns #-}
 {-# OPTIONS_GHC -fno-warn-unused-matches #-}
 {-# OPTIONS_GHC -fno-warn-unused-binds #-}
 {-# OPTIONS_GHC -fno-warn-unused-imports #-}
@@ -66,6 +67,7 @@ import UniqFM
 import DynFlags
 import Module
 import Ctype
+import BasicTypes      ( InlineSpec(..), RuleMatchInfo(..) )
 import Util            ( readRational )
 
 import Control.Monad
@@ -139,7 +141,7 @@ haskell :-
 
 -- everywhere: skip whitespace and comments
 $white_no_nl+                          ;
-$tab+         { warn Opt_WarnTabs (text "Tab character") }
+$tab+         { warn Opt_WarnTabs (text "Warning: Tab character") }
 
 -- Everywhere: deal with nested comments.  We explicitly rule out
 -- pragmas, "{-#", so that we don't accidentally treat them as comments.
@@ -307,6 +309,10 @@ $tab+         { warn Opt_WarnTabs (text "Tab character") }
   \$ @varid / { ifExtension thEnabled }        { skip_one_varid ITidEscape }
   "$("     / { ifExtension thEnabled } { token ITparenEscape }
 
+-- For backward compatibility, accept the old dollar syntax
+  "[$" @varid "|"  / { ifExtension qqEnabled }
+                     { lex_quasiquote_tok }
+
   "[" @varid "|"  / { ifExtension qqEnabled }
                      { lex_quasiquote_tok }
 }
@@ -451,6 +457,7 @@ data Token
   | ITdynamic
   | ITsafe
   | ITthreadsafe
+  | ITinterruptible
   | ITunsafe
   | ITstdcallconv
   | ITccallconv
@@ -462,8 +469,7 @@ data Token
   | ITusing
 
        -- Pragmas
-  | ITinline_prag Bool         -- True <=> INLINE, False <=> NOINLINE
-  | ITinline_conlike_prag Bool  -- same
+  | ITinline_prag InlineSpec RuleMatchInfo
   | ITspec_prag                        -- SPECIALISE   
   | ITspec_inline_prag Bool    -- SPECIALISE INLINE (or NOINLINE)
   | ITsource_prag
@@ -596,6 +602,7 @@ isSpecial ITlabel           = True
 isSpecial ITdynamic    = True
 isSpecial ITsafe       = True
 isSpecial ITthreadsafe         = True
+isSpecial ITinterruptible = True
 isSpecial ITunsafe     = True
 isSpecial ITccallconv   = True
 isSpecial ITstdcallconv = True
@@ -658,6 +665,7 @@ reservedWordsFM = listToUFM $
        ( "dynamic",    ITdynamic,       bit ffiBit),
        ( "safe",       ITsafe,          bit ffiBit),
        ( "threadsafe", ITthreadsafe,    bit ffiBit),  -- ToDo: remove
+       ( "interruptible", ITinterruptible, bit ffiBit),
        ( "unsafe",     ITunsafe,        bit ffiBit),
        ( "stdcall",    ITstdcallconv,   bit ffiBit),
        ( "ccall",      ITccallconv,     bit ffiBit),
@@ -1099,10 +1107,12 @@ new_layout_context strict span _buf _len = do
     (AI l _) <- getInput
     let offset = srcLocCol l
     ctx <- getContext
+    relaxed <- extension relaxedLayout
+    let strict' = strict || not relaxed
     case ctx of
        Layout prev_off : _  | 
-          (strict     && prev_off >= offset  ||
-           not strict && prev_off > offset) -> do
+          (strict'     && prev_off >= offset  ||
+           not strict' && prev_off > offset) -> do
                -- token is indented to the left of the previous context.
                -- we must generate a {} sequence now.
                pushLexState layout_left
@@ -1753,6 +1763,8 @@ recBit :: Int
 recBit = 22 -- rec
 alternativeLayoutRuleBit :: Int
 alternativeLayoutRuleBit = 23
+relaxedLayoutBit :: Int
+relaxedLayoutBit = 24
 
 always :: Int -> Bool
 always           _     = True
@@ -1796,6 +1808,8 @@ oldQualOps :: Int -> Bool
 oldQualOps flags = not (newQualOps flags)
 alternativeLayoutRule :: Int -> Bool
 alternativeLayoutRule flags = testBit flags alternativeLayoutRuleBit
+relaxedLayout :: Int -> Bool
+relaxedLayout flags = testBit flags relaxedLayoutBit
 
 -- PState for parsing options pragmas
 --
@@ -1826,29 +1840,30 @@ mkPState flags buf loc =
       alr_justClosedExplicitLetBlock = False
     }
     where
-      bitmap = genericsBit `setBitIf` dopt Opt_Generics flags
-              .|. ffiBit            `setBitIf` dopt Opt_ForeignFunctionInterface flags
-              .|. parrBit           `setBitIf` dopt Opt_PArr         flags
-              .|. arrowsBit         `setBitIf` dopt Opt_Arrows       flags
-              .|. thBit             `setBitIf` dopt Opt_TemplateHaskell flags
-              .|. qqBit             `setBitIf` dopt Opt_QuasiQuotes flags
-              .|. ipBit             `setBitIf` dopt Opt_ImplicitParams flags
-              .|. explicitForallBit `setBitIf` dopt Opt_ExplicitForAll flags
-              .|. bangPatBit        `setBitIf` dopt Opt_BangPatterns flags
-              .|. tyFamBit          `setBitIf` dopt Opt_TypeFamilies flags
+      bitmap = genericsBit `setBitIf` xopt Opt_Generics flags
+              .|. ffiBit            `setBitIf` xopt Opt_ForeignFunctionInterface flags
+              .|. parrBit           `setBitIf` xopt Opt_PArr         flags
+              .|. arrowsBit         `setBitIf` xopt Opt_Arrows       flags
+              .|. thBit             `setBitIf` xopt Opt_TemplateHaskell flags
+              .|. qqBit             `setBitIf` xopt Opt_QuasiQuotes flags
+              .|. ipBit             `setBitIf` xopt Opt_ImplicitParams flags
+              .|. explicitForallBit `setBitIf` xopt Opt_ExplicitForAll flags
+              .|. bangPatBit        `setBitIf` xopt Opt_BangPatterns flags
+              .|. tyFamBit          `setBitIf` xopt Opt_TypeFamilies flags
               .|. haddockBit        `setBitIf` dopt Opt_Haddock      flags
-              .|. magicHashBit      `setBitIf` dopt Opt_MagicHash    flags
-              .|. kindSigsBit       `setBitIf` dopt Opt_KindSignatures flags
-              .|. recursiveDoBit    `setBitIf` dopt Opt_RecursiveDo flags
-              .|. recBit            `setBitIf` dopt Opt_DoRec  flags
-              .|. recBit            `setBitIf` dopt Opt_Arrows flags
-              .|. unicodeSyntaxBit  `setBitIf` dopt Opt_UnicodeSyntax flags
-              .|. unboxedTuplesBit  `setBitIf` dopt Opt_UnboxedTuples flags
-               .|. datatypeContextsBit `setBitIf` dopt Opt_DatatypeContexts flags
-               .|. transformComprehensionsBit `setBitIf` dopt Opt_TransformListComp flags
+              .|. magicHashBit      `setBitIf` xopt Opt_MagicHash    flags
+              .|. kindSigsBit       `setBitIf` xopt Opt_KindSignatures flags
+              .|. recursiveDoBit    `setBitIf` xopt Opt_RecursiveDo flags
+              .|. recBit            `setBitIf` xopt Opt_DoRec  flags
+              .|. recBit            `setBitIf` xopt Opt_Arrows flags
+              .|. unicodeSyntaxBit  `setBitIf` xopt Opt_UnicodeSyntax flags
+              .|. unboxedTuplesBit  `setBitIf` xopt Opt_UnboxedTuples flags
+               .|. datatypeContextsBit `setBitIf` xopt Opt_DatatypeContexts flags
+               .|. transformComprehensionsBit `setBitIf` xopt Opt_TransformListComp flags
                .|. rawTokenStreamBit `setBitIf` dopt Opt_KeepRawTokenStream flags
-               .|. newQualOpsBit `setBitIf` dopt Opt_NewQualifiedOperators flags
-               .|. alternativeLayoutRuleBit `setBitIf` dopt Opt_AlternativeLayoutRule flags
+               .|. newQualOpsBit `setBitIf` xopt Opt_NewQualifiedOperators flags
+               .|. alternativeLayoutRuleBit `setBitIf` xopt Opt_AlternativeLayoutRule flags
+               .|. relaxedLayoutBit `setBitIf` xopt Opt_RelaxedLayout flags
       --
       setBitIf :: Int -> Bool -> Int
       b `setBitIf` cond | cond      = bit b
@@ -1966,7 +1981,7 @@ alternativeLayoutRuleToken t
          justClosedExplicitLetBlock <- getJustClosedExplicitLetBlock
          setJustClosedExplicitLetBlock False
          dflags <- getDynFlags
-         let transitional = dopt Opt_AlternativeLayoutRuleTransitional dflags
+         let transitional = xopt Opt_AlternativeLayoutRuleTransitional dflags
              thisLoc = getLoc t
              thisCol = srcSpanStartCol thisLoc
              newLine = (lastLoc == noSrcSpan)
@@ -2216,8 +2231,11 @@ ignoredPrags = Map.fromList (map ignored pragmas)
                      pragmas = options_pragmas ++ ["cfiles", "contract"]
 
 oneWordPrags = Map.fromList([("rules", rulePrag),
-                           ("inline", token (ITinline_prag True)),
-                           ("notinline", token (ITinline_prag False)),
+                           ("inline", token (ITinline_prag Inline FunLike)),
+                           ("inlinable", token (ITinline_prag Inlinable FunLike)),
+                           ("inlineable", token (ITinline_prag Inlinable FunLike)),
+                                         -- Spelling variant
+                           ("notinline", token (ITinline_prag NoInline FunLike)),
                            ("specialize", token ITspec_prag),
                            ("source", token ITsource_prag),
                            ("warning", token ITwarning_prag),
@@ -2228,8 +2246,8 @@ oneWordPrags = Map.fromList([("rules", rulePrag),
                            ("unpack", token ITunpack_prag),
                            ("ann", token ITann_prag)])
 
-twoWordPrags = Map.fromList([("inline conlike", token (ITinline_conlike_prag True)),
-                             ("notinline conlike", token (ITinline_conlike_prag False)),
+twoWordPrags = Map.fromList([("inline conlike", token (ITinline_prag Inline ConLike)),
+                             ("notinline conlike", token (ITinline_prag NoInline ConLike)),
                              ("specialize inline", token (ITspec_inline_prag True)),
                              ("specialize notinline", token (ITspec_inline_prag False))])