[commit: ghc] master: ghci: Allow :back and :forward to take counts (b03f074)

git at git.haskell.org git at git.haskell.org
Tue May 19 06:26:44 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/b03f074fd51adfb9bc4f5275294712ee62741aed/ghc

>---------------------------------------------------------------

commit b03f074fd51adfb9bc4f5275294712ee62741aed
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Tue May 19 01:23:47 2015 -0500

    ghci: Allow :back and :forward to take counts
    
    These behave like the count arguments of the gdb `up` and `down`
    commands, allowing the user to quickly jump around in history.
    
    Reviewed By: austin
    
    Differential Revision: https://phabricator.haskell.org/D853


>---------------------------------------------------------------

b03f074fd51adfb9bc4f5275294712ee62741aed
 compiler/main/InteractiveEval.hs  |  8 +++----
 docs/users_guide/7.12.1-notes.xml |  5 +++++
 docs/users_guide/ghci.xml         | 16 +++++++++-----
 ghc/InteractiveUI.hs              | 46 ++++++++++++++++++++++++---------------
 4 files changed, 47 insertions(+), 28 deletions(-)

diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index 44b207a..5458368 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -564,11 +564,11 @@ resumeExec canLogSpan step
                 handleRunStatus step expr bindings final_ids
                                 breakMVar statusMVar status hist'
 
-back :: GhcMonad m => m ([Name], Int, SrcSpan)
-back  = moveHist (+1)
+back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan)
+back n = moveHist (+n)
 
-forward :: GhcMonad m => m ([Name], Int, SrcSpan)
-forward  = moveHist (subtract 1)
+forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan)
+forward n = moveHist (subtract n)
 
 moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan)
 moveHist fn = do
diff --git a/docs/users_guide/7.12.1-notes.xml b/docs/users_guide/7.12.1-notes.xml
index 9a87588..d0eefab 100644
--- a/docs/users_guide/7.12.1-notes.xml
+++ b/docs/users_guide/7.12.1-notes.xml
@@ -96,6 +96,11 @@
                     <literal>Main</literal> with an explicit module header but
                     without <literal>main</literal> is now an error (#7765).
                </para>
+               <para>
+                    The <literal>:back</literal> and <literal>:forward</literal>
+                    commands now take an optional count allowing the user to move forward or
+                    backward in history several steps at a time.
+               </para>
            </listitem>
        </itemizedlist>
     </sect3>
diff --git a/docs/users_guide/ghci.xml b/docs/users_guide/ghci.xml
index 6e09f3a..627aa79 100644
--- a/docs/users_guide/ghci.xml
+++ b/docs/users_guide/ghci.xml
@@ -2096,12 +2096,14 @@ $ ghci -lm
 
       <varlistentry>
         <term>
-          <literal>:back</literal>
+          <literal>:back <optional><replaceable>n</replaceable></optional></literal>
           <indexterm><primary><literal>:back</literal></primary></indexterm>
         </term>
         <listitem>
-          <para>Travel back one step in the history.  See <xref
-              linkend="tracing" />.  See also:
+          <para>Travel back <replaceable>n</replaceable> steps in the
+            history. <replaceable>n</replaceable> is one if omitted.
+            See <xref linkend="tracing" /> for more about GHCi's debugging
+            facilities. See also:
             <literal>:trace</literal>, <literal>:history</literal>,
             <literal>:forward</literal>.</para>
         </listitem>
@@ -2474,12 +2476,14 @@ Prelude> :. cmds.ghci
 
       <varlistentry>
         <term>
-          <literal>:forward</literal>
+          <literal>:forward <optional><replaceable>n</replaceable></optional></literal>
           <indexterm><primary><literal>:forward</literal></primary></indexterm>
         </term>
         <listitem>
-          <para>Move forward in the history.   See <xref
-              linkend="tracing" />.  See also:
+          <para>Move forward <replaceable>n</replaceable> steps in the
+            history. <replaceable>n</replaceable> is one if omitted.
+            See <xref linkend="tracing" /> for more about GHCi's debugging
+            facilities. See also:
             <literal>:trace</literal>, <literal>:history</literal>,
             <literal>:back</literal>.</para>
         </listitem>
diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs
index 70e4df1..0adc0cd 100644
--- a/ghc/InteractiveUI.hs
+++ b/ghc/InteractiveUI.hs
@@ -268,14 +268,14 @@ defFullHelpText =
   " -- Commands for debugging:\n" ++
   "\n" ++
   "   :abandon                    at a breakpoint, abandon current computation\n" ++
-  "   :back                       go back in the history (after :trace)\n" ++
+  "   :back [<n>]                 go back in the history N steps (after :trace)\n" ++
   "   :break [<mod>] <l> [<col>]  set a breakpoint at the specified location\n" ++
   "   :break <name>               set a breakpoint on the specified function\n" ++
   "   :continue                   resume after a breakpoint\n" ++
   "   :delete <number>            delete the specified breakpoint\n" ++
   "   :delete *                   delete all breakpoints\n" ++
   "   :force <expr>               print <expr>, forcing unevaluated parts\n" ++
-  "   :forward                    go forward in the history (after :back)\n" ++
+  "   :forward [<n>]              go forward in the history N step s(after :back)\n" ++
   "   :history [<n>]              after :trace, show the execution history\n" ++
   "   :list                       show the source code around current breakpoint\n" ++
   "   :list <identifier>          show the source code for <identifier>\n" ++
@@ -2747,24 +2747,34 @@ bold c | do_bold   = text start_bold <> c <> text end_bold
        | otherwise = c
 
 backCmd :: String -> GHCi ()
-backCmd = noArgs $ withSandboxOnly ":back" $ do
-  (names, _, pan) <- GHC.back
-  printForUser $ ptext (sLit "Logged breakpoint at") <+> ppr pan
-  printTypeOfNames names
-   -- run the command set with ":set stop <cmd>"
-  st <- getGHCiState
-  enqueueCommands [stop st]
+backCmd arg
+  | null arg        = back 1
+  | all isDigit arg = back (read arg)
+  | otherwise       = liftIO $ putStrLn "Syntax:  :back [num]"
+  where
+  back num = withSandboxOnly ":back" $ do
+      (names, _, pan) <- GHC.back num
+      printForUser $ ptext (sLit "Logged breakpoint at") <+> ppr pan
+      printTypeOfNames names
+       -- run the command set with ":set stop <cmd>"
+      st <- getGHCiState
+      enqueueCommands [stop st]
 
 forwardCmd :: String -> GHCi ()
-forwardCmd = noArgs $ withSandboxOnly ":forward" $ do
-  (names, ix, pan) <- GHC.forward
-  printForUser $ (if (ix == 0)
-                    then ptext (sLit "Stopped at")
-                    else ptext (sLit "Logged breakpoint at")) <+> ppr pan
-  printTypeOfNames names
-   -- run the command set with ":set stop <cmd>"
-  st <- getGHCiState
-  enqueueCommands [stop st]
+forwardCmd arg
+  | null arg        = forward 1
+  | all isDigit arg = forward (read arg)
+  | otherwise       = liftIO $ putStrLn "Syntax:  :back [num]"
+  where
+  forward num = withSandboxOnly ":forward" $ do
+      (names, ix, pan) <- GHC.forward num
+      printForUser $ (if (ix == 0)
+                        then ptext (sLit "Stopped at")
+                        else ptext (sLit "Logged breakpoint at")) <+> ppr pan
+      printTypeOfNames names
+       -- run the command set with ":set stop <cmd>"
+      st <- getGHCiState
+      enqueueCommands [stop st]
 
 -- handle the "break" command
 breakCmd :: String -> GHCi ()



More information about the ghc-commits mailing list