[m-rev.] for review: Add web browser-based term browsing in the debugger.

Peter Wang novalazy at gmail.com
Tue Aug 15 14:26:55 AEST 2017


I am considering removing the browse --xml command.
Does it still work, and does anyone use it? dump --xml will still
exist if anyone wants to deal with XML for some reason.

----

Add web browser-based term browsing in the debugger.

browser/browse.m:
    Add save_and_browse_browser_term_web to be called when
    "browse --web" is entered at the mdb prompt.

    Add browser_term_to_html_flat_string, a helper predicate for
    term_to_html.

    Make portray_flat_write_browser_term work take a stream parameter
    instead of writing to the current output stream. It is called by
    browser_term_to_html_flat_string, writing to a string builder
    stream.

browser/browser_info.m:
    Add web_browser_cmd field to browser_persistent_state.

browser/mdb.m:
browser/term_to_html.m:
    Add new module to generate an HTML document. The document contains a
    JavaScript represention of a Mercury term.

    (The JavaScript string escaping code is adapted from Julien's
    mercury-json project.)

browser/percent_encoding.m:
    Add new module to perform percent-encoding.

scripts/mdb_term_browser.css:
scripts/mdb_term_browser.js:
    Add JavaScript and CSS files referenced by the generated HTML file
    to create a tree view of a Mercury term using jstree.

scripts/32px.png:
scripts/40px.png:
scripts/throbber.gif:
scripts/jstree.min.js:
scripts/jstree.style.min.css:
    Add local copy of jstree files <https://www.jstree.com/>

scripts/jquery.slim.min.js:
    Add local copy of jquery <https://jquery.com/>

scripts/Mmakefile:
    Install the new files into the same directory as mdbrc and other
    mdb-related files.

trace/mercury_trace_browse.c:
trace/mercury_trace_browse.h:
trace/mercury_trace_cmd_browsing.c:
trace/mercury_trace_cmd_parameter.c:
trace/mercury_trace_cmd_parameter.h:
trace/mercury_trace_internal.c:
    Add "browse --web" and "web_browser_cmd" commands.

doc/user_guide.texi:
    Document "browse --web" and "web_browser_cmd" commands.

configure.ac:
scripts/mdbrc.in:
    Set a reasonable default command to launch a web browser from mdb.
    (Only tested on Linux.)

NEWS:
    Announce the new feature.

diff --git a/NEWS b/NEWS
index adf897b..dc9f898 100644
--- a/NEWS
+++ b/NEWS
@@ -593,6 +593,8 @@ Change to the Mercury debugger:
     - Non-canonical output bindings are now printed in solutions.
     - Underscore variables are no longer printed in solutions.
 
+* We have added a "browse --web" command to view terms in a web browser.
+
 Changes to the extras distribution:
 
 * We have added support for Unicode and other enhancements to the lex and
diff --git a/browser/browse.m b/browser/browse.m
index f829dfa..195f0b7 100644
--- a/browser/browse.m
+++ b/browser/browse.m
@@ -2,6 +2,7 @@
 % vim: ft=mercury ts=4 sw=4 et
 %---------------------------------------------------------------------------%
 % Copyright (C) 1998-2007, 2009-2010 The University of Melbourne.
+% Copyright (C) 2017 The Mercury Team.
 % This file may only be copied under the terms of the GNU Library General
 % Public License - see the file COPYING.LIB in the Mercury distribution.
 %---------------------------------------------------------------------------%
@@ -27,6 +28,7 @@
 :- import_module mdb.browser_info.
 :- import_module mdb.browser_term.
 
+:- import_module bool.
 :- import_module io.
 :- import_module list.
 :- import_module maybe.
@@ -152,6 +154,18 @@
     io.output_stream::in, io.output_stream::in,
     browser_persistent_state::in, io::di, io::uo) is cc_multi.
 
+    % Save BrowserTerm in an HTML file and launch the web browser specified
+    % by the web_browser_cmd field in the browser_persistent_state.
+    %
+:- pred save_and_browse_browser_term_web(browser_term::in,
+    io.output_stream::in, io.output_stream::in,
+    browser_persistent_state::in, io::di, io::uo) is cc_multi.
+
+    % Exported for term_to_html.
+    %
+:- pred browser_term_to_html_flat_string(browser_term::in, string::out,
+    bool::out, io::di, io::uo) is cc_multi.
+
 %---------------------------------------------------------------------------%
 
     % Remove "/dir/../" sequences from a list of directories to yield
@@ -179,9 +193,10 @@
 :- import_module mdb.parse.
 :- import_module mdb.frame.
 :- import_module mdb.sized_pretty.
+:- import_module mdb.term_to_html.
 
-:- import_module bool.
 :- import_module deconstruct.
+:- import_module dir.
 :- import_module getopt.
 :- import_module int.
 :- import_module map.
@@ -190,6 +205,7 @@
 :- import_module stream.
 :- import_module stream.string_writer.
 :- import_module string.
+:- import_module string.builder.
 :- import_module term_io.
 :- import_module term_to_xml.
 :- import_module type_desc.
@@ -225,6 +241,10 @@
     save_and_browse_browser_term_xml(in, in, in, in, di, uo),
     "ML_BROWSE_browse_term_xml").
 
+:- pragma foreign_export("C",
+    save_and_browse_browser_term_web(in, in, in, in, di, uo),
+    "ML_BROWSE_browse_term_web").
+
 %---------------------------------------------------------------------------%
 %
 % Non-interactive display.
@@ -682,7 +702,8 @@ portray_flat(Debugger, BrowserTerm, Params, !IO) :-
     browser_term_size_left_from_max(BrowserTerm, max_print_size,
         RemainingSize),
     ( if RemainingSize >= 0 then
-        portray_flat_write_browser_term(BrowserTerm, !IO)
+        io.output_stream(Stream, !IO),
+        portray_flat_write_browser_term(Stream, BrowserTerm, !IO)
     else
         io.get_stream_db(StreamDb, !IO),
         BrowserDb = browser_db(StreamDb),
@@ -691,32 +712,38 @@ portray_flat(Debugger, BrowserTerm, Params, !IO) :-
         write_string_debugger(Debugger, Str, !IO)
     ).
 
-:- pred portray_flat_write_browser_term(browser_term::in,
-    io::di, io::uo) is cc_multi.
+:- pred portray_flat_write_browser_term(Stream::in, browser_term::in,
+    State::di, State::uo) is cc_multi
+    <= (stream.writer(Stream, string, State),
+        stream.writer(Stream, character, State)).
 
-portray_flat_write_browser_term(plain_term(Univ), !IO) :-
-    io.output_stream(Stream, !IO),
+portray_flat_write_browser_term(Stream, plain_term(Univ), !IO) :-
     string_writer.write_univ(Stream, include_details_cc, Univ, !IO).
-portray_flat_write_browser_term(synthetic_term(Functor, Args, MaybeReturn),
+portray_flat_write_browser_term(Stream, synthetic_term(Functor, Args, MaybeReturn),
         !IO) :-
-    io.write_string(Functor, !IO),
-    io.output_stream(Stream, !IO),
+    put(Stream, Functor, !IO),
     (
         Args = []
     ;
         Args = [_ | _],
-        io.write_string("(", !IO),
-        io.write_list(Args, ", ", write_univ_or_unbound(Stream), !IO),
-        io.write_string(")", !IO)
+        put(Stream, "(", !IO),
+        put_list(Stream, write_univ_or_unbound, put_comma_space, Args, !IO),
+        put(Stream, ")", !IO)
     ),
     (
         MaybeReturn = yes(Return),
-        io.write_string(" = ", !IO),
+        put(Stream, " = ", !IO),
         string_writer.write_univ(Stream, include_details_cc, Return, !IO)
     ;
         MaybeReturn = no
     ).
 
+:- pred put_comma_space(Stream::in, State::di, State::uo) is det
+    <= stream.writer(Stream, string, State).
+
+put_comma_space(Stream, !State) :-
+    put(Stream, ", ", !State).
+
 :- pred portray_verbose(debugger::in, browser_term::in, format_params::in,
     io::di, io::uo) is cc_multi.
 
@@ -793,12 +820,14 @@ browser_term_size_left_from_max(BrowserTerm, MaxSize, RemainingSize) :-
         list.foldl(term_size_left_from_max, Args, MaxArgsSize, RemainingSize)
     ).
 
-:- pred write_univ_or_unbound(io.output_stream::in, univ::in, io::di, io::uo)
-    is cc_multi.
+:- pred write_univ_or_unbound(Stream::in, univ::in, State::di, State::uo)
+    is cc_multi
+    <= (stream.writer(Stream, string, State),
+        stream.writer(Stream, character, State)).
 
 write_univ_or_unbound(Stream, Univ, !IO) :-
     ( if univ_to_type(Univ, _ `with_type` unbound) then
-        io.write_char(Stream, '_', !IO)
+        put_char(Stream, '_', !IO)
     else
         string_writer.write_univ(Stream, include_details_cc, Univ, !IO)
     ).
@@ -1440,6 +1469,135 @@ launch_xml_browser(OutStream, ErrStream, CommandStr, !IO) :-
 
 %---------------------------------------------------------------------------%
 
+save_and_browse_browser_term_web(Term, OutStream, ErrStream, State, !IO) :-
+    get_mdb_dir(MaybeMdbDir, !IO),
+    (
+        MaybeMdbDir = yes(MdbDir),
+        MaybeBrowserCmd = State ^ web_browser_cmd,
+        (
+            MaybeBrowserCmd = yes(BrowserCmd),
+            io.get_temp_directory(TmpDir, !IO),
+            io.make_temp_file(TmpDir, "mdb", ".html", TmpResult, !IO),
+            (
+                TmpResult = ok(TmpFileName0),
+                ( if string.suffix(TmpFileName0, ".html") then
+                    TmpFileName = TmpFileName0
+                else
+                    % Work around io.make_temp_file ignoring suffix.
+                    io.remove_file(TmpFileName, _, !IO),
+                    TmpFileName = TmpFileName0 ++ ".html"
+                ),
+                save_term_to_file_web(TmpFileName, Term, MdbDir,
+                    SaveResult, !IO),
+                (
+                    SaveResult = ok(_),
+                    % We should actually quote the file name.
+                    CommandStr = BrowserCmd ++ " " ++ TmpFileName,
+                    launch_web_browser(OutStream, ErrStream, CommandStr, !IO)
+                ;
+                    SaveResult = error(Error),
+                    io.error_message(Error, Msg),
+                    io.write_string(ErrStream,
+                        "Error opening file `" ++ TmpFileName ++ "': ", !IO),
+                    io.write_string(ErrStream, Msg, !IO),
+                    io.nl(!IO)
+                )
+            ;
+                TmpResult = error(Error),
+                io.error_message(Error, Msg),
+                io.write_string(ErrStream, "Error opening temporary file: ",
+                    !IO),
+                io.write_string(ErrStream, Msg, !IO),
+                io.nl(!IO)
+            )
+        ;
+            MaybeBrowserCmd = no,
+            io.write_string(ErrStream, "mdb: You need to issue a " ++
+                "\"web_browser_cmd '<command>'\" command first.\n", !IO)
+        )
+    ;
+        MaybeMdbDir = no,
+        io.write_string(ErrStream,
+            "Could not determine directory containing mdb files.\n", !IO)
+    ).
+
+:- pred get_mdb_dir(maybe(string)::out, io::di, io::uo) is det.
+
+get_mdb_dir(Res, !IO) :-
+    get_environment_var("MERCURY_DEBUGGER_INIT", MaybeValue, !IO),
+    ( if
+        MaybeValue = yes(Path),
+        dir.path_name_is_absolute(Path),
+        dir.split_name(Path, MdbDir, "mdbrc")
+    then
+        Res = yes(MdbDir)
+    else
+        Res = no
+    ).
+
+:- pred save_term_to_file_web(string::in, browser_term::in, string::in,
+    io.res(io.output_stream)::out, io::di, io::uo) is cc_multi.
+
+save_term_to_file_web(FileName, BrowserTerm, MdbDir, FileStreamRes,
+        !IO) :-
+    io.open_output(FileName, FileStreamRes, !IO),
+    (
+        FileStreamRes = ok(OutputStream),
+        term_to_html.write_html_doc(OutputStream, BrowserTerm, MdbDir, _, !IO),
+        io.close_output(OutputStream, !IO)
+    ;
+        FileStreamRes = error(_)
+    ).
+
+:- pred launch_web_browser(io.output_stream::in, io.output_stream::in,
+    string::in, io::di, io::uo) is det.
+
+launch_web_browser(OutStream, ErrStream, CommandStr, !IO) :-
+    io.write_string(OutStream, "Launching web browser...\n", !IO),
+    io.flush_output(OutStream, !IO),
+    io.call_system_return_signal(CommandStr, Result, !IO),
+    (
+        Result = ok(ExitStatus),
+        (
+            ExitStatus = exited(ExitCode),
+            ( if ExitCode = 0 then
+                true
+            else
+                io.write_string(ErrStream,
+                    "mdb: The command `" ++ CommandStr ++
+                    "' terminated with a non-zero exit code.\n", !IO)
+            )
+        ;
+            ExitStatus = signalled(_),
+            io.write_string(ErrStream, "mdb: The browser was killed.\n", !IO)
+        )
+    ;
+        Result = error(Error),
+        io.write_string(ErrStream, "mdb: Error launching browser: "
+            ++ string.string(Error) ++ ".\n", !IO)
+    ).
+
+browser_term_to_html_flat_string(BrowserTerm, Str, Elided, !IO) :-
+    % Mimic portray_flat. We can afford larger sizes in a web browser due to
+    % proportional fonts and horizontal scrolling.
+    MaxTermSize = 120,
+    browser_term_size_left_from_max(BrowserTerm, MaxTermSize, RemainingSize),
+    ( if RemainingSize >= 0 then
+        portray_flat_write_browser_term(string.builder.handle, BrowserTerm,
+            string.builder.init, State),
+        Str = to_string(State),
+        Elided = no
+    else
+        io.get_stream_db(StreamDb, !IO),
+        BrowserDb = browser_db(StreamDb),
+        MaxSize = 10,
+        MaxDepth = 5,
+        browser_term_to_string(BrowserDb, BrowserTerm, MaxSize, MaxDepth, Str),
+        Elided = yes
+    ).
+
+%---------------------------------------------------------------------------%
+
 :- pred save_univ(int::in, univ::in, io::di, io::uo) is cc_multi.
 
 save_univ(Indent, Univ, !IO) :-
diff --git a/browser/browser_info.m b/browser/browser_info.m
index 40650d2..dde799e 100644
--- a/browser/browser_info.m
+++ b/browser/browser_info.m
@@ -187,6 +187,9 @@
 :- pred info_set_xml_tmp_filename(string::in,
     browser_info::in, browser_info::out) is det.
 
+:- pred info_set_web_browser_cmd(string::in,
+    browser_info::in, browser_info::out) is det.
+
 %---------------------------------------------------------------------------%
 
     % A data type that holds persistent browser settings.
@@ -203,6 +206,10 @@
 :- func browser_persistent_state ^ xml_tmp_filename := maybe(string) =
     browser_persistent_state.
 
+:- func browser_persistent_state ^ web_browser_cmd = maybe(string).
+:- func browser_persistent_state ^ web_browser_cmd := maybe(string) =
+    browser_persistent_state.
+
     % Initialize the persistent browser state with default values.
     %
 :- pred init_persistent_state(browser_persistent_state).
@@ -435,6 +442,11 @@ info_set_xml_tmp_filename(FileName, !Info) :-
     set_xml_tmp_filename_from_mdb(FileName, PersistentState0, PersistentState),
     !Info ^ bri_state := PersistentState.
 
+info_set_web_browser_cmd(Cmd, !Info) :-
+    PersistentState0 = !.Info ^ bri_state,
+    set_web_browser_cmd_from_mdb(Cmd, PersistentState0, PersistentState),
+    !Info ^ bri_state := PersistentState.
+
 %---------------------------------------------------------------------------%
 
 %
@@ -549,6 +561,32 @@ set_xml_tmp_filename_from_mdb(FileName, !Browser) :-
         !Browser ^ xml_tmp_filename := yes(FileName)
     ).
 
+:- pred get_web_browser_cmd_from_mdb(browser_persistent_state::in,
+    string::out) is det.
+:- pragma foreign_export("C", get_web_browser_cmd_from_mdb(in, out),
+    "ML_BROWSE_get_web_browser_cmd_from_mdb").
+
+get_web_browser_cmd_from_mdb(Browser, Command) :-
+    MaybeCommand = Browser ^ web_browser_cmd,
+    (
+        MaybeCommand = no,
+        Command = ""
+    ;
+        MaybeCommand = yes(Command)
+    ).
+
+:- pred set_web_browser_cmd_from_mdb(string::in,
+    browser_persistent_state::in, browser_persistent_state::out) is det.
+:- pragma foreign_export("C", set_web_browser_cmd_from_mdb(in, in, out),
+    "ML_BROWSE_set_web_browser_cmd_from_mdb").
+
+set_web_browser_cmd_from_mdb(Command, !Browser) :-
+    ( if Command = "" then
+        !Browser ^ web_browser_cmd := no
+    else
+        !Browser ^ web_browser_cmd := yes(Command)
+    ).
+
 %---------------------------------------------------------------------------%
 %
 % The following functions allow C code to create Mercury values of type bool.
@@ -579,7 +617,10 @@ mercury_bool_no = no.
                 xml_browser_cmd         :: maybe(string),
 
                 % The file to save XML to before launching the browser.
-                xml_tmp_filename        :: maybe(string)
+                xml_tmp_filename        :: maybe(string),
+
+                % The command to launch the user's preferred web browser.
+                web_browser_cmd         :: maybe(string)
             ).
 
 :- type caller_params
@@ -617,7 +658,7 @@ init_persistent_state(State) :-
     Browse = caller_type_browse_defaults,
     PrintAll = caller_type_print_all_defaults,
     State = browser_persistent_state(Print, Browse, PrintAll,
-        num_printed_io_actions_default, no, no).
+        num_printed_io_actions_default, no, no, no).
 
 :- func caller_type_print_defaults = caller_params.
 
@@ -699,7 +740,8 @@ set_browser_param(FromBrowser, P0, B0, A0, F0, Pr0, V0, NPr0, Setting,
     maybe_set_param(A, F, Pr, V, NPr, Setting, AParams0, AParams),
     !:State = browser_persistent_state(PParams, BParams, AParams,
         !.State ^ num_printed_io_actions,
-        !.State ^ xml_browser_cmd, !.State ^ xml_tmp_filename).
+        !.State ^ xml_browser_cmd, !.State ^ xml_tmp_filename,
+        !.State ^ web_browser_cmd).
 
 set_browser_param_with_caller_type(CallerType, P0, B0, A0, F0, Pr0, V0, NPr0,
         Setting, !State) :-
@@ -726,7 +768,8 @@ set_browser_param_with_caller_type(CallerType, P0, B0, A0, F0, Pr0, V0, NPr0,
     maybe_set_param(A, F, Pr, V, NPr, Setting, AParams0, AParams),
     !:State = browser_persistent_state(PParams, BParams, AParams,
         !.State ^ num_printed_io_actions,
-        !.State ^ xml_browser_cmd, !.State ^ xml_tmp_filename).
+        !.State ^ xml_browser_cmd, !.State ^ xml_tmp_filename,
+        !.State ^ web_browser_cmd).
 
 set_browser_param_maybe_caller_type(FromBrowser, MaybeCallerType,
         F0, Pr0, V0, NPr0, Setting, !State) :-
@@ -1091,7 +1134,8 @@ send_term_to_socket(Term, !IO) :-
 
 browser_params_to_string(Browser, MDBCommandFormat, Desc) :-
     Browser = browser_persistent_state(PrintParams, BrowseParams,
-        PrintAllParams, NumIOActions, MaybeXMLBrowserCmd, MaybeXMLTmpFileName),
+        PrintAllParams, NumIOActions, MaybeXMLBrowserCmd, MaybeXMLTmpFileName,
+        MaybeWebBrowserCmd),
     (
         MDBCommandFormat = yes,
         ParamCmds =
@@ -1122,8 +1166,18 @@ browser_params_to_string(Browser, MDBCommandFormat, Desc) :-
         else
             XMLTmpFileNameCmd = ""
         ),
+        ( if
+            MaybeWebBrowserCmd = yes(WebBrowserCmd),
+            WebBrowserCmd \= ""
+        then
+            WebBrowserCmdCmd =
+                "web_browser_cmd " ++ WebBrowserCmd ++ "\n"
+        else
+            WebBrowserCmdCmd = ""
+        ),
         Desc = ParamCmds ++ NumIOActionCmd ++
-            XMLBrowserCmdCmd ++ XMLTmpFileNameCmd
+            XMLBrowserCmdCmd ++ XMLTmpFileNameCmd ++
+            WebBrowserCmdCmd
     ;
         MDBCommandFormat = no,
         ParamDesc =
diff --git a/browser/mdb.m b/browser/mdb.m
index 2162beb..e47195b 100644
--- a/browser/mdb.m
+++ b/browser/mdb.m
@@ -40,8 +40,9 @@
 :- include_module frame.
 :- include_module parse.
 :- include_module sized_pretty.
-:- include_module util.
 :- include_module term_rep.
+:- include_module term_to_html.
+:- include_module util.
 
     % XXX these modules are more generally useful, but the
     % dynamic linking library is not yet installed anywhere.
diff --git a/browser/percent_encoding.m b/browser/percent_encoding.m
new file mode 100644
index 0000000..867a049
--- /dev/null
+++ b/browser/percent_encoding.m
@@ -0,0 +1,157 @@
+%---------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%---------------------------------------------------------------------------%
+% Copyright (C) 2017 The Mercury team.
+% This file may only be copied under the terms of the GNU Library General
+% Public License - see the file COPYING.LIB in the Mercury distribution.
+%---------------------------------------------------------------------------%
+%
+% File: percent_encoding.m.
+% Main author: wangp.
+%
+% This module performs percent-encoding.
+%
+%---------------------------------------------------------------------------%
+%---------------------------------------------------------------------------%
+
+:- module percent_encoding.
+:- interface.
+
+    % Apply percent-encoding to a path segment.
+    %
+:- func percent_encode_path_segment(string) = string.
+
+%---------------------------------------------------------------------------%
+%---------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module char.
+:- import_module int.
+:- import_module list.
+:- import_module string.
+
+%---------------------------------------------------------------------------%
+
+percent_encode_path_segment(S0) = S :-
+    ( if string.all_match(unreserved_char_in_path_segment, S0) then
+        S = S0
+    else
+        string.to_utf8_code_unit_list(S0, Octets),
+        list.foldr(percent_encode_octet, Octets, [], Encoded),
+        string.from_char_list(Encoded, S)
+    ).
+
+:- pred percent_encode_octet(int::in, list(char)::in, list(char)::out) is det.
+
+percent_encode_octet(Octet, Encoded0, Encoded) :-
+    ( if
+        Octet =< 0x7f,
+        char.from_int(Octet, Char),
+        unreserved_char_in_path_segment(Char)
+    then
+        Encoded = [Char | Encoded0]
+    else
+        octet_to_hex_chars(Octet, Hi, Lo),
+        Encoded = ['%', Hi, Lo | Encoded0]
+    ).
+
+:- pred octet_to_hex_chars(int::in, char::out, char::out) is det.
+
+octet_to_hex_chars(I, Hi, Lo) :-
+    Int_Hi = (I /\ 0xf0) `unchecked_right_shift` 4,
+    Int_Lo = (I /\ 0x0f),
+    Hi = char.det_int_to_hex_digit(Int_Hi),
+    Lo = char.det_int_to_hex_digit(Int_Lo).
+
+:- pred unreserved_char_in_path_segment(char::in) is semidet.
+
+unreserved_char_in_path_segment(C) :-
+    % These characters are in the reserved set but have no reserved purpose in
+    % path segments.
+    ( C = ('!')
+    ; C = ('*')
+    ; C = ('''')
+    ; C = ('(')
+    ; C = (')')
+    ; C = (';')
+    ; C = (':')
+    ; C = ('@')
+    ; C = ('&')
+    ; C = ('=')
+    ; C = ('+')
+    ; C = ('$')
+    ; C = (',')
+
+    % These characters are in the unreserved set.
+    ; C = ('-')
+    ; C = ('_')
+    ; C = ('.')
+    ; C = ('~')
+    ; C = ('0')
+    ; C = ('1')
+    ; C = ('2')
+    ; C = ('3')
+    ; C = ('4')
+    ; C = ('5')
+    ; C = ('6')
+    ; C = ('7')
+    ; C = ('8')
+    ; C = ('9')
+    ; C = ('A')
+    ; C = ('B')
+    ; C = ('C')
+    ; C = ('D')
+    ; C = ('E')
+    ; C = ('F')
+    ; C = ('G')
+    ; C = ('H')
+    ; C = ('I')
+    ; C = ('J')
+    ; C = ('K')
+    ; C = ('L')
+    ; C = ('M')
+    ; C = ('N')
+    ; C = ('O')
+    ; C = ('P')
+    ; C = ('Q')
+    ; C = ('R')
+    ; C = ('S')
+    ; C = ('T')
+    ; C = ('U')
+    ; C = ('V')
+    ; C = ('W')
+    ; C = ('X')
+    ; C = ('Y')
+    ; C = ('Z')
+    ; C = ('a')
+    ; C = ('b')
+    ; C = ('c')
+    ; C = ('d')
+    ; C = ('e')
+    ; C = ('f')
+    ; C = ('g')
+    ; C = ('h')
+    ; C = ('i')
+    ; C = ('j')
+    ; C = ('k')
+    ; C = ('l')
+    ; C = ('m')
+    ; C = ('n')
+    ; C = ('o')
+    ; C = ('p')
+    ; C = ('q')
+    ; C = ('r')
+    ; C = ('s')
+    ; C = ('t')
+    ; C = ('u')
+    ; C = ('v')
+    ; C = ('w')
+    ; C = ('x')
+    ; C = ('y')
+    ; C = ('z')
+    ).
+
+%---------------------------------------------------------------------------%
+:- end_module percent_encoding.
+%---------------------------------------------------------------------------%
diff --git a/browser/term_to_html.m b/browser/term_to_html.m
new file mode 100644
index 0000000..ff679c3
--- /dev/null
+++ b/browser/term_to_html.m
@@ -0,0 +1,427 @@
+%---------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%---------------------------------------------------------------------------%
+% Copyright (C) 2017 The Mercury team.
+% This file may only be copied under the terms of the GNU Library General
+% Public License - see the file COPYING.LIB in the Mercury distribution.
+%---------------------------------------------------------------------------%
+%
+% File: term_to_html.m.
+% Main author: wangp.
+%
+% This module produces an HTML document for browsing a Mercury term.
+%
+%---------------------------------------------------------------------------%
+%---------------------------------------------------------------------------%
+
+:- module mdb.term_to_html.
+:- interface.
+
+:- import_module io.
+:- import_module maybe.
+
+:- import_module mdb.browser_term.
+
+:- pred write_html_doc(io.output_stream::in, browser_term::in, string::in,
+    maybe_error::out, io::di, io::uo) is cc_multi.
+
+%---------------------------------------------------------------------------%
+%---------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module bool.
+:- import_module char.
+:- import_module construct.
+:- import_module deconstruct.
+:- import_module dir.
+:- import_module exception.
+:- import_module int.
+:- import_module list.
+:- import_module string.
+:- import_module type_desc.
+:- import_module univ.
+
+:- import_module mdb.browse.
+:- import_module percent_encoding.
+
+%---------------------------------------------------------------------------%
+
+write_html_doc(Stream, BrowserTerm, MdbDir, Result, !IO) :-
+    try_io(write_html_doc_2(Stream, BrowserTerm, MdbDir), TryResult, !IO),
+    (
+        TryResult = succeeded({}),
+        Result = ok
+    ;
+        TryResult = exception(Univ),
+        ( if univ_to_type(Univ, Error : io.error) then
+            Result = error(io.error_message(Error))
+        else
+            Result = error(string(univ_value(Univ)))
+        )
+    ).
+
+:- pred write_html_doc_2(io.output_stream::in, browser_term::in, string::in,
+    {}::out, io::di, io::uo) is cc_multi.
+
+write_html_doc_2(Stream, BrowserTerm, MdbDir, {}, !IO) :-
+    make_file_url_prefix(MdbDir, FilePrefix),
+    list.foldl(write_string(Stream), header(FilePrefix), !IO),
+    write_browser_term_in_script(Stream, BrowserTerm, !IO),
+    io.write_string(Stream, footer, !IO).
+
+:- pred make_file_url_prefix(string::in, string::out) is det.
+
+make_file_url_prefix(Path0, FilePrefix) :-
+    % Replace backslashes with forward slashes in Windows paths.
+    ( if dir.directory_separator('\\') then
+        string.replace_all(Path0, "\\", "/", Path)
+    else
+        Path = Path0
+    ),
+    Segments = string.split_at_char('/', Path),
+    EncodedSegments = list.map(percent_encode_path_segment, Segments),
+    EncodedPath = string.join_list("/", EncodedSegments),
+    ( if string.prefix(EncodedPath, "/") then
+        FilePrefix = "file://" ++ EncodedPath
+    else
+        FilePrefix = "file:///" ++ EncodedPath
+    ).
+
+:- func header(string) = list(string).
+
+header(FilePrefix) = [
+    "<!doctype html>\n",
+
+    "<link rel='stylesheet' href='", FilePrefix, "/jstree.style.min.css' />\n",
+    "<script src='", FilePrefix, "/jquery.slim.min.js'></script>\n",
+    "<script src='", FilePrefix, "/jstree.min.js'></script>\n",
+
+    "<link rel='stylesheet' href='", FilePrefix, "/mdb_term_browser.css' />\n",
+    "<script src='", FilePrefix, "/mdb_term_browser.js'></script>\n",
+
+    "<div class='container'>\n",
+    " <div class='search-container'>Search\n",
+    "  <input type='text' id='searchbox' size='50' />\n",
+    " </div>\n",
+    " <div id='treeview'></div>\n",
+    "</div>\n",
+
+    "<script type='text/javascript'>\n",
+    "var term =\n"
+].
+
+:- func footer = string.
+
+footer = ";\n</script>\n".
+
+%---------------------------------------------------------------------------%
+
+:- inst plain_term for browser_term/0
+    --->    plain_term(ground).
+
+    % Write a JavaScript representation of a Mercury term inside a <script>
+    % element. Object keys are left unquoted and we depend on being able to
+    % write trailing commas, so the output is not JSON.
+    %
+:- pred write_browser_term_in_script(io.output_stream, browser_term, io, io).
+:- mode write_browser_term_in_script(in, in(plain_term), di, uo) is cc_multi.
+:- mode write_browser_term_in_script(in, in, di, uo) is cc_multi.
+
+write_browser_term_in_script(Stream, BrowserTerm, !IO) :-
+    (
+        BrowserTerm = plain_term(TermUniv),
+        Term = univ_value(TermUniv),
+        TypeDesc = type_of(Term),
+        TypeName = type_name(TypeDesc),
+        functor(Term, include_details_cc, Functor0, Arity),
+        ( if
+            Functor0 = "[|]",
+            Arity = 2,
+            flatten_list(Term, ElementUnivs0)
+        then
+            length(ElementUnivs0, Length),
+            ( if Length = 1 then
+                Functor = "list of 1 element"
+            else
+                Functor = "list of " ++ from_int(Length) ++ " elements"
+            ),
+            FlattenedList = yes(ElementUnivs0)
+        else
+            Functor = Functor0,
+            FlattenedList = no
+        )
+    ;
+        BrowserTerm = synthetic_term(Functor, Args, MaybeResult),
+        Arity = length(Args),
+        (
+            MaybeResult = no,
+            TypeName = "<<predicate>>"
+        ;
+            MaybeResult = yes(_),
+            TypeName = "<<function>>"
+        ),
+        FlattenedList = no
+    ),
+
+    js_begin_object(Stream, !IO),
+
+    js_object_key(Stream, "type", !IO),
+    js_string(Stream, TypeName, !IO),
+    js_comma(Stream, !IO),
+
+    js_object_key(Stream, "functor", !IO),
+    js_string(Stream, Functor, !IO),
+    js_comma(Stream, !IO),
+
+    ( if Arity = 0 then
+        true
+    else
+        browser_term_to_html_flat_string(BrowserTerm, OneLine, Elided, !IO),
+        js_object_key(Stream, "oneline", !IO),
+        js_string(Stream, OneLine, !IO),
+        js_comma(Stream, !IO),
+        (
+            Elided = yes,
+            js_object_key(Stream, "oneline_elided", !IO),
+            js_bool(Stream, Elided, !IO),
+            js_comma(Stream, !IO)
+        ;
+            Elided = no
+        ),
+
+        js_object_key(Stream, "args", !IO),
+        js_begin_array(Stream, !IO),
+        (
+            FlattenedList = yes(ElementUnivs),
+            foldl2(write_numbered_element_in_script(Stream),
+                ElementUnivs, 1, _ElementNumber, !IO)
+        ;
+            FlattenedList = no,
+            write_browser_term_args_in_script(Stream, BrowserTerm, !IO)
+        ),
+        js_end_array(Stream, !IO)
+    ),
+
+    js_end_object(Stream, !IO).
+
+:- pred write_browser_term_args_in_script(io.output_stream, browser_term,
+    io, io).
+:- mode write_browser_term_args_in_script(in, in(plain_term), di, uo)
+    is cc_multi.
+:- mode write_browser_term_args_in_script(in, in, di, uo)
+    is cc_multi.
+
+write_browser_term_args_in_script(Stream, BrowserTerm, !IO) :-
+    (
+        BrowserTerm = plain_term(TermUniv),
+        Term = univ_value(TermUniv),
+        ( if
+            deconstruct_du(Term, include_details_cc, FunctorNumber, _Arity1,
+                Args)
+        then
+            TypeDesc = type_of(Term),
+            ( if
+                get_functor_with_names(TypeDesc, FunctorNumber, _Functor,
+                    _Arity, _ArgTypes, FieldNames)
+            then
+                list.foldl2_corresponding(write_du_field_in_script(Stream),
+                    Args, FieldNames, 1, _ArgNum, !IO)
+            else
+                list.foldl2(write_numbered_arg_in_script(Stream),
+                    Args, 1, _ArgNum, !IO)
+            )
+        else
+            deconstruct(Term, include_details_cc, _Functor, _Arity, Args),
+            list.foldl2(write_numbered_arg_in_script(Stream),
+                Args, 1, _ArgNum, !IO)
+        )
+    ;
+        BrowserTerm = synthetic_term(_Function, Args, MaybeResult),
+        list.foldl2(write_numbered_arg_in_script(Stream), Args, 1, ArgNum, !IO),
+        (
+            MaybeResult = no
+        ;
+            MaybeResult = yes(ResultUniv),
+            write_arg_in_script(Stream, ResultUniv, yes("result"), ArgNum, !IO)
+        )
+    ).
+
+:- pred write_du_field_in_script(io.output_stream::in, univ::in,
+    maybe(string)::in, int::in, int::out, io::di, io::uo) is cc_multi.
+
+write_du_field_in_script(Stream, ArgUniv, MaybeFieldName, ArgNum, ArgNum + 1,
+        !IO) :-
+    write_arg_in_script(Stream, ArgUniv, MaybeFieldName, ArgNum, !IO).
+
+:- pred write_numbered_arg_in_script(io.output_stream::in, univ::in,
+    int::in, int::out, io::di, io::uo) is cc_multi.
+
+write_numbered_arg_in_script(Stream, ArgUniv, ArgNum, ArgNum + 1, !IO) :-
+    write_arg_in_script(Stream, ArgUniv, no, ArgNum, !IO).
+
+:- pred write_numbered_element_in_script(io.output_stream::in, univ::in,
+    int::in, int::out, io::di, io::uo) is cc_multi.
+
+write_numbered_element_in_script(Stream, ArgUniv, Num, Num + 1, !IO) :-
+    write_arg_in_script(Stream, ArgUniv, yes("#" ++ from_int(Num)), Num, !IO).
+
+:- pred write_arg_in_script(io.output_stream::in, univ::in,
+    maybe(string)::in, int::in, io::di, io::uo) is cc_multi.
+
+write_arg_in_script(Stream, ArgUniv, MaybeFieldName, ArgNum, !IO) :-
+    js_begin_object(Stream, !IO),
+    js_object_key(Stream, "name", !IO),
+    (
+        MaybeFieldName = yes(FieldName),
+        js_string(Stream, FieldName, !IO)
+    ;
+        MaybeFieldName = no,
+        js_int(Stream, ArgNum, !IO)
+    ),
+    js_comma(Stream, !IO),
+    js_object_key(Stream, "term", !IO),
+    write_browser_term_in_script(Stream, plain_term(ArgUniv), !IO),
+    js_end_object(Stream, !IO),
+    js_comma(Stream, !IO).
+
+%---------------------------------------------------------------------------%
+
+:- pred flatten_list(T::in, list(univ)::out) is semidet.
+
+flatten_list(Term, ElementUnivs) :-
+    limited_deconstruct(Term, canonicalize, 2, Functor, Arity, Args),
+    (
+        Functor = "[]",
+        Arity = 0,
+        Args = [],
+        ElementUnivs = []
+    ;
+        Functor = "[|]",
+        Arity = 2,
+        Args = [Head, Tail],
+        flatten_list(univ_value(Tail), ElementUnivs0),
+        ElementUnivs = [Head | ElementUnivs0]
+    ).
+
+%---------------------------------------------------------------------------%
+
+% Helpers for writing out JavaScript values within an HTML <script> element.
+% We do not generate indented output because we may need to write large,
+% deeply nested terms quickly, and have the web browser parse the file as
+% quickly as possible.
+
+:- pred js_begin_object(io.output_stream::in, io::di, io::uo) is det.
+
+js_begin_object(Stream, !IO) :-
+    io.write_string(Stream, "{\n", !IO).
+
+:- pred js_end_object(io.output_stream::in, io::di, io::uo) is det.
+
+js_end_object(Stream, !IO) :-
+    io.write_char(Stream, '}', !IO).
+
+:- pred js_object_key(io.output_stream::in, string::in, io::di, io::uo)
+    is det.
+
+js_object_key(Stream, Key, !IO) :-
+    % Assume that the key does not require escaping.
+    io.write_string(Stream, Key, !IO),
+    io.write_char(Stream, ':', !IO).
+
+:- pred js_begin_array(io.output_stream::in, io::di, io::uo) is det.
+
+js_begin_array(Stream, !IO) :-
+    io.write_string(Stream, "[\n", !IO).
+
+:- pred js_end_array(io.output_stream::in, io::di, io::uo) is det.
+
+js_end_array(Stream, !IO) :-
+    io.write_char(Stream, ']', !IO).
+
+:- pred js_comma(io.output_stream::in, io::di, io::uo) is det.
+
+js_comma(Stream, !IO) :-
+    io.write_string(Stream, ",\n", !IO).
+
+:- pred js_bool(io.output_stream::in, bool::in, io::di, io::uo) is det.
+
+js_bool(Stream, B, !IO) :-
+    (
+        B = yes,
+        S = "true"
+    ;
+        B = no,
+        S = "false"
+    ),
+    io.write_string(Stream, S, !IO).
+
+:- pred js_int(io.output_stream::in, int::in, io::di, io::uo) is det.
+
+js_int(Stream, Int, !IO) :-
+    io.write_int(Stream, Int, !IO).
+
+:- pred js_string(io.output_stream::in, string::in, io::di, io::uo) is det.
+
+js_string(Stream, String, !IO) :-
+    io.write_char(Stream, '"', !IO),
+    string.foldl(escape_and_put_char(Stream), String, !IO),
+    io.write_char(Stream, '"', !IO).
+
+:- pred escape_and_put_char(io.output_stream::in, char::in, io::di, io::uo) is det.
+
+escape_and_put_char(Stream, Char, !IO) :-
+    ( if escape_char(Char, EscapedCharStr) then
+        io.write_string(Stream, EscapedCharStr, !IO)
+    else if char_is_ascii(Char) then
+        io.write_char(Stream, Char, !IO)
+    else
+        put_unicode_escape(Stream, Char, !IO)
+    ).
+
+:- pred escape_char(char::in, string::out) is semidet.
+
+escape_char('"', "\\""").
+escape_char('\\', "\\\\").
+escape_char('/', "\\/").    % prevent HTML parser seeing "</script" in string
+escape_char('\b', "\\b").
+escape_char('\f', "\\f").
+escape_char('\n', "\\n").
+escape_char('\r', "\\r").
+escape_char('\t', "\\t").
+
+:- pred char_is_ascii(char::in) is semidet.
+
+char_is_ascii(Char) :-
+    Code = char.to_int(Char),
+    Code >= 0x00,
+    Code =< 0x7f.
+
+:- pred put_unicode_escape(io.output_stream::in, char::in,
+    io::di, io::uo) is det.
+
+put_unicode_escape(Stream, Char, !State) :-
+    CodePoint = char.to_int(Char),
+    ( if CodePoint > 0xFFFF then
+        code_point_to_utf16_surrogates(CodePoint, LS, TS),
+        put_hex_digits(Stream, LS, !State),
+        put_hex_digits(Stream, TS, !State)
+    else
+        put_hex_digits(Stream, CodePoint, !State)
+    ).
+
+:- pred code_point_to_utf16_surrogates(int::in, int::out, int::out) is det.
+
+code_point_to_utf16_surrogates(CodePoint, LS, TS) :-
+    AdjustedCodePoint = CodePoint - 0x10000,
+    LS = 0xD800 + (AdjustedCodePoint >> 10),
+    TS = 0xDC00 + (AdjustedCodePoint /\ 0x3FF).
+
+:- pred put_hex_digits(io.output_stream::in, int::in, io::di, io::uo) is det.
+
+put_hex_digits(Stream, Int, !IO) :-
+    io.format(Stream, "\\u%04x", [i(Int)], !IO).
+
+%---------------------------------------------------------------------------%
+:- end_module mdb.term_to_html.
+%---------------------------------------------------------------------------%
diff --git a/configure.ac b/configure.ac
index f191554..a609a39 100644
--- a/configure.ac
+++ b/configure.ac
@@ -5320,6 +5320,26 @@ fi
 AC_SUBST(DEFAULT_XML_BROWSER_CMD)
 AC_SUBST(DEFAULT_XML_TMP_FILENAME)
 
+#-----------------------------------------------------------------------------#
+#
+# Set the default web_browser_cmd.
+#
+
+AC_PATH_PROGS(WEB_BROWSER, xdg-open, "")
+case "$host" in
+    *apple*darwin*)
+        DEFAULT_WEB_BROWSER_CMD="open"
+        ;;
+    *-cygwin* | *mingw*)
+        DEFAULT_WEB_BROWSER_CMD="start"
+        ;;
+    *)
+        DEFAULT_WEB_BROWSER_CMD="xdg-open"
+        ;;
+esac
+
+AC_SUBST(DEFAULT_WEB_BROWSER_CMD)
+
 #-----------------------------------------------------------------------------#
 
 # We need to check that any existing .c files are compatible with the selected
diff --git a/doc/user_guide.texi b/doc/user_guide.texi
index a067e1d..97b515d 100644
--- a/doc/user_guide.texi
+++ b/doc/user_guide.texi
@@ -3013,8 +3013,8 @@ and @samp{-v} or @samp{--verbose} specify the format to use for printing.
 @c The options @samp{-f} or @samp{--flat}, @samp{-p} or @samp{--pretty},
 @c and @samp{-v} or @samp{--verbose} specify the format to use for printing.
 @sp 1
- at item browse [-fpvx] @var{name}[@var{termpath}]
- at itemx browse [-fpvx] @var{num}[@var{termpath}]
+ at item browse [-fpvxw] @var{name}[@var{termpath}]
+ at itemx browse [-fpvxw] @var{num}[@var{termpath}]
 @kindex browse (mdb command)
 Invokes an interactive term browser to browse
 the value of the variable in the current environment
@@ -3034,13 +3034,15 @@ variable to an XML file and then invoke an XML browser on the file.
 The XML filename as well as the command to invoke the XML browser can
 be set using the @samp{set} command.  See the documentation for @samp{set}
 for more details.
+The @samp{-w} or @samp{--web} option tells mdb to dump the value of the
+variable to an HTML file and then invoke a web browser on the file.
 @sp 1
 For further documentation on the interactive term browser,
 invoke the @samp{browse} command from within @samp{mdb} and then
 type @samp{help} at the @samp{browser>} prompt.
 @sp 1
- at item browse [-fpvx]
- at itemx browse [-fpvx] goal
+ at item browse [-fpvxw]
+ at itemx browse [-fpvxw] goal
 Invokes the interactive term browser to browse
 the goal of the current call in its present state of instantiation.
 @sp 1
@@ -3050,8 +3052,10 @@ The @samp{-x} or @samp{--xml} option tells mdb to dump the goal to an XML file
 and then invoke an XML browser on the file.  The XML filename as well as the
 command to invoke the XML browser can be set using the @samp{set} command.  See
 the documentation for @samp{set} for more details.
+The @samp{-w} or @samp{--web} option tells mdb to dump the goal to an HTML file
+and then invoke a web browser on the file.
 @sp 1
- at item browse [-fpvx] exception
+ at item browse [-fpvxw] exception
 Invokes the interactive term browser to browse
 the value of the exception at an EXCP port.
 Reports an error if the current event does not refer to such a port.
@@ -3062,8 +3066,10 @@ The @samp{-x} or @samp{--xml} option tells mdb to dump the exception to an
 XML file and then invoke an XML browser on the file.  The XML filename as well
 as the command to invoke the XML browser can be set using the @samp{set}
 command.  See the documentation for @samp{set} for more details.
+The @samp{-w} or @samp{--web} option tells mdb to dump the exception to an
+HTML file and then invoke a web browser on the file.
 @sp 1
- at item browse [-fpvx] action @var{num}
+ at item browse [-fpvxw] action @var{num}
 Invokes an interactive term browser to browse a representation
 of the @var{num}'th I/O action executed by the program.
 @sp 1
@@ -3073,6 +3079,8 @@ The @samp{-x} or @samp{--xml} option tells mdb to dump the io action
 representation to an XML file and then invoke an XML browser on the file.  The
 XML filename as well as the command to invoke the XML browser can be set using
 the @samp{set} command.  See the documentation for @samp{set} for more details.
+The @samp{-w} or @samp{--web} option tells mdb to dump the io action
+representation to an HTML file and then invoke a web browser on the file.
 @c @sp 1
 @c @item browse [-fpvx] proc_body
 @c Invokes an interactive term browser to browse a representation
@@ -4006,6 +4014,14 @@ will usually refer to this file.
 Prints the temporary filename used for XML browsing,
 if this has been set.
 @sp 1
+ at item web_browser_cmd @var{command}
+ at kindex web_browser_cmd (mdb command)
+Set the shell command used to launch a web browser to @var{command}.
+ at sp 1
+ at item web_browser_cmd
+Prints the shell command used to launch a web browser,
+if this has been set.
+ at sp 1
 @item format [-APB] @var{format}
 @kindex format (mdb command)
 Sets the default format of the browser to @var{format},
@@ -4900,7 +4916,7 @@ Undo the most recent answer or mode change.
 Change the current search mode.  The search modes may be abbreviated to
 @samp{td}, @samp{dq} and @samp{b} respectively.
 @sp 1
- at item browse [--xml] [@var{n}]
+ at item browse [--xml | --web] [@var{n}]
 Start the interactive term browser and browse the @var{n}th argument
 before answering.  If the argument number
 is omitted then browse the whole call as if it were a data term.
@@ -4914,8 +4930,10 @@ interactive query browser.
 @sp 1
 Giving the @samp{--xml} or @samp{-x} option causes the term to be displayed
 in an XML browser.
+Giving the @samp{--web} or @samp{-w} option causes the term to be displayed
+in a web browser.
 @sp 1
- at item browse io [--xml] @var{n}
+ at item browse io [--xml | --web] @var{n}
 Browse the @var{n}'th I/O action.
 @sp 1
 @item print [@var{n}]
diff --git a/scripts/32px.png b/scripts/32px.png
new file mode 100644
...

diff --git a/scripts/40px.png b/scripts/40px.png
new file mode 100644
...

diff --git a/scripts/Mmakefile b/scripts/Mmakefile
index fec7841..0ba70e5 100644
--- a/scripts/Mmakefile
+++ b/scripts/Mmakefile
@@ -54,7 +54,15 @@ DEBUGGER_SCRIPTS = $(CONF_DEBUG_SCRIPTS) 	\
 		xul_tree.xsl			\
 		mdb_open			\
 		mdb_grep			\
-		mdb_track
+		mdb_track			\
+		mdb_term_browser.js		\
+		mdb_term_browser.css		\
+		jquery.slim.min.js		\
+		jstree.min.js			\
+		jstree.style.min.css		\
+		32px.png			\
+		40px.png			\
+		throbber.gif
 
 EMACS_SCRIPTS = gud.el
 
diff --git a/scripts/jquery.slim.min.js b/scripts/jquery.slim.min.js
new file mode 100644
index 0000000..105d00e
--- /dev/null
+++ b/scripts/jquery.slim.min.js
@@ -0,0 +1,4 @@
...

diff --git a/scripts/jstree.min.js b/scripts/jstree.min.js
new file mode 100644
index 0000000..30b73e7
--- /dev/null
+++ b/scripts/jstree.min.js
@@ -0,0 +1,5 @@
...

diff --git a/scripts/jstree.style.min.css b/scripts/jstree.style.min.css
new file mode 100644
index 0000000..a24ff30
--- /dev/null
+++ b/scripts/jstree.style.min.css
@@ -0,0 +1 @@
...

diff --git a/scripts/mdb_term_browser.css b/scripts/mdb_term_browser.css
new file mode 100644
index 0000000..ce33a76
--- /dev/null
+++ b/scripts/mdb_term_browser.css
@@ -0,0 +1,25 @@
+/*
+** Copyright (C) 2017 The Mercury team.
+** This file may only be copied under the terms of the GNU Library General
+** Public License - see the file COPYING.LIB in the Mercury distribution.
+*/
+
+body {
+    font-family: Sans-Serif;
+}
+div.search-container {
+    padding-top: 5px;
+    padding-bottom: 5px;
+}
+li.jstree-node a span.pos {
+    color: blue;
+}
+li.jstree-node a span.name {
+    color: purple;
+}
+li.jstree-node a span {
+    padding-right: 0.5em;
+}
+.jstree-anchor, .jstree-animated, .jstree-wholerow {
+    transition: none !important;
+}
diff --git a/scripts/mdb_term_browser.js b/scripts/mdb_term_browser.js
new file mode 100644
index 0000000..08d550c
--- /dev/null
+++ b/scripts/mdb_term_browser.js
@@ -0,0 +1,238 @@
+// Copyright (C) 2017 The Mercury team.
+// This file may only be copied under the terms of the GNU Library General
+// Public License - see the file COPYING.LIB in the Mercury distribution.
+
+const OPEN_DEPTH = 3;
+const OPEN_MAX_ARGS = 10;
+
+function escapeHTML(html) {
+    return document.createElement('div')
+        .appendChild(document.createTextNode(html))
+        .parentNode.innerHTML;
+}
+
+function term_functor_to_html(term)
+{
+    return escapeHTML(term.functor);
+}
+
+function term_oneline_to_html(term)
+{
+    if (term.oneline) {
+        return escapeHTML(term.oneline);
+    } else {
+        return term_functor_to_html(term);
+    }
+}
+
+function term_to_json(term)
+{
+    const field = {
+        name: "term",
+        term: term
+    };
+    return field_to_json(field, 0, true);
+}
+
+function field_to_json(field, open_depth, root)
+{
+    const name_html = field_name_to_html(field.name);
+    const term = field.term;
+
+    var initial_text;
+    var initial_open;
+    var children;
+    var userdata = {}
+    if (term.args) {
+        userdata.opened_text = name_html + term_functor_to_html(term);
+        userdata.closed_text = name_html + term_oneline_to_html(term);
+        initial_open = false;
+        if (term.oneline_elided) {
+            if (root) {
+                initial_open = true;
+            } else {
+                initial_open = (open_depth < OPEN_DEPTH &&
+                    term.args.length < OPEN_MAX_ARGS);
+            }
+        }
+        if (initial_open) {
+            initial_text = userdata.opened_text;
+        } else {
+            initial_text = userdata.closed_text;
+        }
+        var new_depth;
+        if (initial_open) {
+            new_depth = open_depth + 1;
+        } else {
+            // Reset depth so that opening a closed node reveals
+            // some of its children as well.
+            new_depth = 0;
+        }
+        children = term.args.map(function(arg) {
+            return field_to_json(arg, new_depth, false);
+        });
+    } else {
+        initial_text = name_html + term_oneline_to_html(term);
+        initial_open = false;
+        children = false;
+    }
+
+    if (typeof(field.name) == "string") {
+        userdata.search_name = field.name;
+    }
+    userdata.search_value = term.functor.toString();
+
+    return {
+        text: initial_text,
+        state: {opened: initial_open},
+        children: children,
+        a_attr: {title: term.type},
+        data: userdata
+    };
+}
+
+function field_name_to_html(name)
+{
+    if (typeof(name) == "number") {
+        return '<span class="pos">[' + name + ']</span>';
+    } else {
+        return '<span class="name">' + escapeHTML(name) + '</span>';
+    }
+}
+
+function short_search_callback(s, node)
+{
+    const userdata = node.data;
+    if (userdata.search_name && userdata.search_name.startsWith(s)) {
+        return true;
+    }
+    return userdata.search_value.startsWith(s);
+}
+
+function long_search_callback(s, node)
+{
+    const userdata = node.data;
+    if (userdata.search_name && userdata.search_name.indexOf(s) !== -1) {
+        return true;
+    }
+    return userdata.search_value.indexOf(s) !== -1;
+}
+
+function choose_search_callback(s)
+{
+    if (s.length < 3) {
+        return short_search_callback;
+    } else {
+        return long_search_callback;
+    }
+}
+
+function setup(term)
+{
+    const treeview = $('#treeview');
+
+    var term_stack = [term_to_json(term)];
+
+    // Create jstree instance.
+    treeview.jstree({
+        core: {
+            data: [term_stack[0]],
+            check_callback: true,   // enable modifications (including rename)
+            multiple: false,        // no multiple selection
+            animation: 0,           // no animation
+            themes: {icons: false}  // no icons
+        },
+        plugins: ["search", "contextmenu"],
+        search: {
+            search_callback: short_search_callback
+        },
+        contextmenu: {
+            select_node: false,
+            items: {
+                expand_all: {
+                    label: "Expand all",
+                    action: expand_all_action
+                },
+                collapse_all: {
+                    label: "Collapse all",
+                    action: collapse_all_action
+                },
+                view_subterm: {
+                    label: "View subterm",
+                    action: view_subterm_action
+                },
+                back: {
+                    label: "Back to previous term",
+                    action: back_action
+                }
+            }
+        }
+    });
+
+    // Keep reference to jstree instance.
+    const inst = treeview.jstree(true);
+
+    function expand_all_action(data) {
+        const obj = inst.get_node(data.reference);
+        inst.open_all(obj);
+    }
+    function collapse_all_action(data) {
+        const obj = inst.get_node(data.reference);
+        inst.close_all(obj);
+    }
+    function view_subterm_action(data) {
+        const obj = inst.get_node(data.reference);
+        // This seems to work...
+        inst.move_node(obj, treeview, 0);
+        inst.delete_node(inst.get_next_dom(obj, true));
+
+        term_stack.push(inst.get_json(obj));
+    }
+    function back_action(data) {
+        if (term_stack.length > 1) {
+            term_stack.pop();
+            inst.settings.core.data = term_stack[term_stack.length - 1];
+            inst.refresh();
+        }
+    }
+
+    function on_open_node(e, data) {
+        const node = data.node;
+        const userdata = node.data;
+        inst.rename_node(node, userdata.opened_text);
+    }
+    function on_close_node(e, data) {
+        const node = data.node;
+        const userdata = node.data;
+        inst.rename_node(node, userdata.closed_text);
+    }
+    function on_select_node(e, data) {
+        const node = data.node;
+        inst.toggle_node(node);
+    }
+    treeview.on('open_node.jstree', on_open_node);
+    treeview.on('close_node.jstree', on_close_node);
+    treeview.on('select_node.jstree', on_select_node);
+
+    const searchbox = $('#searchbox');
+    var timeout = false;
+    searchbox.keyup(function() {
+        if (timeout) {
+            clearTimeout(timeout);
+        }
+        timeout = setTimeout(
+            function() {
+                const v = searchbox.val();
+                inst.settings.search.search_callback =
+                    choose_search_callback(v);
+                inst.search(v);
+            },
+            250
+        );
+    });
+}
+
+$(document).ready(function() {
+    setup(term);
+    term = null;    // don't need it any more
+});
diff --git a/scripts/mdbrc.in b/scripts/mdbrc.in
index aa8c18d..bebbed6 100644
--- a/scripts/mdbrc.in
+++ b/scripts/mdbrc.in
@@ -21,3 +21,4 @@ alias	grep	source @DEFAULT_MERCURY_DEBUGGER_INIT_DIR@/mdb_grep
 alias	track	source @DEFAULT_MERCURY_DEBUGGER_INIT_DIR@/mdb_track
 xml_browser_cmd '@DEFAULT_XML_BROWSER_CMD@'
 xml_tmp_filename '@DEFAULT_XML_TMP_FILENAME@'
+web_browser_cmd '@DEFAULT_WEB_BROWSER_CMD@'
diff --git a/scripts/throbber.gif b/scripts/throbber.gif
new file mode 100644
...

diff --git a/trace/mercury_trace_browse.c b/trace/mercury_trace_browse.c
index 136cef0..1869a5b 100644
--- a/trace/mercury_trace_browse.c
+++ b/trace/mercury_trace_browse.c
@@ -124,6 +124,23 @@ MR_trace_save_and_invoke_xml_browser(MR_Word browser_term)
     );
 }
 
+void
+MR_trace_save_and_invoke_web_browser(MR_Word browser_term)
+{
+    MercuryFile mdb_out;
+    MercuryFile mdb_err;
+
+    MR_c_file_to_mercury_file(MR_mdb_out, &mdb_out);
+    MR_c_file_to_mercury_file(MR_mdb_err, &mdb_err);
+
+    MR_TRACE_CALL_MERCURY(
+        ML_BROWSE_browse_term_web(browser_term,
+            MR_wrap_output_stream(&mdb_out),
+            MR_wrap_output_stream(&mdb_err),
+            MR_trace_browser_persistent_state);
+    );
+}
+
 MR_bool
 MR_trace_is_portray_format(const char *str, MR_BrowseFormat *format)
 {
diff --git a/trace/mercury_trace_browse.h b/trace/mercury_trace_browse.h
index d886ffa..394e812 100644
--- a/trace/mercury_trace_browse.h
+++ b/trace/mercury_trace_browse.h
@@ -78,6 +78,10 @@ extern  void        MR_trace_browse_external(MR_Word type_info, MR_Word value,
 
 extern  void        MR_trace_save_and_invoke_xml_browser(MR_Word browser_term);
 
+// Browse a term using a web browser.
+
+extern  void        MR_trace_save_and_invoke_web_browser(MR_Word browser_term);
+
 // Display a term non-interactively.
 
 extern  void        MR_trace_print(MR_Word type_info, MR_Word value,
diff --git a/trace/mercury_trace_cmd_browsing.c b/trace/mercury_trace_cmd_browsing.c
index 7e8880e..af2aa9c 100644
--- a/trace/mercury_trace_cmd_browsing.c
+++ b/trace/mercury_trace_cmd_browsing.c
@@ -51,6 +51,13 @@ static  void        MR_trace_browse_goal_xml(MR_ConstString name,
                         MR_Word arg_list, MR_Word is_func,
                         MR_BrowseCallerType caller, MR_BrowseFormat format);
 
+// Functions to invoke the user's web browser on terms or goals.
+static  void        MR_trace_browse_web(MR_Word type_info, MR_Word value,
+                        MR_BrowseCallerType caller, MR_BrowseFormat format);
+static  void        MR_trace_browse_goal_web(MR_ConstString name,
+                        MR_Word arg_list, MR_Word is_func,
+                        MR_BrowseCallerType caller, MR_BrowseFormat format);
+
 static  void        MR_trace_cmd_stack_2(MR_EventInfo *event_info,
                         MR_bool detailed, MR_FrameLimit frame_limit,
                         int line_limit);
@@ -68,7 +75,7 @@ static  MR_bool     MR_trace_options_stack_trace(MR_bool *print_all,
                         MR_FrameLimit *frame_limit,
                         char ***words, int *word_count);
 static  MR_bool     MR_trace_options_format(MR_BrowseFormat *format,
-                        MR_bool *xml, char ***words, int *word_count);
+                        MR_bool *xml, MR_bool *web, char ***words, int *word_count);
 static  MR_bool     MR_trace_options_view(const char **window_cmd,
                         const char **server_cmd, const char **server_name,
                         MR_Unsigned *timeout, MR_bool *force, MR_bool *verbose,
@@ -209,6 +216,7 @@ MR_trace_cmd_print(char **words, int word_count, MR_TraceCmdInfo *cmd,
 {
     MR_BrowseFormat     format;
     MR_bool             xml;
+    MR_bool             web;
     const char          *problem;
     MR_Unsigned         action;
     MR_Unsigned         lo_action;
@@ -216,12 +224,15 @@ MR_trace_cmd_print(char **words, int word_count, MR_TraceCmdInfo *cmd,
     static MR_bool      have_next_io_action = MR_FALSE;
     static MR_Unsigned  next_io_action = 0;
 
-    if (! MR_trace_options_format(&format, &xml, &words, &word_count)) {
+    if (! MR_trace_options_format(&format, &xml, &web, &words, &word_count)) {
         // The usage message has already been printed.
         ;
     } else if (xml) {
         // The --xml option is not valid for print.
         MR_trace_usage_cur_cmd();
+    } else if (web) {
+        // The --web option is not valid for print.
+        MR_trace_usage_cur_cmd();
     } else if (word_count == 1) {
         problem = MR_trace_browse_one_goal(MR_mdb_out,
             MR_trace_browse_goal_internal, MR_BROWSE_CALLER_PRINT, format);
@@ -450,18 +461,22 @@ MR_trace_cmd_browse(char **words, int word_count, MR_TraceCmdInfo *cmd,
 {
     MR_BrowseFormat     format;
     MR_bool             xml;
+    MR_bool             web;
     MR_IoActionNum      action;
     MR_GoalBrowser      goal_browser;
     MR_Browser          browser;
     const char          *problem;
 
-    if (! MR_trace_options_format(&format, &xml, &words, &word_count)) {
+    if (! MR_trace_options_format(&format, &xml, &web, &words, &word_count)) {
         // The usage message has already been printed.
         ;
     } else {
         if (xml) {
             goal_browser = MR_trace_browse_goal_xml;
             browser = MR_trace_browse_xml;
+        } else if (web) {
+            goal_browser = MR_trace_browse_goal_web;
+            browser = MR_trace_browse_web;
         } else {
             goal_browser = MR_trace_browse_goal_internal;
             browser = MR_trace_browse_internal;
@@ -749,6 +764,7 @@ MR_trace_cmd_dump(char **words, int word_count, MR_TraceCmdInfo *cmd,
     const char      *problem = NULL;
     MR_bool         quiet = MR_FALSE;
     MR_bool         xml = MR_FALSE;
+    MR_bool         web = MR_FALSE;
 
     // Set this to NULL to avoid uninitialization warnings.
 
@@ -1033,6 +1049,28 @@ MR_trace_browse_goal_xml(MR_ConstString name, MR_Word arg_list,
     MR_trace_save_and_invoke_xml_browser(browser_term);
 }
 
+static void
+MR_trace_browse_web(MR_Word type_info, MR_Word value,
+    MR_BrowseCallerType caller, MR_BrowseFormat format)
+{
+    MR_Word     browser_term;
+
+    browser_term = MR_type_value_to_browser_term((MR_TypeInfo) type_info,
+        value);
+
+    MR_trace_save_and_invoke_web_browser(browser_term);
+}
+
+static void
+MR_trace_browse_goal_web(MR_ConstString name, MR_Word arg_list,
+    MR_Word is_func, MR_BrowseCallerType caller, MR_BrowseFormat format)
+{
+    MR_Word     browser_term;
+
+    browser_term = MR_synthetic_to_browser_term(name, arg_list, is_func);
+    MR_trace_save_and_invoke_web_browser(browser_term);
+}
+
 // Implement the `view' command. First, check if there is a server attached.
 // If so, either stop it or abort the command, depending on whether '-f'
 // was given. Then, if a server name was not supplied, start a new server
@@ -1261,19 +1299,21 @@ static struct MR_option MR_trace_format_opts[] =
     { "verbose",    MR_no_argument, NULL,   'v' },
     { "pretty",     MR_no_argument, NULL,   'p' },
     { "xml",        MR_no_argument, NULL,   'x' },
+    { "web",        MR_no_argument, NULL,   'w' },
     { NULL,         MR_no_argument, NULL,   0   }
 };
 
 static MR_bool
-MR_trace_options_format(MR_BrowseFormat *format, MR_bool *xml, char ***words,
-    int *word_count)
+MR_trace_options_format(MR_BrowseFormat *format, MR_bool *xml, MR_bool *web,
+    char ***words, int *word_count)
 {
     int c;
 
     *format = MR_BROWSE_DEFAULT_FORMAT;
     *xml = MR_FALSE;
+    *web = MR_FALSE;
     MR_optind = 0;
-    while ((c = MR_getopt_long(*word_count, *words, "frvpx",
+    while ((c = MR_getopt_long(*word_count, *words, "frvpxw",
         MR_trace_format_opts, NULL)) != EOF)
     {
         switch (c) {
@@ -1296,6 +1336,12 @@ MR_trace_options_format(MR_BrowseFormat *format, MR_bool *xml, char ***words,
 
             case 'x':
                 *xml = MR_TRUE;
+                *web = MR_FALSE;
+                break;
+
+            case 'w':
+                *web = MR_TRUE;
+                *xml = MR_FALSE;
                 break;
 
             default:
diff --git a/trace/mercury_trace_cmd_parameter.c b/trace/mercury_trace_cmd_parameter.c
index dc47103..38135a1 100644
--- a/trace/mercury_trace_cmd_parameter.c
+++ b/trace/mercury_trace_cmd_parameter.c
@@ -748,6 +748,44 @@ MR_trace_cmd_xml_tmp_filename(char **words, int word_count,
     return KEEP_INTERACTING;
 }
 
+MR_Next
+MR_trace_cmd_web_browser_cmd(char **words, int word_count,
+    MR_TraceCmdInfo *cmd, MR_EventInfo *event_info, MR_Code **jumpaddr)
+{
+    if (word_count == 2) {
+        char    *copied_value;
+        char    *aligned_value;
+
+        copied_value = (char *) MR_GC_malloc(strlen(words[1]) + 1);
+        strcpy(copied_value, words[1]);
+        MR_TRACE_USE_HP(
+            MR_make_aligned_string(aligned_value, copied_value);
+        );
+        MR_TRACE_CALL_MERCURY(
+            ML_BROWSE_set_web_browser_cmd_from_mdb(aligned_value,
+                MR_trace_browser_persistent_state,
+                &MR_trace_browser_persistent_state);
+        );
+    } else if (word_count == 1) {
+        MR_String   command;
+
+        MR_TRACE_CALL_MERCURY(
+            ML_BROWSE_get_web_browser_cmd_from_mdb(
+                MR_trace_browser_persistent_state, &command);
+        );
+
+        if (command != NULL && strlen(command) > 0) {
+            fprintf(MR_mdb_out, "The web browser command is %s\n", command);
+        } else {
+            fprintf(MR_mdb_out, "The web browser command has not been set.\n");
+        }
+    } else {
+        MR_trace_usage_cur_cmd();
+    }
+
+    return KEEP_INTERACTING;
+}
+
 MR_Next
 MR_trace_cmd_format(char **words, int word_count,
     MR_TraceCmdInfo *cmd, MR_EventInfo *event_info, MR_Code **jumpaddr)
diff --git a/trace/mercury_trace_cmd_parameter.h b/trace/mercury_trace_cmd_parameter.h
index 8359545..0154f42 100644
--- a/trace/mercury_trace_cmd_parameter.h
+++ b/trace/mercury_trace_cmd_parameter.h
@@ -104,6 +104,7 @@ extern  MR_TraceCmdFunc     MR_trace_cmd_pass_trace_counts;
 extern  MR_TraceCmdFunc     MR_trace_cmd_max_io_actions;
 extern  MR_TraceCmdFunc     MR_trace_cmd_xml_browser_cmd;
 extern  MR_TraceCmdFunc     MR_trace_cmd_xml_tmp_filename;
+extern  MR_TraceCmdFunc     MR_trace_cmd_web_browser_cmd;
 extern  MR_TraceCmdFunc     MR_trace_cmd_format;
 extern  MR_TraceCmdFunc     MR_trace_cmd_format_param;
 extern  MR_TraceCmdFunc     MR_trace_cmd_alias;
diff --git a/trace/mercury_trace_internal.c b/trace/mercury_trace_internal.c
index 86a275e..08b9e8b 100644
--- a/trace/mercury_trace_internal.c
+++ b/trace/mercury_trace_internal.c
@@ -1571,6 +1571,8 @@ static const MR_TraceCmdTableEntry  MR_trace_command_table[] =
         NULL, MR_trace_null_completer },
     { "parameter", "xml_tmp_filename", MR_trace_cmd_xml_tmp_filename,
         NULL, MR_trace_null_completer },
+    { "parameter", "web_browser_cmd", MR_trace_cmd_web_browser_cmd,
+        NULL, MR_trace_null_completer },
     { "parameter", "format", MR_trace_cmd_format,
         MR_trace_format_cmd_args, MR_trace_null_completer },
     { "parameter", "format_param", MR_trace_cmd_format_param,


More information about the reviews mailing list