From e68c8280fa2e1b7071378cfdd876155c73ec944f Mon Sep 17 00:00:00 2001
From: Andrew MacLeod <amacleod@redhat.com>
Date: Fri, 30 Jul 2021 15:15:29 -0400
Subject: [PATCH] Abstract tracing routines into a class.

Generalize range tracing into a class and integrae it with gimple_ranger.
Remove the old derived trace_ranger class.

	* Makefile.in (OBJS): Add gimple-range-trace.o.
	* gimple-range-cache.h (enable_new_values): Remove unused prototype.
	* gimple-range-fold.cc: Adjust headers.
	* gimple-range-trace.cc: New.
	* gimple-range-trace.h: New.
	* gimple-range.cc (gimple_ranger::gimple_ranger): Enable tracer.
	(gimple_ranger::range_of_expr): Add tracing.
	(gimple_ranger::range_on_entry): Ditto.
	(gimple_ranger::range_on_exit): Ditto.
	(gimple_ranger::range_on_edge): Ditto.
	(gimple_ranger::fold_range_internal): Ditto.
	(gimple_ranger::dump_bb): Do not calculate edge range twice.
	(trace_ranger::*): Remove.
	(enable_ranger): Never create a trace_ranger.
	(debug_seed_ranger): Move to gimple-range-trace.cc.
	(dump_ranger): Ditto.
	(debug_ranger): Ditto.
	* gimple-range.h: Include gimple-range-trace.h.
	(range_on_entry, range_on_exit): No longer virtual.
	(class trace_ranger): Remove.
	(DEBUG_RANGE_CACHE): Move to gimple-range-trace.h.
---
 gcc/Makefile.in           |   1 +
 gcc/gimple-range-cache.h  |   1 -
 gcc/gimple-range-fold.cc  |   4 +-
 gcc/gimple-range-trace.cc | 206 ++++++++++++++++++++
 gcc/gimple-range-trace.h  |  64 +++++++
 gcc/gimple-range.cc       | 393 ++++++++++----------------------------
 gcc/gimple-range.h        |  34 +---
 7 files changed, 377 insertions(+), 326 deletions(-)
 create mode 100644 gcc/gimple-range-trace.cc
 create mode 100644 gcc/gimple-range-trace.h

diff --git a/gcc/Makefile.in b/gcc/Makefile.in
index 6653e9e21427..9714fcaac37f 100644
--- a/gcc/Makefile.in
+++ b/gcc/Makefile.in
@@ -1406,6 +1406,7 @@ OBJS = \
 	gimple-range-edge.o \
 	gimple-range-fold.o \
 	gimple-range-gori.o \
+	gimple-range-trace.o \
 	gimple-ssa-backprop.o \
 	gimple-ssa-evrp.o \
 	gimple-ssa-evrp-analyze.o \
diff --git a/gcc/gimple-range-cache.h b/gcc/gimple-range-cache.h
index 1e77c9bf3a93..3b55673fd29a 100644
--- a/gcc/gimple-range-cache.h
+++ b/gcc/gimple-range-cache.h
@@ -103,7 +103,6 @@ public:
   bool get_non_stale_global_range (irange &r, tree name);
   void set_global_range (tree name, const irange &r);
 
-  bool enable_new_values (bool state);
   non_null_ref m_non_null;
   gori_compute m_gori;
 
diff --git a/gcc/gimple-range-fold.cc b/gcc/gimple-range-fold.cc
index d3e3e14ff64f..94dd042721e7 100644
--- a/gcc/gimple-range-fold.cc
+++ b/gcc/gimple-range-fold.cc
@@ -42,9 +42,7 @@ along with GCC; see the file COPYING3.  If not see
 #include "range.h"
 #include "value-query.h"
 #include "range-op.h"
-#include "gimple-range-fold.h"
-#include "gimple-range-edge.h"
-#include "gimple-range-gori.h"
+#include "gimple-range.h"
 // Construct a fur_source, and set the m_query field.
 
 fur_source::fur_source (range_query *q)
diff --git a/gcc/gimple-range-trace.cc b/gcc/gimple-range-trace.cc
new file mode 100644
index 000000000000..1feb978e9284
--- /dev/null
+++ b/gcc/gimple-range-trace.cc
@@ -0,0 +1,206 @@
+/* Code for GIMPLE range trace and debugging related routines.
+   Copyright (C) 2019-2021 Free Software Foundation, Inc.
+   Contributed by Andrew MacLeod <amacleod@redhat.com>
+   and Aldy Hernandez <aldyh@redhat.com>.
+
+This file is part of GCC.
+
+GCC is free software; you can redistribute it and/or modify
+it under the terms of the GNU General Public License as published by
+the Free Software Foundation; either version 3, or (at your option)
+any later version.
+
+GCC is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+GNU General Public License for more details.
+
+You should have received a copy of the GNU General Public License
+along with GCC; see the file COPYING3.  If not see
+<http://www.gnu.org/licenses/>.  */
+
+#include "config.h"
+#include "system.h"
+#include "coretypes.h"
+#include "backend.h"
+#include "tree.h"
+#include "gimple.h"
+#include "ssa.h"
+#include "gimple-pretty-print.h"
+#include "gimple-iterator.h"
+#include "tree-cfg.h"
+#include "fold-const.h"
+#include "tree-cfg.h"
+#include "cfgloop.h"
+#include "tree-scalar-evolution.h"
+#include "gimple-range.h"
+
+
+// Breakpoint to trap at a specific index.  From GDB, this provides a simple
+// place to put a breakpoint to stop at a given trace line.
+// ie.  b range_tracer::breakpoint if index == 45678
+
+void
+range_tracer::breakpoint (unsigned index ATTRIBUTE_UNUSED)
+{
+}
+
+// Construct a range_tracer with component NAME.
+
+range_tracer::range_tracer (const char *name)
+{
+  gcc_checking_assert (strlen(name) < name_len -1);
+  strcpy (component, name);
+  indent = 0;
+  tracing = false;
+}
+
+// This routine does the initial line spacing/indenting for a trace.
+// If BLANKS is false, then IDX is printed, otherwise spaces.
+
+void
+range_tracer::print_prefix (unsigned idx, bool blanks)
+{
+  // Print counter index as well as INDENT spaces.
+  if (!blanks)
+    fprintf (dump_file, "%-7u ", idx);
+  else
+    fprintf (dump_file, "        ");
+  fprintf (dump_file, "%s ", component);
+  unsigned x;
+  for (x = 0; x< indent; x++)
+    fputc (' ', dump_file);
+
+}
+// If dumping, return the next call index and print the prefix for the next
+// output line.  If not, retrurn 0.
+// Counter is static to monotonically increase across the compilation unit.
+
+unsigned
+range_tracer::do_header (const char *str)
+{
+  static unsigned trace_count = 0;
+
+  unsigned idx = ++trace_count;
+  print_prefix (idx, false);
+  fprintf (dump_file, "%s", str);
+  indent += bump;
+  breakpoint (idx);
+  return idx;
+}
+
+// Print a line without starting or ending a trace.
+
+void
+range_tracer::print (unsigned counter, const char *str)
+{
+  print_prefix (counter, true);
+  fprintf (dump_file, "%s", str);
+}
+
+// End a trace and print the CALLER, NAME, and RESULT and range R,
+
+void
+range_tracer::trailer (unsigned counter, const char *caller, bool result,
+		      tree name, const irange &r)
+{
+  gcc_checking_assert (tracing && counter != 0);
+
+  indent -= bump;
+  print_prefix (counter, true);
+  fputs(result ? "TRUE : " : "FALSE : ", dump_file);
+  fprintf (dump_file, "(%u) ", counter);
+  fputs (caller, dump_file);
+  fputs (" (",dump_file);
+  if (name)
+    print_generic_expr (dump_file, name, TDF_SLIM);
+  fputs (") ",dump_file);
+  if (result)
+    {
+      r.dump (dump_file);
+      fputc('\n', dump_file);
+    }
+  else
+    fputc('\n', dump_file);
+}
+
+// =========================================
+// Debugging helpers.
+// =========================================
+
+// Query all statements in the IL to precalculate computable ranges in RANGER.
+
+static DEBUG_FUNCTION void
+debug_seed_ranger (gimple_ranger &ranger)
+{
+  // Recalculate SCEV to make sure the dump lists everything.
+  if (scev_initialized_p ())
+    {
+      scev_finalize ();
+      scev_initialize ();
+    }
+
+  basic_block bb;
+  int_range_max r;
+  gimple_stmt_iterator gsi;
+  FOR_EACH_BB_FN (bb, cfun)
+    for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
+      {
+	gimple *stmt = gsi_stmt (gsi);
+
+	if (is_gimple_debug (stmt))
+	  continue;
+
+	ranger.range_of_stmt (r, stmt);
+      }
+}
+
+// Dump all that ranger knows for the current function.
+
+DEBUG_FUNCTION void
+dump_ranger (FILE *out)
+{
+  gimple_ranger ranger;
+  debug_seed_ranger (ranger);
+  ranger.dump (out);
+}
+
+DEBUG_FUNCTION void
+debug_ranger ()
+{
+  dump_ranger (stderr);
+}
+
+// Dump all that ranger knows on a path of BBs.
+//
+// Note that the blocks are in reverse order, thus the exit block is
+// path[0].
+
+DEBUG_FUNCTION void
+dump_ranger (FILE *dump_file, const vec<basic_block> &path)
+{
+  if (path.length () == 0)
+    {
+      fprintf (dump_file, "empty\n");
+      return;
+    }
+
+  gimple_ranger ranger;
+  debug_seed_ranger (ranger);
+
+  unsigned i = path.length ();
+  do
+    {
+      i--;
+      ranger.dump_bb (dump_file, path[i]);
+    }
+  while (i > 0);
+}
+
+DEBUG_FUNCTION void
+debug_ranger (const vec<basic_block> &path)
+{
+  dump_ranger (stderr, path);
+}
+
+#include "gimple-range-tests.cc"
diff --git a/gcc/gimple-range-trace.h b/gcc/gimple-range-trace.h
new file mode 100644
index 000000000000..6f89fcccf4fa
--- /dev/null
+++ b/gcc/gimple-range-trace.h
@@ -0,0 +1,64 @@
+/* Header file for the GIMPLE range tracing/debugging facilties.
+   Copyright (C) 2021 Free Software Foundation, Inc.
+   Contributed by Andrew MacLeod <amacleod@redhat.com>
+   and Aldy Hernandez <aldyh@redhat.com>.
+
+This file is part of GCC.
+
+GCC is free software; you can redistribute it and/or modify it under
+the terms of the GNU General Public License as published by the Free
+Software Foundation; either version 3, or (at your option) any later
+version.
+
+GCC is distributed in the hope that it will be useful, but WITHOUT ANY
+WARRANTY; without even the implied warranty of MERCHANTABILITY or
+FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+ for more details.
+
+You should have received a copy of the GNU General Public License
+along with GCC; see the file COPYING3.  If not see
+<http://www.gnu.org/licenses/>.  */
+
+#ifndef GCC_GIMPLE_RANGE_TRACE_H
+#define GCC_GIMPLE_RANGE_TRACE_H
+
+// This class manages range tracing for the ranger and gori components.
+// Tracing will provide a unique integer index whenever a new trace
+// is started. This can be used to identify where a calculation has gone wrong.
+
+class range_tracer
+{
+public:
+  range_tracer (const char *name = "");
+  unsigned header (const char *str);
+  void trailer (unsigned counter, const char *caller, bool result, tree name,
+		const irange &r);
+  void print (unsigned counter, const char *str);
+  inline void enable_trace () { tracing = true; }
+  inline void disable_trace () { tracing = false; }
+  virtual void breakpoint (unsigned index);
+private:
+  unsigned do_header (const char *str);
+  void print_prefix (unsigned idx, bool blanks);
+  static const unsigned bump = 2;
+  unsigned indent;
+  static const unsigned name_len = 100;
+  char component[name_len];
+  bool tracing;
+};
+
+
+// If tracing is enabled, start a new trace header, returning the trace index.
+// Otherwise return 0.
+
+inline unsigned
+range_tracer::header (const char *str)
+{
+  if (tracing)
+    return do_header (str);
+  return 0;
+}
+
+#define DEBUG_RANGE_CACHE (dump_file && (param_evrp_mode & EVRP_MODE_DEBUG))
+
+#endif // GCC_GIMPLE_RANGE_TRACE_H
diff --git a/gcc/gimple-range.cc b/gcc/gimple-range.cc
index b210787d0b7b..60b7d3a59cd7 100644
--- a/gcc/gimple-range.cc
+++ b/gcc/gimple-range.cc
@@ -35,46 +35,61 @@ along with GCC; see the file COPYING3.  If not see
 #include "tree-scalar-evolution.h"
 #include "gimple-range.h"
 
-gimple_ranger::gimple_ranger ()
+gimple_ranger::gimple_ranger () : tracer ("")
 {
   // If the cache has a relation oracle, use it.
   m_oracle = m_cache.oracle ();
+  if (dump_file && (param_evrp_mode & EVRP_MODE_TRACE))
+    tracer.enable_trace ();
 }
 
 bool
 gimple_ranger::range_of_expr (irange &r, tree expr, gimple *stmt)
 {
+  unsigned idx;
   if (!gimple_range_ssa_p (expr))
     return get_tree_range (r, expr, stmt);
 
+  if ((idx = tracer.header ("range_of_expr(")))
+    {
+      print_generic_expr (dump_file, expr, TDF_SLIM);
+      fputs (")", dump_file);
+      if (stmt)
+	{
+	  fputs (" at stmt ", dump_file);
+	  print_gimple_stmt (dump_file, stmt, 0, TDF_SLIM);
+	}
+      else
+	fputs ("\n", dump_file);
+    }
+
   // If there is no statement, just get the global value.
   if (!stmt)
     {
       if (!m_cache.get_global_range (r, expr))
         r = gimple_range_global (expr);
-      return true;
     }
-
   // For a debug stmt, pick the best value currently available, do not
   // trigger new value calculations.  PR 100781.
-  if (is_gimple_debug (stmt))
+  else if (is_gimple_debug (stmt))
+    m_cache.range_of_expr (r, expr, stmt);
+  else
     {
-      m_cache.range_of_expr (r, expr, stmt);
-      return true;
-    }
-  basic_block bb = gimple_bb (stmt);
-  gimple *def_stmt = SSA_NAME_DEF_STMT (expr);
+      basic_block bb = gimple_bb (stmt);
+      gimple *def_stmt = SSA_NAME_DEF_STMT (expr);
 
-  // If name is defined in this block, try to get an range from S.
-  if (def_stmt && gimple_bb (def_stmt) == bb)
-    {
-      range_of_stmt (r, def_stmt, expr);
-      m_cache.m_non_null.adjust_range (r, expr, bb, true);
+      // If name is defined in this block, try to get an range from S.
+      if (def_stmt && gimple_bb (def_stmt) == bb)
+	{
+	  range_of_stmt (r, def_stmt, expr);
+	  m_cache.m_non_null.adjust_range (r, expr, bb, true);
+	}
+      // Otherwise OP comes from outside this block, use range on entry.
+      else
+	range_on_entry (r, bb, expr);
     }
-  else
-    // Otherwise OP comes from outside this block, use range on entry.
-    range_on_entry (r, bb, expr);
-
+  if (idx)
+    tracer.trailer (idx, "range_of_expr", true, expr, r);
   return true;
 }
 
@@ -86,6 +101,13 @@ gimple_ranger::range_on_entry (irange &r, basic_block bb, tree name)
   int_range_max entry_range;
   gcc_checking_assert (gimple_range_ssa_p (name));
 
+  unsigned idx;
+  if ((idx = tracer.header ("range_on_entry (")))
+    {
+      print_generic_expr (dump_file, name, TDF_SLIM);
+      fprintf (dump_file, ") to BB %d\n", bb->index);
+    }
+
   // Start with any known range
   range_of_stmt (r, SSA_NAME_DEF_STMT (name), name);
 
@@ -94,6 +116,9 @@ gimple_ranger::range_on_entry (irange &r, basic_block bb, tree name)
     r.intersect (entry_range);
 
   m_cache.m_non_null.adjust_range (r, name, bb, true);
+
+  if (idx)
+    tracer.trailer (idx, "range_on_entry", true, name, r);
 }
 
 // Calculate the range for NAME at the end of block BB and return it in R.
@@ -106,6 +131,13 @@ gimple_ranger::range_on_exit (irange &r, basic_block bb, tree name)
   gcc_checking_assert (bb != EXIT_BLOCK_PTR_FOR_FN (cfun));
   gcc_checking_assert (gimple_range_ssa_p (name));
 
+  unsigned idx;
+  if ((idx = tracer.header ("range_on_exit (")))
+    {
+      print_generic_expr (dump_file, name, TDF_SLIM);
+      fprintf (dump_file, ") from BB %d\n", bb->index);
+    }
+
   gimple *s = SSA_NAME_DEF_STMT (name);
   basic_block def_bb = gimple_bb (s);
   // If this is not the definition block, get the range on the last stmt in
@@ -119,6 +151,9 @@ gimple_ranger::range_on_exit (irange &r, basic_block bb, tree name)
     range_on_entry (r, bb, name);
   gcc_checking_assert (r.undefined_p ()
 		       || range_compatible_p (r.type (), TREE_TYPE (name)));
+  
+  if (idx)
+    tracer.trailer (idx, "range_on_exit", true, name, r);
 }
 
 // Calculate a range for NAME on edge E and return it in R.
@@ -133,6 +168,13 @@ gimple_ranger::range_on_edge (irange &r, edge e, tree name)
   if (!gimple_range_ssa_p (name))
     return range_of_expr (r, name);
 
+  unsigned idx;
+  if ((idx = tracer.header ("range_on_edge (")))
+    {
+      print_generic_expr (dump_file, name, TDF_SLIM);
+      fprintf (dump_file, ") on edge %d->%d\n", e->src->index, e->dest->index);
+    }
+
   range_on_exit (r, e->src, name);
   gcc_checking_assert  (r.undefined_p ()
 			|| range_compatible_p (r.type(), TREE_TYPE (name)));
@@ -141,6 +183,8 @@ gimple_ranger::range_on_edge (irange &r, edge e, tree name)
   if (m_cache.range_on_edge (edge_range, e, name))
     r.intersect (edge_range);
 
+  if (idx)
+    tracer.trailer (idx, "range_on_edge", true, name, r);
   return true;
 }
 
@@ -163,33 +207,50 @@ gimple_ranger::fold_range_internal (irange &r, gimple *s, tree name)
 bool
 gimple_ranger::range_of_stmt (irange &r, gimple *s, tree name)
 {
+  bool res;
   r.set_undefined ();
 
+  unsigned idx;
+  if ((idx = tracer.header ("range_of_stmt (")))
+    {
+      if (name)
+	print_generic_expr (dump_file, name, TDF_SLIM);
+      fputs (") at stmt ", dump_file);
+      print_gimple_stmt (dump_file, s, 0, TDF_SLIM);
+    }
+
   if (!name)
     name = gimple_get_lhs (s);
 
   // If no name, simply call the base routine.
   if (!name)
-    return fold_range_internal (r, s, NULL_TREE);
-
-  if (!gimple_range_ssa_p (name))
-    return false;
-
+    res = fold_range_internal (r, s, NULL_TREE);
+  else if (!gimple_range_ssa_p (name))
+    res = false;
   // Check if the stmt has already been processed, and is not stale.
-  if (m_cache.get_non_stale_global_range (r, name))
-    return true;
-
-  // Otherwise calculate a new value.
-  int_range_max tmp;
-  fold_range_internal (tmp, s, name);
-
-  // Combine the new value with the old value.  This is required because
-  // the way value propagation works, when the IL changes on the fly we
-  // can sometimes get different results.  See PR 97741.
-  r.intersect (tmp);
-  m_cache.set_global_range (name, r);
+  else if (m_cache.get_non_stale_global_range (r, name))
+    {
+      if (idx)
+	tracer.trailer (idx, " cached", true, name, r);
+      return true;
+    }
+  else
+    {
+      // Otherwise calculate a new value.
+      int_range_max tmp;
+      fold_range_internal (tmp, s, name);
+
+      // Combine the new value with the old value.  This is required because
+      // the way value propagation works, when the IL changes on the fly we
+      // can sometimes get different results.  See PR 97741.
+      r.intersect (tmp);
+      m_cache.set_global_range (name, r);
+      res = true;
+    }
 
-  return true;
+  if (idx)
+    tracer.trailer (idx, "range_of_stmt", res, name, r);
+  return res;
 }
 
 // This routine will export whatever global ranges are known to GCC
@@ -243,7 +304,7 @@ gimple_ranger::dump_bb (FILE *f, basic_block bb)
   unsigned x;
   edge_iterator ei;
   edge e;
-  int_range_max range;
+  int_range_max range, tmp_range;
   fprintf (f, "\n=========== BB %d ============\n", bb->index);
   m_cache.dump_bb (f, bb);
 
@@ -282,10 +343,9 @@ gimple_ranger::dump_bb (FILE *f, basic_block bb)
 	      // the on entry cache for either end of the edge is
 	      // set.
 	      if ((s && bb == gimple_bb (s)) ||
-		  m_cache.block_range (range, bb, name, false) ||
-		  m_cache.block_range (range, e->dest, name, false))
+		  m_cache.block_range (tmp_range, bb, name, false) ||
+		  m_cache.block_range (tmp_range, e->dest, name, false))
 		{
-		  m_cache.range_on_edge (range, e, name);
 		  if (!range.varying_p ())
 		    {
 		      fprintf (f, "%d->%d ", e->src->index,
@@ -321,182 +381,12 @@ gimple_ranger::dump (FILE *f)
   m_cache.dump (f);
 }
 
-// trace_ranger implementation.
-
-
-trace_ranger::trace_ranger ()
-{
-  indent = 0;
-  trace_count = 0;
-}
-
-// If dumping, return true and print the prefix for the next output line.
-
-bool
-trace_ranger::dumping (unsigned counter, bool trailing)
-{
-  if (dump_file && (dump_flags & TDF_DETAILS))
-    {
-      // Print counter index as well as INDENT spaces.
-      if (!trailing)
-	fprintf (dump_file, " %-7u ", counter);
-      else
-	fprintf (dump_file, "         ");
-      unsigned x;
-      for (x = 0; x< indent; x++)
-	fputc (' ', dump_file);
-      return true;
-    }
-  return false;
-}
-
-// After calling a routine, if dumping, print the CALLER, NAME, and RESULT,
-// returning RESULT.
-
-bool
-trace_ranger::trailer (unsigned counter, const char *caller, bool result,
-		       tree name, const irange &r)
-{
-  if (dumping (counter, true))
-    {
-      indent -= bump;
-      fputs(result ? "TRUE : " : "FALSE : ", dump_file);
-      fprintf (dump_file, "(%u) ", counter);
-      fputs (caller, dump_file);
-      fputs (" (",dump_file);
-      if (name)
-	print_generic_expr (dump_file, name, TDF_SLIM);
-      fputs (") ",dump_file);
-      if (result)
-	{
-	  r.dump (dump_file);
-	  fputc('\n', dump_file);
-	}
-      else
-	fputc('\n', dump_file);
-      // Marks the end of a request.
-      if (indent == 0)
-	fputc('\n', dump_file);
-    }
-  return result;
-}
-
-// Tracing version of range_on_edge.  Call it with printing wrappers.
-
-bool
-trace_ranger::range_on_edge (irange &r, edge e, tree name)
-{
-  unsigned idx = ++trace_count;
-  if (dumping (idx))
-    {
-      fprintf (dump_file, "range_on_edge (");
-      print_generic_expr (dump_file, name, TDF_SLIM);
-      fprintf (dump_file, ") on edge %d->%d\n", e->src->index, e->dest->index);
-      indent += bump;
-    }
-
-  bool res = gimple_ranger::range_on_edge (r, e, name);
-  trailer (idx, "range_on_edge", true, name, r);
-  return res;
-}
-
-// Tracing version of range_on_entry.  Call it with printing wrappers.
-
-void
-trace_ranger::range_on_entry (irange &r, basic_block bb, tree name)
-{
-  unsigned idx = ++trace_count;
-  if (dumping (idx))
-    {
-      fprintf (dump_file, "range_on_entry (");
-      print_generic_expr (dump_file, name, TDF_SLIM);
-      fprintf (dump_file, ") to BB %d\n", bb->index);
-      indent += bump;
-    }
-
-  gimple_ranger::range_on_entry (r, bb, name);
-
-  trailer (idx, "range_on_entry", true, name, r);
-}
-
-// Tracing version of range_on_exit.  Call it with printing wrappers.
-
-void
-trace_ranger::range_on_exit (irange &r, basic_block bb, tree name)
-{
-  unsigned idx = ++trace_count;
-  if (dumping (idx))
-    {
-      fprintf (dump_file, "range_on_exit (");
-      print_generic_expr (dump_file, name, TDF_SLIM);
-      fprintf (dump_file, ") from BB %d\n", bb->index);
-      indent += bump;
-    }
-
-  gimple_ranger::range_on_exit (r, bb, name);
-
-  trailer (idx, "range_on_exit", true, name, r);
-}
-
-// Tracing version of range_of_stmt.  Call it with printing wrappers.
-
-bool
-trace_ranger::range_of_stmt (irange &r, gimple *s, tree name)
-{
-  bool res;
-  unsigned idx = ++trace_count;
-  if (dumping (idx))
-    {
-      fprintf (dump_file, "range_of_stmt (");
-      if (name)
-	print_generic_expr (dump_file, name, TDF_SLIM);
-      fputs (") at stmt ", dump_file);
-      print_gimple_stmt (dump_file, s, 0, TDF_SLIM);
-      indent += bump;
-    }
-
-  res = gimple_ranger::range_of_stmt (r, s, name);
-
-  return trailer (idx, "range_of_stmt", res, name, r);
-}
-
-// Tracing version of range_of_expr.  Call it with printing wrappers.
-
-bool
-trace_ranger::range_of_expr (irange &r, tree name, gimple *s)
-{
-  bool res;
-  unsigned idx = ++trace_count;
-  if (dumping (idx))
-    {
-      fprintf (dump_file, "range_of_expr(");
-      print_generic_expr (dump_file, name, TDF_SLIM);
-      fputs (")", dump_file);
-      if (s)
-	{
-	  fputs (" at stmt ", dump_file);
-	  print_gimple_stmt (dump_file, s, 0, TDF_SLIM);
-	}
-      else
-	fputs ("\n", dump_file);
-      indent += bump;
-    }
-
-  res = gimple_ranger::range_of_expr (r, name, s);
-
-  return trailer (idx, "range_of_expr", res, name, r);
-}
-
 gimple_ranger *
 enable_ranger (struct function *fun)
 {
   gimple_ranger *r;
 
-  if (param_evrp_mode & EVRP_MODE_TRACE)
-    r = new trace_ranger;
-  else
-    r = new gimple_ranger;
-
+  r = new gimple_ranger;
   fun->x_range_query = r;
 
   return r;
@@ -509,84 +399,3 @@ disable_ranger (struct function *fun)
 
   fun->x_range_query = &global_ranges;
 }
-
-// =========================================
-// Debugging helpers.
-// =========================================
-
-// Query all statements in the IL to precalculate computable ranges in RANGER.
-
-static DEBUG_FUNCTION void
-debug_seed_ranger (gimple_ranger &ranger)
-{
-  // Recalculate SCEV to make sure the dump lists everything.
-  if (scev_initialized_p ())
-    {
-      scev_finalize ();
-      scev_initialize ();
-    }
-
-  basic_block bb;
-  int_range_max r;
-  gimple_stmt_iterator gsi;
-  FOR_EACH_BB_FN (bb, cfun)
-    for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
-      {
-	gimple *stmt = gsi_stmt (gsi);
-
-	if (is_gimple_debug (stmt))
-	  continue;
-
-	ranger.range_of_stmt (r, stmt);
-      }
-}
-
-// Dump all that ranger knows for the current function.
-
-DEBUG_FUNCTION void
-dump_ranger (FILE *out)
-{
-  gimple_ranger ranger;
-  debug_seed_ranger (ranger);
-  ranger.dump (out);
-}
-
-DEBUG_FUNCTION void
-debug_ranger ()
-{
-  dump_ranger (stderr);
-}
-
-// Dump all that ranger knows on a path of BBs.
-//
-// Note that the blocks are in reverse order, thus the exit block is
-// path[0].
-
-DEBUG_FUNCTION void
-dump_ranger (FILE *dump_file, const vec<basic_block> &path)
-{
-  if (path.length () == 0)
-    {
-      fprintf (dump_file, "empty\n");
-      return;
-    }
-
-  gimple_ranger ranger;
-  debug_seed_ranger (ranger);
-
-  unsigned i = path.length ();
-  do
-    {
-      i--;
-      ranger.dump_bb (dump_file, path[i]);
-    }
-  while (i > 0);
-}
-
-DEBUG_FUNCTION void
-debug_ranger (const vec<basic_block> &path)
-{
-  dump_ranger (stderr, path);
-}
-
-#include "gimple-range-tests.cc"
diff --git a/gcc/gimple-range.h b/gcc/gimple-range.h
index aa620393dea9..41845b14fd63 100644
--- a/gcc/gimple-range.h
+++ b/gcc/gimple-range.h
@@ -22,10 +22,10 @@ along with GCC; see the file COPYING3.  If not see
 #ifndef GCC_GIMPLE_RANGE_H
 #define GCC_GIMPLE_RANGE_H
 
-
 #include "range.h"
 #include "value-query.h"
 #include "range-op.h"
+#include "gimple-range-trace.h"
 #include "gimple-range-edge.h"
 #include "gimple-range-fold.h"
 #include "gimple-range-gori.h"
@@ -43,7 +43,6 @@ along with GCC; see the file COPYING3.  If not see
 // type is not supported, then false is returned.  Non-statement
 // related methods return whatever the current global value is.
 
-
 class gimple_ranger : public range_query
 {
 public:
@@ -51,8 +50,8 @@ public:
   virtual bool range_of_stmt (irange &r, gimple *, tree name = NULL) OVERRIDE;
   virtual bool range_of_expr (irange &r, tree name, gimple * = NULL) OVERRIDE;
   virtual bool range_on_edge (irange &r, edge e, tree name) OVERRIDE;
-  virtual void range_on_entry (irange &r, basic_block bb, tree name);
-  virtual void range_on_exit (irange &r, basic_block bb, tree name);
+  void range_on_entry (irange &r, basic_block bb, tree name);
+  void range_on_exit (irange &r, basic_block bb, tree name);
   void export_global_ranges ();
   inline gori_compute &gori ()  { return m_cache.m_gori; }
   virtual void dump (FILE *f) OVERRIDE;
@@ -60,34 +59,9 @@ public:
 protected:
   bool fold_range_internal (irange &r, gimple *s, tree name);
   ranger_cache m_cache;
+  range_tracer tracer;
 };
 
-
-// This class overloads the ranger routines to provide tracing facilties
-// Entry and exit values to each of the APIs is placed in the dumpfile.
-
-class trace_ranger : public gimple_ranger
-{
-public:
-  trace_ranger ();
-  virtual bool range_of_stmt (irange &r, gimple *s, tree name = NULL_TREE);
-  virtual bool range_of_expr (irange &r, tree name, gimple *s = NULL);
-  virtual bool range_on_edge (irange &r, edge e, tree name);
-  virtual void range_on_entry (irange &r, basic_block bb, tree name);
-  virtual void range_on_exit (irange &r, basic_block bb, tree name);
-private:
-  static const unsigned bump = 2;
-  unsigned indent;
-  unsigned trace_count;		// Current trace index count.
-
-  bool dumping (unsigned counter, bool trailing = false);
-  bool trailer (unsigned counter, const char *caller, bool result, tree name,
-		const irange &r);
-};
-
-// Flag to enable debugging the various internal Caches.
-#define DEBUG_RANGE_CACHE (dump_file && (param_evrp_mode & EVRP_MODE_DEBUG))
-
 extern gimple_ranger *enable_ranger (struct function *);
 extern void disable_ranger (struct function *);
 
-- 
GitLab