[Git][ghc/ghc][master] Fix #1620: ModBreaks.modBreaks_array not initialised

Marge Bot gitlab at gitlab.haskell.org
Thu Jun 20 02:15:10 UTC 2019



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


Commits:
39c758e1 by Roland Senn at 2019-06-20T02:15:04Z
Fix #1620: ModBreaks.modBreaks_array not initialised

After a :cd command and after setting some package flags,
GHCi unloads all loaded modules by resetting the list of targets.

This patch deletes eventually defined debugger breakpoints, before GHCi resets the target list.

The common code is factored out into the new function clearAllTargets.

- - - - -


5 changed files:

- ghc/GHCi/UI.hs
- + testsuite/tests/ghci.debugger/scripts/T1620.script
- + testsuite/tests/ghci.debugger/scripts/T1620.stdout
- + testsuite/tests/ghci.debugger/scripts/T1620/T1620.hs
- testsuite/tests/ghci.debugger/scripts/all.T


Changes:

=====================================
ghc/GHCi/UI.hs
=====================================
@@ -1543,8 +1543,8 @@ changeDirectory dir = do
   graph <- GHC.getModuleGraph
   when (not (null $ GHC.mgModSummaries graph)) $
         liftIO $ putStrLn "Warning: changing directory causes all loaded modules to be unloaded,\nbecause the search path has changed."
-  GHC.setTargets []
-  _ <- GHC.load LoadAllTargets
+  -- delete targets and all eventually defined breakpoints (#1620)
+  clearAllTargets
   setContextAfterLoad False []
   GHC.workingDirectoryChanged
   dir' <- expandPath dir
@@ -1852,9 +1852,7 @@ loadModule' files = do
 
   -- unload first
   _ <- GHC.abandonAll
-  discardActiveBreakPoints
-  GHC.setTargets []
-  _ <- GHC.load LoadAllTargets
+  clearAllTargets
 
   GHC.setTargets targets
   success <- doLoadAndCollectInfo False LoadAllTargets
@@ -2916,8 +2914,8 @@ newDynFlags interactive_only minus_opts = do
           when (verbosity dflags2 > 0) $
             liftIO . putStrLn $
               "package flags have changed, resetting and loading new packages..."
-          GHC.setTargets []
-          _ <- GHC.load LoadAllTargets
+          -- delete targets and all eventually defined breakpoints. (#1620)
+          clearAllTargets
           liftIO $ linkPackages hsc_env new_pkgs
           -- package flags changed, we can't re-use any of the old context
           setContextAfterLoad False []
@@ -4128,3 +4126,9 @@ wantNameFromInterpretedModule noCanDo str and_then =
                then noCanDo n $ text "module " <> ppr modl <>
                                 text " is not interpreted"
                else and_then n
+
+clearAllTargets :: GhciMonad m => m ()
+clearAllTargets = discardActiveBreakPoints
+                >> GHC.setTargets []
+                >> GHC.load LoadAllTargets
+                >> pure ()


=====================================
testsuite/tests/ghci.debugger/scripts/T1620.script
=====================================
@@ -0,0 +1,18 @@
+-- Test 1: No hanging breakpoints after :cd
+:cd T1620
+:l T1620.hs
+:break 2
+:cd ..
+:break 2
+:show breaks
+:cd T1620
+:l T1620.hs
+:main
+:l T1620.hs
+-- Test 2: Non hanging breakpoints after :set <some-package-flag>
+:break 2
+:set -no-user-package-db
+:show breaks
+:l T1620.hs
+:main
+:l T1620.hs


=====================================
testsuite/tests/ghci.debugger/scripts/T1620.stdout
=====================================
@@ -0,0 +1,9 @@
+Breakpoint 0 activated at T1620.hs:2:16-47
+Warning: changing directory causes all loaded modules to be unloaded,
+because the search path has changed.
+No modules are loaded with debugging support.
+No active breakpoints.
+[1,3,4,7,10]
+Breakpoint 1 activated at T1620.hs:2:16-47
+No active breakpoints.
+[1,3,4,7,10]


=====================================
testsuite/tests/ghci.debugger/scripts/T1620/T1620.hs
=====================================
@@ -0,0 +1,5 @@
+qsort [] = []
+qsort (a:as) = qsort left ++ [a] ++ qsort right
+  where (left,right) = (filter (<=a) as, filter (>a) as)
+
+main = print $ qsort [4, 1, 7, 10, 3]


=====================================
testsuite/tests/ghci.debugger/scripts/all.T
=====================================
@@ -100,6 +100,8 @@ test('hist001', [extra_files(['../Test3.hs']), extra_run_opts('+RTS -I0')],
 test('hist002', [extra_files(['../Test3.hs']), extra_run_opts('+RTS -I0')],
      ghci_script, ['hist002.script'])
 
+test('T1620', extra_files(['T1620/', 'T1620/T1620.hs']),
+              ghci_script, ['T1620.script'])
 test('T2740', normal, ghci_script, ['T2740.script'])
 
 test('getargs', extra_files(['../getargs.hs']), ghci_script, ['getargs.script'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/39c758e1426c9e5b00de2207ad53bb4377c1e6a6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/39c758e1426c9e5b00de2207ad53bb4377c1e6a6
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/20190619/376e68f7/attachment-0001.html>


More information about the ghc-commits mailing list