[m-rev.] Add a listing facility to mdb

Ralph Becket rafe at cs.mu.OZ.AU
Fri Oct 21 16:37:31 AEST 2005


Ian MacLarty, Thursday, 13 October 2005:
> 
> You need to add some tests.
> 

I'll do that in a bit.

> > trace/mercury_trace_internal.c:
> > 	Implement the C part of the `list', `push_list_dir', and `pop_list_dir'
> > 	commands
> 
> It would be more consistent with the current mdb interface to add a new
> configuration parameter that can be set with the `set' command. The format
> options and the xml browser command and temporary filename are all set with the
> `set' command, so why not the search path?
> For example:
> 
> set search_path '.;../browser;../compiler;../mdbcomp'

I've added `set list_path dir1 dir2 ...'

> > Index: browser/listing.m
> > ===================================================================
> > +
> > +:- interface.
> > +
> > +:- import_module io.
> > +:- import_module string.
> > +
> > +
> > +
> > +:- type listings.
> > +:- type line_no   == int.
> > +:- type path_name == string.
> > +:- type file_name == string.
> > +
> > +
> > +
> 
> It doesn't say so in the coding standards, but to be more consistent with
> the other modules in the browser directory please have at most one blank line
> between non-blank lines.

I'm not doing that because I think the extra blank lines improve
readability.  They act as an obvious separator, but are lighter than
using %---------...

> > +    % Construct a new listings structure with a default search path of
> > +    % [dir.this_directory].
> > +    %
> > +:- func new_listings = listings.
> > +
> 
> Isn't adding the current directory to the path redundent, since you always
> search the current directory first anyway (at least according to your list_file
> comments below)?

Fixed.

> > +
> > +    % These predicates are called from trace/mercury_trace_internal.c.
> > +    %
> > +:- pragma export(new_listings = out,
> > +        "MR_listing__new_listings").
> > +:- pragma export(push_file_name_path(in, in, out),
> > +        "MR_listing__push_file_name_path").
> > +:- pragma export(pop_file_name_path(in, out),
> > +        "MR_listing__pop_file_name_path").
> > +:- pragma export(list_file(in, in, in, in, in, out, di, uo),
> > +        "MR_listing__list_file").
> 
> To conform to the convention for exported names in the rest of the browser
> directory, prefix the names with `MR_LISTING_' instead of `MR_listing__'.

Fixed.

> > +        ;
> > +            MaybeFileNameLineOffsets = no,
> > +            io.write_string("cannot find file " ++ FileName0 ++ "\n", !IO)
> 
> You need to write this out to mdb's output stream, which could be different
> from stdout.  The same goes for printing out the listing.

Fixed.

> 
> I'm not convinced that caching all the newline positions is a good idea.
> It may not require a lot of memory, but it does require some, and it also
> increases the complexity of the code which will make it harder to maintain.
> Is there really any noticable speedup to be had from caching the line numbers?

There is a more serious problem here: debugging grades don't support
tail recursion, so either method in Mercury (scanning once for newlines
vs. every time a listing is requested) can exhaust the stack.  This
happens when trying to look at, say, io.m in the library.

The solution I've come up with is to write that part in C and not cache
the line number offsets.  (See the diff).

> > +
> > +:- pred find_line_offsets(io.input_stream::in, int::in, list(int)::in,
> > +        line_offsets::out, io::di, io::uo) is det.
> > +
> 
> I think you need to document the above predicate.

Done.

> > +
> > +:- pred print_lines_in_range(file_name::in, line_no::in, line_no::in,
> > +        line_no::in, line_offsets::in, io::di, io::uo) is det.
> > +
> > +print_lines_in_range(FileName, FirstLine0, LastLine0, MarkLine0, LineOffsets,
> > +        !IO) :-
> 
> You need to document this too.  What is MarkLine0?

Done.  Lines are shown indented with "  ", except for the one numbered
MarkLine0 which is indented with "> ".

> > +    ;
> > +        Result = error(Error),
> > +        io.nl(!IO),
> > +        report_io_error(Error, !IO)
> > +    ).
> 
> You need to write this out to mdb's output stream, not stdout.

Done.

> > +report_io_error(Error, !IO) :-
> > +    io.write_string("* ", !IO),
> > +    io.write_string(io.error_message(Error), !IO),
> > +    io.nl(!IO).
> 
> mdb error messages should be prefixed with "mdb:" and written to the MR_mdb_err
> stream (see mercury_trace_internal.c).

Done.

> >
> > Index: doc/user_guide.texi
> > ===================================================================
> > RCS file: /home/mercury1/repository/mercury/doc/user_guide.texi,v
> > retrieving revision 1.453
> > diff -u -r1.453 user_guide.texi
> > --- doc/user_guide.texi	10 Oct 2005 06:54:56 -0000	1.453
> > +++ doc/user_guide.texi	11 Oct 2005 06:53:24 -0000
> > @@ -2886,6 +2886,22 @@
> >  @c if it is available,
> >  @c to the specified file. The option @samp{-x} (or @samp{--xml}) causes the
> >  @c output to be in XML.
> > + at sp 1
> > + at item list [@var{num}]
> > + at kindex list (mdb command)
> > +Lists the source code text for the current environment, including
> > + at var{num} preceding and following lines.  If @var{num} is not provided then
> > +a default of three is used.
> 
> It would be nice if the default were configurable.

Fixed (see below).

> > +/*
> > +** MR_num_context_lines holds the current number of context lines to be
> > +** printed before and after the current callee/caller's file context.
> > +*/
> > +
> > +static  int         MR_num_context_lines = 2;
> 
> The documentation says the default is three.
> I suggest you define a symbolic constant for the default value.

I've fixed the documentation and added a `set list_context lines <num>'
option.

> > +
> > +static MR_Next
> > +MR_trace_list_part_of_file(char **words, int word_count,
> > +    MR_Trace_Cmd_Info *cmd, MR_Event_Info *event_info,
> > +    MR_Event_Details *event_details, MR_Code **jumpaddr)
> > +{
> 
> Please follow the convention of naming functions that handle mdb commands
> ``MR_trace_<command>_cmd''.  This makes it much easier to find the code that
> handles a particular command.

Done. 

> > +
> > +    if (word_count == 2) {
> > +        char *last_char_parsed;
> > +
> > +        num = strtoul(words[1], &last_char_parsed, 10);
> 
> Use MR_trace_is_natural_number instead.

Done.

> > +
> > +    MR_trace_current_level_details(&entry_ptr, &filename, &lineno,
> > +        &base_sp_ptr, &base_curfr_ptr);
> > +
> > +    /* rafe: XXX Maybe need to use MR_make_aligned_string() for filename? */
> 
> I think you need to align the string before passing it to Mercury in case the
> Mercury code puts the string into another structure, and so uses the tag bits.

Done. 

> > +    /* rafe: XXX Maybe need to use MR_make_aligned_string() for filename? */
> > +
> 
> Yes I think you do (see above).

Done. 

Thanks for the review - here's the relative diff:

diff -u browser/listing.m browser/listing.m
--- browser/listing.m	11 Oct 2005 06:38:06 -0000
+++ browser/listing.m	21 Oct 2005 06:31:31 -0000
@@ -6,6 +6,11 @@
 %
 % Support for providing file listing functionality in the debugger.
 %
+% Unfortunately, scanning large files such as library/io.m byte-by-byte
+% in a debugging grade is likely to exhaust the stack, because debugging
+% grades do not support tail recursion.  Instead we have to handle this
+% aspect using a bit of C code.
+%
 %-----------------------------------------------------------------------------%
 
 :- module mdb.listing.
@@ -13,49 +18,63 @@
 :- interface.
 
 :- import_module io.
+:- import_module list.
 :- import_module string.
 
 
 
-:- type listings.
-:- type line_no   == int.
-:- type path_name == string.
-:- type file_name == string.
+:- type search_path.
+:- type line_no    == int.
+:- type path_name  == string.
+:- type file_name  == string.
+:- type c_file_ptr.                     % For passing `FILE *' arguments.
 
 
 
-    % Construct a new listings structure with a default search path of
-    % [dir.this_directory].
+    % Construct an empty search_path structure.
+    %
+:- func new_list_path = search_path.
+
+    % Get/set/clear the stack of directories searched for FileName matches by
+    %   list_file/7.
     %
-:- func new_listings = listings.
+:- func get_list_path(search_path::in) = (list(path_name)::out) is det.
+:- pred set_list_path(list(path_name)::in,
+        search_path::in, search_path::out) is det.
+:- pred clear_list_path(search_path::in, search_path::out) is det.
 
-    % push_file_name_path(PathName, !Listings)
-    %   Push PathName on to the stack of directories searched for
+    % push_list_path(Dir, !Path)
+    %   Push Dir on to the stack of directories searched for
     %   FileName matches by list_file/7.
     %
-:- pred push_file_name_path(path_name::in, listings::in, listings::out) is det.
+:- pred push_list_path(path_name::in, search_path::in, search_path::out)
+        is det.
 
-    % pop_file_name_path(!Listings)
-    %   Pop the last PathName pushed on to the stack of directories.
+    % pop_list_path(!Path)
+    %   Pop the last Dir pushed on to the stack of directories.
     %   Does nothing if the search path stack is empty.
     %
-:- pred pop_file_name_path(listings::in, listings::out) is det.
+:- pred pop_list_path(search_path::in, search_path::out) is det.
 
-    % list_file(FileName, FirstLine, LastLine, MarkLine, !Listings, !IO)
+    % list_file(OutStrm, ErrStrm, FileName, FirstLine, LastLine, MarkLine,
+    %   Path, !IO)
     %
-    %   Print the lines from FileName with numbers in the range
+    %   Print, on OutStrm, the lines from FileName with numbers in the range
     %   FirstLine ..  LastLine (the first line is numbered 1).
     %   The line numbered MarkLine is marked with a chevron, all
     %   other lines are indented appropriately.
     %
     %   A file matching FileName is searched for by first looking
     %   in the current working directory or, failing that, by
-    %   prepending each PathName on the search path stack in
+    %   prepending each Dir on the search path stack in
     %   turn until a match is found.  If no match is found then
     %   an error message is printed.
     %
-:- pred list_file(file_name::in, line_no::in, line_no::in, line_no::in,
-        listings::in, listings::out, io::di, io::uo) is det.
+    %   Any errors are reported on ErrStrm.
+    %
+:- pred list_file(c_file_ptr::in, c_file_ptr::in,
+        file_name::in, line_no::in, line_no::in, line_no::in,
+        search_path::in, io::di, io::uo) is det.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -66,212 +85,159 @@
 :- import_module char.
 :- import_module dir.
 :- import_module int.
-:- import_module list.
 :- import_module map.
 :- import_module std_util.
 
 
 
-:- type listings
-    --->    listings(
-                search_path             :: search_path,
-                file_name_line_offsets  :: file_name_line_offsets
-            ).
-
 :- type search_path  == list(path_name).
-:- type line_offsets == array(int).     % Offset into file of each newline.
 
-    % A mapping from file names to absolute file names and line offsets.
-    %
-:- type file_name_line_offsets == map(file_name, {file_name, line_offsets}).
+
+
+:- pragma foreign_type("C", c_file_ptr, "FILE *", [can_pass_as_mercury_type]).
 
 
 
     % These predicates are called from trace/mercury_trace_internal.c.
     %
-:- pragma export(new_listings = out,
-        "MR_listing__new_listings").
-:- pragma export(push_file_name_path(in, in, out),
-        "MR_listing__push_file_name_path").
-:- pragma export(pop_file_name_path(in, out),
-        "MR_listing__pop_file_name_path").
-:- pragma export(list_file(in, in, in, in, in, out, di, uo),
-        "MR_listing__list_file").
+:- pragma export(new_list_path = out,
+        "MR_LISTING_new_list_path").
+:- pragma export(get_list_path(in) = out,
+        "MR_LISTING_get_list_path").
+:- pragma export(set_list_path(in, in, out),
+        "MR_LISTING_set_list_path").
+:- pragma export(clear_list_path(in, out),
+        "MR_LISTING_clear_list_path").
+:- pragma export(push_list_path(in, in, out),
+        "MR_LISTING_push_list_path").
+:- pragma export(pop_list_path(in, out),
+        "MR_LISTING_pop_list_path").
+:- pragma export(list_file(in, in, in, in, in, in, in, di, uo),
+        "MR_LISTING_list_file").
 
 %-----------------------------------------------------------------------------%
 
-new_listings = listings([dir.this_directory], map.init).
+new_list_path = [].
 
 %-----------------------------------------------------------------------------%
 
-push_file_name_path(PathName, Listings0, Listings) :-
-    Listings =
-        Listings0 ^ search_path := [PathName | Listings0 ^ search_path].
+get_list_path(Path) = Path.
 
-%-----------------------------------------------------------------------------%
+set_list_path(Dirs, _, Dirs).
 
-pop_file_name_path(Listings0, Listings) :-
-    SearchPath0 = Listings0 ^ search_path,
-    (
-        SearchPath0 = [],
-        Listings = Listings0
-    ;
-        SearchPath0 = [_PathName | SearchPath],
-        Listings = Listings0 ^ search_path := SearchPath
-    ).
+clear_list_path(_, []).
 
 %-----------------------------------------------------------------------------%
 
-list_file(FileName0, FirstLine, LastLine, MarkLine, !Listings, !IO) :-
-    ( if
-        !.Listings ^ file_name_line_offsets ^ elem(FileName0) =
-            {FileName, LineOffsets}
-      then
-        print_lines_in_range(FileName, FirstLine, LastLine, MarkLine,
-            LineOffsets, !IO)
-      else
-        SearchPath = !.Listings ^ search_path,
-        find_file_name_line_offsets(SearchPath, FileName0,
-            MaybeFileNameLineOffsets, !IO),
-        (
-            MaybeFileNameLineOffsets = yes({FileName, LineOffsets}),
-            !:Listings =
-                !.Listings ^ file_name_line_offsets ^ elem(FileName0) :=
-                    {FileName, LineOffsets},
-            print_lines_in_range(FileName, FirstLine, LastLine, MarkLine,
-                LineOffsets, !IO)
-        ;
-            MaybeFileNameLineOffsets = no,
-            io.write_string("cannot find file " ++ FileName0 ++ "\n", !IO)
-        )
-    ).
+push_list_path(Dir, Path, [Dir | Path]).
 
 %-----------------------------------------------------------------------------%
 
-:- pred find_file_name_line_offsets(search_path::in, file_name::in,
-        maybe({file_name, line_offsets})::out, io::di, io::uo) is det.
-
-find_file_name_line_offsets(SearchPath, FileName0, Result, !IO) :-
-    find_file_stream(SearchPath, FileName0, MaybeFileNameStream, !IO),
-    (
-        MaybeFileNameStream = no,
-        Result = no
-    ;
-        MaybeFileNameStream = yes({FileName, Stream}),
-        find_line_offsets(Stream, 0, [0], LineOffsets, !IO),
-        Result = yes({FileName, LineOffsets})
-    ).
+pop_list_path([],         []).
+pop_list_path([_ | Path], Path).
 
 %-----------------------------------------------------------------------------%
 
-    % Search for the first file with the given name on the search path
-    % that we can open for reading and return the complete file name
-    % (including the path component) and input stream handle.
-    %
-:- pred find_file_stream(search_path::in, file_name::in,
-        maybe({file_name, io.input_stream})::out, io::di, io::uo) is det.
-
-find_file_stream([], _, no, !IO).
-
-find_file_stream([Path | SearchPath], FileName0, MaybeFileNameStream, !IO) :-
-    FileName = Path / FileName0,
-    io.open_input(FileName, Result, !IO),
+list_file(OutStrm, ErrStrm, FileName, FirstLine, LastLine, MarkLine, Path,
+        !IO) :-
+    find_and_open_file([dir.this_directory | Path], FileName, Result, !IO),
     (
-        Result = ok(Stream),
-        MaybeFileNameStream = yes({FileName, Stream})
+        Result = yes(InStrm),
+        print_lines_in_range(InStrm, OutStrm, 1, FirstLine, LastLine,
+            MarkLine, !IO)
     ;
-        Result = error(_),
-        find_file_stream(SearchPath, FileName0, MaybeFileNameStream, !IO)
+        Result = no,
+        write_to_c_file(ErrStrm, "mdb: cannot find file ", !IO),
+        write_to_c_file(ErrStrm, FileName, !IO),
+        write_to_c_file(ErrStrm, "\n", !IO)
     ).
 
-%-----------------------------------------------------------------------------%
 
-:- pred find_line_offsets(io.input_stream::in, int::in, list(int)::in,
-        line_offsets::out, io::di, io::uo) is det.
+:- pred write_to_c_file(c_file_ptr::in, string::in, io::di, io::uo) is det.
 
-find_line_offsets(Stream, I, RevOffsets0, LineOffsets, !IO) :-
-    io.read_char(Stream, Result, !IO),
-    (
-        Result = ok(Char),
-        ( if Char = '\n' then RevOffsets = [I + 1 | RevOffsets0]
-                         else RevOffsets = RevOffsets0 ),
-        find_line_offsets(Stream, I + 1, RevOffsets, LineOffsets, !IO)
-    ;
-        Result = eof,
-        LineOffsets = array(list.reverse(RevOffsets0))
-    ;
-        Result = error(Error),
-        report_io_error(Error, !IO),
-        LineOffsets = make_empty_array
-    ).
+:- pragma foreign_proc("C",
+    write_to_c_file(ErrStrm::in, Str::in, IO0::di, IO::uo),
+    [promise_pure, thread_safe, will_not_call_mercury],
+"
+    fputs(Str, (FILE *)ErrStrm);
+    IO = IO0;
+").
 
 %-----------------------------------------------------------------------------%
 
-:- pred print_lines_in_range(file_name::in, line_no::in, line_no::in,
-        line_no::in, line_offsets::in, io::di, io::uo) is det.
-
-print_lines_in_range(FileName, FirstLine0, LastLine0, MarkLine0, LineOffsets,
-        !IO) :-
-    FirstLine = max(1, FirstLine0) - 1,
-    LastLine  = min(array.max(LineOffsets), LastLine0) - 1,
-    MarkLine  = MarkLine0 - 1,
-    io.open_binary_input(FileName, Result, !IO),
-    (
-        Result = ok(Stream),
-        ( if 0 =< FirstLine, FirstLine =< LastLine then
-            io.seek_binary(Stream, io.set, LineOffsets ^ elem(FirstLine), !IO)
-          else
-            true
-        ),
-        echo_lines(Stream, FirstLine, LastLine, MarkLine, !IO),
-        io.close_binary_input(Stream, !IO)
-    ;
-        Result = error(Error),
-        report_io_error(Error, !IO)
-    ).
-
-
-:- pred echo_lines(io.binary_input_stream::in, line_no::in, line_no::in,
-        line_no::in, io::di, io::uo) is det.
-
-echo_lines(Stream, CurrentLine, LastLine, MarkLine, !IO) :-
-    ( if CurrentLine > LastLine then
-        true
-      else
-        io.write_string((if CurrentLine = MarkLine then "> " else "  "), !IO),
-        echo_line(Stream, !IO),
-        echo_lines(Stream, CurrentLine + 1, LastLine, MarkLine, !IO)
-    ).
-
+    % Search for the first file with the given name on the search path
+    % that we can open for reading and return the complete file name
+    % (including the path component) and input stream handle.
+    %
+:- pred find_and_open_file(search_path::in, file_name::in,
+        maybe(c_file_ptr)::out, io::di, io::uo) is det.
 
-:- pred echo_line(io.binary_input_stream::in, io::di, io::uo) is det.
+find_and_open_file([], _, no, !IO).
 
-echo_line(Stream, !IO) :-
-    io.read_byte(Stream, Result, !IO),
+find_and_open_file([Dir | Path], FileName, Result, !IO) :-
+    io.open_input(Dir / FileName, Result0, !IO),
     (
-        Result = ok(Byte),
-        Char = char.det_from_int(Byte),
-        io.write_char(Char, !IO),
-        ( if   Char = '\n'
-          then true
-          else echo_line(Stream, !IO)
-        )
-    ;
-        Result = eof
-    ;
-        Result = error(Error),
-        io.nl(!IO),
-        report_io_error(Error, !IO)
-    ).
-
-%-----------------------------------------------------------------------------%
-
-:- pred report_io_error(io.error::in, io::di, io::uo) is det.
-
-report_io_error(Error, !IO) :-
-    io.write_string("* ", !IO),
-    io.write_string(io.error_message(Error), !IO),
-    io.nl(!IO).
+        Result0 = ok(InStream),
+        InStrm = mercury_stream_to_c_FILE_star(InStream),
+        Result  = yes(InStrm)
+    ;
+        Result0 = error(_),
+        find_and_open_file(Path, FileName, Result, !IO)
+    ).
+
+
+:- func mercury_stream_to_c_FILE_star(io.input_stream) = c_file_ptr.
+
+:- pragma foreign_proc("C",
+    mercury_stream_to_c_FILE_star(InStream::in) = (InStrm::out),
+    [promise_pure, thread_safe, will_not_call_mercury],
+"
+    InStrm = MR_file(*InStream);
+").
+
+%-----------------------------------------------------------------------------%
+
+    % print_lines_in_range(InStrm, OutStrm, ThisLine, FirstLine, LastLine,
+    %   MarkLine, !IO)
+    %
+    %   Print the lines numbered FirstLine to LastLine from InStrm
+    %   on OutStrm (the current line number is taken as ThisLine).
+    %   Each line is printed indented with "  ", except for the line
+    %   numbered MarkLine, if it occurs in the range FirstLine .. LastLine,
+    %   which is indented with "> ".
+    %
+:- pred print_lines_in_range(c_file_ptr::in, c_file_ptr::in,
+        line_no::in, line_no::in, line_no::in, line_no::in, io::di, io::uo)
+        is det.
+
+:- pragma foreign_proc("C",
+    print_lines_in_range(InStrm::in, OutStrm::in, ThisLine::in, FirstLine::in,
+        LastLine::in, MarkLine::in, IO0::di, IO::uo),
+    [promise_pure, thread_safe, will_not_call_mercury],
+"
+    if (FirstLine <= ThisLine && ThisLine <= LastLine) {
+        const char *s = (ThisLine == MarkLine) ? \"> \" : \"  \";
+        fputs(s, (FILE *)OutStrm);
+    }
+    while(ThisLine <= LastLine) {
+        int c = fgetc((FILE *)InStrm);
+        if (c == EOF) {
+            fputc('\\n', (FILE *)OutStrm);
+            break;
+        }
+        if (FirstLine <= ThisLine) {
+            fputc(c, (FILE *)OutStrm);
+        }
+        if (c == '\\n') {
+            ThisLine++;
+            if (FirstLine <= ThisLine && ThisLine <= LastLine)  {
+                const char *s = (ThisLine == MarkLine) ? \"> \" : \"  \";
+                fputs(s, (FILE *)OutStrm);
+            }
+        }
+    }
+    IO = IO0;
+").
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
diff -u doc/user_guide.texi doc/user_guide.texi
--- doc/user_guide.texi	11 Oct 2005 06:53:24 -0000
+++ doc/user_guide.texi	21 Oct 2005 05:47:13 -0000
@@ -2891,7 +2891,7 @@
 @kindex list (mdb command)
 Lists the source code text for the current environment, including
 @var{num} preceding and following lines.  If @var{num} is not provided then
-a default of three is used.
+the default of two is used.
 @sp 1
 @item push_list_dir @var{dir1} @var{dir2} ...
 @kindex push_list_dir (mdb command)
@@ -3658,6 +3658,8 @@
 @kindex xml_tmp_filename (mdb command)
 @kindex fail_trace_counts (mdb command)
 @kindex pass_trace_counts (mdb command)
+ at kindex list_path (mdb command)
+ at kindex list_context_lines (mdb command)
 Updates the given configuration parameter.
 The parameters that can be configured are
 @samp{format}, @samp{depth}, @samp{size}, @samp{width}, @samp{lines}, 
@@ -4240,7 +4242,8 @@
 @item set @var{param} @var{value}
 Update the given configuration parameter.
 The parameters that can be configured are
- at samp{format}, @samp{depth}, @samp{size}, @samp{width} and @samp{lines}.
+ at samp{list_path}, @samp{list_context_lines}, @samp{format}, @samp{depth},
+ at samp{size}, @samp{width} and @samp{lines}.
 @sp 1
 @item mark [@var{term-path}]
 The @samp{mark} command can only be given from within the interactive
diff -u trace/mercury_trace_internal.c trace/mercury_trace_internal.c
--- trace/mercury_trace_internal.c	11 Oct 2005 06:41:52 -0000
+++ trace/mercury_trace_internal.c	21 Oct 2005 06:32:04 -0000
@@ -231,11 +231,11 @@
 static  MR_bool     MR_print_goal_paths = MR_TRUE;
 
 /*
-** MR_listings_state holds the current value of the listings structure
+** MR_LISTING_path holds the current value of the listings structure
 ** as defined in browser/listing.m.
 */
 
-static  MR_Word     MR_listings_state;
+static  MR_Word     MR_LISTING_path;
 
 /*
 ** MR_num_context_lines holds the current number of context lines to be
@@ -479,9 +479,10 @@
 static  MR_TraceCmdFunc MR_trace_cmd_hold;
 static  MR_TraceCmdFunc MR_trace_cmd_diff;
 static  MR_TraceCmdFunc MR_trace_cmd_save_to_file;
-static  MR_TraceCmdFunc MR_trace_list_part_of_file;
-static  MR_TraceCmdFunc MR_trace_push_list_dir;
-static  MR_TraceCmdFunc MR_trace_pop_list_dir;
+static  MR_TraceCmdFunc MR_trace_cmd_list;
+static  MR_TraceCmdFunc MR_trace_cmd_set_list_dir_path;
+static  MR_TraceCmdFunc MR_trace_cmd_push_list_dir;
+static  MR_TraceCmdFunc MR_trace_cmd_pop_list_dir;
 static  MR_TraceCmdFunc MR_trace_cmd_break;
 static  MR_TraceCmdFunc MR_trace_cmd_condition;
 static  MR_TraceCmdFunc MR_trace_cmd_ignore;
@@ -950,10 +951,10 @@
         }
 
         /*
-        ** Set up MR_listings_state.
+        ** Set up MR_LISTING_path.
         */
 
-        MR_listings_state = MR_listing__new_listings();
+        MR_LISTING_path = MR_LISTING_new_list_path();
 
         /*
         ** These functions add the commands to the front of the queue, so
@@ -2396,24 +2397,34 @@
     MR_Word             verbose_format;
     MR_Word             pretty_format;
 
-    if (word_count == 3 &&
-        ( MR_streq(words[1], "fail_trace_count")
-        || MR_streq(words[1], "fail_trace_counts")))
+    if (word_count >= 3 && MR_streq(words[1], "list_context_lines")) {
+
+        if (word_count > 3
+            || !MR_trace_is_natural_number(words[2], &MR_num_context_lines)) {
+            MR_trace_usage("misc", "set");
+        }
+
+    } else if (word_count >= 3 && MR_streq(words[1], "list_path")) {
+
+        MR_trace_cmd_set_list_dir_path(words, word_count, cmd, event_info,
+        event_details, jumpaddr);
+
+    } else if (word_count == 3 && (  MR_streq(words[1], "fail_trace_count")
+                                  || MR_streq(words[1], "fail_trace_counts")))
     {
         if (MR_dice_fail_trace_counts_file != NULL) {
             free(MR_dice_fail_trace_counts_file);
         }
-
         MR_dice_fail_trace_counts_file = MR_copy_string(words[2]);
-    } else if (word_count == 3 &&
-        ( MR_streq(words[1], "pass_trace_count")
-        || MR_streq(words[1], "pass_trace_counts")))
+
+    } else if (word_count == 3 && (  MR_streq(words[1], "pass_trace_count")
+                                  || MR_streq(words[1], "pass_trace_counts")))
     {
         if (MR_dice_pass_trace_counts_file != NULL) {
             free(MR_dice_pass_trace_counts_file);
         }
-
         MR_dice_pass_trace_counts_file = MR_copy_string(words[2]);
+
     } else if (! MR_trace_options_param_set(&print_set, &browse_set,
         &print_all_set, &flat_format, &raw_pretty_format, &verbose_format,
         &pretty_format, &words, &word_count, "misc", "set"))
@@ -2682,7 +2693,7 @@
     */
 
 static MR_Next
-MR_trace_list_part_of_file(char **words, int word_count,
+MR_trace_cmd_list(char **words, int word_count,
     MR_Trace_Cmd_Info *cmd, MR_Event_Info *event_info,
     MR_Event_Details *event_details, MR_Code **jumpaddr)
 {
@@ -2692,61 +2703,77 @@
     MR_Word                 *base_sp_ptr;
     MR_Word                 *base_curfr_ptr;
     MR_bool                 num = MR_num_context_lines;
+    MR_String               aligned_filename;
 
     if (word_count > 2) {
         MR_trace_usage("browsing", "list");
         return KEEP_INTERACTING;
     }
 
-    if (word_count == 2) {
-        char *last_char_parsed;
-
-        num = strtoul(words[1], &last_char_parsed, 10);
-        if (*last_char_parsed != '\0') {
-            MR_trace_usage("browsing", "list");
-            return KEEP_INTERACTING;
-        }
+    if (word_count == 2 && !MR_trace_is_natural_number(words[1], &num)) {
+        MR_trace_usage("browsing", "list");
+        return KEEP_INTERACTING;
     }
 
     MR_trace_current_level_details(&entry_ptr, &filename, &lineno,
         &base_sp_ptr, &base_curfr_ptr);
 
-    /* rafe: XXX Maybe need to use MR_make_aligned_string() for filename? */
+    MR_make_aligned_string(aligned_filename, (MR_String) filename);
+
+    MR_TRACE_CALL_MERCURY(
+        MR_LISTING_list_file(MR_mdb_out, MR_mdb_err, (char *) aligned_filename,
+            lineno - num, lineno + num, lineno, MR_LISTING_path);
+    );
+
+    return KEEP_INTERACTING;
+}
+
+static MR_Next
+MR_trace_cmd_set_list_dir_path(char **words, int word_count,
+    MR_Trace_Cmd_Info *cmd, MR_Event_Info *event_info,
+    MR_Event_Details *event_details, MR_Code **jumpaddr)
+{
+    int       i;
+    MR_String aligned_word;
 
     MR_TRACE_CALL_MERCURY(
-        MR_listing__list_file((char *) filename, lineno - num, lineno + num,
-            lineno, MR_listings_state, &MR_listings_state);
+        MR_LISTING_clear_list_path(MR_LISTING_path, &MR_LISTING_path);
+        for(i = word_count - 1; i >= 1; i--) {
+            MR_make_aligned_string(aligned_word, (MR_String) words[i]);
+            MR_LISTING_push_list_path(aligned_word,
+                MR_LISTING_path, &MR_LISTING_path);
+        }
     );
 
     return KEEP_INTERACTING;
 }
 
 static MR_Next
-MR_trace_push_list_dir(char **words, int word_count,
+MR_trace_cmd_push_list_dir(char **words, int word_count,
     MR_Trace_Cmd_Info *cmd, MR_Event_Info *event_info,
     MR_Event_Details *event_details, MR_Code **jumpaddr)
 {
-    int i;
+    int       i;
+    MR_String aligned_word;
 
     if (word_count < 2) {
         MR_trace_usage("browsing", "push_list_dir");
         return KEEP_INTERACTING;
     }
 
-    /* rafe: XXX Maybe need to use MR_make_aligned_string() for filename? */
-
-    for(i = 1; i < word_count; i++) {
-        MR_TRACE_CALL_MERCURY(
-            MR_listing__push_file_name_path((MR_String) words[i],
-                MR_listings_state, &MR_listings_state);
-        );
-    }
+    MR_TRACE_CALL_MERCURY(
+        for(i = word_count - 1; i >= 1; i--) {
+            MR_make_aligned_string(aligned_word, (MR_String) words[i]);
+            MR_LISTING_push_list_path(aligned_word,
+                MR_LISTING_path, &MR_LISTING_path);
+        }
+    );
 
     return KEEP_INTERACTING;
 }
 
 static MR_Next
-MR_trace_pop_list_dir(char **words, int word_count,
+MR_trace_cmd_pop_list_dir(char **words, int word_count,
     MR_Trace_Cmd_Info *cmd, MR_Event_Info *event_info,
     MR_Event_Details *event_details, MR_Code **jumpaddr)
 {
@@ -2756,7 +2783,7 @@
     }
 
     MR_TRACE_CALL_MERCURY(
-        MR_listing__pop_file_name_path(MR_listings_state, &MR_listings_state);
+        MR_LISTING_pop_list_path(MR_LISTING_path, &MR_LISTING_path);
     );
 
     return KEEP_INTERACTING;
@@ -8475,11 +8502,11 @@
         NULL, MR_trace_var_completer },
     { "browsing", "save_to_file", MR_trace_cmd_save_to_file,
         NULL, MR_trace_var_completer },
-    { "browsing", "list", MR_trace_list_part_of_file,
+    { "browsing", "list", MR_trace_cmd_list,
         NULL, MR_trace_null_completer },
-    { "browsing", "push_list_dir", MR_trace_push_list_dir,
+    { "browsing", "push_list_dir", MR_trace_cmd_push_list_dir,
         NULL, MR_trace_null_completer },
-    { "browsing", "pop_list_dir", MR_trace_pop_list_dir,
+    { "browsing", "pop_list_dir", MR_trace_cmd_pop_list_dir,
         NULL, MR_trace_null_completer },
 
     { "breakpoint", "break", MR_trace_cmd_break,
only in patch2:
unchanged:
--- NEWS	29 Sep 2005 06:33:05 -0000	1.389
+++ NEWS	11 Oct 2005 06:57:30 -0000
@@ -23,6 +23,8 @@
 * None yet.
 
 Changes to the Mercury debugger:
+* Users can now see a listing of the source code line referred to by the
+  current environment.
 * Users can now keep hold of a term, referring to it even when execution has
   left the goal at which the term was available as the value of a program
   variable.
only in patch2:
unchanged:
--- trace/mercury_trace_browse.h	1 Sep 2005 07:37:26 -0000	1.20
+++ trace/mercury_trace_browse.h	10 Oct 2005 05:09:20 -0000
@@ -132,4 +132,5 @@
 */
 extern	void	MR_trace_browse_ensure_init(void);
 
+
 #endif	/* MERCURY_TRACE_BROWSE_H */
--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list