[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Treat existentials correctly in dubiousDataConInstArgTys

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Feb 1 19:33:27 UTC 2023



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


Commits:
955a99ea by Simon Peyton Jones at 2023-02-01T12:31:23-05:00
Treat existentials correctly in dubiousDataConInstArgTys

Consider (#22849)

 data T a where
   MkT :: forall k (t::k->*) (ix::k). t ix -> T @k a

Then dubiousDataConInstArgTys MkT [Type, Foo] should return
        [Foo (ix::Type)]
NOT     [Foo (ix::k)]

A bit of an obscure case, but it's an outright bug, and the fix is easy.

- - - - -
0cc16aaf by Matthew Pickering at 2023-02-01T12:31:58-05:00
Bump supported LLVM range from 10 through 15 to 11 through 16

LLVM 15 turns on the new pass manager by default, which we have yet to
migrate to so for new we pass the `-enable-new-pm-0` flag in our
llvm-passes flag.

LLVM 11 was the first version to support the `-enable-new-pm` flag so we
bump the lowest supported version to 11.

Our CI jobs are using LLVM 12 so they should continue to work despite
this bump to the lower bound.

Fixes #21936

- - - - -
f94f1450 by Matthew Pickering at 2023-02-01T12:31:58-05:00
Bump DOCKER_REV to use alpine image without LLVM installed

alpine_3_12 only supports LLVM 10, which is now outside the supported
version range.

- - - - -
d4b4edd1 by Matthew Pickering at 2023-02-01T14:33:12-05:00
Remove tracing OPTIONS_GHC

These were accidentally left over from !9542

- - - - -
586646a4 by Teo Camarasu at 2023-02-01T14:33:16-05:00
doc: fix gcdetails_block_fragmentation_bytes since annotation

- - - - -


8 changed files:

- .gitlab-ci.yml
- compiler/GHC.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- configure.ac
- libraries/base/GHC/Stats.hsc
- llvm-passes
- + testsuite/tests/simplCore/should_compile/T22849.hs
- testsuite/tests/simplCore/should_compile/all.T


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -2,7 +2,7 @@ variables:
   GIT_SSL_NO_VERIFY: "1"
 
   # Commit of ghc/ci-images repository from which to pull Docker images
-  DOCKER_REV: 2d59d551647d102c4af44f257c520a94f04ea3f6
+  DOCKER_REV: 572353e0644044fe3a5465bba4342a9a0b0eb60e
 
   # Sequential version number of all cached things.
   # Bump to invalidate GitLab CI cache.


=====================================
compiler/GHC.hs
=====================================
@@ -3,7 +3,6 @@
 {-# LANGUAGE TupleSections, NamedFieldPuns #-}
 {-# LANGUAGE ViewPatterns #-}
 {-# LANGUAGE TypeFamilies #-}
-{-# OPTIONS_GHC -ddump-stg-final -ddump-to-file #-}
 
 -- -----------------------------------------------------------------------------
 --


=====================================
compiler/GHC/Core/Opt/WorkWrap/Utils.hs
=====================================
@@ -707,7 +707,7 @@ Worker/wrapper will unbox
        * is an algebraic data type (not a newtype)
        * is not recursive (as per 'isRecDataCon')
        * has a single constructor (thus is a "product")
-       * that may bind existentials
+       * that may bind existentials (#18982)
      We can transform
      > data D a = forall b. D a b
      > f (D @ex a b) = e
@@ -1272,16 +1272,25 @@ also unbox its components. That is governed by the `usefulSplit` mechanism.
 -}
 
 -- | Exactly 'dataConInstArgTys', but lacks the (ASSERT'ed) precondition that
--- the 'DataCon' may not have existentials. The lack of cloning the existentials
--- compared to 'dataConInstExAndArgVars' makes this function \"dubious\";
--- only use it where type variables aren't substituted for!
+-- the 'DataCon' may not have existentials. The lack of cloning the
+-- existentials this function \"dubious\"; only use it where type variables
+-- aren't substituted for!  Why may the data con bind existentials?
+--    See Note [Which types are unboxed?]
 dubiousDataConInstArgTys :: DataCon -> [Type] -> [Type]
 dubiousDataConInstArgTys dc tc_args = arg_tys
   where
-    univ_tvs = dataConUnivTyVars dc
-    ex_tvs   = dataConExTyCoVars dc
-    subst    = extendSubstInScopeList (zipTvSubst univ_tvs tc_args) ex_tvs
-    arg_tys  = map (GHC.Core.Type.substTy subst . scaledThing) (dataConRepArgTys dc)
+    univ_tvs        = dataConUnivTyVars dc
+    ex_tvs          = dataConExTyCoVars dc
+    univ_subst      = zipTvSubst univ_tvs tc_args
+    (full_subst, _) = substTyVarBndrs univ_subst ex_tvs
+    arg_tys         = map (substTy full_subst . scaledThing) $
+                      dataConRepArgTys dc
+    -- NB: use substTyVarBndrs on ex_tvs to ensure that we
+    --     substitute in their kinds.  For example (#22849)
+    -- Consider data T a where
+    --            MkT :: forall k (t::k->*) (ix::k). t ix -> T @k a
+    -- Then dubiousDataConInstArgTys MkT [Type, Foo] should return
+    --        [Foo (ix::Type)], not [Foo (ix::k)]!
 
 findTypeShape :: FamInstEnvs -> Type -> TypeShape
 -- Uncover the arrow and product shape of a type


=====================================
configure.ac
=====================================
@@ -554,8 +554,8 @@ AC_SUBST(InstallNameToolCmd)
 # tools we are looking for. In the past, GHC supported a number of
 # versions of LLVM simultaneously, but that stopped working around
 # 3.5/3.6 release of LLVM.
-LlvmMinVersion=10  # inclusive
-LlvmMaxVersion=15 # not inclusive
+LlvmMinVersion=11  # inclusive
+LlvmMaxVersion=16 # not inclusive
 AC_SUBST([LlvmMinVersion])
 AC_SUBST([LlvmMaxVersion])
 sUPPORTED_LLVM_VERSION_MIN=$(echo \($LlvmMinVersion\) | sed 's/\./,/')


=====================================
libraries/base/GHC/Stats.hsc
=====================================
@@ -162,7 +162,8 @@ data GCDetails = GCDetails {
     -- | The amount of memory lost due to block fragmentation in bytes.
     -- Block fragmentation is the difference between the amount of blocks retained by the RTS and the blocks that are in use.
     -- This occurs when megablocks are only sparsely used, eg, when data that cannot be moved retains a megablock.
-    -- @since 4.17.0.0
+    --
+    -- @since 4.18.0.0
   , gcdetails_block_fragmentation_bytes :: Word64
     -- | The time elapsed during synchronisation before GC
   , gcdetails_sync_elapsed_ns :: RtsTime


=====================================
llvm-passes
=====================================
@@ -1,5 +1,5 @@
 [
-(0, "-mem2reg -globalopt -lower-expect"),
-(1, "-O1 -globalopt"),
-(2, "-O2")
+(0, "-enable-new-pm=0 -mem2reg -globalopt -lower-expect"),
+(1, "-enable-new-pm=0 -O1 -globalopt"),
+(2, "-enable-new-pm=0 -O2")
 ]


=====================================
testsuite/tests/simplCore/should_compile/T22849.hs
=====================================
@@ -0,0 +1,14 @@
+{-# LANGUAGE GADTs #-}
+
+module T22849 where
+
+data Foo a where
+  Foo :: Foo Int
+
+data Bar a = Bar a (Foo a)
+
+data Some t = forall ix. Some (t ix)
+
+instance Show (Some Bar) where
+  show (Some (Bar v t)) = case t of
+    Foo -> show v


=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -453,7 +453,7 @@ test('T22375', normal, compile, ['-O -ddump-simpl -dsuppress-uniques -dno-typeab
 test('T21851_2', [grep_errmsg(r'wwombat') ], multimod_compile, ['T21851_2', '-O -dno-typeable-binds -dsuppress-uniques'])
 # Should not inline m, so there shouldn't be a single YES
 test('T22317', [grep_errmsg(r'ANSWER = YES') ], compile, ['-O -dinline-check m -ddebug-output'])
-
+test('T22849', normal, compile, ['-O'])
 test('T22634', normal, compile, ['-O -fcatch-nonexhaustive-cases'])
 test('T22494', [grep_errmsg(r'case') ], compile, ['-O -ddump-simpl -dsuppress-uniques'])
 test('T22491', normal, compile, ['-O2'])
@@ -472,3 +472,4 @@ test('T22611', [when(wordsize(32), skip), grep_errmsg(r'\$salterF') ], compile,
 test('T22715_2', normal, multimod_compile, ['T22715_2', '-v0 -O -fspecialise-aggressively'])
 test('T22802', normal, compile, ['-O'])
 test('T15205', normal, compile, ['-O -ddump-simpl -dno-typeable-binds -dsuppress-uniques'])
+



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/407703c34ffb649bbcf87a3218304342fd48ac16...586646a4d0e86cbf6b563fc6ab58d08f54ea3052

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/407703c34ffb649bbcf87a3218304342fd48ac16...586646a4d0e86cbf6b563fc6ab58d08f54ea3052
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/20230201/d9efd71b/attachment-0001.html>


More information about the ghc-commits mailing list