]> gcc.gnu.org Git - gcc.git/commitdiff
*** empty log message ***
authorRichard Stallman <rms@gnu.org>
Thu, 7 May 1992 06:41:23 +0000 (06:41 +0000)
committerRichard Stallman <rms@gnu.org>
Thu, 7 May 1992 06:41:23 +0000 (06:41 +0000)
From-SVN: r930

42 files changed:
gcc/c-typeck.c
gcc/config/m68k/m68k.md
gcc/config/m88k/m88k.c
gcc/config/pa/pa.c
gcc/config/sparc/sparc.md
gcc/dbxout.c
gcc/dwarfout.c
gcc/enquire.c
gcc/expr.c
gcc/expr.h
gcc/fixincludes
gcc/flow.c
gcc/fold-const.c
gcc/function.c
gcc/gcc.c
gcc/genattrtab.c
gcc/genrecog.c
gcc/ginclude/va-pyr.h
gcc/ginclude/va-sparc.h
gcc/global.c
gcc/jump.c
gcc/local-alloc.c
gcc/loop.h
gcc/optabs.c
gcc/protoize.c
gcc/recog.c
gcc/reg-stack.c
gcc/regclass.c
gcc/reload.c
gcc/reload1.c
gcc/reorg.c
gcc/rtl.c
gcc/rtl.def
gcc/rtl.h
gcc/sched.c
gcc/sdbout.c
gcc/stmt.c
gcc/toplev.c
gcc/tree.h
gcc/unroll.c
gcc/varasm.c
gcc/xcoffout.c

index e37bb9e0422f19f9170675fe4ea1eb1f560dd8c6..0a0813ade437cb6fac519122200647ac5bf6a551 100644 (file)
@@ -3554,7 +3554,7 @@ build_compound_expr (list)
 
   if (TREE_CHAIN (list) == 0)
     {
-#if 0 /* If something inside inhibited lvalueness, we shoukd not override.  */
+#if 0 /* If something inside inhibited lvalueness, we should not override.  */
       /* Consider (x, y+0), which is not an lvalue since y+0 is not.  */
 
       /* Strip NON_LVALUE_EXPRs since we aren't using as an lvalue.  */
@@ -4369,7 +4369,7 @@ get_spelling (errtype)
    into the message.
 
    If OFWHAT is null, the component name is stored on the spelling stack.
-   If the compoment name is a null string, then LOCAL is omitted entirely.  */
+   If the component name is a null string, then LOCAL is omitted entirely.  */
 
 void
 error_init (format, local, ofwhat)
@@ -4395,7 +4395,7 @@ error_init (format, local, ofwhat)
    into the message.
 
    If OFWHAT is null, the component name is stored on the spelling stack.
-   If the compoment name is a null string, then LOCAL is omitted entirely.  */
+   If the component name is a null string, then LOCAL is omitted entirely.  */
 
 void
 pedwarn_init (format, local, ofwhat)
index 8d76aa92ff65ffdddd528bd342a9964738fc59a7..4a901dddd374927813945ed60a983c02f556bd3d 100644 (file)
          return \"subq%.w %2,%0\";
        }
       /* On everything except the 68000 it is faster to use two
-        addqw insttuctions to add a small integer (8 < N <= 16)
+        addqw instructions to add a small integer (8 < N <= 16)
         to an address register.  Likewise for subqw. */
       if (INTVAL (operands[2]) > 8
          && INTVAL (operands[2]) <= 16
          return \"subq%.w %1,%0\";
        }
       /* On everything except the 68000 it is faster to use two
-        addqw instuctions to add a small integer (8 < N <= 16)
+        addqw instructions to add a small integer (8 < N <= 16)
         to an address register.  Likewise for subqw. */
       if (INTVAL (operands[1]) > 8
          && INTVAL (operands[1]) <= 16
          return \"subq%.w %1,%0\";
        }
       /* On everything except the 68000 it is faster to use two
-        addqw instuctions to add a small integer (8 < N <= 16)
+        addqw instructions to add a small integer (8 < N <= 16)
         to an address register.  Likewise for subqw. */
       if (INTVAL (operands[1]) > 8
          && INTVAL (operands[1]) <= 16
index 4aca80d5981cc79768db4e07c93bbeb863147416..1147694f5e68e471baaf97809fe237853ca4ef81 100644 (file)
@@ -1729,7 +1729,7 @@ m88k_layout_frame ()
       }
 
   /* Achieve greatest use of double memory ops.  Either we end up saving
-     r30 or we use that slot to align the regsters we do save.  */
+     r30 or we use that slot to align the registers we do save.  */
   if (nregs >= 2 && save_regs[1] && !save_regs[FRAME_POINTER_REGNUM])
     sp_size += 4;
 
index 3c10ef8268278b48a6ae91817ac936b5997247de..ec774d4629c58d69e2c1b822632f5251426021f0 100644 (file)
@@ -1056,7 +1056,7 @@ output_block_move (operands, size_is_constant)
            goto copy_with_loop;
 
          /* Read and store using two registers, and hide latency
-            by defering the stores until three instructions after
+            by deferring the stores until three instructions after
             the corresponding load.  The last load insn will read
             the entire word were the last bytes are, possibly past
             the end of the source block, but since loads are aligned,
@@ -1144,7 +1144,7 @@ output_block_move (operands, size_is_constant)
       output_asm_insn ("addib,<,n -4,%2,.+16", operands);
     }
 
-  /* Copying loop.  Note that the first load is in the anulled delay slot
+  /* Copying loop.  Note that the first load is in the annulled delay slot
      of addib.  Is it OK on PA to have a load in a delay slot, i.e. is a
      possible page fault stopped in time?  */
   output_asm_insn ("ldws,ma 4(0,%1),%3", operands);
@@ -1170,7 +1170,7 @@ output_block_move (operands, size_is_constant)
       output_asm_insn ("addib,=,n 4,%2,.+16", operands);
 
       /* Read the entire word of the source block tail.  (Also this
-        load is in an anulled delay slot.)  */
+        load is in an annulled delay slot.)  */
       output_asm_insn ("ldw 0(0,%1),%3", operands);
 
       /* Make %0 point at the first byte after the destination block.  */
index 857046c7c44a1d89e5e4b1bb245fd1d0eac7aba5..43ec22a45ddfedd0e4776d503bda6b24dbf275f9 100644 (file)
 {
   rtx op2 = operands[2];
 
-  /* If constant is postive, upper bits zeroed, otherwise unchanged.
+  /* If constant is positive, upper bits zeroed, otherwise unchanged.
      Give the assembler a chance to pick the move instruction. */
   if (GET_CODE (op2) == CONST_INT)
     {
index c82eb00b305cdd2bc71c8c419c5dc993bb4b5c8b..49789ae619f4e90b5c0212af1dd24af1720747e9 100644 (file)
@@ -521,7 +521,7 @@ dbxout_continue ()
   current_sym_nchars = 0;
 }
 \f
-/* Subtroutine of `dbxout_type'.  Output the type fields of TYPE.
+/* Subroutine of `dbxout_type'.  Output the type fields of TYPE.
    This must be a separate function because anonymous unions require
    recursive calls.  */
 
@@ -614,7 +614,7 @@ dbxout_type_fields (type)
     }
 }
 \f
-/* Subtroutine of `dbxout_type_methods'.  Output debug info about the
+/* Subroutine of `dbxout_type_methods'.  Output debug info about the
    method described DECL.  DEBUG_NAME is an encoding of the method's
    type signature.  ??? We may be able to do without DEBUG_NAME altogether
    now.  */
index 72d86ce1b41678b46d8ff2bd4bf35d5246056021..4c32e59a416cea0ecfafaa65ecc2f5e55894f4f7 100644 (file)
@@ -243,7 +243,7 @@ static unsigned pending_siblings_allocated;
 #define PENDING_SIBLINGS_INCREMENT 64
 
 /* Non-zero if we are performing our file-scope finalization pass and if
-   we should force out Dwarf decsriptions of any and all file-scope
+   we should force out Dwarf descriptions of any and all file-scope
    tagged types which are still incomplete types.  */
 
 static int finalizing = 0;
@@ -268,11 +268,11 @@ static unsigned pending_types;
 
 #define PENDING_TYPES_INCREMENT 64
 
-/* Pointer to an artifical RECORD_TYPE which we create in dwarfout_init.
+/* Pointer to an artificial RECORD_TYPE which we create in dwarfout_init.
    This is used in a hack to help us get the DIEs describing types of
    formal parameters to come *after* all of the DIEs describing the formal
    parameters themselves.  That's necessary in order to be compatible
-   with what the brain-dammaged svr4 SDB debugger requires.  */
+   with what the brain-damaged svr4 SDB debugger requires.  */
 
 static tree fake_containing_scope;
 
@@ -2405,7 +2405,7 @@ type_tag (type)
         does.  It always makes the TYPE_NAME for each tagged type be either
         NULL (signifying an anonymous tagged type) or else a pointer to an
         IDENTIFIER_NODE.  Obviously, we would like to generate correct Dwarf
-        for both C and C++, but given this inconsistancy in the TREE
+        for both C and C++, but given this inconsistency in the TREE
         representation of tagged types for C and C++ in the GNU front-ends,
         we cannot support both languages correctly unless we introduce some
         front-end specific code here, and rms objects to that, so we can
@@ -3374,7 +3374,7 @@ output_type (type, containing_scope)
 
       case FILE_TYPE:
        output_type (TREE_TYPE (type), containing_scope);
-       abort ();       /* No way to reprsent these in Dwarf yet!  */
+       abort ();       /* No way to represent these in Dwarf yet!  */
        break;
 
       case STRING_TYPE:
@@ -4043,7 +4043,9 @@ dwarfout_file_scope_decl (decl, set_finalizing)
       if (TREE_EXTERNAL (decl) && !TREE_USED (decl))
        return;
 
-      if (TREE_PUBLIC (decl) && ! TREE_EXTERNAL (decl))
+      if (TREE_PUBLIC (decl)
+         && ! TREE_EXTERNAL (decl)
+         && GET_CODE (DECL_RTL (decl)) == MEM)
        {
          char label[MAX_ARTIFICIAL_LABEL_BYTES];
 
@@ -4064,7 +4066,7 @@ dwarfout_file_scope_decl (decl, set_finalizing)
          if (DECL_INITIAL (decl) == NULL)
            {
              /* Output a .debug_aranges entry for a public variable
-                which is tenatively defined in this compilation unit.  */
+                which is tentatively defined in this compilation unit.  */
 
              fputc ('\n', asm_out_file);
              ASM_OUTPUT_PUSH_SECTION (asm_out_file, ARANGES_SECTION);
@@ -4660,7 +4662,7 @@ dwarfout_finish ()
 
      In order to force the label `..D2' to get aligned to a 4 byte boundary,
      the trick used is to insert extra (otherwise useless) padding bytes
-     into the (null) DIE that we know must preceed the ..D2 label in the
+     into the (null) DIE that we know must precede the ..D2 label in the
      .debug section.  The amount of padding required can be anywhere between
      0 and 3 bytes.  The length word at the start of this DIE (i.e. the one
      with the padding) would normally contain the value 4, but now it will
index e59db661f240ae3eb29ccd031a7f7571eb2f69b9..331a48c6df59925af3eb19648fea548eac2e1e24 100644 (file)
 #include <setjmp.h>
 #endif
 
-/* Kludge around the possiblity that <stdio.h> includes <limits.h> */
+/* Kludge around the possibility that <stdio.h> includes <limits.h> */
 #ifdef CHAR_BIT
 #undef CHAR_BIT
 #undef CHAR_MAX
index 680e258c071b1609ca333373aea9eb20892f6523..a895a5b9a6a57c027a7b55db9d98fad981ce4b78 100644 (file)
@@ -1330,7 +1330,7 @@ gen_push_operand ()
    REG must be a hard register in this case.
 
    EXTRA is the amount in bytes of extra space to leave next to this arg.
-   This is ignored if an argument block has already been allocted.
+   This is ignored if an argument block has already been allocated.
 
    On a machine that lacks real push insns, ARGS_ADDR is the address of
    the bottom of the argument block for this call.  We use indexing off there
@@ -2880,7 +2880,7 @@ fixed_type_p (exp)
 
    EXPAND_INITIALIZER is much like EXPAND_SUM except that
    it also marks a label as absolutely required (it can't be dead).
-   This is used for outputting expressions used in intializers.  */
+   This is used for outputting expressions used in initializers.  */
 
 rtx
 expand_expr (exp, target, tmode, modifier)
@@ -5101,8 +5101,8 @@ expand_builtin (exp, target, subtarget, mode, ignore)
       target = allocate_dynamic_stack_space (op0, target, BITS_PER_UNIT);
 
       /* Record the new stack level for nonlocal gotos.  */
-      if (nonlocal_goto_stack_level != 0)
-       emit_move_insn (nonlocal_goto_stack_level, stack_pointer_rtx);
+      if (nonlocal_goto_handler_slot != 0)
+       emit_stack_save (SAVE_NONLOCAL, &nonlocal_goto_stack_level, 0);
       return target;
 
     case BUILT_IN_FFS:
index 3a140d2db9bae9f20f861bb8112ea210872842c1..da440ec3472d42b539800325d2b67c00e7aaf1b9 100644 (file)
@@ -442,7 +442,7 @@ extern void emit_0_to_1_insn ();
 /* Emit one rtl insn to compare two rtx's.  */
 extern void emit_cmp_insn ();
 
-/* Generate rtl to compate two rtx's, will call emit_cmp_insn.  */
+/* Generate rtl to compare two rtx's, will call emit_cmp_insn.  */
 extern rtx compare_from_rtx ();
 
 /* Emit some rtl insns to move data between rtx's, converting machine modes.
index 33be324bbb7f2fa8f98a412668edb855dcdee67b..006858391fc9008c64a68ca20b490d86b4efb01c 100755 (executable)
@@ -182,7 +182,7 @@ EOF
   fi
 fi
 
-# Fix this Sun file to avoid intefering with stddef.h.
+# Fix this Sun file to avoid interfering with stddef.h.
 file=sys/stdtypes.h
 if [ -r $file ] && [ ! -r ${LIB}/$file ]; then
   cp $file ${LIB}/$file >/dev/null 2>&1 || echo "Can't copy $file"
@@ -227,7 +227,7 @@ EOF
   fi
 fi
 
-# Fix this file to avoid intefering with stddef.h.
+# Fix this file to avoid interfering with stddef.h.
 file=sys/types.h
 if [ -r $file ] && [ ! -r ${LIB}/$file ]; then
   cp $file ${LIB}/$file >/dev/null 2>&1 || echo "Can't copy $file"
index b5a07fa0687989fbfe96dcdc29bbba0106e00da1..bc9096ffff12f2141ce5f59ce504243d94308f0f 100644 (file)
@@ -466,7 +466,7 @@ find_basic_blocks (f, nonlocal_label_list)
 
        BLOCK_NUM (insn) = i;
 
-       /* Don't separare a CALL_INSN from following CLOBBER insns.  This is
+       /* Don't separate a CALL_INSN from following CLOBBER insns.  This is
           a kludge that will go away when each CALL_INSN records its
           USE and CLOBBERs.  */
 
index 89baef5fbcc1f169306de045532003325eb42846..2b39c1153e5365b3d27946bdd4c88d6b1b0f0810 100644 (file)
@@ -19,7 +19,7 @@ the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  */
 
 /*@@ Fix lossage on folding division of big integers.  */
 
-/*@@ This file should be rewritten to use an arbitary precision
+/*@@ This file should be rewritten to use an arbitrary precision
   @@ representation for "struct tree_int_cst" and "struct tree_real_cst".
   @@ Perhaps the routines could also be used for bc/dc, and made a lib.
   @@ The routines that translate from the ap rep should
@@ -509,7 +509,7 @@ div_and_round_double (code, uns,
     }
   else {                       /* full double precision,
                                   with thanks to Don Knuth's
-                                  "Semi-Numericial Algorithms".  */
+                                  "Seminumerical Algorithms".  */
 #define BASE 256
     int quo_est, scale, num_hi_sig, den_hi_sig, quo_hi_sig;
 
@@ -549,7 +549,7 @@ div_and_round_double (code, uns,
 
     /* Main loop */
     for (i = quo_hi_sig; i > 0; i--) {
-      /* quess the next quotient digit, quo_est, by dividing the first
+      /* guess the next quotient digit, quo_est, by dividing the first
         two remaining dividend digits by the high order quotient digit.
         quo_est is never low and is at most 2 high.  */
 
@@ -2008,7 +2008,7 @@ make_bit_field_ref (inner, type, bitsize, bitpos, unsignedp)
    COMPARE_TYPE is the type of the comparison, and LHS and RHS
    are the left and right operands of the comparison, respectively.
 
-   If the optimization described above can be done, we return the resuling
+   If the optimization described above can be done, we return the resulting
    tree.  Otherwise we return zero.  */
 
 static tree
@@ -2239,7 +2239,7 @@ decode_field_reference (exp, pbitsize, pbitpos, pmode, punsignedp,
   return inner;
 }
 
-/* Return non-zero if MASK respresents a mask of SIZE ones in the low-order
+/* Return non-zero if MASK represents a mask of SIZE ones in the low-order
    bit positions.  */
 
 static int
index 45dc777581afdcf69656e7e80b68eee27bfa94a8..602544f1fd4a42d13ca0cef5b37cc0ffa963cdb2 100644 (file)
@@ -372,7 +372,7 @@ find_function_data (decl)
 /* Save the current context for compilation of a nested function.
    This is called from language-specific code.
    The caller is responsible for saving any language-specific status,
-   since this function knows only about language-indepedent variables.  */
+   since this function knows only about language-independent variables.  */
 
 void
 push_function_context ()
@@ -1178,7 +1178,7 @@ fixup_var_refs_1 (var, loc, insn, replacements)
              if (GET_CODE (x) == SIGN_EXTRACT)
                wanted_mode = insn_operand_mode[(int) CODE_FOR_extv][1];
 #endif
-             /* If we have a narrower mode, we can do someting.  */
+             /* If we have a narrower mode, we can do something.  */
              if (wanted_mode != VOIDmode
                  && GET_MODE_SIZE (wanted_mode) < GET_MODE_SIZE (is_mode))
                {
@@ -1338,7 +1338,7 @@ fixup_var_refs_1 (var, loc, insn, replacements)
                int width = INTVAL (XEXP (outerdest, 1));
                int pos = INTVAL (XEXP (outerdest, 2));
 
-               /* If we have a narrower mode, we can do someting.  */
+               /* If we have a narrower mode, we can do something.  */
                if (GET_MODE_SIZE (wanted_mode) < GET_MODE_SIZE (is_mode))
                  {
                    int offset = pos / BITS_PER_UNIT;
index 4b8a3be570eca0e8ae90c891522ae301a805d51d..6a6449d679caa53361e8d0961440ab44bd0fdc37 100644 (file)
--- a/gcc/gcc.c
+++ b/gcc/gcc.c
@@ -125,7 +125,7 @@ static int cross_compile = 0;
 static struct obstack obstack;
 
 /* This is the obstack to build an environment variable to pass to
-   collect2 that describes all of the relavant switches of what to
+   collect2 that describes all of the relevant switches of what to
    pass the compiler in building the list of pointers to constructors
    and destructors.  */
 
@@ -237,7 +237,7 @@ or with constant text in a single argument.
  %{S*:X} substitutes X if one or more switches whose names with -S are
        specified to CC.  Note that the tail part of the -S option
        (i.e. the part matched by the `*') will be substituted for each
-       occurance of %* within X.
+       occurrence of %* within X.
  %{S:X} substitutes X, but only if the -S switch was given to CC.
  %{!S:X} substitutes X, but only if the -S switch was NOT given to CC.
  %{|S:X} like %{S:X}, but if no S switch, substitute `-'.
@@ -549,7 +549,7 @@ static char *link_command_spec = "\
 #endif
 
 /* A vector of options to give to the linker.
-   These options are accumlated by %x
+   These options are accumulated by %x
    and substituted into the linker command with %X.  */
 static int n_linker_options;
 static char **linker_options;
index b7e1be9141d51be1ea324858218da5634ff9187d..7fea0f99b01b452e5459b1dd2ac91a43dd7c2683 100644 (file)
@@ -18,7 +18,7 @@ You should have received a copy of the GNU General Public License
 along with GNU CC; see the file COPYING.  If not, write to
 the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  */
 
-/* This program handles insn attribues and the DEFINE_DELAY and
+/* This program handles insn attributes and the DEFINE_DELAY and
    DEFINE_FUNCTION_UNIT definitions.
 
    It produces a series of functions named `get_attr_...', one for each insn
@@ -1344,7 +1344,7 @@ get_attr_value (value, attr, insn_code)
    Finally, for each [DEFINE_DELAY, slot #] pair, we compute an attribute that
    tells whether a given insn can be in that delay slot.
 
-   Normal attrbute filling and optimization expands these to contain the
+   Normal attribute filling and optimization expands these to contain the
    information needed to handle delay slots.  */
 
 static void
@@ -1387,8 +1387,8 @@ expand_delays ()
       make_internal_attr ("*delay_type", condexp, 1);
     }
 
-  /* For each delay possibility and delay slot, compute an eligability
-     attribute for non-anulled insns and for each type of annulled (annul
+  /* For each delay possibility and delay slot, compute an eligibility
+     attribute for non-annulled insns and for each type of annulled (annul
      if true and annul if false).  */
  for (delay = delays; delay; delay = delay->next)
    {
@@ -2386,7 +2386,7 @@ simplify_and_tree (exp, pterm, insn_code, insn_index)
   return exp;
 }
 \f
-/* Similiar to `simplify_and_tree', but for IOR trees.  */
+/* Similar to `simplify_and_tree', but for IOR trees.  */
 
 static rtx
 simplify_or_tree (exp, pterm, insn_code, insn_index)
@@ -3238,7 +3238,7 @@ gen_unit (def)
   struct function_unit_op *op;
 
   /* See if we have already seen this function unit.  If so, check that
-     the multipicity and simultaneity values are the same.  If not, make
+     the multiplicity and simultaneity values are the same.  If not, make
      a structure for this function unit.  */
   for (unit = units; unit; unit = unit->next)
     if (! strcmp (unit->name, XSTR (def, 0)))
@@ -3913,7 +3913,7 @@ write_indent (indent)
    the specified insn can be annulled if the branch is true, and likewise
    for `eligible_for_annul_false'.
 
-   KIND is a string distingushing these three cases ("delay", "annul_true",
+   KIND is a string distinguishing these three cases ("delay", "annul_true",
    or "annul_false").  */
 
 static void
@@ -4149,7 +4149,7 @@ write_function_unit_info ()
     }
 
   /* Now that all functions have been written, write the table describing
-     the function units.   The name is included for documenation purposes
+     the function units.   The name is included for documentation purposes
      only.  */
 
   printf ("struct function_unit_desc function_units[] = {\n");
index 7e88f3c1e16a41f11fedc69c94fe4d21c8f9a560..83a6d260fc4c56168d0e661876785fcf1d8fa814 100644 (file)
@@ -633,7 +633,7 @@ not_both_true (d1, d2, toplevel)
 
    We would like to list nodes testing for specific codes before those
    that test predicates to avoid unnecessary function calls.  Similarly,
-   tests for specific modes should preceed nodes that allow any mode.
+   tests for specific modes should precede nodes that allow any mode.
 
    This function returns the merit (with 0 being the best) of inserting
    a test involving the specified MODE and CODE after node P.  If P is
@@ -991,7 +991,7 @@ static char *indents[]
    of the same mode, we also group tests with the same code, followed by a
    group that does not test a code.
 
-   Occasionally, we cannot arbitarily reorder the tests so that multiple
+   Occasionally, we cannot arbitrarily reorder the tests so that multiple
    sequence of groups as described above are present.
 
    We generate two nested switch statements, the outer statement for
index be4b3f52fcad8d1fea4e9d0b11f41ced20dfb792..7034f2377cc52357e061f811011b60a415bb788a 100644 (file)
@@ -8,7 +8,7 @@
  * a way that is compatible with code compiled by the Pyramid Technology
  * C compiler.
  * As such, it depends strongly on the Pyramid conventions for
- * parameter passing.ct and indepenent implementation. 
+ * parameter passing.ct and independent implementation. 
  * These (somewhat bizarre) parameter-passing conventions are described
  * in the ``OSx Operating System Porting Guide''.
  * 
index 02c6613d407913e8473d08d10c00c09bf3907410..eee5f38e4a4822e75342c2dd1d41c193e6299e75 100644 (file)
@@ -1,5 +1,5 @@
 /* This is just like the default gvarargs.h
-   except for differences decribed below.  */
+   except for differences described below.  */
 
 /* Make this a macro rather than a typedef, so we can undef any other defn.  */
 #define va_list __va___list
index fca911e247f847f27656066cef0f88b452255f07..3f9b08190290ef3ae883850fc678707c8df26825 100644 (file)
@@ -91,7 +91,7 @@ static int *allocno_order;
 static int *allocno_size;
 
 /* Indexed by (pseudo) reg number, gives the number of another
-   lower-numbered pseudo reg which can share a hard reg with this peudo
+   lower-numbered pseudo reg which can share a hard reg with this pseudo
    *even if the two pseudos would otherwise appear to conflict*.  */
 
 static int *reg_may_share;
@@ -1458,7 +1458,7 @@ mark_reg_live_nc (regno, mode)
    try to set a preference.  If one of the two is a hard register and the other
    is a pseudo-register, mark the preference.
    
-   Note that we are not as agressive as local-alloc in trying to tie a
+   Note that we are not as aggressive as local-alloc in trying to tie a
    pseudo-register to a hard register.  */
 
 static void
index 1ba6c6b6141a120566366b0108c9a89ee6bd06df..60d74a148a84a42274cc8f1a37111d1f6a7b6a1b 100644 (file)
@@ -927,7 +927,7 @@ jump_optimize (f, cross_jump, noop_moves, after_regscan)
             INSN is the conditional branch around the arithmetic.  We set:
 
             TEMP is the arithmetic insn.
-            TEMP1 is the SET doing the arthmetic.
+            TEMP1 is the SET doing the arithmetic.
             TEMP2 is the operand being incremented or decremented.
             TEMP3 to the condition being tested.
             TEMP4 to the earliest insn used to find the condition.  */
@@ -1109,7 +1109,7 @@ jump_optimize (f, cross_jump, noop_moves, after_regscan)
 
             It is questionable whether we want this optimization anyways,
             since if the user wrote code like this because he/she knew that
-            the jump to label1 is taken most of the time, then rewritting
+            the jump to label1 is taken most of the time, then rewriting
             this gives slower code.  */
          /* @@ This should call get_condition to find the values being
             compared, instead of looking for a COMPARE insn when HAVE_cc0
@@ -2123,7 +2123,7 @@ get_label_before (insn)
     {
       rtx prev = PREV_INSN (insn);
 
-      /* Don't put a label between a CALL_INSN and USE insns that preceed
+      /* Don't put a label between a CALL_INSN and USE insns that precede
         it.  */
 
       if (GET_CODE (insn) == CALL_INSN
@@ -3266,7 +3266,7 @@ redirect_exp (loc, olabel, nlabel, insn)
 
    If the old jump target label (before the dispatch table) becomes unused,
    it and the dispatch table may be deleted.  In that case, find the insn
-   before the jump references that label and delete it and logical sucessors
+   before the jump references that label and delete it and logical successors
    too.  */
 
 void
@@ -3792,7 +3792,7 @@ rtx_equal_for_thread_p (x, y, yinsn)
       break;
 
     case MEM:
-      /* If memory modified or either volatile, not eqivalent.
+      /* If memory modified or either volatile, not equivalent.
         Else, check address. */
       if (modified_mem || MEM_VOLATILE_P (x) || MEM_VOLATILE_P (y))
        return 0;
index fc45217d11aa56667f6070aa8af4700a9bef07cb..72e7f5122dc5755cfff614c4c3c9d81a5900b549 100644 (file)
@@ -369,7 +369,7 @@ local_alloc ()
 
   /* This sets the maximum number of quantities we can have.  Quantity
      numbers start at zero and we can have one for each pseudo plus the
-     number of SCRATCHs in the largest block, in the worst case.  */
+     number of SCRATCHes in the largest block, in the worst case.  */
   max_qty = (max_regno - FIRST_PSEUDO_REGISTER) + max_scratch;
 
   /* Allocate vectors of temporary data.
@@ -1114,7 +1114,7 @@ block_alloc (b)
 
              if (GET_CODE (r0) == REG || GET_CODE (r0) == SUBREG)
                {
-                 /* We have two priorities for hard register preferrences.
+                 /* We have two priorities for hard register preferences.
                     If we have a move insn or an insn whose first input can
                     only be in the same register as the output, give
                     priority to an equivalence found from that insn.  */
@@ -1372,8 +1372,8 @@ block_alloc (b)
 \f
 /* Compare two quantities' priority for getting real registers.
    We give shorter-lived quantities higher priority.
-   Quantities with more references are also preferred, as are quanties that
-   require multiple registers.  This is the identical prioritorization as
+   Quantities with more references are also preferred, as are quantities that
+   require multiple registers.  This is the identical prioritization as
    done by global-alloc.
 
    We used to give preference to registers with *longer* lives, but using
@@ -1462,7 +1462,7 @@ combine_regs (usedreg, setreg, may_save_copy, insn_number, insn, already_dead)
   register int sqty;
 
   /* Determine the numbers and sizes of registers being used.  If a subreg
-     is present that does not change the entire register, don't conside
+     is present that does not change the entire register, don't consider
      this a copy insn.  */
 
   while (GET_CODE (usedreg) == SUBREG)
index 301a02dc08b6011de2654a2f91c0adf549eb66f3..f57b4c9a187f6967f9b2835d03557cdbcb397142 100644 (file)
@@ -121,7 +121,7 @@ struct iv_class {
   rtx initial_value;           /* Value of reg at loop start */
   rtx initial_test;            /* Test performed on BIV before loop */
   struct iv_class *next;       /* Links all class structures together */
-  rtx init_insn;               /* insn which intializes biv, 0 if none. */
+  rtx init_insn;               /* insn which initializes biv, 0 if none. */
   rtx init_set;                        /* SET of INIT_INSN, if any. */
   unsigned incremented : 1;    /* 1 if somewhere incremented/decremented */
   unsigned eliminable : 1;     /* 1 if plausible candidate for elimination. */
index 52a24893de060b7666dfc3030b0dfab251627c78..3ec2bcad18a6733c424003b802130c37e84b6cf8 100644 (file)
@@ -2668,7 +2668,7 @@ expand_fix (to, from, unsignedp)
      one plus the highest signed number, convert, and add it back.
 
      We only need to check all real modes, since we know we didn't find
-     anything with a wider inetger mode.  */
+     anything with a wider integer mode.  */
 
   if (unsignedp && GET_MODE_BITSIZE (GET_MODE (to)) <= HOST_BITS_PER_INT)
     for (fmode = GET_MODE (from); fmode != VOIDmode;
index d176142c0f0d5beb74ae995ef73c201de75259c2..edeae33896a4de2e492894fbc5ac7e8e83cbd425 100644 (file)
@@ -423,12 +423,12 @@ struct def_dec_info_struct {
 #ifndef UNPROTOIZE
   const f_list_chain_item * f_list_chain;      /* -> chain of formals lists */
   const def_dec_info * definition;     /* -> def/dec containing related def */
-  char                 is_static;      /* = 0 means visiblilty is "extern"  */
+  char                 is_static;      /* = 0 means visibility is "extern"  */
   char                 is_implicit;    /* != 0 for implicit func decl's */
   char                 written;        /* != 0 means written for implicit */
 #else /* !defined (UNPROTOIZE) */
   const char *         formal_names;   /* -> to list of names of formals */
-  const char *         formal_decls;   /* -> to string of formal declartions */
+  const char *         formal_decls;   /* -> to string of formal declarations */
 #endif /* !defined (UNPROTOIZE) */
 };
 
@@ -701,7 +701,7 @@ dupnstr (s, n)
   return ret_val;
 }
 
-/* Return a pointer to the first occurance of s2 within s1 or NULL if s2
+/* Return a pointer to the first occurrence of s2 within s1 or NULL if s2
    does not occur within s1.  Assume neither s1 nor s2 are null pointers.  */
 
 static const char *
@@ -829,7 +829,7 @@ file_could_be_converted (const char *path)
    convert and for which we don't issue the usual warnings.  */
 
 static int
-file_normally_convertable (const char *path)
+file_normally_convertible (const char *path)
 {
   char *const dir_name = alloca (strlen (path) + 1);
 
@@ -3060,7 +3060,7 @@ edit_fn_declaration (def_dec_p, clean_text_p)
          identifier we just found.  We ignore whitespace while hunting.  If
          the next non-whitespace byte we see is *not* an open left paren,
          then we must assume that we have been fooled and we start over
-         again accordingly.  Note that there is no guarrantee, that even if
+         again accordingly.  Note that there is no guarantee, that even if
          we do see the open paren, that we are in the right place.
          Programmers do the strangest things sometimes!  */
     
@@ -4363,7 +4363,7 @@ do_processing ()
 #endif /* !defined (UNPROTOIZE) */
 
   /* When we first read in all of the information from the aux_info files
-     we saved in it decending line number order, because that was likely to
+     we saved in it descending line number order, because that was likely to
      be faster.  Now however, we want the chains of def & dec records to
      appear in ascending line number order as we get further away from the
      file_info record that they hang from.  The following line causes all of
index b9fcdbe7aa266d950db51a579ce52b8fa8d9d39e..94c4eca74a69a25e98ed86812ae8847559de0184 100644 (file)
@@ -389,7 +389,7 @@ validate_replace_rtx_1 (loc, from, to, object)
         of the operand.  If we are replacing the operand with a VOIDmode
         constant, we lose the information.  So try to simplify the operation
         in that case.  If it fails, substitute in something that we know
-        won't be recogized.  */
+        won't be recognized.  */
       if (GET_MODE (to) == VOIDmode
          && (XEXP (x, 0) == from
              || (GET_CODE (XEXP (x, 0)) == REG && GET_CODE (from) == REG
@@ -465,7 +465,7 @@ validate_replace_rtx_1 (loc, from, to, object)
            wanted_mode = insn_operand_mode[(int) CODE_FOR_extv][1];
 #endif
 
-         /* If we have a narrower mode, we can do someting.  */
+         /* If we have a narrower mode, we can do something.  */
          if (wanted_mode != VOIDmode
              && GET_MODE_SIZE (wanted_mode) < GET_MODE_SIZE (is_mode))
            {
@@ -745,7 +745,7 @@ find_single_use (dest, insn, ploc)
    The main use of this function is as a predicate in match_operand
    expressions in the machine description.
 
-   For an explaination of this function's behavior for registers of
+   For an explanation of this function's behavior for registers of
    class NO_REGS, see the comment for `register_operand'.  */
 
 int
index af7af39acb9e4bceb44fcfa91c034eabb39d6c25..3f40732e079831678875122213e93df33484422a 100644 (file)
@@ -1266,7 +1266,7 @@ find_blocks (first)
   if (block + 1 != blocks)
     abort ();
 
-  /* generate all label references to the correspondending jump insn */
+  /* generate all label references to the corresponding jump insn */
   for (block = 0; block < blocks; block++)
     {
       insn = block_end[block];
@@ -2038,12 +2038,12 @@ subst_stack_regs_pat (insn, regstack, pat)
 \f
 /* Substitute hard regnums for any stack regs in INSN, which has
    N_INPUTS inputs and N_OUTPUTS outputs.  REGSTACK is the stack info
-   before the insn, and is updated with changes made here.  CONSTAINTS is
+   before the insn, and is updated with changes made here.  CONSTRAINTS is
    an array of the constraint strings used in the asm statement.
 
    OPERANDS is an array of the operands, and OPERANDS_LOC is a
    parallel array of where the operands were found.  The output operands
-   all preceed the input operands.
+   all precede the input operands.
 
    There are several requirements and assumptions about the use of
    stack-like regs in asm statements.  These rules are enforced by
index 544d78e23799b85eb31b6466b9eb11b161707f82..eda799c6406b7145e4e150785dae16c49dd76d4c 100644 (file)
@@ -359,7 +359,7 @@ static struct savings *savings;
 static char *prefclass;
 
 /* preferred_or_nothing[R] is nonzero if we should put pseudo number R
-   in memory if we can't get its perferred class.
+   in memory if we can't get its preferred class.
    This is available after `regclass' is run.  */
 
 static char *preferred_or_nothing;
index a9d82ae6a6e1016ea2b12c6d0dcf31888a8ee868..2095b0069c045dfa072020a518b97e6dfb10ce8b 100644 (file)
@@ -1076,7 +1076,7 @@ combine_reloads ()
   if (reload_in[output_reload] != 0)
     return;
 
-  /* If this reload is for an earlyclobber operand, we can't do anyting.  */
+  /* If this reload is for an earlyclobber operand, we can't do anything.  */
 
   for (i = 0; i < n_earlyclobbers; i++)
     if (reload_out[output_reload] == reload_earlyclobbers[i])
@@ -2026,7 +2026,7 @@ find_reloads (insn, replace, ind_levels, live_known, reload_reg_p)
              RTX_UNCHANGING_P (recog_operand[i])
                = RTX_UNCHANGING_P (regno_reg_rtx[regno]);
              find_reloads_address (GET_MODE (recog_operand[i]),
-                                   recog_operand_loc[i],
+             /* This is no longer a pseudo register.  To prevent later code
                                    XEXP (recog_operand[i], 0),
                                    &XEXP (recog_operand[i], 0),
                                    recog_operand[i], ind_levels);
@@ -3144,7 +3144,7 @@ alternative_allows_memconst (constraint, altnum)
 /* Scan X for memory references and scan the addresses for reloading.
    Also checks for references to "constant" regs that we want to eliminate
    and replaces them with the values they stand for.
-   We may alter X descructively if it contains a reference to such.
+   We may alter X destructively if it contains a reference to such.
    If X is just a constant reg, we return the equivalent value
    instead of X.
 
index bac9c2f29e121865bfd20280cc74ef4e583d6ada..8a719d58def55d57cc11101db25246ae9cded4f7 100644 (file)
@@ -2646,7 +2646,7 @@ eliminate_regs (x, mem_mode, insn)
            if (ep->to_rtx == SET_DEST (x)
                && SET_DEST (x) != frame_pointer_rtx)
              {
-               /* If it is being incrememented, adjust the offset.  Otherwise,
+               /* If it is being incremented, adjust the offset.  Otherwise,
                   this elimination can't be done.  */
                rtx src = SET_SRC (x);
 
index ebd208e1863819f9c7a22e7569c56f0be17c07df..ff8c24cbbc921e2eedda22aff7cac749100a236c 100644 (file)
@@ -30,7 +30,7 @@ the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  */
    optimization.  It should be the last pass to run before peephole.
    It serves primarily to fill delay slots of insns, typically branch
    and call insns.  Other insns typically involve more complicated
-   interractions of data dependencies and resource constraints, and
+   interactions of data dependencies and resource constraints, and
    are better handled by scheduling before register allocation (by the
    function `schedule_insns').
 
@@ -176,7 +176,7 @@ static struct resources end_of_function_needs;
 /* Points to the label before the end of the function.  */
 static rtx end_of_function_label;
 
-/* This structure is used to record livness information at the targets or
+/* This structure is used to record liveness information at the targets or
    fallthrough insns of branches.  We will most likely need the information
    at targets again, so save them in a hash table rather than recomputing them
    each time.  */
@@ -371,7 +371,7 @@ mark_referenced_resources (x, res, include_called_routine)
            }
        }
 
-      /* ... fall through to other INSN procesing ... */
+      /* ... fall through to other INSN processing ... */
 
     case INSN:
     case JUMP_INSN:
@@ -403,7 +403,7 @@ mark_referenced_resources (x, res, include_called_routine)
 
    We never mark the insn as modifying the condition code unless it explicitly
    SETs CC0 even though this is not totally correct.  The reason for this is
-   that we require a SET of CC0 to immediately preceed the reference to CC0.
+   that we require a SET of CC0 to immediately precede the reference to CC0.
    So if some other insn sets CC0 as a side-effect, we know it cannot affect
    our computation and thus may be placed in a delay slot.   */
 
@@ -911,8 +911,8 @@ note_delay_statistics (slots_filled, index)
 
    1.  When a conditional branch skips over only one instruction,
        use an annulling branch and put that insn in the delay slot.
-       Use either a branch that annulls when the condition if true or
-       invert the test with a branch that annulls when the condition is
+       Use either a branch that annuls when the condition if true or
+       invert the test with a branch that annuls when the condition is
        false.  This saves insns, since otherwise we must copy an insn
        from the L1 target.
 
@@ -3251,7 +3251,7 @@ relax_delay_slots (first)
          /* If the last insn in the delay slot sets CC0 for some insn,
             various code assumes that it is in a delay slot.  We could
             put it back where it belonged and delete the register notes,
-            but it doesn't seem worhwhile in this uncommon case.  */
+            but it doesn't seem worthwhile in this uncommon case.  */
          && ! find_reg_note (XVECEXP (pat, 0, XVECLEN (pat, 0) - 1),
                              REG_CC_USER, 0)
 #endif
index 2bd43eb1fb03c435bfae797fcfb39b9e11ae3d7b..dc9e2187a6f9bf5f17a1ebc519feceec3524e79d 100644 (file)
--- a/gcc/rtl.c
+++ b/gcc/rtl.c
@@ -128,7 +128,7 @@ enum machine_mode word_mode;        /* Mode whose width is BITS_PER_WORD */
 
 /* Indexed by rtx code, gives a sequence of operand-types for
    rtx's of that code.  The sequence is a C string in which
-   each charcter describes one operand.  */
+   each character describes one operand.  */
 
 char *rtx_format[] = {
   /* "*" undefined.
index 6088aa57a866ad909048a0897f820f86436ada32..86f866190b34fb666d897eff70314e1cc8416925 100644 (file)
@@ -81,7 +81,7 @@ DEF_RTL_EXPR(EXPR_LIST, "expr_list", "ee", 'x')
 DEF_RTL_EXPR(INSN_LIST, "insn_list", "ue", 'x')
 
 /* ----------------------------------------------------------------------
-   Expression types for machine descripions.
+   Expression types for machine descriptions.
    These do not appear in actual rtl code in the compiler.
    ---------------------------------------------------------------------- */
 
@@ -408,7 +408,7 @@ DEF_RTL_EXPR(ASM_OPERANDS, "asm_operands", "ssiEEsi", 'x')
    or inside an expression.  */
 DEF_RTL_EXPR(UNSPEC, "unspec", "Ei", 'x')
 
-/* Similiar, but a volatile operation and one which may trap.  */
+/* Similar, but a volatile operation and one which may trap.  */
 DEF_RTL_EXPR(UNSPEC_VOLATILE, "unspec_volatile", "Ei", 'x')
 
 /* Vector of addresses, stored as full words.  */
index 6936302917f0e12d6264394b7211dfb83ca00473..e649a8dc506cfb838d0b159d76d5ac76e1924371 100644 (file)
--- a/gcc/rtl.h
+++ b/gcc/rtl.h
@@ -32,9 +32,9 @@ enum rtx_code  {
 #include "rtl.def"             /* rtl expressions are documented here */
 #undef DEF_RTL_EXPR
 
-  LAST_AND_UNUSED_RTX_CODE};   /* A convienent way to get a value for
+  LAST_AND_UNUSED_RTX_CODE};   /* A convenient way to get a value for
                                   NUM_RTX_CODE.
-                                  Assumes default enum value assignement.  */
+                                  Assumes default enum value assignment.  */
 
 #define NUM_RTX_CODE ((int)LAST_AND_UNUSED_RTX_CODE)
                                /* The cast here, saves many elsewhere.  */
@@ -219,7 +219,7 @@ typedef struct rtvec_def{
 #define INSN_ANNULLED_BRANCH_P(INSN) ((INSN)->unchanging)
 
 /* 1 if insn is in a delay slot and is from the target of the branch.  If
-   the branch insn has INSN_ANULLED_BRANCH_P set, this insn should only be
+   the branch insn has INSN_ANNULLED_BRANCH_P set, this insn should only be
    executed if the branch is taken.  For annulled branches with this bit
    clear, the insn should be executed only if the branch is not taken.  */
 #define INSN_FROM_TARGET_P(INSN) ((INSN)->in_struct)
index ce4e59d22d972a13091a938362a339c46e96a2e4..819008a7d9355f4c94181c37a2ed55305bb09445 100644 (file)
@@ -173,7 +173,7 @@ static regset bb_live_regs;
 
 /* Regset telling whether a given register is live after the insn currently
    being scheduled.  Before processing an insn, this is equal to bb_live_regs
-   above.  This is used so that we can find regsiters that are newly born/dead
+   above.  This is used so that we can find registers that are newly born/dead
    after processing an insn.  */
 static regset old_live_regs;
 
@@ -442,7 +442,7 @@ find_symbolic_term (x)
            with addresses involving static variables.
        (2) static variables with different addresses cannot conflict.
 
-   Nice to notice that varying addresses cannot confict with fp if no
+   Nice to notice that varying addresses cannot conflict with fp if no
    local variables had their addresses taken, but that's too hard now.  */
 
 static int
@@ -503,15 +503,15 @@ memrefs_conflict_p (xsize, x, ysize, y, c)
 
   if (GET_CODE (x) == PLUS)
     {
-      /* The fact that X is canonnicallized means that this
-        PLUS rtx is canonnicallized.  */
+      /* The fact that X is canonicalized means that this
+        PLUS rtx is canonicalized.  */
       rtx x0 = XEXP (x, 0);
       rtx x1 = XEXP (x, 1);
 
       if (GET_CODE (y) == PLUS)
        {
-         /* The fact that Y is canonnicallized means that this
-            PLUS rtx is canonnicallized.  */
+         /* The fact that Y is canonicalized means that this
+            PLUS rtx is canonicalized.  */
          rtx y0 = XEXP (y, 0);
          rtx y1 = XEXP (y, 1);
 
@@ -543,8 +543,8 @@ memrefs_conflict_p (xsize, x, ysize, y, c)
     }
   else if (GET_CODE (y) == PLUS)
     {
-      /* The fact that Y is canonnicallized means that this
-        PLUS rtx is canonnicallized.  */
+      /* The fact that Y is canonicalized means that this
+        PLUS rtx is canonicalized.  */
       rtx y0 = XEXP (y, 0);
       rtx y1 = XEXP (y, 1);
 
@@ -1238,7 +1238,7 @@ sched_analyze_1 (x, insn)
          /* Flush all pending reads and writes to prevent the pending lists
             from getting any larger.  Insn scheduling runs too slowly when
             these lists get long.  The number 32 was chosen because it
-            seems like a resonable number.  When compiling GCC with itself,
+            seems like a reasonable number.  When compiling GCC with itself,
             this flush occurs 8 times for sparc, and 10 times for m88k using
             the number 32.  */
          flush_pending_lists (insn);
@@ -3125,7 +3125,7 @@ schedule_block (b, file)
            prev = PREV_INSN (insn);
            if (LINE_NOTE (note))
              {
-               /* Re-use the orignal line-number note. */
+               /* Re-use the original line-number note. */
                LINE_NOTE (note) = 0;
                PREV_INSN (note) = prev;
                NEXT_INSN (prev) = note;
@@ -3414,7 +3414,7 @@ update_flow_info (notes, first, last, orig_insn)
 
                  /* Sometimes need to convert REG_UNUSED notes to REG_DEAD
                     notes.  */
-                 /* ??? This won't handle mutiple word registers correctly,
+                 /* ??? This won't handle multiple word registers correctly,
                     but should be good enough for now.  */
                  if (REG_NOTE_KIND (note) == REG_UNUSED
                      && ! dead_or_set_p (insn, XEXP (note, 0)))
index 6eebfd1552ddcb41285f6caccc826c2e65e7808c..4f6c4e599667d4b4915d0e8fd70a6458200eae4b 100644 (file)
@@ -34,7 +34,7 @@ AT&T C compiler.  From the example below I would conclude the following:
 4. All structure .defs are emitted before the typedefs that refer to them.
 
 5. All top level static and external variable definitions are moved to the
-   end of file with all top level statics occuring first before externs.
+   end of file with all top level statics occurring first before externs.
 
 6. All undefined references are at the end of the file.
 */
index e2c52bfed17ed3dd5e9f35d026b1c3ac4464c155..a1a2267c5e36b6a9309e55e6cb2b0dc4da564566 100644 (file)
@@ -3966,7 +3966,7 @@ group_case_nodes (head)
 
 /* Take an ordered list of case nodes
    and transform them into a near optimal binary tree,
-   on the assumtion that any target code selection value is as
+   on the assumption that any target code selection value is as
    likely as any other.
 
    The transformation is performed by splitting the ordered
index be93945f595debee3a2b4238527551111ed9d502..9a724283ab3329a445366482d1a8c0c7791478a5 100644 (file)
@@ -1741,7 +1741,7 @@ compile_file (name)
          TIMEVAR (symout_time, sdbout_toplevel_data (decl));
 #endif /* SDB_DEBUGGING_INFO */
 #ifdef DWARF_DEBUGGING_INFO
-       /* Output DWARF information for file-scope tenative data object
+       /* Output DWARF information for file-scope tentative data object
           declarations, file-scope (extern) function declarations (which
           had no corresponding body) and file-scope tagged type declarations
           and definitions which have not yet been forced out.  */
index 57e5f8bfb4a2712acf9709f95293029e0fe25529..544a6a0af74cc655f8f9599e9166ee47e182b8a5 100644 (file)
@@ -26,7 +26,7 @@ the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  */
 enum tree_code {
 #include "tree.def"
 
-  LAST_AND_UNUSED_TREE_CODE    /* A convienent way to get a value for
+  LAST_AND_UNUSED_TREE_CODE    /* A convenient way to get a value for
                                   NUM_TREE_CODE.  */
 };
 
@@ -225,7 +225,7 @@ struct tree_common
 /* In a VAR_DECL or FUNCTION_DECL,
    nonzero means name is to be accessible from outside this module.
    In an identifier node, nonzero means a external declaration
-   accesible from outside this module was previously seen
+   accessible from outside this module was previously seen
    for this name in an inner scope.  */
 #define TREE_PUBLIC(NODE) ((NODE)->common.public_flag)
 
index f4719e3de723eca3c540990567d36c57a06b68c3..8a0b09aa62ddd390ea151dcc8764e371bd189ef0 100644 (file)
@@ -59,7 +59,7 @@ the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  */
 
    - On traditional architectures, unrolling a non-constant bound loop
      is a win if there is a giv whose only use is in memory addresses, the
-     memory addresses can be split, and hence giv incremenets can be
+     memory addresses can be split, and hence giv increments can be
      eliminated.
    - It is also a win if the loop is executed many times, and preconditioning
      can be performed for the loop.
@@ -205,7 +205,7 @@ static rtx fold_rtx_mult_add ();
 /* Try to unroll one loop and split induction variables in the loop.
 
    The loop is described by the arguments LOOP_END, INSN_COUNT, and
-   LOOP_START.  END_INSERT_BEDFORE indicates where insns should be added
+   LOOP_START.  END_INSERT_BEFORE indicates where insns should be added
    which need to be executed when the loop falls through.  STRENGTH_REDUCTION_P
    indicates whether information generated in the strength reduction pass
    is available.
@@ -688,7 +688,7 @@ unroll_loop (loop_end, insn_count, loop_start, end_insert_before,
 
      It is safe to do this here, since the extra registers created by the
      preconditioning code and find_splittable_regs will never be used
-     to accees the splittable_regs[] and addr_combined_regs[] arrays.  */
+     to access the splittable_regs[] and addr_combined_regs[] arrays.  */
 
   splittable_regs = (rtx *) alloca (maxregnum * sizeof (rtx));
   bzero (splittable_regs, maxregnum * sizeof (rtx));
@@ -1138,7 +1138,7 @@ unroll_loop (loop_end, insn_count, loop_start, end_insert_before,
   if (exit_label)
     emit_label_after (exit_label, loop_end);
 
-  /* If debugging, we must replicate the tree nodes corresponsing to the blocks
+  /* If debugging, we must replicate the tree nodes corresponding to the blocks
      inside the loop, so that the original one to one mapping will remain.  */
 
   if (write_symbols != NO_DEBUG)
@@ -1230,7 +1230,7 @@ precondition_loop_p (initial_value, final_value, increment, loop_start,
 
   /* Must ensure that final_value is invariant, so call invariant_p to
      check.  Before doing so, must check regno against max_reg_before_loop
-     to make sure that the register is in the range convered by invariant_p.
+     to make sure that the register is in the range covered by invariant_p.
      If it isn't, then it is most likely a biv/giv which by definition are
      not invariant.  */
   if ((GET_CODE (loop_final_value) == REG
@@ -1883,7 +1883,7 @@ emit_unrolled_add (dest_reg, src_reg, increment)
    is a backward branch in that range that branches to somewhere between
    LOOP_START and INSN.  Returns 0 otherwise.  */
 
-/* ??? This is quadratic algorithm.  Could be rewriten to be linear.
+/* ??? This is quadratic algorithm.  Could be rewritten to be linear.
    In practice, this is not a problem, because this function is seldom called,
    and uses a negligible amount of CPU time on average.  */
 
@@ -2926,7 +2926,7 @@ final_giv_value (v, loop_start, loop_end)
 
 
 /* Calculate the number of loop iterations.  Returns the exact number of loop
-   iterations if it can be calculated, otherwise retusns zero.  */
+   iterations if it can be calculated, otherwise returns zero.  */
 
 unsigned long
 loop_iterations (loop_start, loop_end)
@@ -3069,7 +3069,7 @@ loop_iterations (loop_start, loop_end)
      be addresses with the same base but different constant offsets.
      Final value must be invariant for this to work.
 
-     To do this, need someway to find the values of registers which are
+     To do this, need some way to find the values of registers which are
      invariant.  */
 
   /* Final_larger is 1 if final larger, 0 if they are equal, otherwise -1.  */
index da4849e7a162cd12c2daf15e0f11cf6da825f906..4ddbff78ab6b0c86eaf93f6022ed092a875b1ca4 100644 (file)
@@ -909,7 +909,7 @@ assemble_variable (decl, top_level, at_end)
      declaration.  When something like ".stabx  "aa:S-2",aa,133,0" is emitted 
      and `aa' hasn't been output yet, the assembler generates a stab entry with
      a value of zero, in addition to creating an unnecessary external entry
-     for `aa'.  Hence, we must pospone dbxout_symbol to here at the end.  */
+     for `aa'.  Hence, we must postpone dbxout_symbol to here at the end.  */
 
   /* File-scope global variables are output here.  */
   if (write_symbols == XCOFF_DEBUG && top_level)
index 1b42612270ad773a8ebbc6e0aa66a4f94d685983..bdee41c9ec8ea2cd46b182f7dd2eb24b5e142352 100644 (file)
@@ -433,7 +433,7 @@ xcoffout_end_epilogue (file)
   /* We need to pass the correct function size to .function, otherwise,
      the xas assembler can't figure out the correct size for the function
      aux entry.  So, we emit a label after the last instruction which can
-     be used by the .function psuedo op to calculate the function size.  */
+     be used by the .function pseudo op to calculate the function size.  */
 
   char *fname = XSTR (XEXP (DECL_RTL (current_function_decl), 0), 0);
   if (*fname == '*')
This page took 0.179739 seconds and 5 git commands to generate.