[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Fix typo in 8.8.1 notes related to traceBinaryEvent
Marge Bot
gitlab at gitlab.haskell.org
Sun May 5 14:39:33 UTC 2019
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
63150b9e by iustin at 2019-05-04T21:54:23Z
Fix typo in 8.8.1 notes related to traceBinaryEvent
- fixes double mention of `traceBinaryEvent#` (the second one should be `traceEvent#`, I think)
- fixes note about `traceEvent#` taking a `String` - the docs say it takes a zero-terminated ByteString.
- - - - -
dc8a5868 by gallais at 2019-05-04T22:00:30Z
[ typo ] 'castFloatToWord32' -> 'castFloatToWord64'
Probably due to a copy/paste gone wrong.
- - - - -
615b4be6 by Chaitanya Koparkar at 2019-05-05T14:39:24Z
Fix #16593 by having only one definition of -fprint-explicit-runtime-reps
[skip ci]
- - - - -
ead3f835 by Vladislav Zavialov at 2019-05-05T14:39:24Z
'warnSpaceAfterBang' only in patterns (#16619)
- - - - -
9 changed files:
- compiler/parser/Parser.y
- compiler/parser/RdrHsSyn.hs
- docs/users_guide/8.8.1-notes.rst
- docs/users_guide/glasgow_exts.rst
- docs/users_guide/using.rst
- libraries/base/GHC/Float.hs
- + testsuite/tests/parser/should_compile/T16619.hs
- + testsuite/tests/parser/should_compile/T16619a.hs
- testsuite/tests/parser/should_compile/all.T
Changes:
=====================================
compiler/parser/Parser.y
=====================================
@@ -2601,14 +2601,8 @@ infixexp_top :: { ECP }
$2 >>= \ $2 ->
runECP_PV $1 >>= \ $1 ->
runECP_PV $3 >>= \ $3 ->
- do { when (srcSpanEnd (getLoc $2)
- == srcSpanStart (getLoc $3)
- && checkIfBang (unLoc $2)) $
- warnSpaceAfterBang (comb2 $2 $3);
- amms (mkHsOpAppPV (comb2 $1 $>) $1 $2 $3)
- [mj AnnVal $2]
- }
- }
+ amms (mkHsOpAppPV (comb2 $1 $>) $1 $2 $3)
+ [mj AnnVal $2] }
exp10_top :: { ECP }
: '-' fexp { ECP $
@@ -3963,17 +3957,6 @@ hintExplicitForall tok = do
where
forallSymDoc = text (forallSym (isUnicode tok))
--- | Warn about missing space after bang
-warnSpaceAfterBang :: SrcSpan -> PV ()
-warnSpaceAfterBang span = do
- bang_on <- getBit BangPatBit
- unless bang_on $
- addWarning Opt_WarnSpaceAfterBang span msg
- where
- msg = text "Did you forget to enable BangPatterns?" $$
- text "If you mean to bind (!) then perhaps you want" $$
- text "to add a space after the bang for clarity."
-
-- When two single quotes don't followed by tyvar or gtycon, we report the
-- error as empty character literal, or TH quote that missing proper type
-- variable or constructor. See #13450.
=====================================
compiler/parser/RdrHsSyn.hs
=====================================
@@ -1847,20 +1847,16 @@ ecpFromCmd a = ECP (ecpFromCmd' a)
-- | Disambiguate infix operators.
-- See Note [Ambiguous syntactic categories]
class DisambInfixOp b where
- checkIfBang :: b -> Bool
mkHsVarOpPV :: Located RdrName -> PV (Located b)
mkHsConOpPV :: Located RdrName -> PV (Located b)
mkHsInfixHolePV :: SrcSpan -> PV (Located b)
instance p ~ GhcPs => DisambInfixOp (HsExpr p) where
- checkIfBang (HsVar _ (unLoc -> op)) = isBangRdr op
- checkIfBang _ = False
mkHsVarOpPV v = return $ cL (getLoc v) (HsVar noExt v)
mkHsConOpPV v = return $ cL (getLoc v) (HsVar noExt v)
mkHsInfixHolePV l = return $ cL l hsHoleExpr
instance DisambInfixOp RdrName where
- checkIfBang = isBangRdr
mkHsConOpPV (dL->L l v) = return $ cL l v
mkHsVarOpPV (dL->L l v) = return $ cL l v
mkHsInfixHolePV l =
@@ -2132,7 +2128,9 @@ instance p ~ GhcPs => DisambECP (PatBuilder p) where
mkHsLetPV l _ _ = addFatalError l $ text "(let ... in ...)-syntax in pattern"
type InfixOp (PatBuilder p) = RdrName
superInfixOp m = m
- mkHsOpAppPV l p1 op p2 = return $ cL l $ PatBuilderOpApp p1 op p2
+ mkHsOpAppPV l p1 op p2 = do
+ warnSpaceAfterBang op (getLoc p2)
+ return $ cL l $ PatBuilderOpApp p1 op p2
mkHsCasePV l _ _ = addFatalError l $ text "(case ... of ...)-syntax in pattern"
type FunArg (PatBuilder p) = PatBuilder p
superFunArg m = m
@@ -2193,6 +2191,19 @@ mkPatRec (unLoc -> PatBuilderVar c) (HsRecFields fs dd)
mkPatRec p _ =
addFatalError (getLoc p) $ text "Not a record constructor:" <+> ppr p
+-- | Warn about missing space after bang
+warnSpaceAfterBang :: Located RdrName -> SrcSpan -> PV ()
+warnSpaceAfterBang (dL->L opLoc op) argLoc = do
+ bang_on <- getBit BangPatBit
+ when (not bang_on && noSpace && isBangRdr op) $
+ addWarning Opt_WarnSpaceAfterBang span msg
+ where
+ span = combineSrcSpans opLoc argLoc
+ noSpace = srcSpanEnd opLoc == srcSpanStart argLoc
+ msg = text "Did you forget to enable BangPatterns?" $$
+ text "If you mean to bind (!) then perhaps you want" $$
+ text "to add a space after the bang for clarity."
+
{- Note [Ambiguous syntactic categories]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
docs/users_guide/8.8.1-notes.rst
=====================================
@@ -149,8 +149,9 @@ Template Haskell
~~~~~~~~~~~~~~~~~~~~
- GHC now exposes a new primop, ``traceBinaryEvent#``. This primop writes
- eventlog events similar to ``traceBinaryEvent#`` but allows the user to pass
- the event payload as a binary blob instead of a ``String``.
+ eventlog events similar to ``traceEvent#`` but allows the user to pass
+ the event payload as a binary blob instead of a zero-terminated
+ ``ByteString``.
- The ``StableName#`` type parameter now has a phantom role instead of
a representational one. There is really no reason to care about the
=====================================
docs/users_guide/glasgow_exts.rst
=====================================
@@ -9625,7 +9625,17 @@ when printing, and printing ``TYPE 'LiftedRep`` as ``Type`` (or ``*`` when
:extension:`StarIsType` is on).
Should you wish to see levity polymorphism in your types, enable
-the flag :ghc-flag:`-fprint-explicit-runtime-reps`.
+the flag :ghc-flag:`-fprint-explicit-runtime-reps`. For example,
+
+ .. code-block:: none
+
+ ghci> :t ($)
+ ($) :: (a -> b) -> a -> b
+ ghci> :set -fprint-explicit-runtime-reps
+ ghci> :t ($)
+ ($)
+ :: forall (r :: GHC.Types.RuntimeRep) a (b :: TYPE r).
+ (a -> b) -> a -> b
.. _type-level-literals:
=====================================
docs/users_guide/using.rst
=====================================
@@ -810,27 +810,6 @@ messages and in GHCi:
exposed to the programmer, but it is nevertheless displayed when
:ghc-flag:`-fprint-explicit-kinds` is enabled.
-.. ghc-flag:: -fprint-explicit-runtime-reps
- :shortdesc: Print ``RuntimeRep`` variables in types which are
- runtime-representation polymorphic.
- :type: dynamic
- :reverse: -fno-print-explicit-runtime-reps
- :category: verbosity
-
- When :ghc-flag:`-fprint-explicit-runtime-reps` is enabled, GHC prints
- ``RuntimeRep`` type variables for levity-polymorphic types.
- Otherwise GHC will default these to ``LiftedRep``. For example,
-
- .. code-block:: none
-
- ghci> :t ($)
- ($) :: (a -> b) -> a -> b
- ghci> :set -fprint-explicit-runtime-reps
- ghci> :t ($)
- ($)
- :: forall (r :: GHC.Types.RuntimeRep) a (b :: TYPE r).
- (a -> b) -> a -> b
-
.. ghc-flag:: -fprint-explicit-coercions
:shortdesc: Print coercions in types
:type: dynamic
@@ -1131,4 +1110,3 @@ Some flags only make sense for a particular use case.
included. This option can be used to specify the path to the
``ghcversions.h`` file to be included. This is primarily intended to be
used by GHC's build system.
-
=====================================
libraries/base/GHC/Float.hs
=====================================
@@ -1387,7 +1387,7 @@ foreign import prim "stg_word64ToDoublezh"
#endif
--- | @'castFloatToWord32' f@ does a bit-for-bit copy from a floating-point value
+-- | @'castFloatToWord64' f@ does a bit-for-bit copy from a floating-point value
-- to an integral value.
--
-- @since 4.10.0.0
=====================================
testsuite/tests/parser/should_compile/T16619.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# OPTIONS -Wmissing-space-after-bang #-}
+
+module T16619 where
+
+import T16619a
+
+1!2
=====================================
testsuite/tests/parser/should_compile/T16619a.hs
=====================================
@@ -0,0 +1,3 @@
+module T16619a where
+
+(!) _ _ = return []
=====================================
testsuite/tests/parser/should_compile/all.T
=====================================
@@ -142,3 +142,4 @@ test('T15457', normal, compile, [''])
test('T15675', normal, compile, [''])
test('T15781', normal, compile, [''])
test('T16339', normal, compile, [''])
+test('T16619', [], multimod_compile, ['T16619', '-v0'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/99a5617810945dc77c6cb393bf0418eeef5e3966...ead3f835e24338fb3df3ebdec3e86f9364df7c9c
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/99a5617810945dc77c6cb393bf0418eeef5e3966...ead3f835e24338fb3df3ebdec3e86f9364df7c9c
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190505/1747198a/attachment-0001.html>
More information about the ghc-commits
mailing list