[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Expand on the need to clone local binders.

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Nov 15 18:25:24 UTC 2022



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


Commits:
78f7ecb0 by Andreas Klebinger at 2022-11-14T22:20:29-05:00
Expand on the need to clone local binders.

Fixes #22402.

- - - - -
65ce43cc by Krzysztof Gogolewski at 2022-11-14T22:21:05-05:00
Fix :i Constraint printing "type Constraint = Constraint"

Since Constraint became a synonym for CONSTRAINT 'LiftedRep,
we need the same code for handling printing as for the synonym
Type = TYPE 'LiftedRep.
This addresses the same bug as #18594, so I'm reusing the test.

- - - - -
d20dcacb by ARATA Mizuki at 2022-11-15T13:25:10-05:00
configure: Don't check for an unsupported version of LLVM

The upper bound is not inclusive.

Fixes #22449

- - - - -
86167fc6 by Bodigrim at 2022-11-15T13:25:15-05:00
Fix capitalization in haddock for TestEquality

- - - - -


8 changed files:

- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/Stg/Subst.hs
- libraries/base/Data/Type/Equality.hs
- m4/find_llvm_prog.m4
- testsuite/tests/ghci/should_run/T18594.script
- testsuite/tests/ghci/should_run/T18594.stdout


Changes:

=====================================
compiler/GHC/CoreToStg/Prep.hs
=====================================
@@ -112,6 +112,17 @@ The goal of this pass is to prepare for code generation.
     and doing so would be tiresome because then we'd need
     to substitute in types and coercions.
 
+    We need to clone ids for two reasons:
+    + Things associated with labels in the final code must be truly unique in
+      order to avoid labels being shadowed in the final output.
+    + Even binders without info tables like function arguments or alternative
+      bound binders must be unique at least in their type/unique combination.
+      We only emit a single declaration for each binder when compiling to C
+      so if binders are not unique we would either get duplicate declarations
+      or misstyped variables. The later happend in #22402.
+    + We heavily use unique-keyed maps in the backend which can go wrong when
+      ids with the same unique are meant to represent the same variable.
+
 7.  Give each dynamic CCall occurrence a fresh unique; this is
     rather like the cloning step above.
 


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -44,7 +44,8 @@ module GHC.Iface.Syntax (
 
 import GHC.Prelude
 
-import GHC.Builtin.Names ( unrestrictedFunTyConKey, liftedTypeKindTyConKey )
+import GHC.Builtin.Names ( unrestrictedFunTyConKey, liftedTypeKindTyConKey,
+                           constraintKindTyConKey )
 import GHC.Types.Unique ( hasKey )
 import GHC.Iface.Type
 import GHC.Iface.Recomp.Binary
@@ -988,7 +989,8 @@ pprIfaceDecl ss (IfaceSynonym { ifName    = tc
 
     -- See Note [Printing type abbreviations] in GHC.Iface.Type
     ppr_tau | tc `hasKey` liftedTypeKindTyConKey ||
-              tc `hasKey` unrestrictedFunTyConKey
+              tc `hasKey` unrestrictedFunTyConKey ||
+              tc `hasKey` constraintKindTyConKey
             = updSDocContext (\ctx -> ctx { sdocPrintTypeAbbreviations = False }) $ ppr tau
             | otherwise = ppr tau
 


=====================================
compiler/GHC/Iface/Type.hs
=====================================
@@ -846,7 +846,7 @@ Note [Printing type abbreviations]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Normally, we pretty-print
    `TYPE       'LiftedRep` as `Type` (or `*`)
-   `CONSTRAINT 'LiftedRep` as `Constraint` (or `*`)
+   `CONSTRAINT 'LiftedRep` as `Constraint`
    `FUN 'Many`             as `(->)`.
 This way, error messages don't refer to representation polymorphism
 or linearity if it is not necessary.  Normally we'd would represent
@@ -856,14 +856,16 @@ command we specifically expand synonyms (see GHC.Tc.Module.tcRnExpr).
 So here in the pretty-printing we effectively collapse back Type
 and Constraint to their synonym forms.  A bit confusing!
 
-However, when printing the definition of Type or (->) with :info,
+However, when printing the definition of Type, Constraint or (->) with :info,
 this would give confusing output: `type (->) = (->)` (#18594).
 Solution: detect when we are in :info and disable displaying the synonym
 with the SDoc option sdocPrintTypeAbbreviations.
+If you are creating a similar synonym, make sure it is listed in pprIfaceDecl,
+see reference to this Note.
 
 If there will be a need, in the future we could expose it as a flag
--fprint-type-abbreviations or even two separate flags controlling
-TYPE 'LiftedRep and FUN 'Many.
+-fprint-type-abbreviations or even three separate flags controlling
+TYPE 'LiftedRep, CONSTRAINT 'LiftedRep and FUN 'Many.
 -}
 
 -- | Do we want to suppress kind annotations on binders?


=====================================
compiler/GHC/Stg/Subst.hs
=====================================
@@ -12,6 +12,13 @@ import GHC.Utils.Outputable
 import GHC.Utils.Misc
 import GHC.Utils.Panic
 
+-- TODO: This code might make folly of the work done in CorePrep where
+-- we clone local ids in order to ensure *all* local binders are unique.
+-- It's my understanding that here we use "the rapier"/uniqAway which makes up
+-- uniques based on the ids in scope. Which can give the same unique to different
+-- binders as long as they are in different scopes. A guarantee which isn't
+-- strong enough for code generation in general. See Note [CorePrep Overview].
+
 -- | A renaming substitution from 'Id's to 'Id's. Like 'RnEnv2', but not
 -- maintaining pairs of substitutions. Like 'GHC.Core.Subst.Subst', but
 -- with the domain being 'Id's instead of entire 'CoreExpr'.


=====================================
libraries/base/Data/Type/Equality.hs
=====================================
@@ -152,14 +152,14 @@ deriving instance a ~~ b => Bounded (a :~~: b)
 -- The result should be @Just Refl@ if and only if the types applied to @f@ are
 -- equal:
 --
--- @TestEquality (x :: f a) (y :: f b) = Just Refl ⟺ a = b@
+-- @testEquality (x :: f a) (y :: f b) = Just Refl ⟺ a = b@
 --
 -- Typically, only singleton types should inhabit this class. In that case type
 -- argument equality coincides with term equality:
 --
--- @TestEquality (x :: f a) (y :: f b) = Just Refl ⟺ a = b ⟺ x = y@
+-- @testEquality (x :: f a) (y :: f b) = Just Refl ⟺ a = b ⟺ x = y@
 --
--- @isJust (TestEquality x y) = x == y@
+-- @isJust (testEquality x y) = x == y@
 --
 -- Singleton types are not required, however, and so the latter two would-be
 -- laws are not in fact valid in general.


=====================================
m4/find_llvm_prog.m4
=====================================
@@ -11,7 +11,7 @@
 #
 AC_DEFUN([FIND_LLVM_PROG],[
     # Test for program with and without version name.
-    PROG_VERSION_CANDIDATES=$(for llvmVersion in `seq $4 -1 $3`; do echo "$2-$llvmVersion $2-$llvmVersion.0 $2$llvmVersion"; done)
+    PROG_VERSION_CANDIDATES=$(for llvmVersion in `seq $(($4-1)) -1 $3`; do echo "$2-$llvmVersion $2-$llvmVersion.0 $2$llvmVersion"; done)
     AC_CHECK_TOOLS([$1], [$PROG_VERSION_CANDIDATES $2], [])
     AS_IF([test x"$$1" != x],[
         PROG_VERSION=`$$1 --version | awk '/.*version [[0-9\.]]+/{for(i=1;i<=NF;i++){ if(\$i ~ /^[[0-9\.]]+$/){print \$i}}}'`


=====================================
testsuite/tests/ghci/should_run/T18594.script
=====================================
@@ -1,5 +1,6 @@
 :m GHC.Types
 :i (->)
+:i Constraint
 :set -XStarIsType
 :i Type
 :set -XNoStarIsType


=====================================
testsuite/tests/ghci/should_run/T18594.stdout
=====================================
@@ -7,6 +7,9 @@ instance Semigroup b => Semigroup (a -> b) -- Defined in ‘GHC.Base’
 instance Applicative ((->) r) -- Defined in ‘GHC.Base’
 instance Functor ((->) r) -- Defined in ‘GHC.Base’
 instance Monad ((->) r) -- Defined in ‘GHC.Base’
+type Constraint :: *
+type Constraint = CONSTRAINT LiftedRep
+  	-- Defined in ‘GHC.Types’
 type Type :: *
 type Type = TYPE LiftedRep
   	-- Defined in ‘GHC.Types’



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/612cc569bcb1f77db8d9a9ced006156c0f73e0af...86167fc6e6d907c65638ff59bae4a2b5c5c3c2b3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/612cc569bcb1f77db8d9a9ced006156c0f73e0af...86167fc6e6d907c65638ff59bae4a2b5c5c3c2b3
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/20221115/7731bb45/attachment-0001.html>


More information about the ghc-commits mailing list