[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: testsuite: fix predicate on rdynamic test

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon May 22 14:41:17 UTC 2023



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
c6fb6690 by Peter Trommler at 2023-05-20T03:16:08-04:00
testsuite: fix predicate on rdynamic test

Test rdynamic requires dynamic linking support, which is
orthogonal to RTS linker support. Change the predicate accordingly.

Fixes #23316

- - - - -
735d504e by Matthew Pickering at 2023-05-20T03:16:44-04:00
docs: Use ghc-ticket directive where appropiate in users guide

Using the directive automatically formats and links the ticket
appropiately.

- - - - -
e26e1a22 by Sylvain Henry at 2023-05-22T10:41:09-04:00
NCG: remove useless .align directive (#20758)

- - - - -
a94db291 by Simon Peyton Jones at 2023-05-22T10:41:10-04:00
Add test for #23156

This program had exponential typechecking time in GHC 9.4 and 9.6

- - - - -


11 changed files:

- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
- docs/users_guide/9.8.1-notes.rst
- docs/users_guide/extending_ghc.rst
- docs/users_guide/exts/rewrite_rules.rst
- docs/users_guide/exts/template_haskell.rst
- docs/users_guide/using-optimisation.rst
- testsuite/tests/rts/linker/all.T
- + testsuite/tests/typecheck/should_compile/T23156.hs
- + testsuite/tests/typecheck/should_compile/T23156.stderr
- testsuite/tests/typecheck/should_compile/all.T


Changes:

=====================================
compiler/GHC/CmmToAsm/AArch64/Ppr.hs
=====================================
@@ -18,7 +18,6 @@ import GHC.CmmToAsm.Utils
 import GHC.Cmm hiding (topInfoTable)
 import GHC.Cmm.Dataflow.Collections
 import GHC.Cmm.Dataflow.Label
-import GHC.Types.Basic (Alignment, mkAlignment, alignmentBytes)
 
 import GHC.Cmm.BlockId
 import GHC.Cmm.CLabel
@@ -29,18 +28,12 @@ import GHC.Utils.Outputable
 
 import GHC.Utils.Panic
 
-pprProcAlignment :: IsDoc doc => NCGConfig -> doc
-pprProcAlignment config = maybe empty (pprAlign platform . mkAlignment) (ncgProcAlignment config)
-   where
-      platform = ncgPlatform config
-
 pprNatCmmDecl :: IsDoc doc => NCGConfig -> NatCmmDecl RawCmmStatics Instr -> doc
 pprNatCmmDecl config (CmmData section dats) =
   pprSectionAlign config section $$ pprDatas config dats
 
 pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) =
   let platform = ncgPlatform config in
-  pprProcAlignment config $$
   case topInfoTable proc of
     Nothing ->
         -- special case for code without info table:
@@ -80,10 +73,6 @@ pprLabel platform lbl =
    $$ pprTypeDecl platform lbl
    $$ line (pprAsmLabel platform lbl <> char ':')
 
-pprAlign :: IsDoc doc => Platform -> Alignment -> doc
-pprAlign _platform alignment
-        = line $ text "\t.balign " <> int (alignmentBytes alignment)
-
 -- | Print appropriate alignment for the given section type.
 pprAlignForSection :: IsDoc doc => Platform -> SectionType -> doc
 pprAlignForSection _platform _seg


=====================================
compiler/GHC/CmmToAsm/X86/Ppr.hs
=====================================
@@ -74,7 +74,6 @@ pprNatCmmDecl config (CmmData section dats) =
 
 pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) =
   let platform = ncgPlatform config in
-  pprProcAlignment config $$
   case topInfoTable proc of
     Nothing ->
         -- special case for code without info table:


=====================================
docs/users_guide/9.8.1-notes.rst
=====================================
@@ -33,11 +33,10 @@ Compiler
 
 - Incoherent instance applications are no longer specialised. The previous implementation of
   specialisation resulted in nondeterministic instance resolution in certain cases, breaking
-  the specification described in the documentation of the `INCOHERENT` pragma. See GHC ticket
-  #22448 for further details.
+  the specification described in the documentation of the `INCOHERENT` pragma. See :ghc-ticket:`22448` for further details.
 
 - Fix a bug in TH causing excessive calls to ``setNumCapabilities`` when ``-j`` is greater than ``-N``.
-  See GHC ticket #23049.
+  See :ghc-ticket:`23049`.
 
 - The ``-Wno-⟨wflag⟩``, ``-Werror=⟨wflag⟩`` and ``-Wwarn=⟨wflag⟩`` options are
   now defined systematically for all warning groups (for example,
@@ -121,7 +120,7 @@ Runtime system
 ~~~~~~~~~~~~~~
 
 - On POSIX systems that support timerfd, RTS shutdown no longer has to wait for
-  the next RTS 'tick' to occur before continuing the shutdown process. See #22692.
+  the next RTS 'tick' to occur before continuing the shutdown process. See :ghc-ticket:`22692`.
 
 ``base`` library
 ~~~~~~~~~~~~~~~~


=====================================
docs/users_guide/extending_ghc.rst
=====================================
@@ -287,7 +287,7 @@ would invoke GHC like this:
 
 
 Plugins can be also be loaded from libraries directly. It allows plugins to be
-loaded in cross-compilers (as a workaround for #14335).
+loaded in cross-compilers (as a workaround for :ghc-ticket:`14335`).
 
 .. ghc-flag:: -fplugin-library=⟨file-path⟩;⟨unit-id⟩;⟨module⟩;⟨args⟩
     :shortdesc: Load a pre-compiled static plugin from an external library


=====================================
docs/users_guide/exts/rewrite_rules.rst
=====================================
@@ -262,7 +262,7 @@ From a semantic point of view:
 
         {-# RULES forall @m (x :: KnownNat m => Proxy m).  g x = blah #-}
 
-   See `#21093 <https://gitlab.haskell.org/ghc/ghc/-/issues/21093>`_ for discussion.
+   See :ghc-ticket:`21093` for discussion.
 
 .. _rules-inline:
 


=====================================
docs/users_guide/exts/template_haskell.rst
=====================================
@@ -135,7 +135,7 @@ The :extension:`TemplateHaskellQuotes` extension is considered safe under
    spliced expression must have type ``Code Q a``
 
    **NOTE**: Currently typed splices may inhibit the unused identifier warning for
-   identifiers in scope. See `#16524 <https://gitlab.haskell.org/ghc/ghc/-/issues/16524>`
+   identifiers in scope. See :ghc-ticket:`16524`.
 
 -  A *typed* expression quotation is written as ``[|| ... ||]``, or
    ``[e|| ... ||]``, where the "..." is an expression; if the "..."


=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -1691,7 +1691,7 @@ as such you shouldn't need to set any of them explicitly. A flag
     overhead for the check disappears completely.
 
     This can cause slight codesize increases. It will also cause many more functions
-    to get a worker/wrapper split which can play badly with rules (see Ticket #20364)
+    to get a worker/wrapper split which can play badly with rules (see :ghc-ticket:`20364`)
     which is why it's currently disabled by default.
     In particular if you depend on rules firing on functions marked as NOINLINE without
     marking use sites of these functions as INLINE or INLINEABLE then things will break


=====================================
testsuite/tests/rts/linker/all.T
=====================================
@@ -131,7 +131,7 @@ test('linker_error3', [extra_files(['linker_error.c']),
 
 ######################################
 test('rdynamic', [ unless(opsys('linux') or opsys('mingw32'), skip)
-                 , req_rts_linker
+                 , unless(have_dynamic(), skip)
                  # this needs runtime infrastructure to do in ghci:
                  #  '-rdynamic' ghc, load modules only via dlopen(RTLD_BLOBAL) and more.
                  , omit_ways(['ghci'])


=====================================
testsuite/tests/typecheck/should_compile/T23156.hs
=====================================
@@ -0,0 +1,59 @@
+{-# LANGUAGE DataKinds, TypeFamilies, PartialTypeSignatures #-}
+{-# OPTIONS_GHC -fdefer-type-errors #-}
+module T23156 where
+
+import Prelude
+import GHC.TypeLits
+import Data.Kind
+
+type BooleanOf2 :: Type -> Type
+type family BooleanOf2 a
+
+type instance BooleanOf2 Double = Double
+
+-- Needs to be a type family, changing this to a datatype makes it fast
+type TensorOf2 :: Nat -> Type -> Type
+type family TensorOf2 k a
+
+type instance TensorOf2 n Double = Double
+
+
+-- With GHC 9.4 and 9.6, typechecking was
+-- exponential in the size of this tuple
+type ADReady r =
+  (  BooleanOf2 r ~ BooleanOf2 (TensorOf2 1 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 2 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 3 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 4 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 5 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 6 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 7 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 8 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 9 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 10 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 11 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 12 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 13 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 14 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 15 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 16 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 17 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 18 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 19 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 20 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 21 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 22 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 23 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 24 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 25 r)
+  )
+
+f :: forall r . (ADReady r) => ()
+f = undefined
+
+-- This uses a lot of memory
+g :: _ => ()
+g = f
+
+-- This is fine
+g' = f @Double


=====================================
testsuite/tests/typecheck/should_compile/T23156.stderr
=====================================
@@ -0,0 +1,25 @@
+
+T23156.hs:51:6: warning: [GHC-05617] [-Wdeferred-type-errors (in -Wdefault)]
+    • Could not deduce ‘BooleanOf2 (TensorOf2 1 r0) ~ BooleanOf2 r0’
+      from the context: ADReady r
+        bound by the type signature for:
+                   f :: forall r. ADReady r => ()
+        at T23156.hs:51:6-33
+      NB: ‘BooleanOf2’ is a non-injective type family
+      The type variables ‘r0’, ‘r0’ are ambiguous
+    • In the ambiguity check for ‘f’
+      To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
+      In the type signature: f :: forall r. (ADReady r) => ()
+
+T23156.hs:55:6: warning: [GHC-88464] [-Wpartial-type-signatures (in -Wdefault)]
+    • Found extra-constraints wildcard standing for ‘() :: Constraint’
+    • In the type signature: g :: _ => ()
+
+T23156.hs:56:5: warning: [GHC-18872] [-Wdeferred-type-errors (in -Wdefault)]
+    • Couldn't match type: BooleanOf2 (TensorOf2 1 r0)
+                     with: BooleanOf2 r0
+        arising from a use of ‘f’
+      NB: ‘BooleanOf2’ is a non-injective type family
+      The type variables ‘r0’, ‘r0’ are ambiguous
+    • In the expression: f
+      In an equation for ‘g’: g = f


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -874,3 +874,4 @@ test('QualifiedRecordUpdate',
 test('T23171', normal, compile, [''])
 test('T23192', normal, compile, [''])
 test('T23199', normal, compile, [''])
+test('T23156', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d74a11115ee26942262f95a0f617945835cf2ed2...a94db291bc8deb3c25bf077c5d656bbd6ffd9473

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d74a11115ee26942262f95a0f617945835cf2ed2...a94db291bc8deb3c25bf077c5d656bbd6ffd9473
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/20230522/b888a7dc/attachment-0001.html>


More information about the ghc-commits mailing list