[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: Fix merge conflict in T18355.stderr

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Nov 14 11:46:26 UTC 2022



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


Commits:
e160cf47 by Krzysztof Gogolewski at 2022-11-12T08:05:28-05:00
Fix merge conflict in T18355.stderr

Fixes #22446

- - - - -
294f9073 by Simon Peyton Jones at 2022-11-12T23:14:13+00:00
Fix a trivial typo in dataConNonlinearType

Fixes #22416

- - - - -
c938a1db by Ben Gamari at 2022-11-14T06:46:18-05:00
eventlog: Ensure that IPE output contains actual info table pointers

The refactoring in 866c736e introduced a rather subtle change in the
semantics of the IPE eventlog output, changing the eventlog field from
encoding info table pointers to "TNTC pointers" (which point to entry
code when tables-next-to-code is enabled). Fix this.

Fixes #22452.

- - - - -


9 changed files:

- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Type.hs
- rts/eventlog/EventLog.c
- rts/include/rts/IPE.h
- + testsuite/tests/hiefile/should_compile/T22416.hs
- + testsuite/tests/hiefile/should_compile/T22416.stderr
- testsuite/tests/hiefile/should_compile/all.T
- testsuite/tests/roles/should_compile/T8958.stderr
- testsuite/tests/simplCore/should_compile/T18355.stderr


Changes:

=====================================
compiler/GHC/Core/DataCon.hs
=====================================
@@ -1542,14 +1542,18 @@ dataConWrapperType (MkData { dcUserTyVarBinders = user_tvbs,
     res_ty
 
 dataConNonlinearType :: DataCon -> Type
+-- Just like dataConWrapperType, but with the
+-- linearity on the arguments all zapped to Many
 dataConNonlinearType (MkData { dcUserTyVarBinders = user_tvbs,
                                dcOtherTheta = theta, dcOrigArgTys = arg_tys,
-                               dcOrigResTy = res_ty })
-  = let arg_tys' = map (\(Scaled w t) -> Scaled (case w of OneTy -> ManyTy; _ -> w) t) arg_tys
-    in mkInvisForAllTys user_tvbs $
-       mkInvisFunTys theta $
-       mkScaledFunTys arg_tys' $
-       res_ty
+                               dcOrigResTy = res_ty,
+                               dcStupidTheta = stupid_theta })
+  = mkInvisForAllTys user_tvbs $
+    mkInvisFunTys (stupid_theta ++ theta) $
+    mkScaledFunTys arg_tys' $
+    res_ty
+  where
+    arg_tys' = map (\(Scaled w t) -> Scaled (case w of OneTy -> ManyTy; _ -> w) t) arg_tys
 
 dataConDisplayType :: Bool -> DataCon -> Type
 dataConDisplayType show_linear_types dc


=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -1383,7 +1383,7 @@ splitFunTys ty = split [] ty ty
     split args orig_ty ty | Just ty' <- coreView ty = split args orig_ty ty'
     split args orig_ty _                   = (reverse args, orig_ty)
 
-funResultTy :: Type -> Type
+funResultTy :: HasDebugCallStack => Type -> Type
 -- ^ Extract the function result type and panic if that is not possible
 funResultTy ty
   | FunTy { ft_res = res } <- coreFullView ty = res


=====================================
rts/eventlog/EventLog.c
=====================================
@@ -1429,7 +1429,7 @@ void postIPE(const InfoProvEnt *ipe)
     ensureRoomForVariableEvent(&eventBuf, len);
     postEventHeader(&eventBuf, EVENT_IPE);
     postPayloadSize(&eventBuf, len);
-    postWord64(&eventBuf, (StgWord) ipe->info);
+    postWord64(&eventBuf, (StgWord) INFO_PTR_TO_STRUCT(ipe->info));
     postString(&eventBuf, ipe->prov.table_name);
     postString(&eventBuf, ipe->prov.closure_desc);
     postString(&eventBuf, ipe->prov.ty_desc);


=====================================
rts/include/rts/IPE.h
=====================================
@@ -24,6 +24,8 @@ typedef struct InfoProv_ {
 } InfoProv;
 
 typedef struct InfoProvEnt_ {
+    // When TNTC is enabled this will point to the entry code
+    // not the info table itself.
     const StgInfoTable *info;
     InfoProv prov;
 } InfoProvEnt;
@@ -50,6 +52,8 @@ typedef uint32_t StringIdx;
 // The size of this must be a multiple of the word size
 // to ensure correct packing.
 typedef struct {
+    // When TNTC is enabled this will point to the entry code
+    // not the info table itself.
     const StgInfoTable *info;
     StringIdx table_name;
     StringIdx closure_desc;


=====================================
testsuite/tests/hiefile/should_compile/T22416.hs
=====================================
@@ -0,0 +1,20 @@
+{-# LANGUAGE Haskell2010 #-}
+module Swish.GraphMatch where
+
+import qualified Data.Map as M
+import Data.Word (Word32)
+
+class Label lb
+
+type LabelIndex = (Word32, Word32)
+
+data (Label lb, Eq lv, Show lv) => GenLabelMap lb lv =
+    MkLabelMap Word32 (M.Map lb lv)
+
+type LabelMap lb = GenLabelMap lb LabelIndex
+
+emptyMap :: Label lb => LabelMap lb
+emptyMap = MkLabelMap 1 M.empty
+
+-- MkLabelMap :: forall lb lv. (Label lb, Eq lv, Show lv)
+--            => Word32 -> M.Map lb lv -> GenLabelMap lb lv
\ No newline at end of file


=====================================
testsuite/tests/hiefile/should_compile/T22416.stderr
=====================================
@@ -0,0 +1,2 @@
+Got valid scopes
+Got no roundtrip errors


=====================================
testsuite/tests/hiefile/should_compile/all.T
=====================================
@@ -22,3 +22,4 @@ test('Scopes',       normal,                   compile, ['-fno-code -fwrite-ide-
 # See https://gitlab.haskell.org/ghc/ghc/-/issues/18425 and https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2464#note_301989
 test('ScopesBug',    expect_broken(18425),     compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
 test('T18425',       normal,     compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
+test('T22416',       normal,     compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])


=====================================
testsuite/tests/roles/should_compile/T8958.stderr
=====================================
@@ -10,7 +10,9 @@ TYPE CONSTRUCTORS
 COERCION AXIOMS
   axiom T8958.N:Map :: Map k v = [(k, v)]
 DATA CONSTRUCTORS
-  MkMap :: forall k v. [(k, v)] -> Map k v
+  MkMap :: forall k v.
+           (Nominal k, Representational v) =>
+           [(k, v)] -> Map k v
 CLASS INSTANCES
   instance [incoherent] Representational a
     -- Defined at T8958.hs:11:10
@@ -92,3 +94,19 @@ AbsBinds [a] []
    Evidence: [EvBinds{}]}
 
 
+
+T8958.hs:14:54: warning: [-Wsimplifiable-class-constraints (in -Wdefault)]
+    • The constraint ‘Representational v’ matches
+        instance Representational a -- Defined at T8958.hs:11:10
+      This makes type inference for inner bindings fragile;
+        either use MonoLocalBinds, or simplify it using the instance
+    • In the definition of data constructor ‘MkMap’
+      In the newtype declaration for ‘Map’
+
+T8958.hs:14:54: warning: [-Wsimplifiable-class-constraints (in -Wdefault)]
+    • The constraint ‘Nominal k’ matches
+        instance Nominal a -- Defined at T8958.hs:8:10
+      This makes type inference for inner bindings fragile;
+        either use MonoLocalBinds, or simplify it using the instance
+    • In the definition of data constructor ‘MkMap’
+      In the newtype declaration for ‘Map’


=====================================
testsuite/tests/simplCore/should_compile/T18355.stderr
=====================================
@@ -7,16 +7,8 @@ Result size of Tidy Core
 f :: forall {a}. Num a => a -> Bool -> a -> a
 [GblId,
  Arity=4,
-<<<<<<< HEAD
- Str=<1P(MC1(C1(L)),MC1(C1(L)),A,A,A,A,A)><L><1L><L>,
+ Str=<1P(MC(1,C(1,L)),MC(1,C(1,L)),A,A,A,A,A)><L><1L><L>,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
-||||||| parent of 75ae893f7c (Demand: Format Call SubDemands `Cn(sd)` as `C(n,sd)` (#22231))
- Str=<S,1*U(1*C1(C1(U)),1*C1(C1(U)),A,A,A,A,A)><L,U><S,1*U><L,U>,
- Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
-=======
- Str=<S,1*U(1*C(1,C(1,U)),1*C(1,C(1,U)),A,A,A,A,A)><L,U><S,1*U><L,U>,
- Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
->>>>>>> 75ae893f7c (Demand: Format Call SubDemands `Cn(sd)` as `C(n,sd)` (#22231))
          WorkFree=True, Expandable=True,
          Guidance=IF_ARGS [60 0 70 0] 100 0}]
 f = \ (@a)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/18b8c1777766bd44d29874ac46a27c96137f2dea...c938a1db8e51bba1cff55f5493157e4c8afea8b8

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/18b8c1777766bd44d29874ac46a27c96137f2dea...c938a1db8e51bba1cff55f5493157e4c8afea8b8
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/20221114/a0a74bee/attachment-0001.html>


More information about the ghc-commits mailing list