[Git][ghc/ghc][wip/andreask/sse_macro_docs] 4 commits: compiler: Fix pretty printing of ticked prefix constructors (#24237)

Andreas Klebinger (@AndreasK) gitlab at gitlab.haskell.org
Wed Aug 21 12:37:39 UTC 2024



Andreas Klebinger pushed to branch wip/andreask/sse_macro_docs at Glasgow Haskell Compiler / GHC


Commits:
5f972bfb by Zubin Duggal at 2024-08-21T03:18:15-04:00
compiler: Fix pretty printing of ticked prefix constructors (#24237)

- - - - -
ef0a08e7 by Mike Pilgrem at 2024-08-21T03:18:57-04:00
Fix #15773 Clarify further -rtsopts 'defaults' in docs

- - - - -
05a4be58 by Sebastian Graf at 2024-08-21T03:19:33-04:00
Improve efficiency of `assertError` (#24625)

... by moving `lazy` to the exception-throwing branch.
It's all documented in `Note [Strictness of assertError]`.

- - - - -
fee32a30 by Andreas Klebinger at 2024-08-21T14:19:00+02:00
Document the (x86) SIMD macros.

Fixes #25021.

- - - - -


9 changed files:

- compiler/GHC/Iface/Type.hs
- compiler/GHC/SysTools/Cpp.hs
- docs/users_guide/phases.rst
- libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs
- + testsuite/tests/printer/T24237.hs
- + testsuite/tests/printer/T24237.stderr
- testsuite/tests/printer/all.T
- + testsuite/tests/simplCore/should_compile/T24625.hs
- testsuite/tests/simplCore/should_compile/all.T


Changes:

=====================================
compiler/GHC/Iface/Type.hs
=====================================
@@ -1847,17 +1847,16 @@ ppr_iface_tc_app pp ctxt_prec tc tys =
      | tc `ifaceTyConHasKey` liftedTypeKindTyConKey
      -> ppr_kind_type ctxt_prec
 
-     | not (isSymOcc (nameOccName (ifaceTyConName tc)))
-     -> pprIfacePrefixApp ctxt_prec (ppr tc) (map (pp appPrec) tys)
+     | isSymOcc (nameOccName (ifaceTyConName tc))
 
-     | [ ty1@(_, Required), ty2@(_, Required) ] <- tys
+     , [ ty1@(_, Required), ty2@(_, Required) ] <- tys
          -- Infix, two visible arguments (we know nothing of precedence though).
          -- Don't apply this special case if one of the arguments is invisible,
          -- lest we print something like (@LiftedRep -> @LiftedRep) (#15941).
-     -> pprIfaceInfixApp ctxt_prec (ppr tc) (pp opPrec ty1) (pp opPrec ty2)
+     -> pprIfaceInfixApp ctxt_prec (pprIfaceTyCon tc) (pp opPrec ty1) (pp opPrec ty2)
 
      | otherwise
-     -> pprIfacePrefixApp ctxt_prec (parens (ppr tc)) (map (pp appPrec) tys)
+     -> pprIfacePrefixApp ctxt_prec (pprParendIfaceTyCon tc) (map (pp appPrec) tys)
 
 data TupleOrSum = IsSum | IsTuple TupleSort
   deriving (Eq)
@@ -2070,7 +2069,18 @@ instance Outputable IfLclName where
   ppr = ppr . ifLclNameFS
 
 instance Outputable IfaceTyCon where
-  ppr tc = pprPromotionQuote tc <> ppr (ifaceTyConName tc)
+  ppr = pprIfaceTyCon
+
+-- | Print an `IfaceTyCon` with a promotion tick if needed, without parens,
+-- suitable for use in infix contexts
+pprIfaceTyCon :: IfaceTyCon -> SDoc
+pprIfaceTyCon tc = pprPromotionQuote tc <> ppr (ifaceTyConName tc)
+
+-- | Print an `IfaceTyCon` with a promotion tick if needed, possibly with parens,
+-- suitable for use in prefix contexts
+pprParendIfaceTyCon :: IfaceTyCon -> SDoc
+pprParendIfaceTyCon tc = pprPromotionQuote tc <> pprPrefixVar (isSymOcc (nameOccName tc_name)) (ppr tc_name)
+  where tc_name = ifaceTyConName tc
 
 instance Outputable IfaceTyConInfo where
   ppr (IfaceTyConInfo { ifaceTyConIsPromoted = prom


=====================================
compiler/GHC/SysTools/Cpp.hs
=====================================
@@ -106,6 +106,9 @@ command line looks like:
 -- See Note [Preprocessing invocations].
 --
 -- UnitEnv is needed to compute MIN_VERSION macros
+--
+-- If you change the macros defined by this function make sure to update the
+-- user guide.
 doCpp :: Logger -> TmpFs -> DynFlags -> UnitEnv -> CppOpts -> FilePath -> FilePath -> IO ()
 doCpp logger tmpfs dflags unit_env opts input_fn output_fn = do
     let hscpp_opts = picPOpts dflags


=====================================
docs/users_guide/phases.rst
=====================================
@@ -523,7 +523,7 @@ defined by your local GHC installation, the following trick is useful:
 ``arch_HOST_ARCH=1``
     This define allows conditional compilation based on the host
     architecture, where⟨arch⟩ is the name of the current architecture
-    (eg. ``i386``, ``x86_64``, ``powerpc``, ``sparc``, etc.).
+    (eg. ``i386``, ``x86_64``, ``aarch64``, ``powerpc``, ``sparc``, etc.).
 
 ``VERSION_pkgname``
     This macro is available starting GHC 8.0.  It is defined for every
@@ -539,6 +539,16 @@ defined by your local GHC installation, the following trick is useful:
     later.  It is identical in behavior to the ``MIN_VERSION_pkgname``
     macros that Cabal defines.
 
+SIMD macros
+    .. index::
+        single: SIMD Macros
+
+    These are defined conditionally based on the SIMD
+    flags used for compilation:
+
+    ``__SSE__``, ``__SSE2__``, ``__SSE4_2__``, ``__FMA__``,
+    ``__AVX__``, ``__AVX2__``, ``__AVX512CD__``, ``__AVX512ER__``, ``__AVX512F__``, ``__AVX512PF__``,
+
 .. _cpp-string-gaps:
 
 CPP and string gaps
@@ -1151,8 +1161,9 @@ for example).
     :shortdesc: Control whether the RTS behaviour can be tweaked via command-line
         flags and the ``GHCRTS`` environment variable. Using ``none``
         means no RTS flags can be given; ``some`` means only a minimum
-        of safe options can be given (the default); ``all`` (or no
-        argument at all) means that all RTS flags are permitted; ``ignore``
+        of safe options can be given (the default, if ``-rtsopts`` is
+        not passed); ``all`` means that all RTS flags are permitted (the
+        default, if ``-rtsopts`` is passed with no argument); ``ignore``
         means RTS flags can be given, but are treated as regular arguments and
         passed to the Haskell program as arguments; ``ignoreAll`` is the same as
         ``ignore``, but ``GHCRTS`` is also ignored. ``-rtsopts`` does not
@@ -1161,11 +1172,12 @@ for example).
     :type: dynamic
     :category: linking
 
-    :default: some
+    :default: ``some``, if ``-rtsopts`` is not passed; ``all``, if ``-rtsopts``
+        is passed with no argument.
 
     This option affects the processing of RTS control options given
     either on the command line or via the :envvar:`GHCRTS` environment
-    variable. There are five possibilities:
+    variable. There are six possibilities:
 
     ``-rtsopts=none``
         Disable all processing of RTS options. If ``+RTS`` appears
@@ -1181,18 +1193,22 @@ for example).
         ``GHCRTS`` options will be processed normally.
 
     ``-rtsopts=ignoreAll``
-        Same as ``ignore`` but also ignores ``GHCRTS``.
+        Same as ``ignore`` with the exception of ``GHCRTS`` options, which are
+        also ignored.
 
     ``-rtsopts=some``
-        [this is the default setting] Enable only the "safe" RTS
-        options: (Currently only ``-?`` and ``--info``.) Any other RTS
-        options on the command line or in the ``GHCRTS`` environment
-        variable causes the program with to abort with an error message.
+        [this is the default setting, if ``-rtsopts`` is not passed] Enable only
+        the "safe" RTS options: (Currently only ``-?`` and ``--info``.) Any
+        other RTS options on the command line or in the ``GHCRTS`` environment
+        variable causes the program to abort with an error message.
 
-    ``-rtsopts=all`` or just ``-rtsopts``
+    ``-rtsopts=all``
         Enable *all* RTS option processing, both on the command line and
         through the ``GHCRTS`` environment variable.
 
+    ``-rtsopts``
+        Equivalent to ``-rtsopts=all``.
+
     In GHC 6.12.3 and earlier, the default was to process all RTS
     options. However, since RTS options can be used to write logging
     data to arbitrary files under the security context of the running


=====================================
libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs
=====================================
@@ -438,13 +438,10 @@ instance Show IOException where
          "" -> id
          _  -> showString " (" . showString s . showString ")")
 
--- Note the use of "lazy". This means that
---     assert False (throw e)
--- will throw the assertion failure rather than e. See trac #5561.
 assertError :: (?callStack :: CallStack) => Bool -> a -> a
 assertError predicate v
-  | predicate = lazy v
-  | otherwise = unsafeDupablePerformIO $ do
+  | predicate = v
+  | otherwise = lazy $ unsafeDupablePerformIO $ do -- lazy: See Note [Strictness of assertError]
     ccsStack <- currentCallStack
     let
       implicitParamCallStack = prettyCallStackLines ?callStack
@@ -452,6 +449,44 @@ assertError predicate v
       stack = intercalate "\n" $ implicitParamCallStack ++ ccsCallStack
     throwIO (AssertionFailed ("Assertion failed\n" ++ stack))
 
+{- Note [Strictness of assertError]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+It is vital that Demand Analysis does not see `assertError p e` as strict in e.
+#5561 details what happens otherwise, tested by libraries/base/tests/assert.hs:
+
+  let e1 i = throw Overflow
+  in assertError False (e1 5)
+
+This should *not* throw the Overflow exception; rather it should throw an
+AssertionError.
+Hence we use GHC.Exts.lazy to make assertError appear lazy in e, so that it
+is not called by-value.
+(Note that the reason we need `lazy` in the first place is that error has a
+bottoming result, which is strict in all free variables.)
+The way we achieve this is a bit subtle; before #24625 we defined it as
+
+  assertError p e | p         = lazy e
+                  | otherwise = error "assertion"
+
+but this means that in the following example (full code in T24625) we cannot
+cancel away the allocation of `Just x` because of the intervening `lazy`:
+
+  case assertError False (Just x) of Just y -> y
+  ==> { simplify }
+  case lazy (Just x) of Just y -> y
+
+Instead, we put `lazy` in the otherwise branch, thus
+
+  assertError p e | p         = e
+                  | otherwise = lazy $ error "assertion"
+
+The effect on #5561 is the same: since the otherwise branch appears lazy in e,
+the overall demand on `e` must be lazy as well.
+Furthermore, since there is no intervening `lazy` on the expected code path,
+the Simplifier may perform case-of-case on e and simplify the `Just x` example
+to `x`.
+-}
+
 unsupportedOperation :: IOError
 unsupportedOperation =
    (IOError Nothing UnsupportedOperation ""
@@ -480,4 +515,3 @@ untangle coded message
           _         -> (loc, "")
         }
     not_bar c = c /= '|'
-


=====================================
testsuite/tests/printer/T24237.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE DataKinds #-}
+{-# OPTIONS_GHC -fprint-redundant-promotion-ticks #-}
+module T24237 where
+
+import Data.Proxy
+
+foo :: Proxy '(:)
+foo = ()


=====================================
testsuite/tests/printer/T24237.stderr
=====================================
@@ -0,0 +1,7 @@
+T24237.hs:8:7: error: [GHC-83865]
+    • Couldn't match expected type ‘Proxy '(:)’ with actual type ‘()’
+    • In the expression: ()
+      In an equation for ‘foo’: foo = ()
+    • Relevant bindings include
+        foo :: Proxy '(:) (bound at T24237.hs:8:1)
+


=====================================
testsuite/tests/printer/all.T
=====================================
@@ -210,3 +210,5 @@ test('Test24753', [ignore_stderr, req_ppr_deps], makefile_test, ['Test24753'])
 test('Test24771', [ignore_stderr, req_ppr_deps], makefile_test, ['Test24771'])
 test('Test24159', [ignore_stderr, req_ppr_deps], makefile_test, ['Test24159'])
 test('Test25132', [ignore_stderr, req_ppr_deps], makefile_test, ['Test25132'])
+
+test('T24237', normal, compile_fail, [''])


=====================================
testsuite/tests/simplCore/should_compile/T24625.hs
=====================================
@@ -0,0 +1,14 @@
+module T24625 where
+
+import GHC.IO.Exception
+import GHC.Exts
+
+data Foo = Foo !Int !Int String
+
+true :: Bool
+true = True
+{-# NOINLINE true #-}
+
+function :: Int -> Int -> String -> Int
+function !a !b c = case assertError true (Foo a b c) of
+  Foo a b c -> a + b


=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -526,5 +526,6 @@ test('T24808', [ grep_errmsg(r'myFunction') ], compile, ['-O -ddump-simpl'])
 # T24944 needs -O2 because it's about SpecConstr
 test('T24944', [extra_files(['T24944a.hs'])], multimod_compile, ['T24944', '-v0 -O2'])
 
+test('T24625', [ grep_errmsg(r'case lazy') ], compile, ['-O -fno-ignore-asserts -ddump-simpl -dsuppress-uniques'])
 test('T24725a', [ grep_errmsg(r'testedRule')], compile, ['-O -ddump-rule-firings'])
 test('T25033', normal, compile, ['-O'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57903b74717dea668123e3518b9bc59fdfeeaefe...fee32a30247a00e06eca16a0b3ff73b0275e70d0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57903b74717dea668123e3518b9bc59fdfeeaefe...fee32a30247a00e06eca16a0b3ff73b0275e70d0
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/20240821/97b37044/attachment-0001.html>


More information about the ghc-commits mailing list