diff options
Diffstat (limited to 'compiler/GHC')
-rw-r--r-- | compiler/GHC/Driver/Session.hs | 1 | ||||
-rw-r--r-- | compiler/GHC/Hs/Lit.hs | 40 | ||||
-rw-r--r-- | compiler/GHC/Hs/Syn/Type.hs | 6 | ||||
-rw-r--r-- | compiler/GHC/HsToCore/Match/Literal.hs | 27 | ||||
-rw-r--r-- | compiler/GHC/Parser.y | 112 | ||||
-rw-r--r-- | compiler/GHC/Parser/Lexer.x | 195 |
6 files changed, 308 insertions, 73 deletions
diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs index 46290d4ade..544e9ece56 100644 --- a/compiler/GHC/Driver/Session.hs +++ b/compiler/GHC/Driver/Session.hs @@ -3745,6 +3745,7 @@ xFlagsDeps = [ flagSpec "ExplicitForAll" LangExt.ExplicitForAll, flagSpec "ExplicitNamespaces" LangExt.ExplicitNamespaces, flagSpec "ExtendedDefaultRules" LangExt.ExtendedDefaultRules, + flagSpec "ExtendedLiterals" LangExt.ExtendedLiterals, flagSpec "FlexibleContexts" LangExt.FlexibleContexts, flagSpec "FlexibleInstances" LangExt.FlexibleInstances, flagSpec "ForeignFunctionInterface" LangExt.ForeignFunctionInterface, diff --git a/compiler/GHC/Hs/Lit.hs b/compiler/GHC/Hs/Lit.hs index 7d2df811ee..d6c59cc927 100644 --- a/compiler/GHC/Hs/Lit.hs +++ b/compiler/GHC/Hs/Lit.hs @@ -50,7 +50,13 @@ type instance XHsStringPrim (GhcPass _) = SourceText type instance XHsInt (GhcPass _) = NoExtField type instance XHsIntPrim (GhcPass _) = SourceText type instance XHsWordPrim (GhcPass _) = SourceText +type instance XHsInt8Prim (GhcPass _) = SourceText +type instance XHsInt16Prim (GhcPass _) = SourceText +type instance XHsInt32Prim (GhcPass _) = SourceText type instance XHsInt64Prim (GhcPass _) = SourceText +type instance XHsWord8Prim (GhcPass _) = SourceText +type instance XHsWord16Prim (GhcPass _) = SourceText +type instance XHsWord32Prim (GhcPass _) = SourceText type instance XHsWord64Prim (GhcPass _) = SourceText type instance XHsInteger (GhcPass _) = SourceText type instance XHsRat (GhcPass _) = NoExtField @@ -128,14 +134,20 @@ hsLitNeedsParens p = go go (HsString {}) = False go (HsStringPrim {}) = False go (HsInt _ x) = p > topPrec && il_neg x - go (HsIntPrim {}) = False - go (HsWordPrim {}) = False - go (HsInt64Prim {}) = False - go (HsWord64Prim {}) = False go (HsInteger _ x _) = p > topPrec && x < 0 go (HsRat _ x _) = p > topPrec && fl_neg x go (HsFloatPrim {}) = False go (HsDoublePrim {}) = False + go (HsIntPrim {}) = False + go (HsInt8Prim {}) = False + go (HsInt16Prim {}) = False + go (HsInt32Prim {}) = False + go (HsInt64Prim {}) = False + go (HsWordPrim {}) = False + go (HsWord8Prim {}) = False + go (HsWord16Prim {}) = False + go (HsWord64Prim {}) = False + go (HsWord32Prim {}) = False go (XLit _) = False -- | Convert a literal from one index type to another @@ -147,7 +159,13 @@ convertLit (HsStringPrim a x) = HsStringPrim a x convertLit (HsInt a x) = HsInt a x convertLit (HsIntPrim a x) = HsIntPrim a x convertLit (HsWordPrim a x) = HsWordPrim a x +convertLit (HsInt8Prim a x) = HsInt8Prim a x +convertLit (HsInt16Prim a x) = HsInt16Prim a x +convertLit (HsInt32Prim a x) = HsInt32Prim a x convertLit (HsInt64Prim a x) = HsInt64Prim a x +convertLit (HsWord8Prim a x) = HsWord8Prim a x +convertLit (HsWord16Prim a x) = HsWord16Prim a x +convertLit (HsWord32Prim a x) = HsWord32Prim a x convertLit (HsWord64Prim a x) = HsWord64Prim a x convertLit (HsInteger a x b) = HsInteger a x b convertLit (HsRat a x b) = HsRat a x b @@ -182,8 +200,14 @@ instance Outputable (HsLit (GhcPass p)) where ppr (HsFloatPrim _ f) = ppr f <> primFloatSuffix ppr (HsDoublePrim _ d) = ppr d <> primDoubleSuffix ppr (HsIntPrim st i) = pprWithSourceText st (pprPrimInt i) - ppr (HsWordPrim st w) = pprWithSourceText st (pprPrimWord w) + ppr (HsInt8Prim st i) = pprWithSourceText st (pprPrimInt8 i) + ppr (HsInt16Prim st i) = pprWithSourceText st (pprPrimInt16 i) + ppr (HsInt32Prim st i) = pprWithSourceText st (pprPrimInt32 i) ppr (HsInt64Prim st i) = pprWithSourceText st (pprPrimInt64 i) + ppr (HsWordPrim st w) = pprWithSourceText st (pprPrimWord w) + ppr (HsWord8Prim st w) = pprWithSourceText st (pprPrimWord8 w) + ppr (HsWord16Prim st w) = pprWithSourceText st (pprPrimWord16 w) + ppr (HsWord32Prim st w) = pprWithSourceText st (pprPrimWord32 w) ppr (HsWord64Prim st w) = pprWithSourceText st (pprPrimWord64 w) -- in debug mode, print the expression that it's resolved to, too @@ -211,7 +235,13 @@ pmPprHsLit (HsStringPrim _ s) = pprHsBytes s pmPprHsLit (HsInt _ i) = integer (il_value i) pmPprHsLit (HsIntPrim _ i) = integer i pmPprHsLit (HsWordPrim _ w) = integer w +pmPprHsLit (HsInt8Prim _ i) = integer i +pmPprHsLit (HsInt16Prim _ i) = integer i +pmPprHsLit (HsInt32Prim _ i) = integer i pmPprHsLit (HsInt64Prim _ i) = integer i +pmPprHsLit (HsWord8Prim _ w) = integer w +pmPprHsLit (HsWord16Prim _ w) = integer w +pmPprHsLit (HsWord32Prim _ w) = integer w pmPprHsLit (HsWord64Prim _ w) = integer w pmPprHsLit (HsInteger _ i _) = integer i pmPprHsLit (HsRat _ f _) = ppr f diff --git a/compiler/GHC/Hs/Syn/Type.hs b/compiler/GHC/Hs/Syn/Type.hs index a7e21d2458..edcdc39ea0 100644 --- a/compiler/GHC/Hs/Syn/Type.hs +++ b/compiler/GHC/Hs/Syn/Type.hs @@ -77,7 +77,13 @@ hsLitType (HsStringPrim _ _) = addrPrimTy hsLitType (HsInt _ _) = intTy hsLitType (HsIntPrim _ _) = intPrimTy hsLitType (HsWordPrim _ _) = wordPrimTy +hsLitType (HsInt8Prim _ _) = int8PrimTy +hsLitType (HsInt16Prim _ _) = int16PrimTy +hsLitType (HsInt32Prim _ _) = int32PrimTy hsLitType (HsInt64Prim _ _) = int64PrimTy +hsLitType (HsWord8Prim _ _) = word8PrimTy +hsLitType (HsWord16Prim _ _) = word16PrimTy +hsLitType (HsWord32Prim _ _) = word32PrimTy hsLitType (HsWord64Prim _ _) = word64PrimTy hsLitType (HsInteger _ _ ty) = ty hsLitType (HsRat _ _ ty) = ty diff --git a/compiler/GHC/HsToCore/Match/Literal.hs b/compiler/GHC/HsToCore/Match/Literal.hs index 1c21f2a5e6..b44f325b60 100644 --- a/compiler/GHC/HsToCore/Match/Literal.hs +++ b/compiler/GHC/HsToCore/Match/Literal.hs @@ -106,7 +106,13 @@ dsLit l = do HsCharPrim _ c -> return (Lit (LitChar c)) HsIntPrim _ i -> return (Lit (mkLitIntWrap platform i)) HsWordPrim _ w -> return (Lit (mkLitWordWrap platform w)) + HsInt8Prim _ i -> return (Lit (mkLitInt8Wrap i)) + HsInt16Prim _ i -> return (Lit (mkLitInt16Wrap i)) + HsInt32Prim _ i -> return (Lit (mkLitInt32Wrap i)) HsInt64Prim _ i -> return (Lit (mkLitInt64Wrap i)) + HsWord8Prim _ w -> return (Lit (mkLitWord8Wrap w)) + HsWord16Prim _ w -> return (Lit (mkLitWord16Wrap w)) + HsWord32Prim _ w -> return (Lit (mkLitWord32Wrap w)) HsWord64Prim _ w -> return (Lit (mkLitWord64Wrap w)) -- This can be slow for very large literals. See Note [FractionalLit representation] @@ -455,10 +461,23 @@ getSimpleIntegralLit :: HsLit GhcTc -> Maybe (Integer, Type) getSimpleIntegralLit (HsInt _ IL{ il_value = i }) = Just (i, intTy) getSimpleIntegralLit (HsIntPrim _ i) = Just (i, intPrimTy) getSimpleIntegralLit (HsWordPrim _ i) = Just (i, wordPrimTy) +getSimpleIntegralLit (HsInt8Prim _ i) = Just (i, int8PrimTy) +getSimpleIntegralLit (HsInt16Prim _ i) = Just (i, int16PrimTy) +getSimpleIntegralLit (HsInt32Prim _ i) = Just (i, int32PrimTy) getSimpleIntegralLit (HsInt64Prim _ i) = Just (i, int64PrimTy) +getSimpleIntegralLit (HsWord8Prim _ i) = Just (i, word8PrimTy) +getSimpleIntegralLit (HsWord16Prim _ i) = Just (i, word16PrimTy) +getSimpleIntegralLit (HsWord32Prim _ i) = Just (i, word32PrimTy) getSimpleIntegralLit (HsWord64Prim _ i) = Just (i, word64PrimTy) getSimpleIntegralLit (HsInteger _ i ty) = Just (i, ty) -getSimpleIntegralLit _ = Nothing + +getSimpleIntegralLit HsChar{} = Nothing +getSimpleIntegralLit HsCharPrim{} = Nothing +getSimpleIntegralLit HsString{} = Nothing +getSimpleIntegralLit HsStringPrim{} = Nothing +getSimpleIntegralLit HsRat{} = Nothing +getSimpleIntegralLit HsFloatPrim{} = Nothing +getSimpleIntegralLit HsDoublePrim{} = Nothing -- | Extract the Char if the expression is a Char literal. getLHsCharLit :: LHsExpr GhcTc -> Maybe Char @@ -638,7 +657,13 @@ hsLitKey :: Platform -> HsLit GhcTc -> Literal -- HsLit does not. hsLitKey platform (HsIntPrim _ i) = mkLitIntWrap platform i hsLitKey platform (HsWordPrim _ w) = mkLitWordWrap platform w +hsLitKey _ (HsInt8Prim _ i) = mkLitInt8Wrap i +hsLitKey _ (HsInt16Prim _ i) = mkLitInt16Wrap i +hsLitKey _ (HsInt32Prim _ i) = mkLitInt32Wrap i hsLitKey _ (HsInt64Prim _ i) = mkLitInt64Wrap i +hsLitKey _ (HsWord8Prim _ w) = mkLitWord8Wrap w +hsLitKey _ (HsWord16Prim _ w) = mkLitWord16Wrap w +hsLitKey _ (HsWord32Prim _ w) = mkLitWord32Wrap w hsLitKey _ (HsWord64Prim _ w) = mkLitWord64Wrap w hsLitKey _ (HsCharPrim _ c) = mkLitChar c -- This following two can be slow. See Note [FractionalLit representation] diff --git a/compiler/GHC/Parser.y b/compiler/GHC/Parser.y index bbbc12df56..310210b5e9 100644 --- a/compiler/GHC/Parser.y +++ b/compiler/GHC/Parser.y @@ -718,6 +718,14 @@ are the most common patterns, rewritten as regular expressions for clarity: PRIMSTRING { L _ (ITprimstring _ _) } PRIMINTEGER { L _ (ITprimint _ _) } PRIMWORD { L _ (ITprimword _ _) } + PRIMINTEGER8 { L _ (ITprimint8 _ _) } + PRIMINTEGER16 { L _ (ITprimint16 _ _) } + PRIMINTEGER32 { L _ (ITprimint32 _ _) } + PRIMINTEGER64 { L _ (ITprimint64 _ _) } + PRIMWORD8 { L _ (ITprimword8 _ _) } + PRIMWORD16 { L _ (ITprimword16 _ _) } + PRIMWORD32 { L _ (ITprimword32 _ _) } + PRIMWORD64 { L _ (ITprimword64 _ _) } PRIMFLOAT { L _ (ITprimfloat _) } PRIMDOUBLE { L _ (ITprimdouble _) } @@ -3876,6 +3884,22 @@ literal :: { Located (HsLit GhcPs) } $ getPRIMINTEGER $1 } | PRIMWORD { sL1 $1 $ HsWordPrim (getPRIMWORDs $1) $ getPRIMWORD $1 } + | PRIMINTEGER8 { sL1 $1 $ HsInt8Prim (getPRIMINTEGER8s $1) + $ getPRIMINTEGER8 $1 } + | PRIMINTEGER16 { sL1 $1 $ HsInt16Prim (getPRIMINTEGER16s $1) + $ getPRIMINTEGER16 $1 } + | PRIMINTEGER32 { sL1 $1 $ HsInt32Prim (getPRIMINTEGER32s $1) + $ getPRIMINTEGER32 $1 } + | PRIMINTEGER64 { sL1 $1 $ HsInt64Prim (getPRIMINTEGER64s $1) + $ getPRIMINTEGER64 $1 } + | PRIMWORD8 { sL1 $1 $ HsWord8Prim (getPRIMWORD8s $1) + $ getPRIMWORD8 $1 } + | PRIMWORD16 { sL1 $1 $ HsWord16Prim (getPRIMWORD16s $1) + $ getPRIMWORD16 $1 } + | PRIMWORD32 { sL1 $1 $ HsWord32Prim (getPRIMWORD32s $1) + $ getPRIMWORD32 $1 } + | PRIMWORD64 { sL1 $1 $ HsWord64Prim (getPRIMWORD64s $1) + $ getPRIMWORD64 $1 } | PRIMCHAR { sL1 $1 $ HsCharPrim (getPRIMCHARs $1) $ getPRIMCHAR $1 } | PRIMSTRING { sL1 $1 $ HsStringPrim (getPRIMSTRINGs $1) @@ -3916,43 +3940,59 @@ bars :: { ([SrcSpan],Int) } -- One or more bars happyError :: P a happyError = srcParseFail -getVARID (L _ (ITvarid x)) = x -getCONID (L _ (ITconid x)) = x -getVARSYM (L _ (ITvarsym x)) = x -getCONSYM (L _ (ITconsym x)) = x -getDO (L _ (ITdo x)) = x -getMDO (L _ (ITmdo x)) = x -getQVARID (L _ (ITqvarid x)) = x -getQCONID (L _ (ITqconid x)) = x -getQVARSYM (L _ (ITqvarsym x)) = x -getQCONSYM (L _ (ITqconsym x)) = x -getIPDUPVARID (L _ (ITdupipvarid x)) = x -getLABELVARID (L _ (ITlabelvarid _ x)) = x -getCHAR (L _ (ITchar _ x)) = x -getSTRING (L _ (ITstring _ x)) = x -getINTEGER (L _ (ITinteger x)) = x -getRATIONAL (L _ (ITrational x)) = x -getPRIMCHAR (L _ (ITprimchar _ x)) = x -getPRIMSTRING (L _ (ITprimstring _ x)) = x -getPRIMINTEGER (L _ (ITprimint _ x)) = x -getPRIMWORD (L _ (ITprimword _ x)) = x -getPRIMFLOAT (L _ (ITprimfloat x)) = x -getPRIMDOUBLE (L _ (ITprimdouble x)) = x -getINLINE (L _ (ITinline_prag _ inl conl)) = (inl,conl) -getSPEC_INLINE (L _ (ITspec_inline_prag src True)) = (Inline src,FunLike) -getSPEC_INLINE (L _ (ITspec_inline_prag src False)) = (NoInline src,FunLike) +getVARID (L _ (ITvarid x)) = x +getCONID (L _ (ITconid x)) = x +getVARSYM (L _ (ITvarsym x)) = x +getCONSYM (L _ (ITconsym x)) = x +getDO (L _ (ITdo x)) = x +getMDO (L _ (ITmdo x)) = x +getQVARID (L _ (ITqvarid x)) = x +getQCONID (L _ (ITqconid x)) = x +getQVARSYM (L _ (ITqvarsym x)) = x +getQCONSYM (L _ (ITqconsym x)) = x +getIPDUPVARID (L _ (ITdupipvarid x)) = x +getLABELVARID (L _ (ITlabelvarid _ x)) = x +getCHAR (L _ (ITchar _ x)) = x +getSTRING (L _ (ITstring _ x)) = x +getINTEGER (L _ (ITinteger x)) = x +getRATIONAL (L _ (ITrational x)) = x +getPRIMCHAR (L _ (ITprimchar _ x)) = x +getPRIMSTRING (L _ (ITprimstring _ x)) = x +getPRIMINTEGER (L _ (ITprimint _ x)) = x +getPRIMWORD (L _ (ITprimword _ x)) = x +getPRIMINTEGER8 (L _ (ITprimint8 _ x)) = x +getPRIMINTEGER16 (L _ (ITprimint16 _ x)) = x +getPRIMINTEGER32 (L _ (ITprimint32 _ x)) = x +getPRIMINTEGER64 (L _ (ITprimint64 _ x)) = x +getPRIMWORD8 (L _ (ITprimword8 _ x)) = x +getPRIMWORD16 (L _ (ITprimword16 _ x)) = x +getPRIMWORD32 (L _ (ITprimword32 _ x)) = x +getPRIMWORD64 (L _ (ITprimword64 _ x)) = x +getPRIMFLOAT (L _ (ITprimfloat x)) = x +getPRIMDOUBLE (L _ (ITprimdouble x)) = x +getINLINE (L _ (ITinline_prag _ inl conl)) = (inl,conl) +getSPEC_INLINE (L _ (ITspec_inline_prag src True)) = (Inline src,FunLike) +getSPEC_INLINE (L _ (ITspec_inline_prag src False)) = (NoInline src,FunLike) getCOMPLETE_PRAGs (L _ (ITcomplete_prag x)) = x -getVOCURLY (L (RealSrcSpan l _) ITvocurly) = srcSpanStartCol l - -getINTEGERs (L _ (ITinteger (IL src _ _))) = src -getCHARs (L _ (ITchar src _)) = src -getSTRINGs (L _ (ITstring src _)) = src -getPRIMCHARs (L _ (ITprimchar src _)) = src -getPRIMSTRINGs (L _ (ITprimstring src _)) = src -getPRIMINTEGERs (L _ (ITprimint src _)) = src -getPRIMWORDs (L _ (ITprimword src _)) = src - -getLABELVARIDs (L _ (ITlabelvarid src _)) = src +getVOCURLY (L (RealSrcSpan l _) ITvocurly) = srcSpanStartCol l + +getINTEGERs (L _ (ITinteger (IL src _ _))) = src +getCHARs (L _ (ITchar src _)) = src +getSTRINGs (L _ (ITstring src _)) = src +getPRIMCHARs (L _ (ITprimchar src _)) = src +getPRIMSTRINGs (L _ (ITprimstring src _)) = src +getPRIMINTEGERs (L _ (ITprimint src _)) = src +getPRIMWORDs (L _ (ITprimword src _)) = src +getPRIMINTEGER8s (L _ (ITprimint8 src _)) = src +getPRIMINTEGER16s (L _ (ITprimint16 src _)) = src +getPRIMINTEGER32s (L _ (ITprimint32 src _)) = src +getPRIMINTEGER64s (L _ (ITprimint64 src _)) = src +getPRIMWORD8s (L _ (ITprimword8 src _)) = src +getPRIMWORD16s (L _ (ITprimword16 src _)) = src +getPRIMWORD32s (L _ (ITprimword32 src _)) = src +getPRIMWORD64s (L _ (ITprimword64 src _)) = src + +getLABELVARIDs (L _ (ITlabelvarid src _)) = src -- See Note [Pragma source text] in "GHC.Types.SourceText" for the following getINLINE_PRAGs (L _ (ITinline_prag _ inl _)) = inlineSpecSource inl diff --git a/compiler/GHC/Parser/Lexer.x b/compiler/GHC/Parser/Lexer.x index 380a30ca78..48a1a367c2 100644 --- a/compiler/GHC/Parser/Lexer.x +++ b/compiler/GHC/Parser/Lexer.x @@ -194,6 +194,10 @@ $docsym = [\| \^ \* \$] @exponent = @numspc [eE] [\-\+]? @decimal @bin_exponent = @numspc [pP] [\-\+]? @decimal +@binarylit = 0[bB] @numspc @binary +@octallit = 0[oO] @numspc @octal +@hexadecimallit = 0[xX] @numspc @hexadecimal + @qual = (@conid \.)+ @qvarid = @qual @varid @qconid = @qual @conid @@ -517,15 +521,15 @@ $unigraphic / { isSmartQuote } { smart_quote_error } -- <0> { -- Normal integral literals (:: Num a => a, from Integer) - @decimal { tok_num positive 0 0 decimal } - 0[bB] @numspc @binary / { ifExtension BinaryLiteralsBit } { tok_num positive 2 2 binary } - 0[oO] @numspc @octal { tok_num positive 2 2 octal } - 0[xX] @numspc @hexadecimal { tok_num positive 2 2 hexadecimal } - @negative @decimal / { negLitPred } { tok_num negative 1 1 decimal } - @negative 0[bB] @numspc @binary / { negLitPred `alexAndPred` - ifExtension BinaryLiteralsBit } { tok_num negative 3 3 binary } - @negative 0[oO] @numspc @octal / { negLitPred } { tok_num negative 3 3 octal } - @negative 0[xX] @numspc @hexadecimal / { negLitPred } { tok_num negative 3 3 hexadecimal } + @decimal { tok_num positive 0 0 decimal } + @binarylit / { ifExtension BinaryLiteralsBit } { tok_num positive 2 2 binary } + @octallit { tok_num positive 2 2 octal } + @hexadecimallit { tok_num positive 2 2 hexadecimal } + @negative @decimal / { negLitPred } { tok_num negative 1 1 decimal } + @negative @binarylit / { negLitPred `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_num negative 3 3 binary } + @negative @octallit / { negLitPred } { tok_num negative 3 3 octal } + @negative @hexadecimallit / { negLitPred } { tok_num negative 3 3 hexadecimal } -- Normal rational literals (:: Fractional a => a, from Rational) @floating_point { tok_frac 0 tok_float } @@ -540,31 +544,116 @@ $unigraphic / { isSmartQuote } { smart_quote_error } -- Unboxed ints (:: Int#) and words (:: Word#) -- It's simpler (and faster?) to give separate cases to the negatives, -- especially considering octal/hexadecimal prefixes. - @decimal \# / { ifExtension MagicHashBit } { tok_primint positive 0 1 decimal } - 0[bB] @numspc @binary \# / { ifExtension MagicHashBit `alexAndPred` - ifExtension BinaryLiteralsBit } { tok_primint positive 2 3 binary } - 0[oO] @numspc @octal \# / { ifExtension MagicHashBit } { tok_primint positive 2 3 octal } - 0[xX] @numspc @hexadecimal \# / { ifExtension MagicHashBit } { tok_primint positive 2 3 hexadecimal } - @negative @decimal \# / { negHashLitPred } { tok_primint negative 1 2 decimal } - @negative 0[bB] @numspc @binary \# / { negHashLitPred `alexAndPred` - ifExtension BinaryLiteralsBit } { tok_primint negative 3 4 binary } - @negative 0[oO] @numspc @octal \# / { negHashLitPred } { tok_primint negative 3 4 octal } - @negative 0[xX] @numspc @hexadecimal \# - / { negHashLitPred } { tok_primint negative 3 4 hexadecimal } - - @decimal \# \# / { ifExtension MagicHashBit } { tok_primword 0 2 decimal } - 0[bB] @numspc @binary \# \# / { ifExtension MagicHashBit `alexAndPred` - ifExtension BinaryLiteralsBit } { tok_primword 2 4 binary } - 0[oO] @numspc @octal \# \# / { ifExtension MagicHashBit } { tok_primword 2 4 octal } - 0[xX] @numspc @hexadecimal \# \# / { ifExtension MagicHashBit } { tok_primword 2 4 hexadecimal } + @decimal \# / { ifExtension MagicHashBit } { tok_primint positive 0 1 decimal } + @binarylit \# / { ifExtension MagicHashBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primint positive 2 3 binary } + @octallit \# / { ifExtension MagicHashBit } { tok_primint positive 2 3 octal } + @hexadecimallit \# / { ifExtension MagicHashBit } { tok_primint positive 2 3 hexadecimal } + @negative @decimal \# / { negHashLitPred MagicHashBit } { tok_primint negative 1 2 decimal } + @negative @binarylit \# / { negHashLitPred MagicHashBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primint negative 3 4 binary } + @negative @octallit \# / { negHashLitPred MagicHashBit } { tok_primint negative 3 4 octal } + @negative @hexadecimallit \# / { negHashLitPred MagicHashBit } { tok_primint negative 3 4 hexadecimal } + + @decimal \# \# / { ifExtension MagicHashBit } { tok_primword 0 2 decimal } + @binarylit \# \# / { ifExtension MagicHashBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primword 2 4 binary } + @octallit \# \# / { ifExtension MagicHashBit } { tok_primword 2 4 octal } + @hexadecimallit \# \# / { ifExtension MagicHashBit } { tok_primword 2 4 hexadecimal } -- Unboxed floats and doubles (:: Float#, :: Double#) -- prim_{float,double} work with signed literals @floating_point \# / { ifExtension MagicHashBit } { tok_frac 1 tok_primfloat } @floating_point \# \# / { ifExtension MagicHashBit } { tok_frac 2 tok_primdouble } - @negative @floating_point \# / { negHashLitPred } { tok_frac 1 tok_primfloat } - @negative @floating_point \# \# / { negHashLitPred } { tok_frac 2 tok_primdouble } + @negative @floating_point \# / { negHashLitPred MagicHashBit } { tok_frac 1 tok_primfloat } + @negative @floating_point \# \# / { negHashLitPred MagicHashBit } { tok_frac 2 tok_primdouble } + + @decimal \#"Int8" / { ifExtension ExtendedLiteralsBit } { tok_primint8 positive 0 decimal } + @binarylit \#"Int8" / { ifExtension ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primint8 positive 2 binary } + @octallit \#"Int8" / { ifExtension ExtendedLiteralsBit } { tok_primint8 positive 2 octal } + @hexadecimallit \#"Int8" / { ifExtension ExtendedLiteralsBit } { tok_primint8 positive 2 hexadecimal } + @negative @decimal \#"Int8" / { negHashLitPred ExtendedLiteralsBit } { tok_primint8 negative 1 decimal } + @negative @binarylit \#"Int8" / { negHashLitPred ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primint8 negative 3 binary } + @negative @octallit \#"Int8" / { negHashLitPred ExtendedLiteralsBit } { tok_primint8 negative 3 octal } + @negative @hexadecimallit \#"Int8" / { negHashLitPred ExtendedLiteralsBit } { tok_primint8 negative 3 hexadecimal } + + @decimal \#"Int16" / { ifExtension ExtendedLiteralsBit } { tok_primint16 positive 0 decimal } + @binarylit \#"Int16" / { ifExtension ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primint16 positive 2 binary } + @octallit \#"Int16" / { ifExtension ExtendedLiteralsBit } { tok_primint16 positive 2 octal } + @hexadecimallit \#"Int16" / { ifExtension ExtendedLiteralsBit } { tok_primint16 positive 2 hexadecimal } + @negative @decimal \#"Int16" / { negHashLitPred ExtendedLiteralsBit} { tok_primint16 negative 1 decimal } + @negative @binarylit \#"Int16" / { negHashLitPred ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primint16 negative 3 binary } + @negative @octallit \#"Int16" / { negHashLitPred ExtendedLiteralsBit} { tok_primint16 negative 3 octal } + @negative @hexadecimallit \#"Int16" / { negHashLitPred ExtendedLiteralsBit} { tok_primint16 negative 3 hexadecimal } + + @decimal \#"Int32" / { ifExtension ExtendedLiteralsBit } { tok_primint32 positive 0 decimal } + @binarylit \#"Int32" / { ifExtension ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primint32 positive 2 binary } + @octallit \#"Int32" / { ifExtension ExtendedLiteralsBit } { tok_primint32 positive 2 octal } + @hexadecimallit \#"Int32" / { ifExtension ExtendedLiteralsBit } { tok_primint32 positive 2 hexadecimal } + @negative @decimal \#"Int32" / { negHashLitPred ExtendedLiteralsBit } { tok_primint32 negative 1 decimal } + @negative @binarylit \#"Int32" / { negHashLitPred ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primint32 negative 3 binary } + @negative @octallit \#"Int32" / { negHashLitPred ExtendedLiteralsBit} { tok_primint32 negative 3 octal } + @negative @hexadecimallit \#"Int32" / { negHashLitPred ExtendedLiteralsBit} { tok_primint32 negative 3 hexadecimal } + + @decimal \#"Int64" / { ifExtension ExtendedLiteralsBit } { tok_primint64 positive 0 decimal } + @binarylit \#"Int64" / { ifExtension ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primint64 positive 2 binary } + @octallit \#"Int64" / { ifExtension ExtendedLiteralsBit } { tok_primint64 positive 2 octal } + @hexadecimallit \#"Int64" / { ifExtension ExtendedLiteralsBit } { tok_primint64 positive 2 hexadecimal } + @negative @decimal \#"Int64" / { negHashLitPred ExtendedLiteralsBit } { tok_primint64 negative 1 decimal } + @negative @binarylit \#"Int64" / { negHashLitPred ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primint64 negative 3 binary } + @negative @octallit \#"Int64" / { negHashLitPred ExtendedLiteralsBit } { tok_primint64 negative 3 octal } + @negative @hexadecimallit \#"Int64" / { negHashLitPred ExtendedLiteralsBit } { tok_primint64 negative 3 hexadecimal } + + @decimal \#"Int" / { ifExtension ExtendedLiteralsBit } { tok_primint positive 0 4 decimal } + @binarylit \#"Int" / { ifExtension ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primint positive 2 6 binary } + @octallit \#"Int" / { ifExtension ExtendedLiteralsBit } { tok_primint positive 2 6 octal } + @hexadecimallit \#"Int" / { ifExtension ExtendedLiteralsBit } { tok_primint positive 2 6 hexadecimal } + @negative @decimal \#"Int" / { negHashLitPred ExtendedLiteralsBit } { tok_primint negative 1 5 decimal } + @negative @binarylit \#"Int" / { negHashLitPred ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primint negative 3 7 binary } + @negative @octallit \#"Int" / { negHashLitPred ExtendedLiteralsBit } { tok_primint negative 3 7 octal } + @negative @hexadecimallit \#"Int" / { negHashLitPred ExtendedLiteralsBit } { tok_primint negative 3 7 hexadecimal } + + @decimal \#"Word8" / { ifExtension ExtendedLiteralsBit } { tok_primword8 0 decimal } + @binarylit \#"Word8" / { ifExtension ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primword8 2 binary } + @octallit \#"Word8" / { ifExtension ExtendedLiteralsBit } { tok_primword8 2 octal } + @hexadecimallit \#"Word8" / { ifExtension ExtendedLiteralsBit } { tok_primword8 2 hexadecimal } + + @decimal \#"Word16" / { ifExtension ExtendedLiteralsBit } { tok_primword16 0 decimal } + @binarylit \#"Word16" / { ifExtension ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primword16 2 binary } + @octallit \#"Word16" / { ifExtension ExtendedLiteralsBit } { tok_primword16 2 octal } + @hexadecimallit \#"Word16" / { ifExtension ExtendedLiteralsBit } { tok_primword16 2 hexadecimal } + + @decimal \#"Word32" / { ifExtension ExtendedLiteralsBit } { tok_primword32 0 decimal } + @binarylit \#"Word32" / { ifExtension ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primword32 2 binary } + @octallit \#"Word32" / { ifExtension ExtendedLiteralsBit } { tok_primword32 2 octal } + @hexadecimallit \#"Word32" / { ifExtension ExtendedLiteralsBit } { tok_primword32 2 hexadecimal } + + @decimal \#"Word64" / { ifExtension ExtendedLiteralsBit } { tok_primword64 0 decimal } + @binarylit \#"Word64" / { ifExtension ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primword64 2 binary } + @octallit \#"Word64" / { ifExtension ExtendedLiteralsBit } { tok_primword64 2 octal } + @hexadecimallit \#"Word64" / { ifExtension ExtendedLiteralsBit } { tok_primword64 2 hexadecimal } + + @decimal \#"Word" / { ifExtension ExtendedLiteralsBit } { tok_primword 0 5 decimal } + @binarylit \#"Word" / { ifExtension ExtendedLiteralsBit `alexAndPred` + ifExtension BinaryLiteralsBit } { tok_primword 2 7 binary } + @octallit \#"Word" / { ifExtension ExtendedLiteralsBit } { tok_primword 2 7 octal } + @hexadecimallit \#"Word" / { ifExtension ExtendedLiteralsBit } { tok_primword 2 7 hexadecimal } + } -- Strings and chars are lexed by hand-written code. The reason is @@ -866,6 +955,14 @@ data Token | ITprimstring SourceText ByteString -- Note [Literal source text] in "GHC.Types.SourceText" | ITprimint SourceText Integer -- Note [Literal source text] in "GHC.Types.SourceText" | ITprimword SourceText Integer -- Note [Literal source text] in "GHC.Types.SourceText" + | ITprimint8 SourceText Integer -- Note [Literal source text] in "GHC.Types.SourceText" + | ITprimint16 SourceText Integer -- Note [Literal source text] in "GHC.Types.SourceText" + | ITprimint32 SourceText Integer -- Note [Literal source text] in "GHC.Types.SourceText" + | ITprimint64 SourceText Integer -- Note [Literal source text] in "GHC.Types.SourceText" + | ITprimword8 SourceText Integer -- Note [Literal source text] in "GHC.Types.SourceText" + | ITprimword16 SourceText Integer -- Note [Literal source text] in "GHC.Types.SourceText" + | ITprimword32 SourceText Integer -- Note [Literal source text] in "GHC.Types.SourceText" + | ITprimword64 SourceText Integer -- Note [Literal source text] in "GHC.Types.SourceText" | ITprimfloat FractionalLit | ITprimdouble FractionalLit @@ -1281,10 +1378,10 @@ negLitPred = alexNotPred precededByClosingToken -- Check if we should parse an unboxed negative literal (e.g. -123#) as a single token. -negHashLitPred :: AlexAccPred ExtsBitmap -negHashLitPred = prefix_minus `alexAndPred` magic_hash +negHashLitPred :: ExtBits -> AlexAccPred ExtsBitmap +negHashLitPred ext = prefix_minus `alexAndPred` magic_hash where - magic_hash = ifExtension MagicHashBit + magic_hash = ifExtension ext -- Either MagicHashBit or ExtendedLiteralsBit prefix_minus = -- Note [prefix_minus in negLitPred and negHashLitPred] alexNotPred precededByClosingToken @@ -1829,6 +1926,40 @@ binary = (2,octDecDigit) octal = (8,octDecDigit) hexadecimal = (16,hexDigit) +-- | Helper for defining @IntX@ primitive literal parsers (specifically for +-- the ExtendedLiterals extension, such as @123#Int8@). +tok_primintX :: (SourceText -> Integer -> Token) + -> Int + -> (Integer -> Integer) + -> Int + -> (Integer, (Char->Int)) -> Action +tok_primintX itint addlen transint transbuf = + tok_integral itint transint transbuf (transbuf+addlen) + +tok_primint8, tok_primint16, tok_primint32, tok_primint64 + :: (Integer -> Integer) + -> Int -> (Integer, (Char->Int)) -> Action +tok_primint8 = tok_primintX ITprimint8 5 +tok_primint16 = tok_primintX ITprimint16 6 +tok_primint32 = tok_primintX ITprimint32 6 +tok_primint64 = tok_primintX ITprimint64 6 + +-- | Helper for defining @WordX@ primitive literal parsers (specifically for +-- the ExtendedLiterals extension, such as @234#Word8@). +tok_primwordX :: (SourceText -> Integer -> Token) + -> Int + -> Int + -> (Integer, (Char->Int)) -> Action +tok_primwordX itint addlen transbuf = + tok_integral itint positive transbuf (transbuf+addlen) + +tok_primword8, tok_primword16, tok_primword32, tok_primword64 + :: Int -> (Integer, (Char->Int)) -> Action +tok_primword8 = tok_primwordX ITprimword8 6 +tok_primword16 = tok_primwordX ITprimword16 7 +tok_primword32 = tok_primwordX ITprimword32 7 +tok_primword64 = tok_primwordX ITprimword64 7 + -- readSignificandExponentPair can understand negative rationals, exponents, everything. tok_frac :: Int -> (String -> Token) -> Action tok_frac drop f span buf len _buf2 = do @@ -2903,6 +3034,7 @@ data ExtBits | NoLexicalNegationBit -- See Note [Why not LexicalNegationBit] | OverloadedRecordDotBit | OverloadedRecordUpdateBit + | ExtendedLiteralsBit -- Flags that are updated once parsing starts | InRulePragBit @@ -2982,6 +3114,7 @@ mkParserOpts extensionFlags diag_opts supported .|. NoLexicalNegationBit `xoptNotBit` LangExt.LexicalNegation -- See Note [Why not LexicalNegationBit] .|. OverloadedRecordDotBit `xoptBit` LangExt.OverloadedRecordDot .|. OverloadedRecordUpdateBit `xoptBit` LangExt.OverloadedRecordUpdate -- Enable testing via 'getBit OverloadedRecordUpdateBit' in the parser (RecordDotSyntax parsing uses that information). + .|. ExtendedLiteralsBit `xoptBit` LangExt.ExtendedLiterals optBits = HaddockBit `setBitIf` isHaddock .|. RawTokenStreamBit `setBitIf` rawTokStream |