[Git][ghc/ghc][master] GHCi debugger: drop record name spaces for Ids

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Aug 21 17:11:53 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
c29b2b5a by sheaf at 2024-08-21T13:11:30-04:00
GHCi debugger: drop record name spaces for Ids

When binding new local variables at a breakpoint, we should create
Ids with variable namespace, and not record field namespace. Otherwise
the rest of the compiler falls over because the IdDetails are wrong.

Fixes #25109

- - - - -


6 changed files:

- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Types/Id.hs
- + testsuite/tests/ghci.debugger/scripts/T25109.hs
- + testsuite/tests/ghci.debugger/scripts/T25109.script
- + testsuite/tests/ghci.debugger/scripts/T25109.stdout
- testsuite/tests/ghci.debugger/scripts/all.T


Changes:

=====================================
compiler/GHC/Runtime/Eval.hs
=====================================
@@ -625,8 +625,10 @@ bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do
         -- saved/restored, but not the linker state.  See #1743, test break026.
    mkNewId :: OccName -> Type -> Id -> IO Id
    mkNewId occ ty old_id
-     = do { name <- newInteractiveBinder hsc_env occ (getSrcSpan old_id)
-          ; return (Id.mkVanillaGlobalWithInfo name ty (idInfo old_id)) }
+     = do { name <- newInteractiveBinder hsc_env (mkVarOccFS (occNameFS occ)) (getSrcSpan old_id)
+              -- NB: use variable namespace.
+              -- Don't use record field namespaces, lest we cause #25109.
+          ; return $ Id.mkVanillaGlobalWithInfo name ty (idInfo old_id) }
 
    newTyVars :: UniqSupply -> [TcTyVar] -> Subst
      -- Similarly, clone the type variables mentioned in the types


=====================================
compiler/GHC/Types/Id.hs
=====================================
@@ -301,26 +301,28 @@ mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> Id
 mkGlobalId = Var.mkGlobalVar
 
 -- | Make a global 'Id' without any extra information at all
-mkVanillaGlobal :: Name -> Type -> Id
+mkVanillaGlobal :: HasDebugCallStack => Name -> Type -> Id
 mkVanillaGlobal name ty = mkVanillaGlobalWithInfo name ty vanillaIdInfo
 
 -- | Make a global 'Id' with no global information but some generic 'IdInfo'
-mkVanillaGlobalWithInfo :: Name -> Type -> IdInfo -> Id
-mkVanillaGlobalWithInfo = mkGlobalId VanillaId
-
+mkVanillaGlobalWithInfo :: HasDebugCallStack => Name -> Type -> IdInfo -> Id
+mkVanillaGlobalWithInfo nm =
+  assertPpr (not $ isFieldNameSpace $ nameNameSpace nm)
+    (text "mkVanillaGlobalWithInfo called on record field:" <+> ppr nm) $
+    mkGlobalId VanillaId nm
 
 -- | For an explanation of global vs. local 'Id's, see "GHC.Types.Var#globalvslocal"
 mkLocalId :: HasDebugCallStack => Name -> Mult -> Type -> Id
 mkLocalId name w ty = mkLocalIdWithInfo name w (assert (not (isCoVarType ty)) ty) vanillaIdInfo
 
 -- | Make a local CoVar
-mkLocalCoVar :: Name -> Type -> CoVar
+mkLocalCoVar :: HasDebugCallStack => Name -> Type -> CoVar
 mkLocalCoVar name ty
   = assert (isCoVarType ty) $
     Var.mkLocalVar CoVarId name ManyTy ty vanillaIdInfo
 
 -- | Like 'mkLocalId', but checks the type to see if it should make a covar
-mkLocalIdOrCoVar :: Name -> Mult -> Type -> Id
+mkLocalIdOrCoVar :: HasDebugCallStack => Name -> Mult -> Type -> Id
 mkLocalIdOrCoVar name w ty
   -- We should assert (eqType w Many) in the isCoVarType case.
   -- However, currently this assertion does not hold.
@@ -344,7 +346,10 @@ mkExportedLocalId details name ty = Var.mkExportedLocalVar details name ty vanil
         -- Note [Free type variables]
 
 mkExportedVanillaId :: Name -> Type -> Id
-mkExportedVanillaId name ty = Var.mkExportedLocalVar VanillaId name ty vanillaIdInfo
+mkExportedVanillaId name ty =
+  assertPpr (not $ isFieldNameSpace $ nameNameSpace name)
+    (text "mkExportedVanillaId called on record field:" <+> ppr name) $
+    Var.mkExportedLocalVar VanillaId name ty vanillaIdInfo
         -- Note [Free type variables]
 
 


=====================================
testsuite/tests/ghci.debugger/scripts/T25109.hs
=====================================
@@ -0,0 +1,10 @@
+module T25109 where
+
+data R = R { fld :: Int }
+
+foo :: R -> IO ()
+foo r = case fld r of
+  !i -> print i
+
+main :: IO ()
+main = foo (R 1)


=====================================
testsuite/tests/ghci.debugger/scripts/T25109.script
=====================================
@@ -0,0 +1,7 @@
+:l T25109.hs
+:break foo
+main
+:step
+:step
+:step
+:step


=====================================
testsuite/tests/ghci.debugger/scripts/T25109.stdout
=====================================
@@ -0,0 +1,15 @@
+Breakpoint 0 activated at T25109.hs:(6,9)-(7,15)
+Stopped in T25109.foo, T25109.hs:(6,9)-(7,15)
+_result :: IO () = _
+r :: R = _
+Stopped in T25109.foo, T25109.hs:6:14-18
+_result :: Int = _
+r :: R = _
+Stopped in T25109.main, T25109.hs:10:13-15
+_result :: R = _
+Stopped in T25109.fld, T25109.hs:3:14-16
+_result :: Int = _
+fld :: Int = 1
+Stopped in T25109.foo, T25109.hs:7:9-15
+_result :: IO () = _
+i :: Int = 1


=====================================
testsuite/tests/ghci.debugger/scripts/all.T
=====================================
@@ -142,3 +142,4 @@ test('break030',
 test('T23057', [only_ghci, extra_hc_opts('-fno-break-points')], ghci_script, ['T23057.script'])
 test('T24306', normal, ghci_script, ['T24306.script'])
 test('T24712', normal, ghci_script, ['T24712.script'])
+test('T25109', normal, ghci_script, ['T25109.script'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c29b2b5a77611b2bd6c3089765079bc43aec3e22

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c29b2b5a77611b2bd6c3089765079bc43aec3e22
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/a6caf90e/attachment-0001.html>


More information about the ghc-commits mailing list