From f42f5a1b1ec954dd53ea998ff4188c1de8001b0d Mon Sep 17 00:00:00 2001
From: Bob Wilson <bwilson@gcc.gnu.org>
Date: Wed, 14 May 2003 18:37:26 +0000
Subject: [PATCH] lib2funcs.S (TRAMPOLINE_SIZE): Change from 49 to 59.

        * config/xtensa/lib2funcs.S (TRAMPOLINE_SIZE): Change from 49 to 59.
        * config/xtensa/xtensa-config.h (XCHAL_HAVE_CONST16,
        XCHAL_HAVE_L32R): New.
        * config/xtensa/xtensa-protos.h (non_const_move_operand,
        xtensa_load_constant, xtensa_function_prologue,
        xtensa_function_epilogue): Delete prototypes.
        (xtensa_expand_prologue): New.
        * config/xtensa/xtensa.c (frame_size_const,
        TARGET_ASM_FUNCTION_PROLOGUE, TARGET_MACHINE_DEPENDENT_REORG,
        non_const_move_operand, xtensa_load_constant, xtensa_reorg,
        xtensa_function_prologue): Delete.
        (add_operand, xtensa_mem_offset): Formatting.
        (move_operand): If the const16 option is available, allow any SFmode
        and SImode constants.
        (xtensa_emit_move_sequence): Inline the former contents of
        xtensa_load_constant with modifications to handle the const16 option.
        (override_options): Add xtensa_char_to_class['W'] and set it to
        the general register class only if the const16 option is enabled.
        Fix formatting.  Disallow PIC when using the const16 option.
        (print_operand): Reorganize to switch on "letter" instead of the
        RTL code.  Add output_operand_lossage calls for invalid cases.
        Add support for 't' and 'b' letters.
        (xtensa_expand_prologue): New function to replace
        xtensa_function_prologue and xtensa_reorg.
        (xtensa_function_epilogue): Declare this as static.  Delete code
        to print the retw.n or retw instruction.
        (xtensa_return_addr): Use A0_REG instead of 0.
        (xtensa_rtx_costs): Add costs for using the const16 option.
        * config/xtensa/xtensa.h (MASK_CONST16, TARGET_CONST16): New.
        (TARGET_DEFAULT): Add CONST16 if L32R instructions not available.
        (TARGET_SWITCHES): Add "const16" and "no-const16".
        (REG_CLASS_FROM_LETTER): Add comment about new 'W' letter.
        (EXTRA_CONSTRAINT): Change 'T' constraint to only apply when not
        using the const16 option.
        (TRAMPOLINE_TEMPLATE): Rewrite to avoid hardwired use of l32r insn.
        (TRAMPOLINE_SIZE): Change from 49 to 59.
        (INITIALIZE_TRAMPOLINE): Adjust offsets to match new trampoline.
        (GO_IF_LEGITIMATE_ADDRESS): Do not allow constant pool addresses
        when using the const16 option.
        (PREDICATE_CODES): Delete non_const_move_operand.
        * config/xtensa/xtensa.md (define_constants): Add A1_REG, A8_REG, and
        UNSPECV_ENTRY.
        (movdi, movdf): If the source is a constant, always expand to a
        sequence of movsi insns.
        (movdi_internal, movdf_internal): Remove alternative using l32r insns.
        (movsi_internal, movsf_internal): Add alternative using const16 insns.
        (movsf): Add const16 support.
        (entry, prologue, epilogue): New.
        (set_frame_ptr): Add missing mode for unspec_volatile operation.
        Likewise for subsequent split pattern.
        * doc/invoke.texi (Option Summary, Xtensa Options): Document new
        "-mconst16" and "-mno-const16" options.

From-SVN: r66809
---
 gcc/config/xtensa/lib2funcs.S     |   2 +-
 gcc/config/xtensa/xtensa-config.h |   4 +-
 gcc/config/xtensa/xtensa-protos.h |   5 +-
 gcc/config/xtensa/xtensa.c        | 484 +++++++++++++++---------------
 gcc/config/xtensa/xtensa.h        |  43 ++-
 gcc/config/xtensa/xtensa.md       | 253 +++++++++-------
 gcc/doc/invoke.texi               |  11 +
 7 files changed, 431 insertions(+), 371 deletions(-)

diff --git a/gcc/config/xtensa/lib2funcs.S b/gcc/config/xtensa/lib2funcs.S
index 659f8d0108b9..b424d7611e43 100644
--- a/gcc/config/xtensa/lib2funcs.S
+++ b/gcc/config/xtensa/lib2funcs.S
@@ -151,7 +151,7 @@ __xtensa_nonlocal_goto:
    make sure that the modified instructions are loaded into the instruction
    fetch buffer. */
 	
-#define TRAMPOLINE_SIZE 49
+#define TRAMPOLINE_SIZE 59
 
 	.text
 	.align	4
diff --git a/gcc/config/xtensa/xtensa-config.h b/gcc/config/xtensa/xtensa-config.h
index edeae978890a..a9c679f125ef 100644
--- a/gcc/config/xtensa/xtensa-config.h
+++ b/gcc/config/xtensa/xtensa-config.h
@@ -1,5 +1,5 @@
 /* Xtensa configuration settings.
-   Copyright (C) 2001,2002 Free Software Foundation, Inc.
+   Copyright (C) 2001,2002,2003 Free Software Foundation, Inc.
    Contributed by Bob Wilson (bwilson@tensilica.com) at Tensilica.
 
 ** NOTE: This file was automatically generated by the Xtensa Processor
@@ -27,6 +27,8 @@ Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
 
 #define XCHAL_HAVE_BE			1
 #define XCHAL_HAVE_DENSITY		1
+#define XCHAL_HAVE_CONST16		0
+#define XCHAL_HAVE_L32R			1
 #define XCHAL_HAVE_MAC16		0
 #define XCHAL_HAVE_MUL16		0
 #define XCHAL_HAVE_MUL32		0
diff --git a/gcc/config/xtensa/xtensa-protos.h b/gcc/config/xtensa/xtensa-protos.h
index 74620e037ea8..b5ca61144d05 100644
--- a/gcc/config/xtensa/xtensa-protos.h
+++ b/gcc/config/xtensa/xtensa-protos.h
@@ -57,11 +57,9 @@ extern int smalloffset_mem_p PARAMS ((rtx));
 extern int smalloffset_double_mem_p PARAMS ((rtx));
 extern int constantpool_address_p PARAMS ((rtx));
 extern int constantpool_mem_p PARAMS ((rtx));
-extern int non_const_move_operand PARAMS ((rtx, enum machine_mode));
 extern int const_float_1_operand PARAMS ((rtx, enum machine_mode));
 extern int fpmem_offset_operand PARAMS ((rtx, enum machine_mode));
 extern void xtensa_extend_reg PARAMS ((rtx, rtx));
-extern void xtensa_load_constant PARAMS ((rtx, rtx));
 extern int branch_operator PARAMS ((rtx, enum machine_mode));
 extern int ubranch_operator PARAMS ((rtx, enum machine_mode));
 extern int boolean_operator PARAMS ((rtx, enum machine_mode));
@@ -110,8 +108,7 @@ extern int xtensa_dbx_register_number PARAMS ((int));
 extern void override_options PARAMS ((void));
 extern long compute_frame_size PARAMS ((int));
 extern int xtensa_frame_pointer_required PARAMS ((void));
-extern void xtensa_function_prologue PARAMS ((FILE *, HOST_WIDE_INT));
-extern void xtensa_function_epilogue PARAMS ((FILE *, HOST_WIDE_INT));
+extern void xtensa_expand_prologue PARAMS ((void));
 extern void order_regs_for_local_alloc PARAMS ((void));
 
 #endif /* !__XTENSA_PROTOS_H__ */
diff --git a/gcc/config/xtensa/xtensa.c b/gcc/config/xtensa/xtensa.c
index cc5db918ecc9..25bf6475b460 100644
--- a/gcc/config/xtensa/xtensa.c
+++ b/gcc/config/xtensa/xtensa.c
@@ -198,29 +198,18 @@ static rtx gen_conditional_move PARAMS ((rtx));
 static rtx fixup_subreg_mem PARAMS ((rtx x));
 static enum machine_mode xtensa_find_mode_for_size PARAMS ((unsigned));
 static struct machine_function * xtensa_init_machine_status PARAMS ((void));
-static void xtensa_reorg PARAMS ((void));
 static void printx PARAMS ((FILE *, signed int));
+static void xtensa_function_epilogue PARAMS ((FILE *, HOST_WIDE_INT));
 static unsigned int xtensa_multibss_section_type_flags
   PARAMS ((tree, const char *, int));
 static void xtensa_select_rtx_section
   PARAMS ((enum machine_mode, rtx, unsigned HOST_WIDE_INT));
 static bool xtensa_rtx_costs PARAMS ((rtx, int, int, int *));
 
-static rtx frame_size_const;
 static int current_function_arg_words;
 static const int reg_nonleaf_alloc_order[FIRST_PSEUDO_REGISTER] =
   REG_ALLOC_ORDER;
 
-/* This macro generates the assembly code for function entry.
-   FILE is a stdio stream to output the code to.
-   SIZE is an int: how many units of temporary storage to allocate.
-   Refer to the array 'regs_ever_live' to determine which registers
-   to save; 'regs_ever_live[I]' is nonzero if register number I
-   is ever used in the function.  This macro is responsible for
-   knowing which registers should not be saved even if used.  */
-
-#undef TARGET_ASM_FUNCTION_PROLOGUE
-#define TARGET_ASM_FUNCTION_PROLOGUE xtensa_function_prologue
 
 /* This macro generates the assembly code for function exit,
    on machines that need it.  If FUNCTION_EPILOGUE is not defined
@@ -244,9 +233,6 @@ static const int reg_nonleaf_alloc_order[FIRST_PSEUDO_REGISTER] =
 #undef TARGET_ADDRESS_COST
 #define TARGET_ADDRESS_COST hook_int_rtx_0
 
-#undef TARGET_MACHINE_DEPENDENT_REORG
-#define TARGET_MACHINE_DEPENDENT_REORG xtensa_reorg
-
 struct gcc_target targetm = TARGET_INITIALIZER;
 
 
@@ -412,8 +398,7 @@ add_operand (op, mode)
      enum machine_mode mode;
 {
   if (GET_CODE (op) == CONST_INT)
-    return (xtensa_simm8 (INTVAL (op)) ||
-	    xtensa_simm8x256 (INTVAL (op)));
+    return (xtensa_simm8 (INTVAL (op)) || xtensa_simm8x256 (INTVAL (op)));
 
   return register_operand (op, mode);
 }
@@ -610,19 +595,23 @@ move_operand (op, mode)
      rtx op;
      enum machine_mode mode;
 {
-  if (register_operand (op, mode))
+  if (register_operand (op, mode)
+      || memory_operand (op, mode))
     return TRUE;
 
+  if (mode == SFmode)
+    return TARGET_CONST16 && CONSTANT_P (op);
+
   /* Accept CONSTANT_P_RTX, since it will be gone by CSE1 and
      result in 0/1.  */
   if (GET_CODE (op) == CONSTANT_P_RTX)
     return TRUE;
 
-  if (GET_CODE (op) == CONST_INT)
-    return xtensa_simm12b (INTVAL (op));
+  if (GET_CODE (op) == CONST_INT && xtensa_simm12b (INTVAL (op)))
+    return TRUE;
 
-  if (GET_CODE (op) == MEM)
-    return memory_address_p (mode, XEXP (op, 0));
+  if (mode == SImode)
+    return TARGET_CONST16 && CONSTANT_P (op);
 
   return FALSE;
 }
@@ -702,21 +691,6 @@ constantpool_mem_p (op)
 }
 
 
-int
-non_const_move_operand (op, mode)
-     rtx op;
-     enum machine_mode mode;
-{
-  if (register_operand (op, mode))
-    return 1;
-  if (GET_CODE (op) == SUBREG)
-    op = SUBREG_REG (op);
-  if (GET_CODE (op) == MEM)
-    return memory_address_p (mode, XEXP (op, 0));
-  return FALSE;
-}
-
-
 /* Accept the floating point constant 1 in the appropriate mode.  */
 
 int
@@ -778,32 +752,6 @@ xtensa_extend_reg (dst, src)
 }
 
 
-void
-xtensa_load_constant (dst, src)
-     rtx dst;
-     rtx src;
-{
-  enum machine_mode mode = GET_MODE (dst);
-  src = force_const_mem (SImode, src);
-
-  /* PC-relative loads are always SImode so we have to add a SUBREG if that
-     is not the desired mode */
-
-  if (mode != SImode)
-    {
-      if (register_operand (dst, mode))
-	dst = simplify_gen_subreg (SImode, dst, mode, 0);
-      else
-	{
-	  src = force_reg (SImode, src);
-	  src = gen_lowpart_SUBREG (mode, src);
-	}
-    }
-
-  emit_move_insn (dst, src);
-}
-
-
 int
 branch_operator (x, mode)
      rtx x;
@@ -899,8 +847,8 @@ xtensa_mem_offset (v, mode)
 	 moved in < "move_ratio" pieces.  The worst case is when the block is
 	 aligned but has a size of (3 mod 4) (does this happen?) so that the
 	 last piece requires a byte load/store.  */
-      return (xtensa_uimm8 (v) &&
-	      xtensa_uimm8 (v + MOVE_MAX * LARGEST_MOVE_RATIO));
+      return (xtensa_uimm8 (v)
+	      && xtensa_uimm8 (v + MOVE_MAX * LARGEST_MOVE_RATIO));
 
     case QImode:
       return xtensa_uimm8 (v);
@@ -1260,7 +1208,6 @@ xtensa_expand_scc (operands)
 
 
 /* Emit insns to move operands[1] into operands[0].
-
    Return 1 if we have written out everything that needs to be done to
    do the move.  Otherwise, return 0 and the caller will emit the move
    normally.  */
@@ -1275,8 +1222,27 @@ xtensa_emit_move_sequence (operands, mode)
       && (GET_CODE (operands[1]) != CONST_INT
 	  || !xtensa_simm12b (INTVAL (operands[1]))))
     {
-      xtensa_load_constant (operands[0], operands[1]);
-      return 1;
+      if (!TARGET_CONST16)
+	operands[1] = force_const_mem (SImode, operands[1]);
+
+      /* PC-relative loads are always SImode, and CONST16 is only
+	 supported in the movsi pattern, so add a SUBREG for any other
+	 (smaller) mode.  */
+
+      if (mode != SImode)
+	{
+	  if (register_operand (operands[0], mode))
+	    {
+	      operands[0] = simplify_gen_subreg (SImode, operands[0], mode, 0);
+	      emit_move_insn (operands[0], operands[1]);
+	      return 1;
+	    }
+	  else
+	    {
+	      operands[1] = force_reg (SImode, operands[1]);
+	      operands[1] = gen_lowpart_SUBREG (mode, operands[1]);
+	    }
+	}
     }
 
   if (!(reload_in_progress | reload_completed))
@@ -1299,6 +1265,7 @@ xtensa_emit_move_sequence (operands, mode)
   return 0;
 }
 
+
 static rtx
 fixup_subreg_mem (x)
      rtx x;
@@ -1848,6 +1815,7 @@ override_options ()
   xtensa_char_to_class['C'] = ((TARGET_MUL16) ? GR_REGS: NO_REGS);
   xtensa_char_to_class['D'] = ((TARGET_DENSITY) ? GR_REGS: NO_REGS);
   xtensa_char_to_class['d'] = ((TARGET_DENSITY) ? AR_REGS: NO_REGS);
+  xtensa_char_to_class['W'] = ((TARGET_CONST16) ? GR_REGS: NO_REGS);
 
   /* Set up array giving whether a given register can hold a given mode.  */
   for (mode = VOIDmode;
@@ -1862,8 +1830,8 @@ override_options ()
 	  int temp;
 
 	  if (ACC_REG_P (regno))
-	    temp = (TARGET_MAC16 &&
-		    (class == MODE_INT) && (size <= UNITS_PER_WORD));
+	    temp = (TARGET_MAC16
+		    && (class == MODE_INT) && (size <= UNITS_PER_WORD));
 	  else if (GP_REG_P (regno))
 	    temp = ((regno & 1) == 0 || (size <= UNITS_PER_WORD));
 	  else if (FP_REG_P (regno))
@@ -1879,9 +1847,19 @@ override_options ()
 
   init_machine_status = xtensa_init_machine_status;
 
-  /* Check PIC settings.  There's no need for -fPIC on Xtensa and
-     some targets need to always use PIC.  */
-  if (flag_pic > 1 || (XTENSA_ALWAYS_PIC))
+  /* Check PIC settings.  PIC is only supported when using L32R
+     instructions, and some targets need to always use PIC.  */
+  if (flag_pic && TARGET_CONST16)
+    error ("-f%s is not supported with CONST16 instructions",
+	   (flag_pic > 1 ? "PIC" : "pic"));
+  else if (XTENSA_ALWAYS_PIC)
+    {
+      if (TARGET_CONST16)
+	error ("PIC is required but not supported with CONST16 instructions");
+      flag_pic = 1;
+    }
+  /* There's no need for -fPIC (as opposed to -fpic) on Xtensa.  */
+  if (flag_pic > 1)
     flag_pic = 1;
 }
 
@@ -1918,6 +1896,8 @@ override_options ()
    'D'  REG, print second register of double-word register operand
    'N'  MEM, print address of next word following a memory operand
    'v'  MEM, if memory reference is volatile, output a MEMW before it
+   't'  any constant, add "@h" suffix for top 16 bits
+   'b'  any constant, add "@l" suffix for bottom 16 bits
 */
 
 static void
@@ -1936,94 +1916,146 @@ printx (file, val)
 
 
 void
-print_operand (file, op, letter)
+print_operand (file, x, letter)
      FILE *file;		/* file to write to */
-     rtx op;		/* operand to print */
+     rtx x;			/* operand to print */
      int letter;		/* %<letter> or 0 */
 {
-  enum rtx_code code;
-
-  if (! op)
+  if (!x)
     error ("PRINT_OPERAND null pointer");
 
-  code = GET_CODE (op);
-  switch (code)
+  switch (letter)
     {
-    case REG:
-    case SUBREG:
-      {
-	int regnum = xt_true_regnum (op);
-	if (letter == 'D')
-	  regnum++;
-	fprintf (file, "%s", reg_names[regnum]);
-	break;
-      }
+    case 'D':
+      if (GET_CODE (x) == REG || GET_CODE (x) == SUBREG)
+	fprintf (file, "%s", reg_names[xt_true_regnum (x) + 1]);
+      else
+	output_operand_lossage ("invalid %%D value");
+      break;
 
-    case MEM:
-      /* For a volatile memory reference, emit a MEMW before the
-	 load or store.  */
- 	if (letter == 'v')
-	  {
-	    if (MEM_VOLATILE_P (op) && TARGET_SERIALIZE_VOLATILE)
-	      fprintf (file, "memw\n\t");
-	    break;
-	  }
- 	else if (letter == 'N')
-	  {
-	    enum machine_mode mode;
-	    switch (GET_MODE (op))
-	      {
-	      case DFmode: mode = SFmode; break;
-	      case DImode: mode = SImode; break;
-	      default: abort ();
-	      }
-	    op = adjust_address (op, mode, 4);
-	  }
+    case 'v':
+      if (GET_CODE (x) == MEM)
+	{
+	  /* For a volatile memory reference, emit a MEMW before the
+	     load or store.  */
+	  if (MEM_VOLATILE_P (x) && TARGET_SERIALIZE_VOLATILE)
+	    fprintf (file, "memw\n\t");
+	}
+      else
+	output_operand_lossage ("invalid %%v value");
+      break;
 
-	output_address (XEXP (op, 0));
-	break;
+    case 'N':
+      if (GET_CODE (x) == MEM
+	  && (GET_MODE (x) == DFmode || GET_MODE (x) == DImode))
+	{
+	  x = adjust_address (x, GET_MODE (x) == DFmode ? SFmode : SImode, 4);
+	  output_address (XEXP (x, 0));
+	}
+      else
+	output_operand_lossage ("invalid %%N value");
+      break;
 
-    case CONST_INT:
-      switch (letter)
+    case 'K':
+      if (GET_CODE (x) == CONST_INT)
 	{
-	case 'K':
-	  {
-	    int num_bits = 0;
-	    unsigned val = INTVAL (op);
-	    while (val & 1)
-	      {
-		num_bits += 1;
-		val = val >> 1;
-	      }
-	    if ((val != 0) || (num_bits == 0) || (num_bits > 16))
-	      fatal_insn ("invalid mask", op);
+	  int num_bits = 0;
+	  unsigned val = INTVAL (x);
+	  while (val & 1)
+	    {
+	      num_bits += 1;
+	      val = val >> 1;
+	    }
+	  if ((val != 0) || (num_bits == 0) || (num_bits > 16))
+	    fatal_insn ("invalid mask", x);
 
-	    fprintf (file, "%d", num_bits);
-	    break;
-	  }
+	  fprintf (file, "%d", num_bits);
+	}
+      else
+	output_operand_lossage ("invalid %%K value");
+      break;
 
-	case 'L':
-	  fprintf (file, "%ld", (32 - INTVAL (op)) & 0x1f);
-	  break;
+    case 'L':
+      if (GET_CODE (x) == CONST_INT)
+	fprintf (file, "%ld", (32 - INTVAL (x)) & 0x1f);
+      else
+	output_operand_lossage ("invalid %%L value");
+      break;
 
-	case 'R':
-	  fprintf (file, "%ld", INTVAL (op) & 0x1f);
-	  break;
+    case 'R':
+      if (GET_CODE (x) == CONST_INT)
+	fprintf (file, "%ld", INTVAL (x) & 0x1f);
+      else
+	output_operand_lossage ("invalid %%R value");
+      break;
 
-	case 'x':
-	  printx (file, INTVAL (op));
-	  break;
+    case 'x':
+      if (GET_CODE (x) == CONST_INT)
+	printx (file, INTVAL (x));
+      else
+	output_operand_lossage ("invalid %%x value");
+      break;
 
-	case 'd':
-	default:
-	  fprintf (file, "%ld", INTVAL (op));
-	  break;
+    case 'd':
+      if (GET_CODE (x) == CONST_INT)
+	fprintf (file, "%ld", INTVAL (x));
+      else
+	output_operand_lossage ("invalid %%d value");
+      break;
 
+    case 't':
+    case 'b':
+      if (GET_CODE (x) == CONST_INT)
+	{
+	  printx (file, INTVAL (x));
+	  fputs (letter == 't' ? "@h" : "@l", file);
+	}
+      else if (GET_CODE (x) == CONST_DOUBLE)
+	{
+	  REAL_VALUE_TYPE r;
+	  REAL_VALUE_FROM_CONST_DOUBLE (r, x);
+	  if (GET_MODE (x) == SFmode)
+	    {
+	      long l;
+	      REAL_VALUE_TO_TARGET_SINGLE (r, l);
+	      fprintf (file, "0x%08lx@%c", l, letter == 't' ? 'h' : 'l');
+	    }
+	  else
+	    output_operand_lossage ("invalid %%t/%%b value");
+	}
+      else if (GET_CODE (x) == CONST)
+	{
+	  /* X must be a symbolic constant on ELF.  Write an expression
+	     suitable for 'const16' that sets the high or low 16 bits.  */
+	  if (GET_CODE (XEXP (x, 0)) != PLUS
+	      || (GET_CODE (XEXP (XEXP (x, 0), 0)) != SYMBOL_REF
+		  && GET_CODE (XEXP (XEXP (x, 0), 0)) != LABEL_REF)
+	      || GET_CODE (XEXP (XEXP (x, 0), 1)) != CONST_INT)
+	    output_operand_lossage ("invalid %%t/%%b value");
+	  print_operand (file, XEXP (XEXP (x, 0), 0), 0);
+	  fputs (letter == 't' ? "@h" : "@l", file);
+	  /* There must be a non-alphanumeric character between 'h' or 'l'
+	     and the number.  The '-' is added by print_operand() already.  */
+	  if (INTVAL (XEXP (XEXP (x, 0), 1)) >= 0)
+	    fputs ("+", file);
+	  print_operand (file, XEXP (XEXP (x, 0), 1), 0);
+	}
+      else
+	{ 
+	  output_addr_const (file, x);
+	  fputs (letter == 't' ? "@h" : "@l", file);
 	}
       break;
 
     default:
-      output_addr_const (file, op);
+      if (GET_CODE (x) == REG || GET_CODE (x) == SUBREG)
+	fprintf (file, "%s", reg_names[xt_true_regnum (x)]);
+      else if (GET_CODE (x) == MEM)
+	output_address (XEXP (x, 0));
+      else if (GET_CODE (x) == CONST_INT)
+	fprintf (file, "%ld", INTVAL (x));
+      else
+	output_addr_const (file, x);
     }
 }
 
@@ -2191,129 +2223,85 @@ xtensa_frame_pointer_required ()
 }
 
 
-/* If the stack frame size is too big to fit in the immediate field of
-   the ENTRY instruction, we need to store the frame size in the
-   constant pool.  However, the code in xtensa_function_prologue runs too
-   late to be able to add anything to the constant pool.  Since the
-   final frame size isn't known until reload is complete, this seems
-   like the best place to do it.
+void
+xtensa_expand_prologue ()
+{
+  HOST_WIDE_INT total_size;
+  rtx size_rtx;
 
-   There may also be some fixup required if there is an incoming argument
-   in a7 and the function requires a frame pointer. */
+  total_size = compute_frame_size (get_frame_size ());
+  size_rtx = GEN_INT (total_size);
 
-static void
-xtensa_reorg ()
-{
-  rtx first, insn, set_frame_ptr_insn = 0;
-    
-  unsigned long tsize = compute_frame_size (get_frame_size ());
-  first = get_insns ();
-  if (tsize < (1 << (12+3)))
-    frame_size_const = 0;
+  if (total_size < (1 << (12+3)))
+    emit_insn (gen_entry (size_rtx, size_rtx));
   else
     {
-      frame_size_const = force_const_mem (SImode, GEN_INT (tsize - 16));;
-
-      /* make sure the constant is used so it doesn't get eliminated
-	 from the constant pool */
-      emit_insn_before (gen_rtx_USE (SImode, frame_size_const), first);
+      /* Use a8 as a temporary since a0-a7 may be live.  */
+      rtx tmp_reg = gen_rtx_REG (Pmode, A8_REG);
+      emit_insn (gen_entry (size_rtx, GEN_INT (MIN_FRAME_SIZE)));
+      emit_move_insn (tmp_reg, GEN_INT (total_size - MIN_FRAME_SIZE));
+      emit_insn (gen_subsi3 (tmp_reg, stack_pointer_rtx, tmp_reg));
+      emit_move_insn (stack_pointer_rtx, tmp_reg);
     }
 
-  if (!frame_pointer_needed)
-    return;
-
-  /* Search all instructions, looking for the insn that sets up the
-     frame pointer.  This search will fail if the function does not
-     have an incoming argument in $a7, but in that case, we can just
-     set up the frame pointer at the very beginning of the
-     function.  */
-
-  for (insn = first; insn; insn = NEXT_INSN (insn))
+  if (frame_pointer_needed)
     {
-      rtx pat;
+      rtx first, insn, set_frame_ptr_insn = 0;
 
-      if (!INSN_P (insn))
-	continue;
+      push_topmost_sequence ();
+      first = get_insns ();
+      pop_topmost_sequence ();
 
-      pat = PATTERN (insn);
-      if (GET_CODE (pat) == SET
-	  && GET_CODE (SET_SRC (pat)) == UNSPEC_VOLATILE
-	  && (XINT (SET_SRC (pat), 1) == UNSPECV_SET_FP))
-	{
-	  set_frame_ptr_insn = insn;
-	  break;
-	}
-    }
+      /* Search all instructions, looking for the insn that sets up the
+	 frame pointer.  This search will fail if the function does not
+	 have an incoming argument in $a7, but in that case, we can just
+	 set up the frame pointer at the very beginning of the
+	 function.  */
 
-  if (set_frame_ptr_insn)
-    {
-      /* for all instructions prior to set_frame_ptr_insn, replace
-	 hard_frame_pointer references with stack_pointer */
-      for (insn = first; insn != set_frame_ptr_insn; insn = NEXT_INSN (insn))
+      for (insn = first; insn; insn = NEXT_INSN (insn))
 	{
-	  if (INSN_P (insn))
-	    PATTERN (insn) = replace_rtx (copy_rtx (PATTERN (insn)),
-					  hard_frame_pointer_rtx,
-					  stack_pointer_rtx);
-	}
-    }
-  else
-    {
-      /* emit the frame pointer move immediately after the NOTE that starts
-	 the function */
-      emit_insn_after (gen_movsi (hard_frame_pointer_rtx,
-				  stack_pointer_rtx), first);
-    }
-}
-
+	  rtx pat;
 
-/* Set up the stack and frame (if desired) for the function.  */
+	  if (!INSN_P (insn))
+	    continue;
 
-void
-xtensa_function_prologue (file, size)
-     FILE *file;
-     HOST_WIDE_INT size ATTRIBUTE_UNUSED;
-{
-  unsigned long tsize = compute_frame_size (get_frame_size ());
-
-  if (frame_pointer_needed)
-    fprintf (file, "\t.frame\ta7, %ld\n", tsize);
-  else
-    fprintf (file, "\t.frame\tsp, %ld\n", tsize);
- 
-
-  if (tsize < (1 << (12+3)))
-    {
-      fprintf (file, "\tentry\tsp, %ld\n", tsize);
-    }
-  else
-    {
-      fprintf (file, "\tentry\tsp, 16\n");
+	  pat = PATTERN (insn);
+	  if (GET_CODE (pat) == SET
+	      && GET_CODE (SET_SRC (pat)) == UNSPEC_VOLATILE
+	      && (XINT (SET_SRC (pat), 1) == UNSPECV_SET_FP))
+	    {
+	      set_frame_ptr_insn = insn;
+	      break;
+	    }
+	}
 
-      /* use a8 as a temporary since a0-a7 may be live */
-      fprintf (file, "\tl32r\ta8, ");
-      print_operand (file, frame_size_const, 0);
-      fprintf (file, "\n\tsub\ta8, sp, a8\n");
-      fprintf (file, "\tmovsp\tsp, a8\n");
+      if (set_frame_ptr_insn)
+	{
+	  /* For all instructions prior to set_frame_ptr_insn, replace
+	     hard_frame_pointer references with stack_pointer.  */
+	  for (insn = first;
+	       insn != set_frame_ptr_insn;
+	       insn = NEXT_INSN (insn))
+	    {
+	      if (INSN_P (insn))
+		PATTERN (insn) = replace_rtx (copy_rtx (PATTERN (insn)),
+					      hard_frame_pointer_rtx,
+					      stack_pointer_rtx);
+	    }
+	}
+      else
+	emit_move_insn (hard_frame_pointer_rtx, stack_pointer_rtx);
     }
 }
 
 
-/* Do any necessary cleanup after a function to restore
-   stack, frame, and regs.  */
+/* Clear variables at function end.  */
 
 void
 xtensa_function_epilogue (file, size)
-     FILE *file;
+     FILE *file ATTRIBUTE_UNUSED;
      HOST_WIDE_INT size ATTRIBUTE_UNUSED;
 {
-  rtx insn = get_last_insn ();
-  /* If the last insn was a BARRIER, we don't have to write anything.  */
-  if (GET_CODE (insn) == NOTE)
-    insn = prev_nonnote_insn (insn);
-  if (insn == 0 || GET_CODE (insn) != BARRIER)
-    fprintf (file, TARGET_DENSITY ? "\tretw.n\n" : "\tretw\n");
-
   xtensa_current_frame_size = 0;
 }
 
@@ -2326,7 +2314,7 @@ xtensa_return_addr (count, frame)
   rtx result, retaddr;
 
   if (count == -1)
-    retaddr = gen_rtx_REG (Pmode, 0);
+    retaddr = gen_rtx_REG (Pmode, A0_REG);
   else
     {
       rtx addr = plus_constant (frame, -4 * UNITS_PER_WORD);
@@ -2882,6 +2870,8 @@ xtensa_rtx_costs (x, code, outer_code, total)
 	}
       if (xtensa_simm12b (INTVAL (x)))
 	*total = 5;
+      else if (TARGET_CONST16)
+	*total = COSTS_N_INSNS (2);
       else
 	*total = 6;
       return true;
@@ -2889,11 +2879,17 @@ xtensa_rtx_costs (x, code, outer_code, total)
     case CONST:
     case LABEL_REF:
     case SYMBOL_REF:
-      *total = 5;
+      if (TARGET_CONST16)
+	*total = COSTS_N_INSNS (2);
+      else
+	*total = 5;
       return true;
 
     case CONST_DOUBLE:
-      *total = 7;
+      if (TARGET_CONST16)
+	*total = COSTS_N_INSNS (4);
+      else
+	*total = 7;
       return true;
 
     case MEM:
diff --git a/gcc/config/xtensa/xtensa.h b/gcc/config/xtensa/xtensa.h
index 16fd3d69dd0a..0cce6634f637 100644
--- a/gcc/config/xtensa/xtensa.h
+++ b/gcc/config/xtensa/xtensa.h
@@ -61,6 +61,7 @@ extern unsigned xtensa_current_frame_size;
 #define MASK_HARD_FLOAT_RSQRT	0x00004000	/* floating-point recip sqrt */
 #define MASK_NO_FUSED_MADD	0x00008000	/* avoid f-p mul/add */
 #define MASK_SERIALIZE_VOLATILE 0x00010000	/* serialize volatile refs */
+#define MASK_CONST16		0x00020000	/* use CONST16 instruction */
 
 /* Macros used in the machine description to test the flags.  */
 
@@ -81,12 +82,14 @@ extern unsigned xtensa_current_frame_size;
 #define TARGET_HARD_FLOAT_RSQRT	(target_flags & MASK_HARD_FLOAT_RSQRT)
 #define TARGET_NO_FUSED_MADD	(target_flags & MASK_NO_FUSED_MADD)
 #define TARGET_SERIALIZE_VOLATILE (target_flags & MASK_SERIALIZE_VOLATILE)
+#define TARGET_CONST16		(target_flags & MASK_CONST16)
 
 /* Default target_flags if no switches are specified  */
 
 #define TARGET_DEFAULT (						\
   (XCHAL_HAVE_BE	? MASK_BIG_ENDIAN : 0) |			\
   (XCHAL_HAVE_DENSITY	? MASK_DENSITY : 0) |				\
+  (XCHAL_HAVE_L32R	? 0 : MASK_CONST16) |				\
   (XCHAL_HAVE_MAC16	? MASK_MAC16 : 0) |				\
   (XCHAL_HAVE_MUL16	? MASK_MUL16 : 0) |				\
   (XCHAL_HAVE_MUL32	? MASK_MUL32 : 0) |				\
@@ -114,6 +117,10 @@ extern unsigned xtensa_current_frame_size;
     N_("Use the Xtensa code density option")},				\
   {"no-density",		-MASK_DENSITY,				\
     N_("Do not use the Xtensa code density option")},			\
+  {"const16",			MASK_CONST16,				\
+    N_("Use CONST16 instruction to load constants")},			\
+  {"no-const16",		-MASK_CONST16,				\
+    N_("Use PC-relative L32R instruction to load constants")},		\
   {"mac16",			MASK_MAC16,				\
     N_("Use the Xtensa MAC16 option")},					\
   {"no-mac16",			-MASK_MAC16,				\
@@ -629,6 +636,7 @@ extern const enum reg_class xtensa_regno_to_class[FIRST_PSEUDO_REGISTER];
    'A'	MAC16 accumulator (only if MAC16 option enabled)
    'B'	general-purpose registers (only if sext instruction enabled)
    'C'  general-purpose registers (only if mul16 option enabled)
+   'W'  general-purpose registers (only if const16 option enabled)
    'b'	coprocessor boolean registers
    'f'	floating-point registers
 */
@@ -699,7 +707,7 @@ extern enum reg_class xtensa_char_to_class[256];
         && REGNO (OP) >= FIRST_PSEUDO_REGISTER)				\
    : ((CODE) == 'R') ? smalloffset_mem_p (OP)				\
    : ((CODE) == 'S') ? smalloffset_double_mem_p (OP)			\
-   : ((CODE) == 'T') ? constantpool_mem_p (OP)				\
+   : ((CODE) == 'T') ? !TARGET_CONST16 && constantpool_mem_p (OP)	\
    : ((CODE) == 'U') ? !constantpool_mem_p (OP)				\
    : FALSE)
 
@@ -968,24 +976,27 @@ typedef struct xtensa_args {
     fprintf (STREAM, "\t.begin no-generics\n");				\
     fprintf (STREAM, "\tentry\tsp, %d\n", MIN_FRAME_SIZE);		\
 									\
-    /* GCC isn't prepared to deal with data at the beginning of the	\
-       trampoline, and the Xtensa l32r instruction requires that the	\
-       constant pool be located before the code.  We put the constant	\
-       pool in the middle of the trampoline and jump around it. */ 	\
+    /* save the return address */					\
+    fprintf (STREAM, "\tmov\ta10, a0\n");				\
 									\
-    fprintf (STREAM, "\tj\t.Lskipconsts\n");				\
+    /* Use a CALL0 instruction to skip past the constants and in the	\
+       process get the PC into A0.  This allows PC-relative access to	\
+       the constants without relying on L32R, which may not always be	\
+       available.  */							\
+									\
+    fprintf (STREAM, "\tcall0\t.Lskipconsts\n");			\
     fprintf (STREAM, "\t.align\t4\n");					\
-    fprintf (STREAM, ".Lfnaddr:%s0\n", integer_asm_op (4, TRUE));	\
     fprintf (STREAM, ".Lchainval:%s0\n", integer_asm_op (4, TRUE));	\
+    fprintf (STREAM, ".Lfnaddr:%s0\n", integer_asm_op (4, TRUE));	\
     fprintf (STREAM, ".Lskipconsts:\n");				\
 									\
     /* store the static chain */					\
-    fprintf (STREAM, "\tl32r\ta8, .Lchainval\n");			\
-    fprintf (STREAM, "\ts32i\ta8, sp, %d\n",				\
-	     MIN_FRAME_SIZE - (5 * UNITS_PER_WORD));			\
+    fprintf (STREAM, "\taddi\ta0, a0, 3\n");				\
+    fprintf (STREAM, "\tl32i\ta8, a0, 0\n");				\
+    fprintf (STREAM, "\ts32i\ta8, sp, %d\n", MIN_FRAME_SIZE - 20);	\
 									\
     /* set the proper stack pointer value */				\
-    fprintf (STREAM, "\tl32r\ta8, .Lfnaddr\n");				\
+    fprintf (STREAM, "\tl32i\ta8, a0, 4\n");				\
     fprintf (STREAM, "\tl32i\ta9, a8, 0\n");				\
     fprintf (STREAM, "\textui\ta9, a9, %d, 12\n",			\
 	     TARGET_BIG_ENDIAN ? 8 : 12);				\
@@ -994,6 +1005,9 @@ typedef struct xtensa_args {
     fprintf (STREAM, "\tsub\ta9, sp, a9\n");				\
     fprintf (STREAM, "\tmovsp\tsp, a9\n");				\
 									\
+    /* restore the return address */					\
+    fprintf (STREAM, "\tmov\ta0, a10\n");				\
+									\
     /* jump to the instruction following the entry */			\
     fprintf (STREAM, "\taddi\ta8, a8, 3\n");				\
     fprintf (STREAM, "\tjx\ta8\n");					\
@@ -1001,7 +1015,7 @@ typedef struct xtensa_args {
   } while (0)
 
 /* Size in bytes of the trampoline, as an integer.  */
-#define TRAMPOLINE_SIZE 49
+#define TRAMPOLINE_SIZE 59
 
 /* Alignment required for trampolines, in bits.  */
 #define TRAMPOLINE_ALIGNMENT (32)
@@ -1010,8 +1024,8 @@ typedef struct xtensa_args {
 #define INITIALIZE_TRAMPOLINE(ADDR, FUNC, CHAIN)			\
   do {									\
     rtx addr = ADDR;							\
-    emit_move_insn (gen_rtx_MEM (SImode, plus_constant (addr, 8)), FUNC); \
     emit_move_insn (gen_rtx_MEM (SImode, plus_constant (addr, 12)), CHAIN); \
+    emit_move_insn (gen_rtx_MEM (SImode, plus_constant (addr, 16)), FUNC); \
     emit_library_call (gen_rtx (SYMBOL_REF, Pmode, "__xtensa_sync_caches"), \
 		       0, VOIDmode, 1, addr, Pmode);			\
   } while (0)
@@ -1128,7 +1142,7 @@ typedef struct xtensa_args {
 									\
     /* allow constant pool addresses */					\
     if ((MODE) != BLKmode && GET_MODE_SIZE (MODE) >= UNITS_PER_WORD	\
-	&& constantpool_address_p (xinsn))				\
+	&& !TARGET_CONST16 && constantpool_address_p (xinsn))		\
       goto LABEL;							\
 									\
     while (GET_CODE (xinsn) == SUBREG)					\
@@ -1330,7 +1344,6 @@ typedef struct xtensa_args {
   {"call_insn_operand",		{ CONST_INT, CONST, SYMBOL_REF, REG }},	\
   {"move_operand",		{ REG, SUBREG, MEM, CONST_INT, CONST_DOUBLE, \
 				  CONST, SYMBOL_REF, LABEL_REF }},	\
-  {"non_const_move_operand",	{ REG, SUBREG, MEM }},			\
   {"const_float_1_operand",	{ CONST_DOUBLE }},			\
   {"branch_operator",		{ EQ, NE, LT, GE }},			\
   {"ubranch_operator",		{ LTU, GEU }},				\
diff --git a/gcc/config/xtensa/xtensa.md b/gcc/config/xtensa/xtensa.md
index 7a39cab1e4d2..aa5896ed5118 100644
--- a/gcc/config/xtensa/xtensa.md
+++ b/gcc/config/xtensa/xtensa.md
@@ -29,13 +29,16 @@
 
 (define_constants [
   (A0_REG		0)
+  (A1_REG		1)
   (A7_REG		7)
+  (A8_REG		8)
 
   (UNSPEC_NSAU		1)
   (UNSPEC_NOP		2)
   (UNSPEC_PLT		3)
   (UNSPEC_RET_ADDR	4)
   (UNSPECV_SET_FP	1)
+  (UNSPECV_ENTRY	2)
 ])
 
 ;;
@@ -919,21 +922,19 @@
   ""
   "
 {
-  if (CONSTANT_P (operands[1]))
+  if (CONSTANT_P (operands[1])
+      && register_operand (operands[0], DImode))
     {
       rtx src0, src1, dst0, dst1;
-      if ((dst0 = operand_subword (operands[0], 0, 1, DImode))
-	  && (src0 = operand_subword (operands[1], 0, 1, DImode))
-	  && (dst1 = operand_subword (operands[0], 1, 1, DImode))
-	  && (src1 = operand_subword (operands[1], 1, 1, DImode)))
-	{
-	  emit_insn (gen_movsi (dst0, src0));
-	  emit_insn (gen_movsi (dst1, src1));
-	  DONE;
-	}
-      else
-	/* any other constant will be loaded from memory */
-	operands[1] = force_const_mem (DImode, operands[1]);
+      dst0 = operand_subword (operands[0], 0, 1, DImode);
+      src0 = operand_subword (operands[1], 0, 1, DImode);
+      dst1 = operand_subword (operands[0], 1, 1, DImode);
+      src1 = operand_subword (operands[1], 1, 1, DImode);
+      if (!dst0 || !src0 || !dst1 || !src1)
+        abort ();
+      emit_insn (gen_movsi (dst0, src0));
+      emit_insn (gen_movsi (dst1, src1));
+      DONE;
     }
 
   if (!(reload_in_progress | reload_completed))
@@ -948,60 +949,56 @@
 }")
 
 (define_insn "movdi_internal"
-  [(set (match_operand:DI 0 "nonimmed_operand" "=D,D,S,a,a,a,U")
-	(match_operand:DI 1 "non_const_move_operand" "d,S,d,r,T,U,r"))]
+  [(set (match_operand:DI 0 "nonimmed_operand" "=D,D,S,a,a,U")
+	(match_operand:DI 1 "nonimmed_operand" "d,S,d,r,U,r"))]
   "register_operand (operands[0], DImode)
    || register_operand (operands[1], DImode)"
   "*
 {
+  rtx dstreg;
   switch (which_alternative)
     {
     case 0: return \"mov.n\\t%0, %1\;mov.n\\t%D0, %D1\";
     case 2: return \"%v0s32i.n\\t%1, %0\;s32i.n\\t%D1, %N0\";
     case 3: return \"mov\\t%0, %1\;mov\\t%D0, %D1\";
-    case 6: return \"%v0s32i\\t%1, %0\;s32i\\t%D1, %N0\";
+    case 5: return \"%v0s32i\\t%1, %0\;s32i\\t%D1, %N0\";
 
     case 1:
     case 4:
-    case 5:
-      {
-	/* Check if the first half of the destination register is used
-	   in the source address.  If so, reverse the order of the loads
-	   so that the source address doesn't get clobbered until it is
-	   no longer needed. */
-
-	rtx dstreg = operands[0];
-	if (GET_CODE (dstreg) == SUBREG)
-	  dstreg = SUBREG_REG (dstreg);
-	if (GET_CODE (dstreg) != REG)
-	  abort();
-
-	if (reg_mentioned_p (dstreg, operands[1]))
-	  {
-	    switch (which_alternative)
-	      {
-	      case 1: return \"%v1l32i.n\\t%D0, %N1\;l32i.n\\t%0, %1\";
-	      case 4: return \"%v1l32r\\t%D0, %N1\;l32r\\t%0, %1\";
-	      case 5: return \"%v1l32i\\t%D0, %N1\;l32i\\t%0, %1\";
-	      }
-	  }
-	else
-	  {
-	    switch (which_alternative)
-	      {
-	      case 1: return \"%v1l32i.n\\t%0, %1\;l32i.n\\t%D0, %N1\";
-	      case 4: return \"%v1l32r\\t%0, %1\;l32r\\t%D0, %N1\";
-	      case 5: return \"%v1l32i\\t%0, %1\;l32i\\t%D0, %N1\";
-	      }
-	  }
-      }
+      /* Check if the first half of the destination register is used
+	 in the source address.  If so, reverse the order of the loads
+	 so that the source address doesn't get clobbered until it is
+	 no longer needed. */
+
+      dstreg = operands[0];
+      if (GET_CODE (dstreg) == SUBREG)
+	dstreg = SUBREG_REG (dstreg);
+      if (GET_CODE (dstreg) != REG)
+	abort();
+
+      if (reg_mentioned_p (dstreg, operands[1]))
+	{
+	  switch (which_alternative)
+	    {
+	    case 1: return \"%v1l32i.n\\t%D0, %N1\;l32i.n\\t%0, %1\";
+	    case 4: return \"%v1l32i\\t%D0, %N1\;l32i\\t%0, %1\";
+	    }
+	}
+      else
+	{
+	  switch (which_alternative)
+	    {
+	    case 1: return \"%v1l32i.n\\t%0, %1\;l32i.n\\t%D0, %N1\";
+	    case 4: return \"%v1l32i\\t%0, %1\;l32i\\t%D0, %N1\";
+	    }
+	}
     }
   abort ();
   return \"\";
 }"
-  [(set_attr "type"	"move,load,store,move,load,load,store")
+  [(set_attr "type"	"move,load,store,move,load,store")
    (set_attr "mode"	"DI")
-   (set_attr "length"	"4,4,4,6,6,6,6")])
+   (set_attr "length"	"4,4,4,6,6,6")])
 
 
 ;; 32-bit Integer moves
@@ -1017,8 +1014,8 @@
 }")
 
 (define_insn "movsi_internal"
-  [(set (match_operand:SI 0 "nonimmed_operand" "=D,D,D,D,R,R,a,q,a,a,a,U,*a,*A")
-	(match_operand:SI 1 "move_operand" "M,D,d,R,D,d,r,r,I,T,U,r,*A,*r"))]
+  [(set (match_operand:SI 0 "nonimmed_operand" "=D,D,D,D,R,R,a,q,a,W,a,a,U,*a,*A")
+	(match_operand:SI 1 "move_operand" "M,D,d,R,D,d,r,r,I,i,T,U,r,*A,*r"))]
   "xtensa_valid_move (SImode, operands)"
   "@
    movi.n\\t%0, %x1
@@ -1030,14 +1027,15 @@
    mov\\t%0, %1
    movsp\\t%0, %1
    movi\\t%0, %x1
+   const16\\t%0, %t1\;const16\\t%0, %b1
    %v1l32r\\t%0, %1
    %v1l32i\\t%0, %1
    %v0s32i\\t%1, %0
    rsr\\t%0, 16 # ACCLO
    wsr\\t%1, 16 # ACCLO"
-  [(set_attr "type"	"move,move,move,load,store,store,move,move,move,load,load,store,rsr,wsr")
+  [(set_attr "type" "move,move,move,load,store,store,move,move,move,move,load,load,store,rsr,wsr")
    (set_attr "mode"	"SI")
-   (set_attr "length"	"2,2,2,2,2,2,3,3,3,3,3,3,3,3")])
+   (set_attr "length"	"2,2,2,2,2,2,3,3,3,6,3,3,3,3,3")])
 
 ;; 16-bit Integer moves
 
@@ -1105,15 +1103,16 @@
   ""
   "
 {
-  if (GET_CODE (operands[1]) == CONST_DOUBLE)
+  if (!TARGET_CONST16 && CONSTANT_P (operands[1]))
     operands[1] = force_const_mem (SFmode, operands[1]);
 
   if (!(reload_in_progress | reload_completed))
     {
-      if (((!register_operand (operands[0], SFmode)
+      if ((!register_operand (operands[0], SFmode)
 	   && !register_operand (operands[1], SFmode))
 	  || (FP_REG_P (xt_true_regnum (operands[0]))
-	      && constantpool_mem_p (operands[1]))))
+	      && (constantpool_mem_p (operands[1])
+	          || CONSTANT_P (operands[1]))))
 	operands[1] = force_reg (SFmode, operands[1]);
 
       if (xtensa_copy_incoming_a7 (operands, SFmode))
@@ -1122,14 +1121,12 @@
 }")
 
 (define_insn "movsf_internal"
-  [(set (match_operand:SF 0 "nonimmed_operand"
-			    "=f,f,U,D,D,R,a,f,a,a,a,U")
-	(match_operand:SF 1 "non_const_move_operand"
-			    "f,U,f,d,R,d,r,r,f,T,U,r"))]
+  [(set (match_operand:SF 0 "nonimmed_operand" "=f,f,U,D,D,R,a,f,a,W,a,a,U")
+	(match_operand:SF 1 "move_operand" "f,U,f,d,R,d,r,r,f,F,T,U,r"))]
   "((register_operand (operands[0], SFmode)
      || register_operand (operands[1], SFmode))
-    && (!FP_REG_P (xt_true_regnum (operands[0]))
-        || !constantpool_mem_p (operands[1])))"
+    && !(FP_REG_P (xt_true_regnum (operands[0]))
+         && (constantpool_mem_p (operands[1]) || CONSTANT_P (operands[1]))))"
   "@
    mov.s\\t%0, %1
    %v1lsi\\t%0, %1
@@ -1140,12 +1137,13 @@
    mov\\t%0, %1
    wfr\\t%0, %1
    rfr\\t%0, %1
+   const16\\t%0, %t1\;const16\\t%0, %b1
    %v1l32r\\t%0, %1
    %v1l32i\\t%0, %1
    %v0s32i\\t%1, %0"
-  [(set_attr "type"	"farith,fload,fstore,move,load,store,move,farith,farith,load,load,store")
+  [(set_attr "type"	"farith,fload,fstore,move,load,store,move,farith,farith,move,load,load,store")
    (set_attr "mode"	"SF")
-   (set_attr "length"	"3,3,3,2,2,2,3,3,3,3,3,3")])
+   (set_attr "length"	"3,3,3,2,2,2,3,3,3,6,3,3,3")])
 
 (define_insn "*lsiu"
   [(set (match_operand:SF 0 "register_operand" "=f")
@@ -1189,8 +1187,19 @@
   ""
   "
 {
-  if (GET_CODE (operands[1]) == CONST_DOUBLE)
-    operands[1] = force_const_mem (DFmode, operands[1]);
+  if (CONSTANT_P (operands[1]))
+    {
+      rtx src0, src1, dst0, dst1;
+      dst0 = operand_subword (operands[0], 0, 1, DFmode);
+      src0 = operand_subword (operands[1], 0, 1, DFmode);
+      dst1 = operand_subword (operands[0], 1, 1, DFmode);
+      src1 = operand_subword (operands[1], 1, 1, DFmode);
+      if (!dst0 || !src0 || !dst1 || !src1)
+        abort ();
+      emit_insn (gen_movsi (dst0, src0));
+      emit_insn (gen_movsi (dst1, src1));
+      DONE;
+    }
 
   if (!(reload_in_progress | reload_completed))
     {
@@ -1204,60 +1213,56 @@
 }")
 
 (define_insn "movdf_internal"
-  [(set (match_operand:DF 0 "nonimmed_operand" "=D,D,S,a,a,a,U")
-	(match_operand:DF 1 "non_const_move_operand" "d,S,d,r,T,U,r"))]
+  [(set (match_operand:DF 0 "nonimmed_operand" "=D,D,S,a,a,U")
+	(match_operand:DF 1 "nonimmed_operand" "d,S,d,r,U,r"))]
   "register_operand (operands[0], DFmode)
    || register_operand (operands[1], DFmode)"
   "*
 {
+  rtx dstreg;
   switch (which_alternative)
     {
     case 0: return \"mov.n\\t%0, %1\;mov.n\\t%D0, %D1\";
     case 2: return \"%v0s32i.n\\t%1, %0\;s32i.n\\t%D1, %N0\";
     case 3: return \"mov\\t%0, %1\;mov\\t%D0, %D1\";
-    case 6: return \"%v0s32i\\t%1, %0\;s32i\\t%D1, %N0\";
+    case 5: return \"%v0s32i\\t%1, %0\;s32i\\t%D1, %N0\";
 
     case 1:
     case 4:
-    case 5:
-      {
-	/* Check if the first half of the destination register is used
-	   in the source address.  If so, reverse the order of the loads
-	   so that the source address doesn't get clobbered until it is
-	   no longer needed. */
-
-	rtx dstreg = operands[0];
-	if (GET_CODE (dstreg) == SUBREG)
-	  dstreg = SUBREG_REG (dstreg);
-	if (GET_CODE (dstreg) != REG)
-	  abort ();
-
-	if (reg_mentioned_p (dstreg, operands[1]))
-	  {
-	    switch (which_alternative)
-	      {
-	      case 1: return \"%v1l32i.n\\t%D0, %N1\;l32i.n\\t%0, %1\";
-	      case 4: return \"%v1l32r\\t%D0, %N1\;l32r\\t%0, %1\";
-	      case 5: return \"%v1l32i\\t%D0, %N1\;l32i\\t%0, %1\";
-	      }
-	  }
-	else
-	  {
-	    switch (which_alternative)
-	      {
-	      case 1: return \"%v1l32i.n\\t%0, %1\;l32i.n\\t%D0, %N1\";
-	      case 4: return \"%v1l32r\\t%0, %1\;l32r\\t%D0, %N1\";
-	      case 5: return \"%v1l32i\\t%0, %1\;l32i\\t%D0, %N1\";
-	      }
-	  }
-      }
+      /* Check if the first half of the destination register is used
+	 in the source address.  If so, reverse the order of the loads
+	 so that the source address doesn't get clobbered until it is
+	 no longer needed.  */
+
+      dstreg = operands[0];
+      if (GET_CODE (dstreg) == SUBREG)
+	dstreg = SUBREG_REG (dstreg);
+      if (GET_CODE (dstreg) != REG)
+	abort ();
+
+      if (reg_mentioned_p (dstreg, operands[1]))
+	{
+	  switch (which_alternative)
+	    {
+	    case 1: return \"%v1l32i.n\\t%D0, %N1\;l32i.n\\t%0, %1\";
+	    case 4: return \"%v1l32i\\t%D0, %N1\;l32i\\t%0, %1\";
+	    }
+	}
+      else
+	{
+	  switch (which_alternative)
+	    {
+	    case 1: return \"%v1l32i.n\\t%0, %1\;l32i.n\\t%D0, %N1\";
+	    case 4: return \"%v1l32i\\t%0, %1\;l32i\\t%D0, %N1\";
+	    }
+	}
     }
   abort ();
   return \"\";
 }"
-  [(set_attr "type"	"move,load,store,move,load,load,store")
+  [(set_attr "type"	"move,load,store,move,load,store")
    (set_attr "mode"	"DF")
-   (set_attr "length"	"4,4,4,6,6,6,6")])
+   (set_attr "length"	"4,4,4,6,6,6")])
 
 ;; Block moves
 
@@ -2340,6 +2345,24 @@
    (set_attr "mode"	"none")
    (set_attr "length"	"3")])
 
+(define_insn "entry"
+  [(set (reg:SI A1_REG)
+	(unspec_volatile:SI [(match_operand:SI 0 "const_int_operand" "i")
+			     (match_operand:SI 1 "const_int_operand" "i")]
+			    UNSPECV_ENTRY))]
+  ""
+  "*
+{
+  if (frame_pointer_needed)
+    output_asm_insn (\".frame\\ta7, %0\", operands);
+  else
+    output_asm_insn (\".frame\\tsp, %0\", operands);
+  return \"entry\\tsp, %1\";
+}"
+  [(set_attr "type"	"move")
+   (set_attr "mode"	"SI")
+   (set_attr "length"	"3")])
+
 (define_insn "return"
   [(return)
    (use (reg:SI A0_REG))]
@@ -2361,6 +2384,24 @@
 ;;  ....................
 ;;
 
+(define_expand "prologue"
+  [(const_int 0)]
+  ""
+  "
+{
+  xtensa_expand_prologue ();
+  DONE;
+}")
+
+(define_expand "epilogue"
+  [(return)]
+  ""
+  "
+{
+  emit_jump_insn (gen_return ());
+  DONE;
+}")
+
 (define_insn "nop"
   [(const_int 0)]
   ""
@@ -2400,7 +2441,7 @@
 ;; to set up the frame pointer.
 
 (define_insn "set_frame_ptr"
-  [(set (reg:SI A7_REG) (unspec_volatile [(const_int 0)] UNSPECV_SET_FP))]
+  [(set (reg:SI A7_REG) (unspec_volatile:SI [(const_int 0)] UNSPECV_SET_FP))]
   ""
   "*
 {
@@ -2414,7 +2455,7 @@
 
 ;; Post-reload splitter to remove fp assignment when it's not needed.
 (define_split
-  [(set (reg:SI A7_REG) (unspec_volatile [(const_int 0)] UNSPECV_SET_FP))]
+  [(set (reg:SI A7_REG) (unspec_volatile:SI [(const_int 0)] UNSPECV_SET_FP))]
   "reload_completed && !frame_pointer_needed"
   [(unspec [(const_int 0)] UNSPEC_NOP)]
   "")
diff --git a/gcc/doc/invoke.texi b/gcc/doc/invoke.texi
index a0202fffe57b..47eb09ba39e5 100644
--- a/gcc/doc/invoke.texi
+++ b/gcc/doc/invoke.texi
@@ -632,6 +632,7 @@ in the following sections.
 @emph{Xtensa Options}
 @gccoptlist{-mbig-endian  -mlittle-endian @gol
 -mdensity  -mno-density @gol
+-mconst16 -mno-const16 @gol
 -mmac16  -mno-mac16 @gol
 -mmul16  -mno-mul16 @gol
 -mmul32  -mno-mul32 @gol
@@ -10649,6 +10650,16 @@ processor.
 @opindex mno-density
 Enable or disable use of the optional Xtensa code density instructions.
 
+@item -mconst16
+@itemx -mno-const16
+@opindex mconst16
+@opindex mno-const16
+Enable or disable use of CONST16 instructions for loading constant values.
+The CONST16 instruction is currently not a standard option from Tensilica.
+When enabled, CONST16 instructions are always used in place of the standard
+L32R instructions.  The use of CONST16 is enabled by default only if the
+L32R instruction is not available.
+
 @item -mmac16
 @itemx -mno-mac16
 @opindex mmac16
-- 
GitLab