diff mbox

[doc,committed] fix typos in docs/comments for devirtualization optimizations

Message ID 54A75FC0.7070903@codesourcery.com
State New
Headers show

Commit Message

Sandra Loosemore Jan. 3, 2015, 3:19 a.m. UTC
I noticed a number of typos in the documentation for the 
devirtualization optimization options in invoke.texi, also in the short 
option description in common.opt.  When I was browsing the code to make 
sure I understood the purpose of these options, I noticed that there 
were very many more typos in the comments in ipa-devirt.c.  I've made a 
pass through everything to clean things up and checked in this patch 
under the "obvious fix" rule.

There were a couple things I didn't address here:

* I suggest renaming the function type_known_to_have_no_deriavations_p 
to type_known_to_have_no_derivations_p.  (I suppose such a code change 
requires a complete bootstrap and regression test....  I'm lazy....)

* I noticed the comments documenting possible_polymorphic_call_targets 
appear to be describing parameters and behavior that aren't there any 
more.  I'll leave fixing that up to somebody who has a deeper 
understanding of the code.

-Sandra

2015-01-02  Sandra Loosemore  <sandra@codesourcery.com>

	gcc/
	* doc/invoke.texi (Option Summary): Fix spelling of
	-fdevirtualize-at-ltrans.
	([-fdevirtualize]): Fix markup.
	([-fdevirtualize-speculatively]): Fix typo.
	([-fdevirtualize-at-ltrans]): Likewise.  Make description less
	implementor-speaky.
	* common.opt (fdevirtualize-at-ltrans): Likewise.
	* ipa-devirt.c: Fix typos in comments throughout the file.
	(ipa_devirt): Fix typos in format strings for dump output.

Comments

Gerald Pfeifer Feb. 7, 2015, 1:19 a.m. UTC | #1
Hi Sandra,

Index: gcc/ipa-devirt.c
===================================================================
      polymorphic (indirect) call
-       This is callgraph represention of virtual method call.  Every
+       This is callgraph representation of virtual method call.  Every
        polymorphic call contains otr_type and otr_token taken from
        original OBJ_TYPE_REF at callgraph construction time.

aren't some articles missing here?  "a callgraph representation
of a virtual method call"?

 /* The node of type inheritance graph.  For each type unique in
-   One Defintion Rule (ODR) sense, we produce one node linking all 
+   One Definition Rule (ODR) sense, we produce one node linking all 
    main variants of types equivalent to it, bases and derived types.  
*/

...in the One Definition Rule (ODR) sense... ?

-  /* All derrived types with virtual methods seen in unit;
-     built only for main variants oftypes  */
+  /* All derived types with virtual methods seen in unit;
+     built only for main variants of types.  */
   vec<odr_type> GTY((skip)) derived_types;

Something missing here, too.  "in the unit"?

-/* Return TURE if type's constructors are all visible.  */
+/* Return TRUE if type's constructors are all visible.  */

"if a type's"?

-/* Dump ODR type T and all its derrived type.  INDENT specify indentation for
-   recusive printing.  */
+/* Dump ODR type T and all its derived types.  INDENT specifies indentation for
+   recursive printing.  */

"the indentation"?

-      /* Lookup BINFO with virtual table.  For normal types it is always last
+      /* Look up BINFO with virtual table.  For normal types it is always last
 	 binfo on stack.  */

"with" -> "within"?

"it is always the last"

   for (i = 0; BINFO_BASE_ITERATE (binfo, i, base_binfo); i++)
-    /* Walking bases that have no virtual method is pointless excercise.  */
+    /* Walking bases that have no virtual method is pointless exercise.  */
     if (polymorphic_type_binfo_p (base_binfo))

Shouldn't this just read "Walk bases..."?

+ because the type is always known.  One of entries may be 
+ cxa_pure_virtual so look to at least two of them.  */

"One of the entries"

-  /* If there are no virtual tables refering the target alive,
-     the only way the target can be called is an instance comming from other
-     compilation unit; speculative devirtualization is build around an
+  /* If there are no live virtual tables referring the target,
+     the only way the target can be called is an instance coming from other
+     compilation unit; speculative devirtualization is built around an

"from a different compilation unit"


I will be making and committing those changes, but would prefer
your second pair of eyes given that you have touched this recently.

Gerald
Sandra Loosemore Feb. 7, 2015, 1:55 a.m. UTC | #2
On 02/06/2015 06:19 PM, Gerald Pfeifer wrote:
> Hi Sandra,
>
> Index: gcc/ipa-devirt.c
> ===================================================================
>       polymorphic (indirect) call
> -       This is callgraph represention of virtual method call.  Every
> +       This is callgraph representation of virtual method call.  Every
>         polymorphic call contains otr_type and otr_token taken from
>         original OBJ_TYPE_REF at callgraph construction time.
>
> aren't some articles missing here?  "a callgraph representation
> of a virtual method call"?

Yes.  (FWIW, Slavic languages don't have either definite or indefinite 
articles, and I've noticed that people who are native speakers of those 
languages often omit them in English as well....  in user documentation 
I'd fix that but I'm less motivated to do it in code comments where the 
sense is clear otherwise.)

The other changes you suggest look fine to me, except this one:

>    for (i = 0; BINFO_BASE_ITERATE (binfo, i, base_binfo); i++)
> -    /* Walking bases that have no virtual method is pointless
> excercise.  */
> +    /* Walking bases that have no virtual method is pointless
> exercise.  */
>      if (polymorphic_type_binfo_p (base_binfo))
>
> Shouldn't this just read "Walk bases..."?

No, "Walking" is a noun here.

> I will be making and committing those changes, but would prefer
> your second pair of eyes given that you have touched this recently.

-Sandra
diff mbox

Patch

Index: gcc/doc/invoke.texi
===================================================================
--- gcc/doc/invoke.texi	(revision 219154)
+++ gcc/doc/invoke.texi	(working copy)
@@ -378,7 +378,7 @@  Objective-C and Objective-C++ Dialects}.
 -fcx-limited-range @gol
 -fdata-sections -fdce -fdelayed-branch @gol
 -fdelete-null-pointer-checks -fdevirtualize -fdevirtualize-speculatively @gol
--devirtualize-at-ltrans -fdse @gol
+-fdevirtualize-at-ltrans -fdse @gol
 -fearly-inlining -fipa-sra -fexpensive-optimizations -ffat-lto-objects @gol
 -ffast-math -ffinite-math-only -ffloat-store -fexcess-precision=@var{style} @gol
 -fforward-propagate -ffp-contract=@var{style} -ffunction-sections @gol
@@ -7772,7 +7772,7 @@  are enabled independently at different o
 @opindex fdevirtualize
 Attempt to convert calls to virtual functions to direct calls.  This
 is done both within a procedure and interprocedurally as part of
-indirect inlining (@code{-findirect-inlining}) and interprocedural constant
+indirect inlining (@option{-findirect-inlining}) and interprocedural constant
 propagation (@option{-fipa-cp}).
 Enabled at levels @option{-O2}, @option{-O3}, @option{-Os}.
 
@@ -7781,14 +7781,15 @@  Enabled at levels @option{-O2}, @option{
 Attempt to convert calls to virtual functions to speculative direct calls.
 Based on the analysis of the type inheritance graph, determine for a given call
 the set of likely targets. If the set is small, preferably of size 1, change
-the call into an conditional deciding on direct and indirect call.  The
+the call into a conditional deciding between direct and indirect calls.  The
 speculative calls enable more optimizations, such as inlining.  When they seem
 useless after further optimization, they are converted back into original form.
 
 @item -fdevirtualize-at-ltrans
 @opindex fdevirtualize-at-ltrans
-Perform extra streaming needed for agressive devirtualization during LTO local
-transformation stage. This option enables more devirtualization but
+Stream extra information needed for aggressive devirtualization when running
+the link-time optimizer in local transformation mode.  
+This option enables more devirtualization but
 significantly increases the size of streamed data. For this reason it is
 disabled by default.
 
Index: gcc/common.opt
===================================================================
--- gcc/common.opt	(revision 219153)
+++ gcc/common.opt	(working copy)
@@ -1064,7 +1064,7 @@  Delete useless null pointer checks
 
 fdevirtualize-at-ltrans
 Common Report Var(flag_ltrans_devirtualize)
-Perofrm extra streaming to support more agressive devirtualization at LTO ltrans stage.
+Stream extra data to support more aggressive devirtualization in LTO local transformation mode
 
 fdevirtualize-speculatively
 Common Report Var(flag_devirtualize_speculatively) Optimization
Index: gcc/ipa-devirt.c
===================================================================
--- gcc/ipa-devirt.c	(revision 219153)
+++ gcc/ipa-devirt.c	(working copy)
@@ -19,7 +19,7 @@  You should have received a copy of the G
 along with GCC; see the file COPYING3.  If not see
 <http://www.gnu.org/licenses/>.  */
 
-/* Brief vocalburary:
+/* Brief vocabulary:
      ODR = One Definition Rule
         In short, the ODR states that:
 	1 In any translation unit, a template, type, function, or object can
@@ -44,7 +44,7 @@  along with GCC; see the file COPYING3.  
 
      BINFO
        This is the type inheritance information attached to each tree
-       RECORD_TYPE by the C++ frotend.  It provides information about base
+       RECORD_TYPE by the C++ frontend.  It provides information about base
        types and virtual tables.
 
        BINFO is linked to the RECORD_TYPE by TYPE_BINFO.
@@ -75,7 +75,7 @@  along with GCC; see the file COPYING3.  
        or from DECL_VINDEX of a given virtual table.
 
      polymorphic (indirect) call
-       This is callgraph represention of virtual method call.  Every
+       This is callgraph representation of virtual method call.  Every
        polymorphic call contains otr_type and otr_token taken from
        original OBJ_TYPE_REF at callgraph construction time.
 
@@ -196,17 +196,17 @@  static bool odr_violation_reported = fal
 static hash_set<cgraph_node *> *cached_polymorphic_call_targets;
 
 /* The node of type inheritance graph.  For each type unique in
-   One Defintion Rule (ODR) sense, we produce one node linking all 
+   One Definition Rule (ODR) sense, we produce one node linking all 
    main variants of types equivalent to it, bases and derived types.  */
 
 struct GTY(()) odr_type_d
 {
   /* leader type.  */
   tree type;
-  /* All bases; built only for main variants of types  */
+  /* All bases; built only for main variants of types.  */
   vec<odr_type> GTY((skip)) bases;
-  /* All derrived types with virtual methods seen in unit;
-     built only for main variants oftypes  */
+  /* All derived types with virtual methods seen in unit;
+     built only for main variants of types.  */
   vec<odr_type> GTY((skip)) derived_types;
 
   /* All equivalent types, if more than one.  */
@@ -246,7 +246,7 @@  type_all_derivations_known_p (const_tree
   return (decl_function_context (TYPE_NAME (t)) != NULL);
 }
 
-/* Return TURE if type's constructors are all visible.  */
+/* Return TRUE if type's constructors are all visible.  */
 
 static bool
 type_all_ctors_visible_p (tree t)
@@ -367,7 +367,7 @@  odr_hasher::hash (const value_type *odr_
 /* For languages with One Definition Rule, work out if
    types are the same based on their name.
  
-   This is non-trivial for LTO where minnor differences in
+   This is non-trivial for LTO where minor differences in
    the type representation may have prevented type merging
    to merge two copies of otherwise equivalent type.
 
@@ -397,7 +397,7 @@  types_same_for_odr (const_tree type1, co
 
   /* ODR name of the type is set in DECL_ASSEMBLER_NAME of its TYPE_NAME.
 
-     Ideally we should never meed types without ODR names here.  It can however
+     Ideally we should never need types without ODR names here.  It can however
      happen in two cases:
 
        1) for builtin types that are not streamed but rebuilt in lto/lto-lang.c
@@ -410,8 +410,8 @@  types_same_for_odr (const_tree type1, co
   if ((!TYPE_NAME (type1) || !DECL_ASSEMBLER_NAME_SET_P (TYPE_NAME (type1)))
       || (!TYPE_NAME (type2) || !DECL_ASSEMBLER_NAME_SET_P (TYPE_NAME (type2))))
     {
-      /* See if types are obvoiusly different (i.e. different codes
-	 or polymorphis wrt non-polymorphic).  This is not strictly correct
+      /* See if types are obviously different (i.e. different codes
+	 or polymorphic wrt non-polymorphic).  This is not strictly correct
 	 for ODR violating programs, but we can't do better without streaming
 	 ODR names.  */
       if (TREE_CODE (type1) != TREE_CODE (type2))
@@ -424,8 +424,8 @@  types_same_for_odr (const_tree type1, co
 	     != (BINFO_VTABLE (TYPE_BINFO (type2)) == NULL_TREE))
 	return false;
 
-      /* At the moment we have no way to establish ODR equivlaence at LTO
-	 other than comparing virtual table pointrs of polymorphic types.
+      /* At the moment we have no way to establish ODR equivalence at LTO
+	 other than comparing virtual table pointers of polymorphic types.
 	 Eventually we should start saving mangled names in TYPE_NAME.
 	 Then this condition will become non-trivial.  */
 
@@ -508,7 +508,7 @@  odr_hasher::remove (value_type *v)
   ggc_free (v);
 }
 
-/* ODR type hash used to lookup ODR type based on tree type node.  */
+/* ODR type hash used to look up ODR type based on tree type node.  */
 
 typedef hash_table<odr_hasher> odr_hash_type;
 static odr_hash_type *odr_hash;
@@ -565,7 +565,7 @@  odr_subtypes_equivalent_p (tree t1, tree
         return true;
     }
 
-  /* Component types, builtins and possibly vioalting ODR types
+  /* Component types, builtins and possibly violating ODR types
      have to be compared structurally.  */
   if (TREE_CODE (t1) != TREE_CODE (t2))
     return false;
@@ -586,7 +586,7 @@  odr_subtypes_equivalent_p (tree t1, tree
 }
 
 /* Compare two virtual tables, PREVAILING and VTABLE and output ODR
-   violation warings.  */
+   violation warnings.  */
 
 void
 compare_virtual_tables (varpool_node *prevailing, varpool_node *vtable)
@@ -1445,8 +1445,8 @@  type_known_to_have_no_deriavations_p (tr
 		  && !get_odr_type (t, true)->derived_types.length())));
 }
 
-/* Dump ODR type T and all its derrived type.  INDENT specify indentation for
-   recusive printing.  */
+/* Dump ODR type T and all its derived types.  INDENT specifies indentation for
+   recursive printing.  */
 
 static void
 dump_odr_type (FILE *f, odr_type t, int indent=0)
@@ -1517,7 +1517,7 @@  dump_type_inheritance_graph (FILE *f)
 }
 
 /* Given method type T, return type of class it belongs to.
-   Lookup this pointer and get its type.    */
+   Look up this pointer and get its type.    */
 
 tree
 method_class_type (const_tree t)
@@ -1664,7 +1664,7 @@  maybe_record_node (vec <cgraph_node *> &
 
   target_node = cgraph_node::get (target);
 
-  /* Preffer alias target over aliases, so we do not get confused by
+  /* Prefer alias target over aliases, so we do not get confused by
      fake duplicates.  */
   if (target_node)
     {
@@ -1676,7 +1676,7 @@  maybe_record_node (vec <cgraph_node *> &
     }
 
   /* Method can only be called by polymorphic call if any
-     of vtables refering to it are alive. 
+     of vtables referring to it are alive. 
 
      While this holds for non-anonymous functions, too, there are
      cases where we want to keep them in the list; for example
@@ -1686,7 +1686,7 @@  maybe_record_node (vec <cgraph_node *> &
 
      Currently we ignore these functions in speculative devirtualization.
      ??? Maybe it would make sense to be more aggressive for LTO even
-     eslewhere.  */
+     elsewhere.  */
   if (!flag_ltrans
       && type_in_anonymous_namespace_p (DECL_CONTEXT (target))
       && (!target_node
@@ -1714,12 +1714,12 @@  maybe_record_node (vec <cgraph_node *> &
     *completep = false;
 }
 
-/* See if BINFO's type match OUTER_TYPE.  If so, lookup 
+/* See if BINFO's type matches OUTER_TYPE.  If so, look up 
    BINFO of subtype of OTR_TYPE at OFFSET and in that BINFO find
    method in vtable and insert method to NODES array
    or BASES_TO_CONSIDER if this array is non-NULL.
    Otherwise recurse to base BINFOs.
-   This match what get_binfo_at_offset does, but with offset
+   This matches what get_binfo_at_offset does, but with offset
    being unknown.
 
    TYPE_BINFOS is a stack of BINFOS of types with defined
@@ -1760,7 +1760,7 @@  record_target_from_binfo (vec <cgraph_no
       int i;
       tree type_binfo = NULL;
 
-      /* Lookup BINFO with virtual table.  For normal types it is always last
+      /* Look up BINFO with virtual table.  For normal types it is always last
 	 binfo on stack.  */
       for (i = type_binfos.length () - 1; i >= 0; i--)
 	if (BINFO_OFFSET (type_binfos[i]) == BINFO_OFFSET (binfo))
@@ -1815,7 +1815,7 @@  record_target_from_binfo (vec <cgraph_no
 
   /* Walk bases.  */
   for (i = 0; BINFO_BASE_ITERATE (binfo, i, base_binfo); i++)
-    /* Walking bases that have no virtual method is pointless excercise.  */
+    /* Walking bases that have no virtual method is pointless exercise.  */
     if (polymorphic_type_binfo_p (base_binfo))
       record_target_from_binfo (nodes, bases_to_consider, base_binfo, otr_type,
 				type_binfos, 
@@ -1825,13 +1825,13 @@  record_target_from_binfo (vec <cgraph_no
     type_binfos.pop ();
 }
      
-/* Lookup virtual methods matching OTR_TYPE (with OFFSET and OTR_TOKEN)
+/* Look up virtual methods matching OTR_TYPE (with OFFSET and OTR_TOKEN)
    of TYPE, insert them to NODES, recurse into derived nodes. 
    INSERTED is used to avoid duplicate insertions of methods into NODES.
    MATCHED_VTABLES are used to avoid duplicate walking vtables.
    Clear COMPLETEP if unreferable target is found.
  
-   If CONSIDER_CONSTURCTION is true, record to BASES_TO_CONSDIER
+   If CONSIDER_CONSTRUCTION is true, record to BASES_TO_CONSIDER
    all cases where BASE_SKIPPED is true (because the base is abstract
    class).  */
 
@@ -1989,7 +1989,7 @@  devirt_node_removal_hook (struct cgraph_
     free_polymorphic_call_targets_hash ();
 }
 
-/* Lookup base of BINFO that has virtual table VTABLE with OFFSET.  */
+/* Look up base of BINFO that has virtual table VTABLE with OFFSET.  */
 
 tree
 subbinfo_with_vtable_at_offset (tree binfo, unsigned HOST_WIDE_INT offset,
@@ -2031,7 +2031,7 @@  vtable_pointer_value_to_vtable (const_tr
   /* We expect &MEM[(void *)&virtual_table + 16B].
      We obtain object's BINFO from the context of the virtual table. 
      This one contains pointer to virtual table represented via
-     POINTER_PLUS_EXPR.  Verify that this pointer match to what
+     POINTER_PLUS_EXPR.  Verify that this pointer matches what
      we propagated through.
 
      In the case of virtual inheritance, the virtual tables may
@@ -2084,14 +2084,14 @@  vtable_pointer_value_to_binfo (const_tre
      because we do not have BINFO for those. Eventually we should fix
      our representation to allow this case to be handled, too.
      In the case we see store of BINFO we however may assume
-     that standard folding will be ale to cope with it.  */
+     that standard folding will be able to cope with it.  */
   return subbinfo_with_vtable_at_offset (TYPE_BINFO (DECL_CONTEXT (vtable)),
 					 offset, vtable);
 }
 
 /* Walk bases of OUTER_TYPE that contain OTR_TYPE at OFFSET.
-   Lookup their respecitve virtual methods for OTR_TOKEN and OTR_TYPE
-   and insert them to NODES.
+   Look up their respective virtual methods for OTR_TOKEN and OTR_TYPE
+   and insert them in NODES.
 
    MATCHED_VTABLES and INSERTED is used to avoid duplicated work.  */
 
@@ -2126,10 +2126,10 @@  record_targets_from_bases (tree otr_type
 	      && polymorphic_type_binfo_p (TYPE_BINFO (TREE_TYPE (fld))))
 	    break;
 	}
-      /* Within a class type we should always find correcponding fields.  */
+      /* Within a class type we should always find corresponding fields.  */
       gcc_assert (fld && TREE_CODE (TREE_TYPE (fld)) == RECORD_TYPE);
 
-      /* Nonbasetypes should have been stripped by outer_class_type.  */
+      /* Nonbase types should have been stripped by outer_class_type.  */
       gcc_assert (DECL_ARTIFICIAL (fld));
 
       outer_type = TREE_TYPE (fld);
@@ -2197,8 +2197,8 @@  struct final_warning_record
 struct final_warning_record *final_warning_records;
 
 /* Return vector containing possible targets of polymorphic call of type
-   OTR_TYPE caling method OTR_TOKEN within type of OTR_OUTER_TYPE and OFFSET.
-   If INCLUDE_BASES is true, walk also base types of OUTER_TYPES containig
+   OTR_TYPE calling method OTR_TOKEN within type of OTR_OUTER_TYPE and OFFSET.
+   If INCLUDE_BASES is true, walk also base types of OUTER_TYPES containing
    OTR_TYPE and include their virtual method.  This is useful for types
    possibly in construction or destruction where the virtual table may
    temporarily change to one of base types.  INCLUDE_DERIVER_TYPES make
@@ -2238,7 +2238,7 @@  possible_polymorphic_call_targets (tree 
 
   otr_type = TYPE_MAIN_VARIANT (otr_type);
 
-  /* If ODR is not initialized or the constext is invalid, return empty
+  /* If ODR is not initialized or the context is invalid, return empty
      incomplete list.  */
   if (!odr_hash || context.invalid || !TYPE_BINFO (otr_type))
     {
@@ -2255,11 +2255,11 @@  possible_polymorphic_call_targets (tree 
 
   type = get_odr_type (otr_type, true);
 
-  /* Recording type variants would wast results cache.  */
+  /* Recording type variants would waste results cache.  */
   gcc_assert (!context.outer_type
 	      || TYPE_MAIN_VARIANT (context.outer_type) == context.outer_type);
 
-  /* Lookup the outer class type we want to walk.
+  /* Look up the outer class type we want to walk.
      If we fail to do so, the context is invalid.  */
   if ((context.outer_type || context.speculative_outer_type)
       && !context.restrict_to_inner_class (otr_type))
@@ -2279,10 +2279,10 @@  possible_polymorphic_call_targets (tree 
   /* We canonicalize our query, so we do not need extra hashtable entries.  */
 
   /* Without outer type, we have no use for offset.  Just do the
-     basic search from innter type  */
+     basic search from inner type.  */
   if (!context.outer_type)
     context.clear_outer_type (otr_type);
-  /* We need to update our hiearchy if the type does not exist.  */
+  /* We need to update our hierarchy if the type does not exist.  */
   outer_type = get_odr_type (context.outer_type, true);
   /* If the type is complete, there are no derivations.  */
   if (TYPE_FINAL_P (outer_type->type))
@@ -2313,7 +2313,7 @@  possible_polymorphic_call_targets (tree 
 	  = get_odr_type (context.speculative_outer_type, true)->type;
     }
 
-  /* Lookup cached answer.  */
+  /* Look up cached answer.  */
   key.type = type;
   key.otr_token = otr_token;
   key.speculative = speculative;
@@ -2362,7 +2362,8 @@  possible_polymorphic_call_targets (tree 
       odr_type speculative_outer_type;
       bool speculation_complete = true;
 
-      /* First insert target from type itself and check if it may have derived types.  */
+      /* First insert target from type itself and check if it may have
+	 derived types.  */
       speculative_outer_type = get_odr_type (context.speculative_outer_type, true);
       if (TYPE_FINAL_P (speculative_outer_type->type))
 	context.speculative_maybe_derived_type = false;
@@ -2498,8 +2499,8 @@  possible_polymorphic_call_targets (tree 
       if (!speculative)
 	{
 	  /* Destructors are never called through construction virtual tables,
-	     because the type is always known.  One of entries may be cxa_pure_virtual
-	     so look to at least two of them.  */
+	     because the type is always known.  One of entries may be
+	     cxa_pure_virtual so look to at least two of them.  */
 	  if (context.maybe_in_construction)
 	    for (i =0 ; i < MIN (nodes.length (), 2); i++)
 	      if (DECL_CXX_DESTRUCTOR_P (nodes[i]->decl))
@@ -2705,16 +2706,16 @@  likely_target_p (struct cgraph_node *n)
     return false;
   if (n->frequency < NODE_FREQUENCY_NORMAL)
     return false;
-  /* If there are no virtual tables refering the target alive,
-     the only way the target can be called is an instance comming from other
-     compilation unit; speculative devirtualization is build around an
+  /* If there are no live virtual tables referring the target,
+     the only way the target can be called is an instance coming from other
+     compilation unit; speculative devirtualization is built around an
      assumption that won't happen.  */
   if (!referenced_from_vtable_p (n))
     return false;
   return true;
 }
 
-/* Compare type warning records P1 and P2 and chose one with larger count;
+/* Compare type warning records P1 and P2 and choose one with larger count;
    helper for qsort.  */
 
 int
@@ -2730,7 +2731,7 @@  type_warning_cmp (const void *p1, const 
   return t2->count - t1->count;
 }
 
-/* Compare decl warning records P1 and P2 and chose one with larger count;
+/* Compare decl warning records P1 and P2 and choose one with larger count;
    helper for qsort.  */
 
 int
@@ -2747,7 +2748,7 @@  decl_warning_cmp (const void *p1, const 
 }
 
 
-/* Try speculatively devirtualize call to OTR_TYPE with OTR_TOKEN with
+/* Try to speculatively devirtualize call to OTR_TYPE with OTR_TOKEN with
    context CTX.  */
 
 struct cgraph_node *
@@ -2785,7 +2786,7 @@  try_speculative_devirtualization (tree o
 
 /* The ipa-devirt pass.
    When polymorphic call has only one likely target in the unit,
-   turn it into speculative call.  */
+   turn it into a speculative call.  */
 
 static unsigned int
 ipa_devirt (void)
@@ -2860,7 +2861,7 @@  ipa_devirt (void)
 	    if (e->speculative)
 	      {
 		if (dump_file)
-		  fprintf (dump_file, "Call is aready speculated\n\n");
+		  fprintf (dump_file, "Call is already speculated\n\n");
 		nspeculated++;
 
 		/* When dumping see if we agree with speculation.  */
@@ -2915,7 +2916,7 @@  ipa_devirt (void)
 	    if (!likely_target->definition)
 	      {
 		if (dump_file)
-		  fprintf (dump_file, "Target is not an definition\n\n");
+		  fprintf (dump_file, "Target is not a definition\n\n");
 		nnotdefined++;
 		continue;
 	      }