File 1461-Remove-dialyzer-gui.patch of Package erlang

From f90a1a1cd3e1f32ce0c28f5bc27e91d272540997 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@dashbit.co>
Date: Tue, 27 Jun 2023 11:36:28 +0200
Subject: [PATCH] Remove dialyzer --gui

The GUI does not support the new incremental PLT
and, while support could be added, the --gui provides
only a subset of the CLI functionality.
---
 lib/dialyzer/Makefile                     |    8 +-
 lib/dialyzer/README                       |    6 +-
 lib/dialyzer/doc/src/dialyzer.xml         |   33 +-
 lib/dialyzer/doc/src/dialyzer_chapter.xml |  102 +-
 lib/dialyzer/src/Makefile                 |   11 +-
 lib/dialyzer/src/dialyzer.app.src         |    4 +-
 lib/dialyzer/src/dialyzer.erl             |   61 -
 lib/dialyzer/src/dialyzer_cl_parse.erl    |   13 +-
 lib/dialyzer/src/dialyzer_explanation.erl |   45 -
 lib/dialyzer/src/dialyzer_gui_wx.erl      | 1234 ---------------------
 lib/dialyzer/src/dialyzer_gui_wx.hrl      |  123 --
 lib/dialyzer/src/dialyzer_plt.erl         |   47 -
 12 files changed, 17 insertions(+), 1670 deletions(-)
 delete mode 100644 lib/dialyzer/src/dialyzer_explanation.erl
 delete mode 100644 lib/dialyzer/src/dialyzer_gui_wx.erl
 delete mode 100644 lib/dialyzer/src/dialyzer_gui_wx.hrl

diff --git a/lib/dialyzer/Makefile b/lib/dialyzer/Makefile
index b58f0e0a18..875c74b749 100644
--- a/lib/dialyzer/Makefile
+++ b/lib/dialyzer/Makefile
@@ -1,8 +1,8 @@
 #
 # %CopyrightBegin%
-# 
+#
 # Copyright Ericsson AB 2006-2021. All Rights Reserved.
-# 
+#
 # Licensed under the Apache License, Version 2.0 (the "License");
 # you may not use this file except in compliance with the License.
 # You may obtain a copy of the License at
@@ -14,7 +14,7 @@
 # WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
 # See the License for the specific language governing permissions and
 # limitations under the License.
-# 
+#
 # %CopyrightEnd%
 #
 #=============================================================================
@@ -42,6 +42,6 @@ SPECIAL_TARGETS =
 #
 include $(ERL_TOP)/make/otp_subdir.mk
 
-DIA_PLT_APPS=compiler syntax_tools wx
+DIA_PLT_APPS=compiler syntax_tools
 
 include $(ERL_TOP)/make/app_targets.mk
diff --git a/lib/dialyzer/README b/lib/dialyzer/README
index bbdab21cbf..88381ca0dd 100644
--- a/lib/dialyzer/README
+++ b/lib/dialyzer/README
@@ -15,11 +15,7 @@ The DIALYZER, a DIscrepancy AnaLYZer for ERlang programs.
 --
 -----------------------------------------------
 
-You can use Dialyzer either in its GUI mode, simply by:
-
-	./dialyzer
-
-or in its command-line mode, as e.g. by:
+You can use Dialyzer in its command-line mode by:
 
 	./dialyzer -r OTP_DIR/lib/inets
 
diff --git a/lib/dialyzer/doc/src/dialyzer.xml b/lib/dialyzer/doc/src/dialyzer.xml
index dd14507681..9451b6fc1a 100644
--- a/lib/dialyzer/doc/src/dialyzer.xml
+++ b/lib/dialyzer/doc/src/dialyzer.xml
@@ -11,7 +11,7 @@
       Licensed under the Apache License, Version 2.0 (the "License");
       you may not use this file except in compliance with the License.
       You may obtain a copy of the License at
- 
+
           http://www.apache.org/licenses/LICENSE-2.0
 
       Unless required by applicable law or agreed to in writing, software
@@ -56,10 +56,6 @@
     <code type="none">
 dialyzer --help</code>
 
-    <p>For more details about the operation of Dialyzer, see section
-      <seeguide marker="dialyzer_chapter#dialyzer_gui">
-      Using Dialyzer from the GUI</seeguide> in the User's Guide.</p>
-
     <p><em>Exit status of the command-line version:</em></p>
 
     <taglist>
@@ -85,7 +81,7 @@ dialyzer --help</code>
 dialyzer [--add_to_plt] [--apps applications] [--build_plt]
          [--check_plt] [-Ddefine]* [-Dname]* [--dump_callgraph file]
          [--error_location flag] [files_or_dirs] [--fullpath]
-         [--get_warnings] [--gui] [--help] [-I include_dir]*
+         [--get_warnings] [--help] [-I include_dir]*
          [--incremental] [--metrics_file] [--no_check_plt] [--no_indentation]
          [--no_spec] [-o outfile] [--output_plt file] [-pa dir]* [--plt plt]
          [--plt_info] [--plts plt*] [--quiet] [-r dirs] [--raw]
@@ -185,9 +181,6 @@ dialyzer --apps inets ssl ./ebin ../other_lib/ebin/my_module.beam</code>
         <p>Make Dialyzer emit warnings even when manipulating the PLT.
           Warnings are only emitted for files that are analyzed.</p>
       </item>
-      <tag><c>--gui</c></tag>
-      <item>
-        <p>Use the GUI.</p></item>
       <tag><c>--help</c> (or <c>-h</c>)</tag>
       <item>
         <p>Print this message and exit.</p>
@@ -304,10 +297,6 @@ dialyzer --plts plt_1 ... plt_n -- files_to_analyze</code>
           the PLT. Notice that this can cause a reanalysis of the remaining
           dependent files.</p>
       </item>
-      <tag><c>--shell</c></tag>
-      <item>
-        <p>Do not disable the Erlang shell while running the GUI.</p>
-      </item>
       <tag><c>--src</c></tag>
       <item>
         <p>Override the default, which is to analyze BEAM files, and
@@ -340,9 +329,7 @@ dialyzer --plts plt_1 ... plt_n -- files_to_analyze</code>
     </taglist>
 
     <note>
-      <p>** options <c>-D</c> and <c>-I</c> work both
-        from the command line and in the Dialyzer GUI; the syntax of
-        defines and includes is the same as that used by
+      <p>** the syntax of defines and includes is the same as that used by
         <seecom marker="erts:erlc">erlc(1)</seecom>.</p>
     </note>
 
@@ -482,9 +469,8 @@ dialyzer --plts plt_1 ... plt_n -- files_to_analyze</code>
 
   <section>
     <title>Using Dialyzer from Erlang</title>
-    <p>Dialyzer can be used directly from Erlang. Both the GUI and the
-      command-line versions are also available. The options are similar to the
-      ones given from the command line, see section
+    <p>Dialyzer can be used directly from Erlang. The options are
+      similar to the ones given from the command line, see section
       <seeerl marker="#command_line">
       Using Dialyzer from the Command Line</seeerl>.</p>
   </section>
@@ -662,15 +648,6 @@ dialyzer --plts plt_1 ... plt_n -- files_to_analyze</code>
       </desc>
     </func>
 
-    <func>
-      <name name="gui" arity="0" since=""></name>
-      <name name="gui" arity="1" since=""></name>
-      <fsummary>Dialyzer GUI version.</fsummary>
-      <desc>
-        <p>Dialyzer GUI version.</p>
-      </desc>
-    </func>
-
     <func>
       <name name="plt_info" arity="1" since=""></name>
       <fsummary>Return information about the specified PLT.</fsummary>
diff --git a/lib/dialyzer/doc/src/dialyzer_chapter.xml b/lib/dialyzer/doc/src/dialyzer_chapter.xml
index b5f87e3ab7..abaa9e4ec5 100644
--- a/lib/dialyzer/doc/src/dialyzer_chapter.xml
+++ b/lib/dialyzer/doc/src/dialyzer_chapter.xml
@@ -11,7 +11,7 @@
       Licensed under the Apache License, Version 2.0 (the "License");
       you may not use this file except in compliance with the License.
       You may obtain a copy of the License at
- 
+
           http://www.apache.org/licenses/LICENSE-2.0
 
       Unless required by applicable law or agreed to in writing, software
@@ -19,7 +19,7 @@
       WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
       See the License for the specific language governing permissions and
       limitations under the License.
-    
+
     </legalnotice>
 
     <title>Dialyzer</title>
@@ -39,8 +39,7 @@
         or unreachable because of programming error, and unnecessary tests,
         in single Erlang modules or entire (sets of) applications.</p>
 
-      <p>Dialyzer can be called from the command line, from Erlang,
-        and from a GUI.</p>
+      <p>Dialyzer can be called from the command line and from Erlang.</p>
     </section>
 
     <section>
@@ -132,100 +131,6 @@ dialyzer --plt_info</code>
       See <seeerl marker="dialyzer"><c>dialyzer(3)</c></seeerl>.</p>
   </section>
 
-  <section>
-   <marker id="dialyzer_gui"/>
-    <title>Using Dialyzer from the GUI</title>
-    <section>
-      <title>Choosing the Applications or Modules</title>
-      <p>The <em>File</em> window displays a listing of the current directory.
-        Click your way to the directories/modules you want to add or type the
-        correct path in the entry.</p>
-
-      <p>Mark the directories/modules you want to analyze for discrepancies and
-        click <em>Add</em>. You can either add the <c>.beam</c> and
-        <c>.erl</c> files directly, or add directories that contain
-        these kind of files. Notice that
-        you are only allowed to add the type of files that can be analyzed in
-        the current mode of operation (see below), and that you cannot mix
-        <c>.beam</c> and <c>.erl</c> files.</p>
-    </section>
-
-    <section>
-      <title>Analysis Modes</title>
-      <p>Dialyzer has two analysis modes: "Byte Code" and "Source Code".
-         They are controlled by the buttons in the top-middle part of the
-         main window, under <em>Analysis Options</em>.</p>
-    </section>
-
-    <section>
-      <title>Controlling the Discrepancies Reported by Dialyzer</title>
-      <p>Under the <em>Warnings</em> pull-down menu, there are buttons that
-        control which discrepancies are reported to the user in the
-        <em>Warnings</em> window. By clicking these buttons, you can
-        enable/disable a whole class of warnings. Information about the classes
-        of warnings is found on the "Warnings" item under the <em>Help</em>
-        menu (in the rightmost top corner).</p>
-
-      <p>If modules are compiled with inlining, spurious warnings can be
-        emitted. In the <em>Options</em> menu you can choose to ignore
-        inline-compiled modules when analyzing byte code.
-        When starting from source code, this is not a problem because
-        inlining is explicitly turned off by Dialyzer. The option causes
-        Dialyzer to suppress all warnings from inline-compiled
-        modules, as there is currently no way for Dialyzer to find what
-        parts of the code have been produced by inlining.</p>
-    </section>
-
-    <section>
-      <title>Running the Analysis</title>
-      <p>Once you have chosen the modules or directories you want to analyze,
-        click the <em>Run</em> button to start the analysis. If you for some
-        reason want to stop the analysis while it is running, click the
-        <em>Stop</em> button.</p>
-
-      <p>The information from the analysis is displayed in the <em>Log</em>
-        window and the <em>Warnings</em> window.</p>
-    </section>
-
-    <section>
-      <title>Include Directories and Macro Definitions</title>
-      <p>When analyzing from source, you might have to supply Dialyzer
-        with a list of include directories and macro definitions (as you can do
-        with the <seecom marker="erts:erlc"><c>erlc</c></seecom> flags
-        <c>-I</c> and <c>-D</c>). This can be done
-        either by starting Dialyzer with these flags from the command
-        line as in:</p>
-
-      <code type="none">
-dialyzer -I my_includes -DDEBUG -Dvsn=42 -I one_more_dir</code>
-
-      <p>or by adding these explicitly using submenu
-        <em>Manage Macro Definitions</em> or
-        <em>Manage Include Directories</em> in the <em>Options</em> menu.</p>
-    </section>
-
-    <section>
-      <title>Saving the Information on the Log and Warnings Windows</title>
-      <p>The <em>File</em> menu includes options to save the contents of the
-        <em>Log</em> window and the <em>Warnings</em> window. Simply choose the
-        options and enter the file to save the contents in.</p>
-
-      <p>There are also buttons to clear the contents of each window.</p>
-    </section>
-
-    <section>
-      <title>Inspecting the Inferred Types of the Analyzed Functions</title>
-      <p>Dialyzer stores the information of the analyzed functions in a
-        Persistent Lookup Table (PLT), see section
-        <seeguide marker="#plt">The Persistent Lookup Table</seeguide>.</p>
-
-      <p>After an analysis, you can inspect this information.
-        In the <em>PLT</em> menu you can choose to either search the PLT
-        or inspect the contents of the whole PLT. The information is presented
-        in <seeerl marker="edoc:edoc"><c>EDoc</c></seeerl> format.</p>
-    </section>
-  </section>
-
   <section>
     <title>Dialyzer's Model of Analysis</title>
     <p>Dialyzer operates somewhere between a classical type checker and a more
@@ -367,4 +272,3 @@ some_module.erl:31:9: The call t:baz
       describing the symptoms and how to reproduce them.</p>
   </section>
 </chapter>
-
diff --git a/lib/dialyzer/src/Makefile b/lib/dialyzer/src/Makefile
index 2f0f1f6b71..2c5a87ff14 100644
--- a/lib/dialyzer/src/Makefile
+++ b/lib/dialyzer/src/Makefile
@@ -60,8 +60,6 @@ MODULES = \
 	dialyzer_dataflow \
 	dialyzer_dep \
 	dialyzer_dot \
-	dialyzer_explanation \
-	dialyzer_gui_wx \
 	dialyzer_incremental \
 	dialyzer_options \
 	dialyzer_iplt \
@@ -79,7 +77,7 @@ MODULES = \
 	typer \
 	typer_core
 
-HRL_FILES= dialyzer.hrl dialyzer_gui_wx.hrl
+HRL_FILES= dialyzer.hrl
 ERL_FILES= $(MODULES:%=%.erl)
 INSTALL_FILES= $(MODULES:%=$(EBIN)/%.$(EMULATOR)) $(APP_TARGET) $(APPUP_TARGET)
 TARGET_FILES= $(INSTALL_FILES)
@@ -127,9 +125,6 @@ $(EBIN)/dialyzer_cplt.$(EMULATOR): dialyzer_cplt.erl ../vsn.mk
 $(EBIN)/dialyzer_iplt.$(EMULATOR): dialyzer_iplt.erl ../vsn.mk
 	$(erlc_verbose)erlc -W  $(ERL_COMPILE_FLAGS) -DVSN="\"v$(VSN)\"" -o$(EBIN) dialyzer_iplt.erl
 
-$(EBIN)/dialyzer_gui_wx.$(EMULATOR): dialyzer_gui_wx.erl ../vsn.mk
-	$(erlc_verbose)erlc -W  $(ERL_COMPILE_FLAGS) -DVSN="\"v$(VSN)\"" -o$(EBIN) dialyzer_gui_wx.erl
-
 $(EBIN)/typer.$(EMULATOR): typer.erl ../vsn.mk
 	$(erlc_verbose)erlc -W  $(ERL_COMPILE_FLAGS) -DVSN="\"v$(VSN)\"" -o$(EBIN) typer.erl
 
@@ -153,8 +148,6 @@ $(EBIN)/dialyzer_codeserver.beam: dialyzer.hrl
 $(EBIN)/dialyzer_contracts.beam: dialyzer.hrl
 $(EBIN)/dialyzer_dataflow.beam: dialyzer.hrl
 $(EBIN)/dialyzer_dep.beam: dialyzer.hrl
-$(EBIN)/dialyzer_explanation.beam: dialyzer.hrl
-$(EBIN)/dialyzer_gui_wx.beam: dialyzer.hrl dialyzer_gui_wx.hrl
 $(EBIN)/dialyzer_options.beam: dialyzer.hrl
 $(EBIN)/dialyzer_plt.beam: dialyzer.hrl
 $(EBIN)/dialyzer_race_data_server.beam: dialyzer.hrl
@@ -166,7 +159,7 @@ $(EBIN)/dialyzer_utils.beam: dialyzer.hrl
 
 # ----------------------------------------------------
 # Release Target
-# ---------------------------------------------------- 
+# ----------------------------------------------------
 include $(ERL_TOP)/make/otp_release_targets.mk
 
 release_spec: opt
diff --git a/lib/dialyzer/src/dialyzer.app.src b/lib/dialyzer/src/dialyzer.app.src
index 107da591d1..a460f57f16 100644
--- a/lib/dialyzer/src/dialyzer.app.src
+++ b/lib/dialyzer/src/dialyzer.app.src
@@ -37,8 +37,6 @@
 	     dialyzer_dataflow,
 	     dialyzer_dep,
 	     dialyzer_dot,
-	     dialyzer_explanation,
-	     dialyzer_gui_wx,
 	     dialyzer_incremental,
 	     dialyzer_options,
 	     dialyzer_plt,
@@ -56,6 +54,6 @@
   {registered, []},
   {applications, [compiler, kernel, stdlib]},
   {env, []},
-  {runtime_dependencies, ["wx-2.0","syntax_tools-2.0","stdlib-5.0",
+  {runtime_dependencies, ["syntax_tools-2.0","stdlib-5.0",
 			  "kernel-8.0","erts-12.0",
 			  "compiler-8.0"]}]}.
diff --git a/lib/dialyzer/src/dialyzer.erl b/lib/dialyzer/src/dialyzer.erl
index ecfc509e34..348c1a018b 100644
--- a/lib/dialyzer/src/dialyzer.erl
+++ b/lib/dialyzer/src/dialyzer.erl
@@ -31,8 +31,6 @@
 	 run/1,
 	 run_report_modules_analyzed/1,
 	 run_report_modules_changed_and_analyzed/1,
-	 gui/0,
-	 gui/1,
 	 plt_info/1,
 	 format_warning/1,
 	 format_warning/2]).
@@ -51,7 +49,6 @@
 %%                      had to be analyzed to compute the result, plus the
 %%                      set of modules that have changed since the PLT was
 %%                      created (if applicable)
-%%  - gui/0/1:          Erlang interface for the gui.
 %%  - format_warning/1: Get the string representation of a warning.
 %%  - format_warning/2: Likewise, but with an option whether
 %%			to display full path names or not
@@ -66,19 +63,6 @@ plain_cl() ->
       cl_halt(cl_check_init(Opts), Opts);
     {plt_info, Opts} ->
       cl_halt(cl_print_plt_info(Opts), Opts);
-    {gui, Opts} ->
-      try check_gui_options(Opts)
-      catch throw:{dialyzer_error, Msg} -> cl_error(Msg)
-      end,
-      case Opts#options.check_plt of
-	true ->
-	  case cl_check_init(Opts#options{get_warnings = false}) of
-	    {ok, _} -> gui_halt(internal_gui(Opts), Opts);
-	    {error, _} = Error -> cl_halt(Error, Opts)
-	  end;
-	false ->
-	  gui_halt(internal_gui(Opts), Opts)
-      end;
     {cl, Opts} ->
       case Opts#options.check_plt of
 	true ->
@@ -243,46 +227,6 @@ check_init(#options{check_plt = true} = OptsRecord) ->
 check_init(#options{check_plt = false}) ->
     ok.
 
-internal_gui(OptsRecord) ->
-  F = fun() ->
-	  dialyzer_gui_wx:start(OptsRecord),
-	  ?RET_NOTHING_SUSPICIOUS
-      end,
-  doit(F).
-
--spec gui() -> 'ok'.
-
-gui() ->
-  gui([]).
-
--spec gui(Options) -> 'ok' when
-    Options :: [dial_option()].
-
-gui(Opts) ->
-  try dialyzer_options:build([{report_mode, quiet}|Opts]) of
-    {error, Msg} ->
-      throw({dialyzer_error, Msg});
-    OptsRecord ->
-      ok = check_gui_options(OptsRecord),
-      ok = check_init(OptsRecord),
-      F = fun() ->
-          dialyzer_gui_wx:start(OptsRecord)
-      end,
-      case doit(F) of
-	  {ok, _} -> ok;
-	  {error, Msg} -> throw({dialyzer_error, Msg})
-      end
-  catch
-    throw:{dialyzer_error, ErrorMsg} ->
-      erlang:error({dialyzer_error, lists:flatten(ErrorMsg)})
-  end.
-
-check_gui_options(#options{analysis_type = succ_typings}) ->
-  ok;
-check_gui_options(#options{analysis_type = Mode}) ->
-  Msg = io_lib:format("Analysis mode ~w is illegal in GUI mode", [Mode]),
-  throw({dialyzer_error, Msg}).
-
 -spec plt_info(Plt) ->
      {'ok', ClassicResult | IncrementalResult } | {'error', Reason} when
     Plt :: file:filename(),
@@ -326,11 +270,6 @@ doit(F) ->
 cl_error(Msg) ->
   cl_halt({error, Msg}, #options{}).
 
--spec gui_halt(doit_ret(), #options{}) -> no_return().
-
-gui_halt(R, Opts) ->
-  cl_halt(R, Opts#options{report_mode = quiet}).
-
 -spec cl_halt(doit_ret(), #options{}) -> no_return().
 
 cl_halt({ok, R = ?RET_NOTHING_SUSPICIOUS}, #options{report_mode = quiet}) ->
diff --git a/lib/dialyzer/src/dialyzer_cl_parse.erl b/lib/dialyzer/src/dialyzer_cl_parse.erl
index 2babea0073..5d2b1d8731 100644
--- a/lib/dialyzer/src/dialyzer_cl_parse.erl
+++ b/lib/dialyzer/src/dialyzer_cl_parse.erl
@@ -21,7 +21,6 @@
 -type dial_cl_parse_ret() :: {'check_init', #options{}}
                            | {'plt_info', #options{}}
                            | {'cl', #options{}}
-                           | {'gui', #options{}}
                            | {'error', string()}.
 
 -spec start() -> dial_cl_parse_ret().
@@ -150,8 +149,6 @@ cli() ->
                 no_underspecs, no_unknown, no_unused, underspecs, unknown, unmatched_returns,
                 overspecs, specdiffs, extra_return, no_extra_return, missing_return, no_missing_return]},
                 help => {<<"[-Wwarn]*">>, [<<"A family of options which selectively turn on/off warnings">>]}},
-            #{name => shell, long => "-shell", type => boolean,
-                help => <<"Do not disable the Erlang shell while running the GUI.">>},
             #{name => version, short => $v, long => "-version", type => boolean,
                 help => <<"Print the Dialyzer version and some more information and exit.">>},
             #{name => help, short => $h, long => "-help", type => boolean,
@@ -215,8 +212,6 @@ cli() ->
             #{name => indent_opt, long => "-no_indentation", type => boolean, action => {store, false},
                 help => <<"Do not indent contracts and success typings. Note that this option has "
                         "no effect when combined with the --raw option.">>},
-            #{name => gui, long => "-gui", type => boolean,
-                help => <<"Use the GUI.">>},
             #{name => metrics_file, long => "-metrics_file",
                 help => <<"Write metrics about Dialyzer's incrementality (for example, total number of "
                         "modules considered, how many modules were changed since the PLT was "
@@ -248,8 +243,7 @@ cli() ->
             arguments, options, "
 Note:
   * denotes that multiple occurrences of these options are possible.
- ** options -D and -I work both from command-line and in the Dialyzer GUI;
-    the syntax of defines and includes is the same as that used by \"erlc\".
+ ** the syntax of defines and includes is the same as that used by \"erlc\".
 
 " ++ warning_options_msg() ++ "
 " ++ configuration_file_msg() ++ "
@@ -304,11 +298,6 @@ postprocess_side_effects(ArgMap) ->
         plt_check ->
             %% plt_check is a hidden "check_init" command
             {check_init, ArgMap1};
-        _ when map_get(gui, ArgMap1) ->
-            %% filter out command-line only arguments
-            Allowed = [defines, from, include_dirs, plts, output_plt, report_mode,
-                use_spec, warnings, check_plt, solvers],
-            {gui, maps:with(Allowed, ArgMap1)};
         _ ->
             {cl, ArgMap1}
     end.
diff --git a/lib/dialyzer/src/dialyzer_explanation.erl b/lib/dialyzer/src/dialyzer_explanation.erl
deleted file mode 100644
index 10b3ef8ea5..0000000000
--- a/lib/dialyzer/src/dialyzer_explanation.erl
+++ /dev/null
@@ -1,45 +0,0 @@
-%% -*- erlang-indent-level: 2 -*-
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-
-%%%-------------------------------------------------------------------
-%%% File    : dialyzer_explanation.erl
-%%% Author  : Elli Fragkaki <ellifrag@gmail.com>
-%%% Description : 
-%%%-------------------------------------------------------------------
-
--module(dialyzer_explanation).
-
--export([expl_loop/3]).
-
--include("dialyzer.hrl").
-
--spec expl_loop(pid(), dialyzer_codeserver:codeserver(), dialyzer_plt:plt()) ->
-	no_return().
-
-expl_loop(Parent, CServer, Plt) ->
-  receive
-    {Parent, warning, _Warning} ->
-      send_explanation(Parent, none),
-      expl_loop(Parent, CServer, Plt);
-    {Parent, further, _Explanation} -> 
-      Parent ! {self(), further, none},
-      expl_loop(Parent, CServer, Plt);
-    Other ->
-      io:format("Unknown message: ~p\n", [Other]),
-      expl_loop(Parent, CServer, Plt)
-  end.
-
-send_explanation(Parent, Expl) ->
-  Parent ! {self(), explanation, Expl},
-  ok.
diff --git a/lib/dialyzer/src/dialyzer_gui_wx.erl b/lib/dialyzer/src/dialyzer_gui_wx.erl
deleted file mode 100644
index 13d0a65dbb..0000000000
--- a/lib/dialyzer/src/dialyzer_gui_wx.erl
+++ /dev/null
@@ -1,1234 +0,0 @@
-%% -*- erlang-indent-level: 2 -*-
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-
-%%%-----------------------------------------------------------------------
-%%% File    : dialyzer_gui_wx.erl
-%%% Authors : Elli Fragkaki <ellifrag@gmail.com>
-%%% Description : The wx-based graphical user interface of dialyzer.
-%%%
-%%% Created : 07 Oct 2009 by Elli Fragkaki <ellifrag@gmail.com>
-%%%-----------------------------------------------------------------------
-
--module(dialyzer_gui_wx).
-
--export([start/1]).
-
--include("dialyzer.hrl").
--include("dialyzer_gui_wx.hrl").
-
-%%------------------------------------------------------------------------
-
--define(DIALYZER_ERROR_TITLE,   "Dialyzer Error").
--define(DIALYZER_MESSAGE_TITLE, "Dialyzer Message").
-
-%%------------------------------------------------------------------------
-
--record(menu, {file                   :: wx:wx_object(),
-	       warnings               :: wx:wx_object(),
-	       plt                    :: wx:wx_object(),
-	       options                :: wx:wx_object(),
-	       help                   :: wx:wx_object()}).
--type menu() :: #menu{}.
-
--record(gui_state, {add               :: wx:wx_object(),
-		    add_dir           :: wx:wx_object(),
-		    add_rec           :: wx:wx_object(),
-		    chosen_box        :: wx:wx_object(),
-		    del_file          :: wx:wx_object(),
-		    doc_plt           :: dialyzer_plt:plt(),
-		    clear_chosen      :: wx:wx_object(),
-		    clear_log         :: wx:wx_object(),
-		    explain_warn      :: wx:wx_object(),
-		    clear_warn        :: wx:wx_object(),
-		    init_plt          :: dialyzer_plt:plt(),
-		    dir_entry         :: wx:wx_object(),
-		    file_box          :: wx:wx_object(),
-		    files_to_analyze  :: ordsets:ordset(string()),
-		    gui               :: wx:wx_object(),
-		    log               :: wx:wx_object(),
-		    menu              :: menu(),
-		    mode              :: wx:wx_object(),
-		    options           :: #options{},
-		    run               :: wx:wx_object(),
-		    stop              :: wx:wx_object(),
-		    frame             :: wx:wx_object(),
-		    warnings_box      :: wx:wx_object(),
-		    explanation_box   :: wx:wx_object() | 'undefined',
-		    wantedWarnings    :: list(),
-		    rawWarnings       :: list(),
-		    backend_pid       :: pid() | 'undefined',
-		    expl_pid          :: pid() | 'undefined'}).
-
-%%------------------------------------------------------------------------
-
--spec start(#options{}) -> ?RET_NOTHING_SUSPICIOUS.
-
-start(DialyzerOptions) ->
-  process_flag(trap_exit, true),
-  Wx = wx:new(),
-  State = wx:batch(fun() -> create_window(Wx, DialyzerOptions) end),
-  gui_loop(State).
-
-create_window(Wx, #options{init_plts = InitPltFiles} = DialyzerOptions) ->
-  {ok, Host} = inet:gethostname(),
-
-  %%---------- initializing frame ---------
-  Frame = wxFrame:new(Wx, -1,  "Dialyzer " ++ ?VSN ++ " @ " ++ Host),
-  wxFrame:connect(Frame, close_window),
-  FileMenu = createFileMenu(),
-  WarningsMenu = createWarningsMenu(),
-  PltMenu = createPltMenu(),
-  OptionsMenu = createOptionsMenu(),
-  HelpMenu = createHelpMenu(),
-
-  MenuBar = wxMenuBar:new(),
-  wxMenuBar:append(MenuBar, FileMenu,     "File"),
-  wxMenuBar:append(MenuBar, WarningsMenu, "Warnings"),
-  wxMenuBar:append(MenuBar, PltMenu,      "Plt"),
-  wxMenuBar:append(MenuBar, OptionsMenu,  "Options"),
-  wxMenuBar:append(MenuBar, HelpMenu,     "Help"),
-  wxFrame:setMenuBar(Frame, MenuBar),
-  ok = wxFrame:connect(Frame, command_menu_selected),
-
-  %%----------- Set Labels -------------
-  Lab1 = wxStaticText:new(Frame, ?LABEL1, "Directories or modules to analyze"),
-  OptionsLabel = wxStaticText:new(Frame, ?LABEL2, "Analysis Options"),
-  LogLabel = wxStaticText:new(Frame, ?LABEL3, "Log"),
-  FileLabel = wxStaticText:new(Frame, ?LABEL4, "File: "),
-  DirLabel = wxStaticText:new(Frame, ?LABEL5, "Dir: "),
-  WarningsLabel = wxStaticText:new(Frame, ?LABEL6, "Warnings"),
-
-  %%---------- Set TextBoxes -----------
-  ChosenBox = wxListBox:new(Frame, ?ChosenBox,
-			[{size, {250,200}},
-			 {style, ?wxLB_EXTENDED bor ?wxLB_HSCROLL
-			  bor ?wxLB_NEEDED_SB}]),
-  LogBox = wxTextCtrl:new(Frame, ?LogBox,
-			[{size, {530,200}},
-			 {style, ?wxTE_MULTILINE
-			  bor ?wxTE_READONLY bor ?wxHSCROLL}]),
-  DefaultPath = code:root_dir(),
-
-  FilePicker = wxFilePickerCtrl:new(Frame, ?FilePicker,
-				   [{path, DefaultPath},
-				    {message, "Choose File to Analyse"},
-				    {style,?wxFLP_FILE_MUST_EXIST bor ?wxFLP_USE_TEXTCTRL}]),
-  wxPickerBase:setTextCtrlProportion(FilePicker,3),
-  wxPickerBase:setPickerCtrlProportion(FilePicker,2),
-  DirPicker = wxDirPickerCtrl:new(Frame, ?DirPicker,
-				   [{path, DefaultPath},
-				    {message, "Choose Directory to Analyze"},
-				    {style,?wxDIRP_DIR_MUST_EXIST bor ?wxDIRP_USE_TEXTCTRL}]),
-  WarningsBox = wxListBox:new(Frame, ?WarningsBox,
-			[{size, {700,200}},
-			 {style,  ?wxLB_HSCROLL
-			  bor ?wxLB_NEEDED_SB}]),
-
-  %%--------- Set Buttons --------------
-  DeleteButton = wxButton:new(Frame, ?Del_Button, [{label, "Delete"}]),
-  DeleteAllButton = wxButton:new(Frame, ?DelAll_Button, [{label, "Delete All"}]),
-  FileType = wxRadioBox:new(Frame, ?RADIOBOX, " File Type: " , {1,1}, {150,90},
-			    [["BeamFiles"],["SourceFiles"]]),
-  ClearLogButton = wxButton:new(Frame, ?ClearLog_Button, [{label, "Clear Log"}]),
-  AddButton = wxButton:new(Frame, ?Add_Button, [{label, "Add"}]),
-  AddDirButton = wxButton:new(Frame, ?AddDir_Button, [{label, "Add Dir"}]),
-  AddRecButton = wxButton:new(Frame, ?AddRec_Button, [{label, "Add Recursively"}]),
-  ExplainWarnButton = wxButton:new(Frame, ?ExplWarn_Button, [{label, "Explain Warning"}]),
-  ClearWarningsButton = wxButton:new(Frame, ?ClearWarn_Button, [{label, "Clear Warnings"}]),
-  RunButton = wxButton:new(Frame, ?Run_Button, [{label, "Run"}]),
-  StopButton = wxButton:new(Frame, ?Stop_Button, [{label, "Stop"}]),
-  wxWindow:disable(StopButton),
-  %%--------- Connect Buttons -----------
-  wxButton:connect(DeleteButton, command_button_clicked),
-  wxButton:connect(DeleteAllButton, command_button_clicked),
-  wxButton:connect(ClearLogButton, command_button_clicked),
-  wxButton:connect(AddButton, command_button_clicked),
-  wxButton:connect(AddDirButton, command_button_clicked),
-  wxButton:connect(AddRecButton, command_button_clicked),
-  wxButton:connect(ExplainWarnButton, command_button_clicked),
-  wxButton:connect(ClearWarningsButton, command_button_clicked),
-  wxButton:connect(RunButton, command_button_clicked),
-  wxButton:connect(StopButton, command_button_clicked),
-
-  %%------------Set Layout ------------
-  All = wxBoxSizer:new(?wxVERTICAL),
-  Top = wxBoxSizer:new(?wxHORIZONTAL),
-  Left = wxBoxSizer:new(?wxVERTICAL),
-  Right = wxBoxSizer:new(?wxVERTICAL),
-  RightUp = wxBoxSizer:new(?wxHORIZONTAL),
-
-  Opts = [{flag,?wxEXPAND bor ?wxALL}, {proportion,1}, {border, 1}],
-  Opts3 = [{flag,?wxEXPAND bor ?wxALL}, {proportion,3}, {border, 1}],
-  Center = [{flag, ?wxALIGN_CENTER_HORIZONTAL}],
-
-  ChooseItem = wxBoxSizer:new(?wxVERTICAL),
-  FileTypeItem = wxBoxSizer:new(?wxVERTICAL),
-  LogItem = wxBoxSizer:new(?wxVERTICAL),
-  FileDirItem = wxBoxSizer:new(?wxVERTICAL),
-  FileItem = wxBoxSizer:new(?wxHORIZONTAL),
-  DirItem = wxBoxSizer:new(?wxHORIZONTAL),
-  AddDirButtons = wxBoxSizer:new(?wxHORIZONTAL),
-  WarningsItem = wxBoxSizer:new(?wxVERTICAL),
-  ChooseButtons = wxBoxSizer:new(?wxHORIZONTAL),
-  WarnButtons = wxBoxSizer:new(?wxHORIZONTAL),
-  RunButtons = wxBoxSizer:new(?wxHORIZONTAL),
-  Buttons = wxFlexGridSizer:new(3),
-
-  _ = wxSizer:add(ChooseButtons, DeleteButton, ?BorderOpt),
-  _ = wxSizer:add(ChooseButtons, DeleteAllButton, ?BorderOpt),
-  _ = wxSizer:add(ChooseItem, Lab1, Center),
-  _ = wxSizer:add(ChooseItem, ChosenBox, Opts),
-  _ = wxSizer:add(ChooseItem, ChooseButtons, ?BorderOpt),
-  _ = wxSizer:add(FileTypeItem, OptionsLabel),
-  _ = wxSizer:add(FileTypeItem, FileType, [{border, 5}, {flag, ?wxALL}]),
-  _ = wxSizer:add(LogItem, LogLabel, Center),
-  _ = wxSizer:add(LogItem, LogBox, Opts3),
-  _ = wxSizer:add(LogItem, ClearLogButton, ?BorderOpt),
-  _ = wxSizer:add(FileItem, FileLabel),
-  _ = wxSizer:add(FileItem, FilePicker),
-  _ = wxSizer:add(DirItem, DirLabel),
-  _ = wxSizer:add(DirItem, DirPicker),
-  _ = wxSizer:add(AddDirButtons, AddDirButton, ?BorderOpt),
-  _ = wxSizer:add(AddDirButtons, AddRecButton, ?BorderOpt),
-  _ = wxSizer:add(FileDirItem, FileItem),
-  _ = wxSizer:add(FileDirItem, AddButton, ?BorderOpt),
-  _ = wxSizer:add(FileDirItem, DirItem, ?BorderOpt),
-  _ = wxSizer:add(FileDirItem, AddDirButtons, ?BorderOpt),
-  _ = wxSizer:add(WarnButtons, ExplainWarnButton, ?BorderOpt),
-  _ = wxSizer:add(WarnButtons, ClearWarningsButton, ?BorderOpt),
-  _ = wxSizer:add(RunButtons, RunButton, ?BorderOpt),
-  _ = wxSizer:add(RunButtons, StopButton, ?BorderOpt),
-  _ = wxSizer:add(Buttons, WarnButtons),
-  _ = wxSizer:add(Buttons, wxStaticText:new(Frame, ?LABEL7, ""),
-		  [{flag, ?wxEXPAND}]),
-  _ = wxSizer:add(Buttons, RunButtons),
-  _ = wxFlexGridSizer:addGrowableCol(Buttons, 1),
-  _ = wxSizer:add(WarningsItem, WarningsLabel, Center),
-  _ = wxSizer:add(WarningsItem, WarningsBox, Opts3),
-  _ = wxSizer:add(WarningsItem, Buttons,
-		  [{flag, ?wxEXPAND bor ?wxALL}, ?Border]),
-  _ = wxSizer:add(Left, ChooseItem, Opts),
-  _ = wxSizer:add(Left, FileDirItem,
-		  [{proportion, 1}, {border, 60}, {flag, ?wxTOP}]),
-  _ = wxSizer:add(RightUp, FileTypeItem, ?BorderOpt),
-  _ = wxSizer:add(RightUp, LogItem, Opts3),
-  _ = wxSizer:add(Right, RightUp, Opts3),
-  _ = wxSizer:add(Right, WarningsItem, Opts3),
-  _ = wxSizer:add(Top, Left, Opts),
-  _ = wxSizer:add(Top, Right, Opts3),
-
-  _ = wxSizer:add(All, Top, Opts),
-  wxWindow:setSizer(Frame, All),
-  wxWindow:setSizeHints(Frame, {1150,600}),
-  wxWindow:show(Frame),
-
-  Warnings = [{?WARN_RETURN_NO_RETURN, ?menuID_WARN_NO_RETURN_FUN},
-	      {?WARN_RETURN_ONLY_EXIT, ?menuID_WARN_ERROR_HANDLING_FUN},
-	      {?WARN_NOT_CALLED, ?menuID_WARN_UNUSED_FUN},
-	      {?WARN_NON_PROPER_LIST, ?menuID_WARN_LIST_CONSTR},
-	      {?WARN_FUN_APP, ?menuID_WARN_BAD_FUN},
-	      {?WARN_MATCHING, ?menuID_WARN_MATCH_FAILURES},
-	      {?WARN_OPAQUE, ?menuID_WARN_OPAQUE},
-	      {?WARN_FAILING_CALL, ?menuID_WARN_FAIL_FUN_CALLS},
-	      {?WARN_CALLGRAPH, ?menuID_WARN_UNEXPORTED_FUN},
-	      %% For contracts.
-	      {?WARN_CONTRACT_TYPES,?menuID_WARN_WRONG_CONTRACTS},
-	      {?WARN_CONTRACT_SYNTAX, ?menuID_WARN_CONTRACT_SYNTAX}
-	     ],
-  Menu = #menu{file = FileMenu,
-	       warnings = WarningsMenu,
-	       plt = PltMenu,
-	       options =OptionsMenu,
-	       help = HelpMenu},
-
-  InitPlt =
-    case InitPltFiles of
-      [] -> dialyzer_plt:new();
-      _ ->
-        Plts = [dialyzer_cplt:from_file(F) || F <- InitPltFiles],
-        dialyzer_cplt:merge_plts_or_report_conflicts(InitPltFiles, Plts)
-    end,
-
-  #gui_state{add = AddButton,
-	     add_dir = AddDirButton,
-	     add_rec = AddRecButton,
-	     chosen_box = ChosenBox,
-	     clear_chosen = DeleteAllButton,
-	     clear_log = ClearLogButton,
-	     explain_warn = ExplainWarnButton,
-	     clear_warn = ClearWarningsButton,
-	     del_file = DeleteButton,
-	     doc_plt = dialyzer_plt:new(),
-	     dir_entry = DirPicker,
-	     file_box = FilePicker,
-	     files_to_analyze = ordsets:new(),
-	     gui = Wx,
-	     init_plt = InitPlt,
-	     log = LogBox,
-	     menu = Menu,
-	     mode = FileType,
-	     options = DialyzerOptions,
-	     run = RunButton,
-	     stop = StopButton,
-	     frame = Frame,
-	     warnings_box = WarningsBox,
-	     wantedWarnings = Warnings,
-	     rawWarnings = []}.
-
-createFileMenu() ->
-  FileMenu = wxMenu:new(),
-  _ = wxMenu:append(FileMenu, wxMenuItem:new([{id, ?menuID_FILE_SAVE_WARNINGS},
-					      {text, "Save &Warnings"}])),
-  _ = wxMenu:append(FileMenu, wxMenuItem:new([{id,   ?menuID_FILE_SAVE_LOG},
-					      {text, "Save &Log"}])),
-  _ = wxMenu:append(FileMenu, wxMenuItem:new([{id,   ?menuID_FILE_QUIT},
-					      {text, "E&xit\tAlt-X"}])),
-  FileMenu.
-
-createWarningsMenu() ->
-  WarningsMenu = wxMenu:new(),
-  addCheckedItem(WarningsMenu, ?menuID_WARN_MATCH_FAILURES, "Match failures"),
-  addCheckedItem(WarningsMenu, ?menuID_WARN_FAIL_FUN_CALLS,
-		 "Failing function calls"),
-  addCheckedItem(WarningsMenu, ?menuID_WARN_BAD_FUN, "Bad fun applications"),
-  addCheckedItem(WarningsMenu, ?menuID_WARN_OPAQUE, "Opacity violations"),
-  addCheckedItem(WarningsMenu, ?menuID_WARN_LIST_CONSTR,
-		 "Improper list constructions"),
-  addCheckedItem(WarningsMenu, ?menuID_WARN_UNUSED_FUN, "Unused functions"),
-  _ = wxMenu:appendCheckItem(WarningsMenu, ?menuID_WARN_ERROR_HANDLING_FUN,
-			     "Error handling functions"),
-  addCheckedItem(WarningsMenu, ?menuID_WARN_NO_RETURN_FUN,
-		 "Functions of no return"),
-  addCheckedItem(WarningsMenu, ?menuID_WARN_UNEXPORTED_FUN,
-		 "Call to unexported function"),
-  addCheckedItem(WarningsMenu, ?menuID_WARN_WRONG_CONTRACTS, "Wrong contracts"),
-  addCheckedItem(WarningsMenu, ?menuID_WARN_CONTRACT_SYNTAX,
-		 "Wrong contract syntax"),
-  WarningsMenu.
-
-addCheckedItem(Menu, ItemId, Str) ->
-  _ = wxMenu:appendCheckItem(Menu, ItemId, Str),
-  wxMenu:check(Menu, ItemId, true).
-
-createPltMenu() ->
-  PltMenu = wxMenu:new(),
-  _ = wxMenu:appendCheckItem(PltMenu, ?menuID_PLT_INIT_EMPTY,
-			     "Init with empty PLT"),
-  _ = wxMenu:append(PltMenu, wxMenuItem:new([{id, ?menuID_PLT_SHOW_CONTENTS},
-					     {text, "Show contents"}])),
-  _ = wxMenu:append(PltMenu, wxMenuItem:new([{id, ?menuID_PLT_SEARCH_CONTENTS},
-					     {text, "Search contents"}])),
-  PltMenu.
-
-createOptionsMenu() ->
-  OptsMenu  = wxMenu:new(),
-  _ = wxMenu:append(OptsMenu, wxMenuItem:new([{id, ?menuID_OPTIONS_MACRO},
-					      {text, "Manage Macro Definitions"}])),
-  _ = wxMenu:append(OptsMenu, wxMenuItem:new([{id, ?menuID_OPTIONS_INCLUDE_DIR},
-					      {text, "Manage Include Directories"}])),
-  OptsMenu.
-
-createHelpMenu() ->
-  HelpMenu = wxMenu:new(),
-  _ = wxMenu:append(HelpMenu, wxMenuItem:new([{id, ?menuID_HELP_MANUAL},
-					      {text, "Manual"}])),
-  _ = wxMenu:append(HelpMenu, wxMenuItem:new([{id, ?menuID_HELP_WARNING_OPTIONS},
-					      {text, "Warning Options"}])),
-  _ = wxMenu:append(HelpMenu, wxMenuItem:new([{id, ?menuID_HELP_ABOUT},
-					      {text, "About"}])),
-  HelpMenu.
-
-%% ----------------------------------------------------------------
-%%
-%%  Main GUI Loop
-%%
-
--spec gui_loop(#gui_state{}) -> ?RET_NOTHING_SUSPICIOUS.
-
-gui_loop(#gui_state{backend_pid = BackendPid, doc_plt = DocPlt,
-		    log = Log, frame = Frame,
-		    warnings_box = WarningsBox} = State) ->
-  receive
-    #wx{event = #wxClose{}} ->
-      %% io:format("~p Closing window ~n", [self()]),
-      ok = wxFrame:setStatusText(Frame, "Closing...",[]),
-      wxWindow:destroy(Frame),
-      ?RET_NOTHING_SUSPICIOUS;
-    %% ----- Menu -----
-    #wx{id = ?menuID_FILE_SAVE_LOG, obj = Frame,
-	event = #wxCommand{type = command_menu_selected}} ->
-      save_file(State, log),
-      gui_loop(State);
-    #wx{id=?menuID_FILE_SAVE_WARNINGS, obj=Frame,
-	event=#wxCommand{type=command_menu_selected}} ->
-      save_file(State, warnings),
-      gui_loop(State);
-    #wx{id=?menuID_FILE_QUIT, obj=Frame,
-	event=#wxCommand{type=command_menu_selected}} ->
-      case maybe_quit(State) of
-	true -> ?RET_NOTHING_SUSPICIOUS;
-	false -> gui_loop(State)
-      end;
-    #wx{id=?menuID_PLT_SHOW_CONTENTS, obj=Frame,
-	event=#wxCommand{type=command_menu_selected}} ->
-      show_doc_plt(State),
-      gui_loop(State);
-    #wx{id=?menuID_PLT_SEARCH_CONTENTS, obj=Frame,
-	event=#wxCommand{type=command_menu_selected}} ->
-      case dialyzer_plt:get_specs(DocPlt) of
-	"" -> error_sms(State, "No analysis has been made yet!\n");
-	_ -> search_doc_plt(State)
-      end,
-      gui_loop(State);
-    #wx{id=?menuID_OPTIONS_INCLUDE_DIR, obj=Frame,
-	event=#wxCommand{type=command_menu_selected}} ->
-      NewOptions = include_dialog(State),
-      NewState = State#gui_state{options = NewOptions},
-      gui_loop(NewState);
-    #wx{id=?menuID_OPTIONS_MACRO, obj=Frame,
-	event=#wxCommand{type=command_menu_selected}} ->
-      NewOptions = macro_dialog(State),
-      NewState = State#gui_state{options = NewOptions},
-      gui_loop(NewState);
-    #wx{id=?menuID_HELP_MANUAL, obj=Frame,
-	event=#wxCommand{type=command_menu_selected}} ->
-      handle_help(State, "Dialyzer Manual", "manual.txt"),
-      gui_loop(State);
-    #wx{id=?menuID_HELP_WARNING_OPTIONS, obj=Frame,
-	event=#wxCommand{type=command_menu_selected}} ->
-      handle_help(State, "Dialyzer Warnings", "warnings.txt"),
-      gui_loop(State);
-    #wx{id=?menuID_HELP_ABOUT, obj=Frame,
-	event=#wxCommand{type=command_menu_selected}} ->
-      Message = "	       This is DIALYZER version "  ++ ?VSN ++  " \n"++
-	"DIALYZER is a DIscrepancy AnaLYZer for ERlang programs.\n\n"++
-	"     Copyright (C) Tobias Lindahl <tobiasl@it.uu.se>\n"++
-	"                   Kostis Sagonas <kostis@it.uu.se>\n\n",
-      output_sms(State, "About Dialyzer", Message, info),
-      gui_loop(State);
-    %% ------ Buttons ---------
-    #wx{id=?Add_Button,
-	event=#wxCommand{type=command_button_clicked}} ->
-      State1 = handle_add_files(State),
-      gui_loop(State1);
-    #wx{id=?AddDir_Button,
-	event=#wxCommand{type=command_button_clicked}} ->
-      State1 = handle_add_dir(State),
-      gui_loop(State1);
-    #wx{id=?AddRec_Button,
-	event=#wxCommand{type=command_button_clicked}} ->
-      State1 = handle_add_rec(State),
-      gui_loop(State1);
-    #wx{id=?Del_Button,
-	event=#wxCommand{type=command_button_clicked}} ->
-      State1 = handle_file_delete(State),
-      gui_loop(State1);
-    #wx{id=?DelAll_Button,
-	event=#wxCommand{type=command_button_clicked}} ->
-      State1 = handle_file_delete_all(State),
-      gui_loop(State1);
-    #wx{id=?ClearLog_Button,
-	event=#wxCommand{type=command_button_clicked}} ->
-      wxTextCtrl:clear(State#gui_state.log),
-      gui_loop(State);
-    #wx{id=?ExplWarn_Button,
-	event=#wxCommand{type=command_button_clicked}} ->
-      handle_explanation(State),
-      gui_loop(State);
-    #wx{id=?ClearWarn_Button,
-	event=#wxCommand{type=command_button_clicked}} ->
-      wxListBox:clear(WarningsBox),
-      NewState = State#gui_state{rawWarnings = []},
-      gui_loop(NewState);
-    #wx{id=?Run_Button,
-	event=#wxCommand{type=command_button_clicked}} ->
-      NewState = start_analysis(State),
-      gui_loop(NewState);
-    #wx{id=?Stop_Button,
-	event=#wxCommand{type=command_button_clicked}} ->
-      BackendPid ! {self(), stop},
-      config_gui_stop(State),
-      update_editor(Log, "\n***** Analysis stopped ****\n"),
-      gui_loop(State);
-    %% ----- Analysis -----
-    {BackendPid, ext_calls, ExtCalls} ->
-      ExtCalls1 = lists:usort([MFA || {MFA, _FileLocation} <- ExtCalls]),
-      Map = fun({M,F,A}) -> io_lib:format("\t~tp:~tp/~p",[M,F,A]) end,
-      ExtCallString = lists:join("\n", lists:map(Map, ExtCalls1)),
-      Msg = io_lib:format("The following functions are called "
-			  "but type information about them is not available.\n"
-			  "The analysis might get more precise by including "
-			  "the modules containing these functions:\n\n~ts\n",
-			  [ExtCallString]),
-      free_editor(State,"Analysis Done",  Msg),
-      gui_loop(State);
-    {BackendPid, ext_types, ExtTypes} ->
-      ExtTypes1 = lists:usort([MFA || {MFA, _FileLocation} <- ExtTypes]),
-      Map = fun({M,F,A}) -> io_lib:format("\t~tp:~tp/~p",[M,F,A]) end,
-      ExtTypeString = lists:join("\n", lists:map(Map, ExtTypes1)),
-      Msg = io_lib:format("The following remote types are being used "
-			  "but information about them is not available.\n"
-			  "The analysis might get more precise by including "
-			  "the modules containing these types and making sure "
-			  "that they are exported:\n\n~ts\n",
-                          [ExtTypeString]),
-      free_editor(State, "Analysis done", Msg),
-      gui_loop(State);
-    {BackendPid, log, LogMsg} ->
-      update_editor(Log, LogMsg),
-      gui_loop(State);
-    {BackendPid, warnings, Warns} ->
-      SortedWarns = lists:keysort(2, Warns),  %% Sort on file/location
-      NewState = add_warnings(State, SortedWarns),
-      gui_loop(NewState);
-    {BackendPid, cserver, CServer, Plt} ->
-      Self = self(),
-      Fun =
-	fun() ->
-	    dialyzer_explanation:expl_loop(Self, CServer, Plt)
-	end,
-      ExplanationPid = spawn_link(Fun),
-      gui_loop(State#gui_state{expl_pid = ExplanationPid});
-    {BackendPid, done, _NewPlt, NewDocPlt} ->
-      message(State, "Analysis done"),
-      config_gui_stop(State),
-      dialyzer_plt:delete(State#gui_state.doc_plt),
-      gui_loop(State#gui_state{doc_plt = NewDocPlt});
-    {'EXIT', BackendPid, {error, Reason}} ->
-      free_editor(State, ?DIALYZER_ERROR_TITLE, Reason),
-      config_gui_stop(State),
-      gui_loop(State);
-    {'EXIT', BackendPid, Reason} when Reason =/= 'normal' ->
-      free_editor(State, ?DIALYZER_ERROR_TITLE, io_lib:format("~tp", [Reason])),
-      config_gui_stop(State),
-      gui_loop(State)
-  end.
-
-maybe_quit(#gui_state{frame = Frame} = State) ->
-  case dialog(State, "Do you really want to quit?", ?DIALYZER_MESSAGE_TITLE) of
-    true ->
-      wxWindow:destroy(Frame),
-      true;
-    false ->
-      false
-  end.
-
-%% ------------ Yes/No Question ------------
-dialog(#gui_state{frame = Frame}, Message, Title) ->
-  MessageWin = wxMessageDialog:new(Frame, Message, [{caption, Title},{style, ?wxYES_NO bor ?wxICON_QUESTION bor ?wxNO_DEFAULT}]),
-  case wxDialog:showModal(MessageWin) of
-    ?wxID_YES ->
-      true;
-    ?wxID_NO ->
-      false;
-    ?wxID_CANCEL ->
-      false
-  end.
-
-search_doc_plt(#gui_state{gui = Wx} = State) ->
-  Dialog = wxFrame:new(Wx, ?SearchPltDialog, "Search the PLT",[{size,{400,100}},{style, ?wxSTAY_ON_TOP}]),
-  Size = {size,{120,30}},
-  ModLabel = wxStaticText:new(Dialog, ?ModLabel, "Module"),
-  ModText = wxTextCtrl:new(Dialog, ?ModText,[Size]),
-  FunLabel = wxStaticText:new(Dialog, ?FunLabel, "Function"),
-  FunText = wxTextCtrl:new(Dialog, ?FunText,[Size]),
-  ArLabel = wxStaticText:new(Dialog, ?ArLabel, "Arity"),
-  ArText = wxTextCtrl:new(Dialog, ?ArText,[Size]),
-  SearchButton = wxButton:new(Dialog, ?SearchButton, [{label, "Search"}]),
-  wxButton:connect(SearchButton, command_button_clicked),
-  Cancel = wxButton:new(Dialog, ?Search_Cancel, [{label, "Cancel"}]),
-  wxButton:connect(Cancel, command_button_clicked),
-
-  Layout = wxBoxSizer:new(?wxVERTICAL),
-  Top = wxBoxSizer:new(?wxHORIZONTAL),
-  ModLayout = wxBoxSizer:new(?wxVERTICAL),
-  FunLayout = wxBoxSizer:new(?wxVERTICAL),
-  ArLayout = wxBoxSizer:new(?wxVERTICAL),
-  Buttons = wxBoxSizer:new(?wxHORIZONTAL),
-
-  _ = wxSizer:add(ModLayout, ModLabel, ?BorderOpt),
-  _ = wxSizer:add(ModLayout, ModText, ?BorderOpt),
-  _ = wxSizer:add(FunLayout, FunLabel, ?BorderOpt),
-  _ = wxSizer:add(FunLayout,FunText, ?BorderOpt),
-  _ = wxSizer:add(ArLayout, ArLabel, ?BorderOpt),
-  _ = wxSizer:add(ArLayout,ArText, ?BorderOpt),
-  _ = wxSizer:add(Buttons, SearchButton, ?BorderOpt),
-  _ = wxSizer:add(Buttons,Cancel, ?BorderOpt),
-
-  _ = wxSizer:add(Top, ModLayout),
-  _ = wxSizer:add(Top, FunLayout),
-  _ = wxSizer:add(Top, ArLayout),
-  _ = wxSizer:add(Layout, Top,[{flag, ?wxALIGN_CENTER}]),
-  _ = wxSizer:add(Layout, Buttons,[{flag, ?wxALIGN_CENTER bor ?wxBOTTOM}]),
-  wxFrame:connect(Dialog, close_window),
-  wxWindow:setSizer(Dialog, Layout),
-  wxFrame:show(Dialog),
-  search_plt_loop(State, Dialog, ModText, FunText, ArText, SearchButton, Cancel).
-
-search_plt_loop(State= #gui_state{doc_plt = DocPlt, frame = Frame}, Win, ModText, FunText, ArText, Search, Cancel) ->
-  receive
-    #wx{id = ?Search_Cancel,
-	event = #wxCommand{type = command_button_clicked}} ->
-      wxWindow:destroy(Win);
-    #wx{id = ?SearchPltDialog, event = #wxClose{type = close_window}} ->
-      wxWindow:destroy(Win);
-    #wx{event = #wxClose{type = close_window}} ->
-      wxWindow:destroy(Win),
-      wxWindow:destroy(Frame);
-    #wx{id = ?SearchButton,
-	event = #wxCommand{type = command_button_clicked}} ->
-      M = format_search(wxTextCtrl:getValue(ModText)),
-      F = format_search(wxTextCtrl:getValue(FunText)),
-      A = format_search(wxTextCtrl:getValue(ArText)),
-
-      if
-	(M =:= '_') orelse (F =:= '_') orelse (A =:= '_') ->
-	  error_sms(State, "Please give:\n Module (atom)\n Function (atom)\n Arity (integer)\n"),
-	  search_plt_loop(State, Win, ModText, FunText, ArText, Search, Cancel);
-	 true ->
-	  case dialyzer_plt:get_specs(DocPlt, M, F, A) of
-	    none ->
-	      error_sms(State, "No such function"),
-	      search_plt_loop(State, Win, ModText, FunText, ArText, Search, Cancel);
-	    NonEmptyString ->
-	      wxWindow:destroy(Win),
-	      free_editor(State, "Content of PLT", NonEmptyString)
-	  end
-      end
-  end.
-
-format_search([]) ->
-  '_';
-format_search(String) ->
-  try list_to_integer(String)
-  catch error:_ -> list_to_atom(String)
-  end.
-
-show_doc_plt(#gui_state{doc_plt = DocPLT} = State) ->
-  case dialyzer_plt:get_specs(DocPLT) of
-    "" -> error_sms(State, "No analysis has been made yet!\n");
-    NonEmptyString -> free_editor(State, "Content of PLT", NonEmptyString)
-  end.
-
-message(State, Message) ->
-  output_sms(State, ?DIALYZER_MESSAGE_TITLE, Message, info).
-
-error_sms(State, Message) ->
-  output_sms(State, ?DIALYZER_ERROR_TITLE, Message, error).
-
-output_sms(#gui_state{frame = Frame}, Title, Message, Type) ->
-  Style = case Type of
-	    error -> ?wxOK bor ?wxICON_ERROR;
-	    info  -> ?wxOK bor ?wxICON_INFORMATION
-	  end,
-  Options = [{caption, Title}, {style, Style}],
-  MessageWin = wxMessageDialog:new(Frame, Message, Options),
-  wxWindow:setSizeHints(MessageWin, {350,100}),
-  wxDialog:showModal(MessageWin),
-  ok.
-
-free_editor(#gui_state{gui = Wx, frame = Frame}, Title, Contents0) ->
-  Contents = lists:flatten(Contents0),
-  Tokens = string:lexemes(Contents, "\n"),
-  NofLines = length(Tokens),
-  LongestLine = lists:max([length(X) || X <- Tokens]),
-  Height0 = NofLines * 25 + 80,
-  Height = if Height0 > 500 -> 500; true -> Height0 end,
-  Width0 = LongestLine * 7 + 60,
-  Width = if Width0 > 800 -> 800; true -> Width0 end,
-  Size = {size,{Width, Height}},
-  Win = wxFrame:new(Wx, ?Message, Title, [{size,{Width+4, Height+50}}]),
-
-  Editor = wxTextCtrl:new(Win, ?Message_Info,
-			  [Size,
-			   {style, ?wxTE_MULTILINE
-			    bor ?wxTE_READONLY bor ?wxVSCROLL bor ?wxEXPAND}]),
-  wxTextCtrl:appendText(Editor, Contents),
-  wxFrame:connect(Win, close_window),
-  Ok = wxButton:new(Win, ?Message_Ok, [{label, "OK"}]),
-  wxButton:connect(Ok, command_button_clicked),
-  Layout = wxBoxSizer:new(?wxVERTICAL),
-
-  _ = wxSizer:add(Layout, Editor, ?BorderOpt),
-  Flag = ?wxALIGN_CENTER bor ?wxBOTTOM bor ?wxALL,
-  _ = wxSizer:add(Layout, Ok, [{flag, Flag}, ?Border]),
-  wxWindow:setSizer(Win, Layout),
-  wxWindow:show(Win),
-  show_info_loop(Frame, Win).
-
-show_info_loop(Frame, Win) ->
-  receive
-    #wx{id = ?Message_Ok, event = #wxCommand{type = command_button_clicked}} ->
-      wxWindow:destroy(Win);
-    #wx{id = ?Message, event = #wxClose{type = close_window}} ->
-      wxWindow:destroy(Win);
-    #wx{event = #wxClose{type = close_window}} ->
-      wxWindow:destroy(Frame)
-  end.
-
-handle_add_files(#gui_state{chosen_box = ChosenBox, file_box = FileBox,
-			    files_to_analyze = FileList,
-			    mode = Mode} = State) ->
-  case wxFilePickerCtrl:getPath(FileBox) of
-    "" ->
-      State;
-    File ->
-      NewFile = ordsets:new(),
-      NewFile1 = ordsets:add_element(File,NewFile),
-      Ext =
-	case wxRadioBox:getSelection(Mode) of
-	  0 -> ".beam";
-	  1-> ".erl"
-	end,
-      State#gui_state{files_to_analyze = add_files(filter_mods(NewFile1, Ext), FileList, ChosenBox, Ext)}
-  end.
-
-handle_add_dir(#gui_state{chosen_box = ChosenBox, dir_entry = DirBox,
-			  files_to_analyze = FileList, mode = Mode} = State) ->
-  case wxDirPickerCtrl:getPath(DirBox) of
-    "" ->
-      State;
-    Dir ->
-      NewDir = ordsets:new(),
-      NewDir1 = ordsets:add_element(Dir,NewDir),
-      Ext = case wxRadioBox:getSelection(Mode) of
-	      0 -> ".beam";
-	      1-> ".erl"
-	    end,
-      State#gui_state{files_to_analyze = add_files(filter_mods(NewDir1,Ext), FileList, ChosenBox, Ext)}
-  end.
-
-handle_add_rec(#gui_state{chosen_box = ChosenBox, dir_entry = DirBox,
-			  files_to_analyze = FileList, mode = Mode} = State) ->
-  case wxDirPickerCtrl:getPath(DirBox) of
-    "" ->
-      State;
-    Dir ->
-      NewDir = ordsets:new(),
-      NewDir1 = ordsets:add_element(Dir,NewDir),
-      TargetDirs = ordsets:union(NewDir1, all_subdirs(NewDir1)),
-      Ext = case wxRadioBox:getSelection(Mode) of
-	      0 -> ".beam";
-	      1 -> ".erl"
-	    end,
-      State#gui_state{files_to_analyze = add_files(filter_mods(TargetDirs, Ext), FileList, ChosenBox, Ext)}
-  end.
-
-handle_file_delete(#gui_state{chosen_box = ChosenBox,
-			      files_to_analyze = FileList} = State) ->
-  {_, List} = wxListBox:getSelections(ChosenBox),
-  Set = ordsets:from_list([wxControlWithItems:getString(ChosenBox, X) || X <- List]),
-  FileList1 = ordsets:subtract(FileList,Set),
-  lists:foreach(fun (X) -> wxListBox:delete(ChosenBox, X) end, List),
-  State#gui_state{files_to_analyze = FileList1}.
-
-handle_file_delete_all(#gui_state{chosen_box = ChosenBox} = State) ->
-  wxListBox:clear(ChosenBox),
-  State#gui_state{files_to_analyze = ordsets:new()}.
-
-add_files(File, FileList, ChosenBox, Ext) ->
-  Set = filter_mods(FileList, Ext),
-  Files = ordsets:union(File, Set),
-  Files1 = ordsets:to_list(Files),
-  wxListBox:set(ChosenBox, Files1),
-  Files.
-
-filter_mods(Mods, Extension) ->
-  Fun = fun(X) ->
-	    filename:extension(X) =:= Extension
-	      orelse
-		(filelib:is_dir(X) andalso
-		 contains_files(X, Extension))
-	end,
-  ordsets:filter(Fun, Mods).
-
-contains_files(Dir, Extension) ->
-  {ok, Files} = file:list_dir(Dir),
-  lists:any(fun(X) -> filename:extension(X) =:= Extension end, Files).
-
-all_subdirs(Dirs) ->
-  all_subdirs(Dirs, []).
-
-all_subdirs([Dir|T], Acc) ->
-  {ok, Files} = file:list_dir(Dir),
-  SubDirs = lists:zf(fun(F) ->
-                       SubDir = filename:join(Dir, F),
-                       case filelib:is_dir(SubDir) of
-                         true -> {true, SubDir};
-                         false -> false
-                       end
-                   end, Files),
-  NewAcc = ordsets:union(ordsets:from_list(SubDirs), Acc),
-  all_subdirs(T ++ SubDirs, NewAcc);
-all_subdirs([], Acc) ->
-  Acc.
-
-start_analysis(State) ->
-  Analysis = build_analysis_record(State),
-  case get_anal_files(State, Analysis#analysis.start_from) of
-    error ->
-      Msg = "You must choose one or more files or dirs\n"
-	"before starting the analysis!",
-      error_sms(State, Msg),
-      config_gui_stop(State),
-      State;
-    {ok, Files} ->
-      Msg = "\n========== Starting Analysis ==========\n\n",
-      update_editor(State#gui_state.log, Msg),
-      NewAnalysis = Analysis#analysis{files = Files},
-      run_analysis(State, NewAnalysis)
-  end.
-
-build_analysis_record(#gui_state{mode = Mode, menu = Menu, options = Options,
-				 init_plt = InitPlt0}) ->
-  StartFrom =
-    case wxRadioBox:getSelection(Mode) of
-      0 -> byte_code;
-      1 -> src_code
-    end,
-  InitPlt =
-    case wxMenu:isChecked(Menu#menu.plt, ?menuID_PLT_INIT_EMPTY) of
-      true -> dialyzer_plt:new();
-      false -> InitPlt0
-    end,
-  #analysis{defines = Options#options.defines,
-	    include_dirs = Options#options.include_dirs,
-	    plt = InitPlt,
-	    start_from = StartFrom,
-	    solvers = Options#options.solvers}.
-
-get_anal_files(#gui_state{files_to_analyze = Files}, StartFrom) ->
-  FilteredMods =
-    case StartFrom of
-      src_code -> filter_mods(Files, ".erl");
-      byte_code -> filter_mods(Files, ".beam")
-    end,
-  FilteredDirs = [X || X <- Files, filelib:is_dir(X)],
-  case ordsets:union(FilteredMods, FilteredDirs) of
-    [] -> error;
-    Set -> {ok, Set}
-  end.
-
-run_analysis(State, Analysis) ->
-  config_gui_start(State),
-  Self = self(),
-  NewAnalysis = Analysis#analysis{doc_plt = dialyzer_plt:new()},
-  LegalWarnings = find_legal_warnings(State),
-  Fun =
-    fun() ->
-	dialyzer_analysis_callgraph:start(Self, LegalWarnings, NewAnalysis)
-    end,
-  BackendPid = spawn_link(Fun),
-  State#gui_state{backend_pid = BackendPid}.
-
-find_legal_warnings(#gui_state{menu = #menu{warnings = MenuWarnings},
-			       wantedWarnings = Warnings }) ->
-  ordsets:from_list([Tag || {Tag, MenuItem} <- Warnings,
-			    wxMenu:isChecked(MenuWarnings, MenuItem)]).
-
-update_editor(Editor, Msg) ->
-  wxTextCtrl:appendText(Editor,Msg).
-
-config_gui_stop(State) ->
-  wxWindow:disable(State#gui_state.stop),
-  wxWindow:enable(State#gui_state.run),
-  wxWindow:enable(State#gui_state.del_file),
-  wxWindow:enable(State#gui_state.clear_chosen),
-  wxWindow:enable(State#gui_state.add),
-  wxWindow:enable(State#gui_state.add_dir),
-  wxWindow:enable(State#gui_state.add_rec),
-  wxWindow:enable(State#gui_state.clear_warn),
-  wxWindow:enable(State#gui_state.clear_log),
-  Menu = State#gui_state.menu,
-  wxMenu:enable(Menu#menu.file,?menuID_FILE_SAVE_WARNINGS,true),
-  wxMenu:enable(Menu#menu.file,?menuID_FILE_SAVE_LOG,true),
-  wxMenu:enable(Menu#menu.options,?menuID_OPTIONS_MACRO,true),
-  wxMenu:enable(Menu#menu.options,?menuID_OPTIONS_INCLUDE_DIR,true),
-  wxMenu:enable(Menu#menu.plt,?menuID_PLT_INIT_EMPTY,true),
-  wxMenu:enable(Menu#menu.plt,?menuID_PLT_SHOW_CONTENTS,true),
-  wxMenu:enable(Menu#menu.plt,?menuID_PLT_SEARCH_CONTENTS,true),
-  wxRadioBox:enable(State#gui_state.mode).
-
-config_gui_start(State) ->
-  wxWindow:enable(State#gui_state.stop),
-  wxWindow:disable(State#gui_state.run),
-  wxWindow:disable(State#gui_state.del_file),
-  wxWindow:disable(State#gui_state.clear_chosen),
-  wxWindow:disable(State#gui_state.add),
-  wxWindow:disable(State#gui_state.add_dir),
-  wxWindow:disable(State#gui_state.add_rec),
-  wxWindow:disable(State#gui_state.clear_warn),
-  wxWindow:disable(State#gui_state.clear_log),
-  Menu = State#gui_state.menu,
-  wxMenu:enable(Menu#menu.file,?menuID_FILE_SAVE_WARNINGS, false),
-  wxMenu:enable(Menu#menu.file,?menuID_FILE_SAVE_LOG, false),
-  wxMenu:enable(Menu#menu.options,?menuID_OPTIONS_MACRO, false),
-  wxMenu:enable(Menu#menu.options,?menuID_OPTIONS_INCLUDE_DIR, false),
-  wxMenu:enable(Menu#menu.plt,?menuID_PLT_INIT_EMPTY, false),
-  wxMenu:enable(Menu#menu.plt,?menuID_PLT_SHOW_CONTENTS, false),
-  wxMenu:enable(Menu#menu.plt,?menuID_PLT_SEARCH_CONTENTS, false),
-  wxRadioBox:disable(State#gui_state.mode).
-
-save_file(#gui_state{frame = Frame, warnings_box = WBox, log = Log} = State, Type) ->
-  {Message, Box} = case Type of
-		     warnings -> {"Save Warnings", WBox};
-		     log -> {"Save Log", Log}
-		   end,
-  case wxTextCtrl:getValue(Box) of
-    "" -> error_sms(State,"There is nothing to save...\n");
-    _ ->
-      DefaultPath = code:root_dir(),
-      FileDialog = wxFileDialog:new(Frame,
-				    [{defaultDir, DefaultPath},
-				     {message, Message},
-				     {style,?wxFD_SAVE bor ?wxFD_OVERWRITE_PROMPT}]),
-      case wxFileDialog:showModal(FileDialog) of
-	?wxID_OK ->
-	  Path = wxFileDialog:getPath(FileDialog),
-	  case wxTextCtrl:saveFile(Box,[{file,Path}]) of
-	    true -> ok;
-	    false -> error_sms(State, "Could not write to file:\n" ++ Path)
-	  end;
-	?wxID_CANCEL -> wxWindow:destroy(FileDialog);
-	_ -> error_sms(State, "Could not write to file:\n")
-      end
-  end.
-
-include_dialog(#gui_state{gui = Wx, frame = Frame, options = Options}) ->
-  Size = {size,{300,480}},
-  Dialog = wxFrame:new(Wx, ?IncludeDir, "Include Directories",[Size]),
-  DirLabel = wxStaticText:new(Dialog, ?InclLabel, "Directory: "),
-  DefaultPath = code:root_dir(),
-  DirPicker = wxDirPickerCtrl:new(Dialog, ?InclPicker,
-				   [{path, DefaultPath},
-				    {message, "Choose Directory to Include"},
-				    {style,?wxDIRP_DIR_MUST_EXIST bor ?wxDIRP_USE_TEXTCTRL}]),
-  Box = wxListBox:new(Dialog, ?InclBox,
-			[{size, {200,300}},
-			 {style, ?wxLB_EXTENDED bor ?wxLB_HSCROLL
-			  bor ?wxLB_NEEDED_SB}]),
-  AddButton = wxButton:new(Dialog, ?InclAdd, [{label, "Add"}]),
-  DeleteButton = wxButton:new(Dialog, ?InclDel, [{label, "Delete"}]),
-  DeleteAllButton = wxButton:new(Dialog, ?InclDelAll, [{label, "Delete All"}]),
-  Ok = wxButton:new(Dialog, ?InclOk, [{label, "OK"}]),
-  Cancel = wxButton:new(Dialog, ?InclCancel, [{label, "Cancel"}]),
-  wxButton:connect(AddButton, command_button_clicked),
-  wxButton:connect(DeleteButton, command_button_clicked),
-  wxButton:connect(DeleteAllButton, command_button_clicked),
-  wxButton:connect(Ok, command_button_clicked),
-  wxButton:connect(Cancel, command_button_clicked),
-  Dirs = [io_lib:format("~ts", [X]) || X <- Options#options.include_dirs],
-  wxListBox:set(Box, Dirs),
-  Layout = wxBoxSizer:new(?wxVERTICAL),
-  Buttons = wxBoxSizer:new(?wxHORIZONTAL),
-  Buttons1 = wxBoxSizer:new(?wxHORIZONTAL),
-
-  _ = wxSizer:add(Layout, DirLabel, [{flag, ?wxALIGN_CENTER_HORIZONTAL}]),
-  _ = wxSizer:add(Layout, DirPicker, [{flag, ?wxALIGN_CENTER_HORIZONTAL}]),
-  _ = wxSizer:add(Layout,AddButton, [{flag, ?wxALIGN_CENTER_HORIZONTAL bor ?wxALL}, ?Border]),
-  _ = wxSizer:add(Layout,Box, [{flag, ?wxALIGN_CENTER_HORIZONTAL bor ?wxALL}, ?Border]),
-  _ = wxSizer:add(Buttons, DeleteButton, ?BorderOpt),
-  _ = wxSizer:add(Buttons, DeleteAllButton, ?BorderOpt),
-  _ = wxSizer:add(Layout,Buttons, [{flag, ?wxALIGN_CENTER_HORIZONTAL}]),
-  _ = wxSizer:add(Buttons1, Ok, ?BorderOpt),
-  _ = wxSizer:add(Buttons1,Cancel, ?BorderOpt),
-  _ = wxSizer:add(Layout,Buttons1,[{flag, ?wxALIGN_RIGHT bor ?wxBOTTOM}]),
-
-  wxFrame:connect(Dialog, close_window),
-  wxWindow:setSizer(Dialog, Layout),
-  wxFrame:show(Dialog),
-  include_loop(Options, Dialog, Box, DirPicker, Frame).
-
-include_loop(Options, Win, Box, DirPicker, Frame) ->
-  receive
-    #wx{id = ?InclCancel,
-	event = #wxCommand{type = command_button_clicked}} ->
-      wxWindow:destroy(Win),
-      Options;
-    #wx{id = ?IncludeDir, event = #wxClose{type = close_window}} ->
-      wxWindow:destroy(Win),
-      Options;
-    #wx{event = #wxClose{type = close_window}} ->
-      wxWindow:destroy(Win),
-      wxWindow:destroy(Frame);
-    #wx{id = ?InclOk,
-	event = #wxCommand{type = command_button_clicked}} ->
-     wxWindow:destroy(Win),
-     Options;
-    #wx{id = ?InclAdd,
-	event = #wxCommand{type = command_button_clicked}} ->
-      Dirs = Options#options.include_dirs,
-       NewDirs =
-	case wxDirPickerCtrl:getPath(DirPicker) of
-	  "" -> Dirs;
-	  Add -> [Add|Dirs]
-	end,
-      NewOptions = Options#options{include_dirs = NewDirs},
-      wxListBox:set(Box, NewDirs),
-      include_loop(NewOptions, Win, Box, DirPicker, Frame);
-     #wx{id = ?InclDel,
-	event = #wxCommand{type = command_button_clicked}} ->
-      NewOptions =
-	case wxListBox:getSelections(Box) of
-	  {0,_} -> Options;
-	  {_,List} ->
-	    DelList = [wxControlWithItems:getString(Box,X) || X <- List],
-	    NewDirs = Options#options.include_dirs -- DelList,
-	    lists:foreach(fun (X) -> wxListBox:delete(Box, X) end, List),
-	    Options#options{include_dirs = NewDirs}
-	end,
-      include_loop(NewOptions, Win, Box, DirPicker, Frame);
-    #wx{id = ?InclDelAll,
-	event = #wxCommand{type = command_button_clicked}} ->
-      wxListBox:clear(Box),
-      NewOptions = Options#options{include_dirs = []},
-      include_loop(NewOptions, Win, Box, DirPicker, Frame)
-  end.
-
-macro_dialog(#gui_state{gui = Wx, frame = Frame, options = Options}) ->
-  Size = {size,{300,480}},
-  Size1 = {size,{120,30}},
-  Dialog = wxFrame:new(Wx, ?MacroDir, "Macro Definitions",[Size]),
-  MacroLabel = wxStaticText:new(Dialog, ?MacroLabel, "Macro"),
-  TermLabel = wxStaticText:new(Dialog, ?TermLabel, "Term"),
-  MacroText = wxTextCtrl:new(Dialog, ?MacroText, [Size1]),
-  TermText = wxTextCtrl:new(Dialog, ?TermText, [Size1]),
-  Box = wxListBox:new(Dialog, ?MacroBox,
-			[{size, {250,300}},
-			 {style, ?wxLB_EXTENDED bor ?wxLB_HSCROLL
-			  bor ?wxLB_NEEDED_SB}]),
-
-  AddButton = wxButton:new(Dialog, ?MacroAdd, [{label, "Add"}]),
-  DeleteButton = wxButton:new(Dialog, ?MacroDel, [{label, "Delete"}]),
-  DeleteAllButton = wxButton:new(Dialog, ?MacroDelAll, [{label, "Delete All"}]),
-  Ok = wxButton:new(Dialog, ?MacroOk, [{label, "OK"}]),
-  Cancel = wxButton:new(Dialog, ?MacroCancel, [{label, "Cancel"}]),
-  wxButton:connect(AddButton, command_button_clicked),
-  wxButton:connect(DeleteButton, command_button_clicked),
-  wxButton:connect(DeleteAllButton, command_button_clicked),
-  wxButton:connect(Ok, command_button_clicked),
-  wxButton:connect(Cancel, command_button_clicked),
-
-  Macros = [io_lib:format("~p = ~p", [X, Y])
-	    || {X,Y} <- Options#options.defines],
-
-  wxListBox:set(Box, Macros),
-  Layout = wxBoxSizer:new(?wxVERTICAL),
-  Item = wxBoxSizer:new(?wxHORIZONTAL),
-  MacroItem = wxBoxSizer:new(?wxVERTICAL),
-  TermItem = wxBoxSizer:new(?wxVERTICAL),
-  Buttons = wxBoxSizer:new(?wxHORIZONTAL),
-  Buttons1 = wxBoxSizer:new(?wxHORIZONTAL),
-
-  _ = wxSizer:add(MacroItem, MacroLabel, ?BorderOpt),
-  _ = wxSizer:add(MacroItem, MacroText, ?BorderOpt),
-  _ = wxSizer:add(TermItem, TermLabel, ?BorderOpt),
-  _ = wxSizer:add(TermItem, TermText, ?BorderOpt),
-  _ = wxSizer:add(Item, MacroItem),
-  _ = wxSizer:add(Item, TermItem),
-  _ = wxSizer:add(Layout, Item, [{flag, ?wxALIGN_CENTER_HORIZONTAL}]),
-  _ = wxSizer:add(Layout, AddButton, [{flag, ?wxALIGN_CENTER_HORIZONTAL bor ?wxALL}, ?Border]),
-  _ = wxSizer:add(Layout, Box, [{flag, ?wxALIGN_CENTER_HORIZONTAL bor ?wxALL}, ?Border]),
-  _ = wxSizer:add(Buttons, DeleteButton, ?BorderOpt),
-  _ = wxSizer:add(Buttons, DeleteAllButton, ?BorderOpt),
-  _ = wxSizer:add(Layout, Buttons, [{flag, ?wxALIGN_CENTER_HORIZONTAL}]),
-  _ = wxSizer:add(Buttons1, Ok, ?BorderOpt),
-  _ = wxSizer:add(Buttons1, Cancel, ?BorderOpt),
-  _ = wxSizer:add(Layout, Buttons1, [{flag, ?wxALIGN_RIGHT bor ?wxBOTTOM}]),
-
-  wxFrame:connect(Dialog, close_window),
-  wxWindow:setSizer(Dialog, Layout),
-  wxFrame:show(Dialog),
-  macro_loop(Options, Dialog, Box, MacroText, TermText, Frame).
-
-macro_loop(Options, Win, Box, MacroText, TermText, Frame) ->
-  receive
-    #wx{id = ?MacroCancel,
-	event = #wxCommand{type = command_button_clicked}} ->
-      wxWindow:destroy(Win),
-      Options;
-    #wx{id = ?MacroDir, event = #wxClose{type = close_window}} ->
-      wxWindow:destroy(Win),
-      Options;
-    #wx{event = #wxClose{type = close_window}} ->
-      wxWindow:destroy(Win),
-      wxWindow:destroy(Frame);
-    #wx{id = ?MacroOk,
-	event = #wxCommand{type = command_button_clicked}} ->
-     wxWindow:destroy(Win),
-     Options;
-    #wx{id = ?MacroAdd,
-	event = #wxCommand{type = command_button_clicked}} ->
-      Defines = Options#options.defines,
-       NewDefines =
-	case wxTextCtrl:getValue(MacroText) of
-	  "" -> Defines;
-	  Macro ->
-	    case wxTextCtrl:getValue(TermText) of
-	      "" ->
-		orddict:store(list_to_atom(Macro), true, Defines);
-	      String ->
-		orddict:store(list_to_atom(Macro), String, Defines)
-	    end
-	end,
-      NewOptions = Options#options{defines = NewDefines},
-      NewEntries = [io_lib:format("~p = ~p", [X, Y]) || {X, Y} <- NewDefines],
-      wxListBox:set(Box, NewEntries),
-      macro_loop(NewOptions, Win, Box, MacroText, TermText, Frame);
-     #wx{id = ?MacroDel,
-	event = #wxCommand{type = command_button_clicked}} ->
-      NewOptions =
-	case wxListBox:getSelections(Box) of
-	  {0, _} -> Options;
-	  {_, List} ->
-	    Fun =
-	      fun(X) ->
-		  Val = wxControlWithItems:getString(Box,X),
-		  [MacroName|_] = re:split(Val, " ", [{return, list}, unicode]),
-		  list_to_atom(MacroName)
-	      end,
-	    Delete = [Fun(X) || X <- List],
-	    lists:foreach(fun (X) -> wxListBox:delete(Box, X) end, List),
-	    Defines = Options#options.defines,
-	    NewDefines = lists:foldl(fun(X, Acc) ->
-					 orddict:erase(X, Acc)
-				     end,
-				     Defines, Delete),
-	    Options#options{defines = NewDefines}
-	end,
-      macro_loop(NewOptions, Win, Box, MacroText, TermText, Frame);
-    #wx{id = ?MacroDelAll,
-	event = #wxCommand{type = command_button_clicked}} ->
-      wxListBox:clear(Box),
-      NewOptions = Options#options{defines = []},
-      macro_loop(NewOptions, Win, Box,  MacroText, TermText, Frame)
-  end.
-
-handle_help(State, Title, Txt) ->
-  FileName = filename:join([code:lib_dir(dialyzer), "doc", Txt]),
-  case file:open(FileName, [read]) of
-    {error, Reason} ->
-      error_sms(State,
-		io_lib:format("Could not find doc/~ts file!\n\n ~tp",
-			      [Txt, Reason]));
-    {ok, _Handle} ->
-      case file:read_file(FileName) of
-	{error, Reason} ->
-	  error_sms(State,
-		    io_lib:format("Could not read doc/~ts file!\n\n ~tp",
-				  [Txt, Reason]));
-	{ok, Binary} ->
-	  Contents = binary_to_list(Binary),
-	  free_editor(State, Title, Contents)
-      end
-  end.
-
-add_warnings(#gui_state{warnings_box = WarnBox,
-			rawWarnings = RawWarns} = State, Warnings) ->
-  NewRawWarns = RawWarns ++ Warnings,
-  %% The indentation cannot be turned off.
-  %% The column numbers of locations are always displayed.
-  WarnList = [string:trim(dialyzer:format_warning(W), trailing) ||
-               W <- NewRawWarns],
-  wxListBox:set(WarnBox, WarnList),
-  State#gui_state{rawWarnings = NewRawWarns}.
-
-handle_explanation(#gui_state{rawWarnings = RawWarns,
-			      warnings_box = WarnBox,
-			      expl_pid = ExplPid} = State) ->
-  case wxListBox:isEmpty(WarnBox) of
-    true ->
-      error_sms(State, "\nThere are no warnings.\nRun the dialyzer first.");
-    false ->
-      case wxListBox:getSelections(WarnBox)of
-	{0, []} ->
-	  error_sms(State,"\nYou must choose a warning to be explained\n");
-	{_, [WarnNumber]} ->
-	  Warn = lists:nth(WarnNumber+1,RawWarns),
-	  Self = self(),
-	  ExplPid ! {Self, warning, Warn},
-	  explanation_loop(State)
-      end
-  end.
-
-explanation_loop(#gui_state{expl_pid = ExplPid} = State) ->
-  receive
-    {ExplPid, explanation, Explanation} ->
-      show_explanation(State, Explanation);
-    _ -> io:format("Unknown message\n"),
-	 explanation_loop(State)
-  end.
-
-show_explanation(#gui_state{gui = Wx} = State, Explanation) ->
-  case Explanation of
-    none ->
-      output_sms(State, ?DIALYZER_MESSAGE_TITLE,
-		 "There is not any explanation for this error!\n", info);
-    Expl ->
-      ExplString = format_explanation(Expl),
-      Size = {size,{700, 300}},
-      Win = wxFrame:new(Wx, ?ExplWin, "Dialyzer Explanation", [{size,{740, 350}}]),
-
-      Editor = wxTextCtrl:new(Win, ?ExplText,
-			      [Size,
-			       {style, ?wxTE_MULTILINE
-				bor ?wxTE_READONLY bor ?wxVSCROLL bor ?wxEXPAND}]),
-      wxTextCtrl:appendText(Editor, ExplString),
-      wxFrame:connect(Win, close_window),
-      ExplButton = wxButton:new(Win, ?ExplButton, [{label, "Further Explain"}]),
-      wxButton:connect(ExplButton, command_button_clicked),
-      Ok = wxButton:new(Win, ?ExplOk, [{label, "OK"}]),
-      wxButton:connect(Ok, command_button_clicked),
-      Layout = wxBoxSizer:new(?wxVERTICAL),
-      Buttons = wxBoxSizer:new(?wxHORIZONTAL),
-      _ = wxSizer:add(Buttons, ExplButton, ?BorderOpt),
-      _ = wxSizer:add(Buttons, Ok, ?BorderOpt),
-      _ = wxSizer:add(Layout, Editor, [{flag, ?wxALIGN_CENTER_HORIZONTAL bor ?wxALL}, ?Border]),
-      _ = wxSizer:add(Layout, Buttons,[{flag, ?wxALIGN_CENTER_HORIZONTAL}]),
-      wxWindow:setSizer(Win, Layout),
-      wxWindow:show(Win),
-      NewState = State#gui_state{explanation_box = Editor},
-      show_explanation_loop(NewState, Win, Explanation)
-  end.
-
-show_explanation_loop(#gui_state{frame = Frame, expl_pid = ExplPid} = State, Win, Explanation) ->
-  receive
-    {ExplPid, none, _} ->
-      output_sms(State, ?DIALYZER_MESSAGE_TITLE,
-		       "There is not any other explanation for this error!\n", info),
-      show_explanation_loop(State, Win,  Explanation);
-    {ExplPid, further, NewExplanation} ->
-      update_explanation(State, NewExplanation),
-      show_explanation_loop(State, Win,  NewExplanation);
-    #wx{id = ?ExplButton, event = #wxCommand{type = command_button_clicked}} ->
-      ExplPid ! {self(), further, Explanation},
-      show_explanation_loop(State, Win, Explanation);
-    #wx{id = ?ExplOk, event = #wxCommand{type = command_button_clicked}} ->
-      wxWindow:destroy(Win);
-    #wx{id = ?ExplWin, event = #wxClose{type = close_window}} ->
-       wxWindow:destroy(Win);
-    #wx{event = #wxClose{type = close_window}} ->
-      wxWindow:destroy(Frame)
-  end.
-
-update_explanation(#gui_state{explanation_box = Box}, Explanation) ->
-  ExplString = format_explanation(Explanation),
-  wxTextCtrl:appendText(Box, "\n --------------------------- \n"),
-  wxTextCtrl:appendText(Box, ExplString).
-
-format_explanation({function_return, {M, F, A}, NewList}) ->
-  io_lib:format("The function ~w:~tw/~w returns ~ts\n",
-		[M, F, A, erl_types:t_to_string(NewList)]);
-format_explanation(Explanation) ->
-  io_lib:format("~p\n", [Explanation]).
diff --git a/lib/dialyzer/src/dialyzer_gui_wx.hrl b/lib/dialyzer/src/dialyzer_gui_wx.hrl
deleted file mode 100644
index 0a6ca9e8b2..0000000000
--- a/lib/dialyzer/src/dialyzer_gui_wx.hrl
+++ /dev/null
@@ -1,123 +0,0 @@
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-
--include_lib("wx/include/wx.hrl").
-
-
--define(TEXTSIZE, 9).
-
--define(Border, {border, 2}).
--define(BorderOpt,[{flag,?wxALL}, ?Border]).
-
--define(menuID_FILE_QUIT, 102).
--define(menuID_FILE_SAVE_WARNINGS, 100).
--define(menuID_FILE_SAVE_LOG, 101).
-
--define(menuID_WARN_MATCH_FAILURES, 200).
--define(menuID_WARN_FAIL_FUN_CALLS, 201).
--define(menuID_WARN_BAD_FUN, 202).
--define(menuID_WARN_OPAQUE, 203).
--define(menuID_WARN_LIST_CONSTR, 204).
--define(menuID_WARN_UNUSED_FUN, 205).
--define(menuID_WARN_ERROR_HANDLING_FUN, 206).
--define(menuID_WARN_NO_RETURN_FUN, 207).
--define(menuID_WARN_UNEXPORTED_FUN, 208).
--define(menuID_WARN_WRONG_CONTRACTS, 209).
--define(menuID_WARN_CONTRACT_SYNTAX, 210).
-
--define(menuID_PLT_INIT_EMPTY, 300).
--define(menuID_PLT_SHOW_CONTENTS, 301).
--define(menuID_PLT_SEARCH_CONTENTS, 302).
-
--define(menuID_OPTIONS_MACRO, 400).
--define(menuID_OPTIONS_INCLUDE_DIR, 401).
-
--define(menuID_HELP_MANUAL, 500).
--define(menuID_HELP_WARNING_OPTIONS, 501).
--define(menuID_HELP_ABOUT, 499).
-
--define(LABEL1,502).
--define(LABEL2,503).
--define(LABEL3,504).
--define(LABEL4,505).
--define(LABEL5,505).
--define(LABEL6,506).
--define(LABEL7,507).
--define(LABEL8,508).
--define(LABEL9,509).
-
--define(ChosenBox,510).
--define(LogBox,511).
--define(FilePicker,512).
--define(DirPicker,513).
--define(WarningsBox,521).
-
--define(Del_Button,514).
--define(DelAll_Button,515).
--define(ClearLog_Button,516).
--define(Add_Button,517).
--define(AddDir_Button,532).
--define(AddRec_Button,518).
--define(ClearWarn_Button,519).
--define(Run_Button,520).
--define(Stop_Button,522).
--define(ExplWarn_Button,523).
--define(RADIOBOX, 524).
-
--define(Dialog, 525).
--define(Dialog_Ok, 526).
--define(Dialog_Cancel, 527).
--define(Dialog_Mes, 528).
-
--define(MESSAGE, 529).
--define(Message_Info, 530).
--define(Message_Ok, 531).
-
-
--define(Message, 534).
--define(SaveWarn, 533).
--define(SearchPltDialog, 535).
--define(ModLabel, 536).
--define(FunLabel, 537).
--define(ArLabel, 538).
--define(ModText, 539).
--define(FunText, 540).
--define(ArText, 541).
--define(SearchButton, 542).
--define(Search_Cancel, 543).
-
--define(IncludeDir, 544).
--define(InclLabel, 545).
--define(InclPicker, 546).
--define(InclBox, 547).
--define(InclAdd, 548).
--define(InclDel, 549).
--define(InclDelAll, 550).
--define(InclOk, 551).
--define(InclCancel, 552).
-
--define(MacroDir, 553).
--define(MacroLabel, 554).
--define(MacroText, 555).
--define(TermLabel, 556).
--define(TermText, 557).
--define(MacroBox, 558).
--define(MacroAdd, 559).
--define(MacroDel, 560).
--define(MacroDelAll, 561).
--define(MacroOk, 562).
--define(MacroCancel, 563).
-
--define(ExplWin, 564).
--define(ExplText, 565).
--define(ExplButton, 566).
--define(ExplOk, 567).
diff --git a/lib/dialyzer/src/dialyzer_plt.erl b/lib/dialyzer/src/dialyzer_plt.erl
index 203eafc3c2..5f75dc4146 100644
--- a/lib/dialyzer/src/dialyzer_plt.erl
+++ b/lib/dialyzer/src/dialyzer_plt.erl
@@ -41,8 +41,6 @@
 	 lookup_module/2,
          merge_plts/1,
 	 new/0,
-	 get_specs/1,
-	 get_specs/4,
          delete/1,
          get_all_types/1,
          get_all_contracts/1,
@@ -237,51 +235,6 @@ delete(#plt{info = ETSInfo,
   true = ets:delete(ETSExpTypes),
   ok.
 
-%%---------------------------------------------------------------------------
-%% Edoc
-
--spec get_specs(plt()) -> string().
-
-get_specs(#plt{info = Info}) ->
-  %% TODO: Should print contracts as well.
-  L = lists:sort([{MFA, Val} ||
-                   {{_,_,_} = MFA, Val} <- table_to_list(Info)]),
-  lists:flatten(create_specs(L, [])).
-
--spec get_specs(plt(), atom(), atom(), arity_patt()) -> 'none' | string().
-
-get_specs(#plt{info = Info}, M, F, A) when is_atom(M), is_atom(F) ->
-  MFA = {M, F, A},
-  case ets_table_lookup(Info, MFA) of
-    none -> none;
-    {value, Val} -> lists:flatten(create_specs([{MFA, Val}], []))
-  end.
-
-create_specs([{{M, F, _A}, {Ret, Args}}|Left], M) ->
-  [io_lib:format("-spec ~tw(~ts) -> ~ts\n",
-		 [F, expand_args(Args), erl_types:t_to_string(Ret)])
-   | create_specs(Left, M)];
-create_specs(List = [{{M, _F, _A}, {_Ret, _Args}}| _], _M) ->
-  [io_lib:format("\n\n%% ------- Module: ~w -------\n\n", [M])
-   | create_specs(List, M)];
-create_specs([], _) ->
-  [].
-
-expand_args([]) ->
-  [];
-expand_args([ArgType]) ->
-  case erl_types:t_is_any(ArgType) of
-    true -> ["_"];
-    false -> [erl_types:t_to_string(ArgType)]
-  end;
-expand_args([ArgType|Left]) ->
-  [case erl_types:t_is_any(ArgType) of
-     true -> "_";
-     false -> erl_types:t_to_string(ArgType)
-   end ++
-   ","|expand_args(Left)].
-
-
 %%---------------------------------------------------------------------------
 %% Ets table
 
-- 
2.35.3

openSUSE Build Service is sponsored by