From af1682fc3aaff288f7ac95cf5585971cef15f0ab Mon Sep 17 00:00:00 2001
From: Andrew Sadek <andrew.sadek.se@gmail.com>
Date: Mon, 30 Apr 2018 11:16:55 +0000
Subject: [PATCH] Microblaze Target: PIC data text relative 2018-04-30 Andrew
 Sadek  <andrew.sadek.se@gmail.com>

gcc/ChangeLog:
	* config/microblaze/microblaze.opt: add new option -mpic-data-text-rel.
	* config/microblaze/microblaze-protos.h (microblaze_constant_address_p):
	Add declaration.
	* gcc/config/microblaze/microblaze.h (microblaze_constant_address_p):
	CONSTANT_ADDRESS_P definition to microblaze_constant_address_p.
	* config/microblaze/microblaze.c (TARGET_PIC_DATA_TEXT_REL):
	New addressing mode for data-text relative position indepenedent code.
	(microblaze_classify_unspec): add 'UNSPEC_TEXT' case ->
	'ADDRESS_SYMBOLIC_TXT_REL'.
	(microblaze_classify_address): Add handling for UNSPEC + CONST_INT.
	(microblaze_legitimate_pic_operand): Exclude function calls from
	pic operands in case of TARGET_PIC_DATA_TEXT_REL option.
	(microblaze_legitimize_address): Generate 'UNSPEC_TEXT' for all possible
	addresses cases.
	(microblaze_address_insns): Add 'ADDRESS_SYMBOLIC_TXT_REL' case.
	(print_operand): Add 'ADDRESS_SYMBOLIC_TXT_REL' case.
	(print_operand_address): Add 'ADDRESS_SYMBOLIC_TXT_REL' case + handling
	for 'address + offset'.
	(microblaze_expand_prologue): Add new function prologue call for
	'r20' assignation.
	(microblaze_asm_generate_pic_addr_dif_vec): Override new target hook
	'TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC' to disable address diff vector
	table in case of TARGET_PIC_DATA_TEXT_REL.
	(expand_pic_symbol_ref): Add handling for 'UNSPEC_TEXT'.
	* gcc/config/microblaze/microblaze.md (TARGET_PIC_DATA_TEXT_REL):
	Add new macros 'UNSPEC_TEXT',
	'UNSPEC_SET_TEXT' + add rule for setting r20 in function prologue
	+ exclude function calls from 'UNSPEC_PLT' in case of data text
	relative mode.
	* doc/tm.texi.in (TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC): Add
	new target hook for generating address diff vector tables in case of
	flag_pic.
	* doc/tm.texi : Regenerate.
	* stmt.c (TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC): Append new condition
	'targetm.asm_out.generate_pic_addr_diff_vec' to flag_pic in case
	of addr diff vector generation.
	* target.def (TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC): Add
	target hook definition.
	* targhooks.h, gcc/targhooks.c (TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC):
	Add default function for generate_pic_addr_diff_vec -> flag_pic.
	* doc/invoke.texi (Add new pic option): Add new microblaze pic
	option for data text relative.

testsuite/ChangeLog:
	* gcc.target/microblaze/others/data_var1.c: Include
	PIC case of r20 base register.
	* gcc.target/microblaze/others/data_var2.c: Ditto.
	* gcc.target/microblaze/others/picdtr.c: Add new
	test case for -mpic-is-data-text-relative.
	* gcc.target/microblaze/others/sdata_var1.c: Add
	* gcc.target/microblaze/others/sdata_var2.c: Ditto.
	* gcc.target/microblaze/others/sdata_var3.c: Ditto.
	* gcc.target/microblaze/others/sdata_var4.c: Ditto.
	* gcc.target/microblaze/others/sdata_var5.c: Ditto.
	* gcc.target/microblaze/others/sdata_var6.c: Ditto.
	* gcc.target/microblaze/others/string_cst1_gpopt.c:	Ditto.
	* gcc.target/microblaze/others/string_cst2_gpopt.c: Ditto.

From-SVN: r259758
---
 gcc/ChangeLog                                 |  47 ++++
 gcc/config/microblaze/microblaze-protos.h     |   1 +
 gcc/config/microblaze/microblaze.c            | 210 +++++++++++++++---
 gcc/config/microblaze/microblaze.h            |   6 +-
 gcc/config/microblaze/microblaze.md           |  22 +-
 gcc/config/microblaze/microblaze.opt          |   4 +
 gcc/doc/invoke.texi                           |   9 +-
 gcc/doc/tm.texi                               |   8 +
 gcc/doc/tm.texi.in                            |   2 +
 gcc/stmt.c                                    |   3 +-
 gcc/target.def                                |  12 +
 gcc/targhooks.c                               |   9 +
 gcc/targhooks.h                               |   1 +
 gcc/testsuite/ChangeLog                       |  20 ++
 .../gcc.target/microblaze/others/data_var1.c  |   2 +-
 .../gcc.target/microblaze/others/data_var2.c  |   2 +-
 .../gcc.target/microblaze/others/sdata_var1.c |   2 +-
 .../gcc.target/microblaze/others/sdata_var2.c |   2 +-
 .../gcc.target/microblaze/others/sdata_var3.c |   2 +-
 .../gcc.target/microblaze/others/sdata_var4.c |   2 +-
 .../gcc.target/microblaze/others/sdata_var5.c |   2 +-
 .../gcc.target/microblaze/others/sdata_var6.c |   3 +-
 .../microblaze/others/string_cst1_gpopt.c     |   2 +-
 .../microblaze/others/string_cst2_gpopt.c     |   2 +-
 24 files changed, 319 insertions(+), 56 deletions(-)

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 5edb052836a4..0949337a6842 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,50 @@
+2018-04-30 Andrew Sadek  <andrew.sadek.se@gmail.com>
+
+	Microblaze Target: PIC data text relative
+
+	* config/microblaze/microblaze.opt: add new option -mpic-data-text-rel.
+	* config/microblaze/microblaze-protos.h (microblaze_constant_address_p):
+	Add declaration.
+	* gcc/config/microblaze/microblaze.h (microblaze_constant_address_p):
+	CONSTANT_ADDRESS_P definition to microblaze_constant_address_p.
+	* config/microblaze/microblaze.c (TARGET_PIC_DATA_TEXT_REL):
+	New addressing mode for data-text relative position indepenedent code.
+	(microblaze_classify_unspec): add 'UNSPEC_TEXT' case ->
+	'ADDRESS_SYMBOLIC_TXT_REL'.
+	(microblaze_classify_address): Add handling for UNSPEC + CONST_INT.
+	(microblaze_legitimate_pic_operand): Exclude function calls from
+	pic operands in case of TARGET_PIC_DATA_TEXT_REL option.
+	(microblaze_legitimize_address): Generate 'UNSPEC_TEXT' for all possible
+	addresses cases.
+	(microblaze_address_insns): Add 'ADDRESS_SYMBOLIC_TXT_REL' case.
+	(print_operand): Add 'ADDRESS_SYMBOLIC_TXT_REL' case.
+	(print_operand_address): Add 'ADDRESS_SYMBOLIC_TXT_REL' case + handling
+	for 'address + offset'.
+	(microblaze_expand_prologue): Add new function prologue call for
+	'r20' assignation.
+	(microblaze_asm_generate_pic_addr_dif_vec): Override new target hook
+	'TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC' to disable address diff vector
+	table in case of TARGET_PIC_DATA_TEXT_REL.
+	(expand_pic_symbol_ref): Add handling for 'UNSPEC_TEXT'.
+	* gcc/config/microblaze/microblaze.md (TARGET_PIC_DATA_TEXT_REL):
+	Add new macros 'UNSPEC_TEXT',
+	'UNSPEC_SET_TEXT' + add rule for setting r20 in function prologue
+	+ exclude function calls from 'UNSPEC_PLT' in case of data text
+	relative mode.
+	* doc/tm.texi.in (TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC): Add
+	new target hook for generating address diff vector tables in case of
+	flag_pic.
+	* doc/tm.texi : Regenerate.
+	* stmt.c (TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC): Append new condition
+	'targetm.asm_out.generate_pic_addr_diff_vec' to flag_pic in case
+	of addr diff vector generation.
+	* target.def (TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC): Add
+	target hook definition.
+	* targhooks.h, gcc/targhooks.c (TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC):
+	Add default function for generate_pic_addr_diff_vec -> flag_pic.
+	* doc/invoke.texi (Add new pic option): Add new microblaze pic
+	option for data text relative.
+
 2018-04-30  Richard Biener  <rguenther@suse.de>
 
 	* tree-chrec.h (evolution_function_is_constant_p): Remove
diff --git a/gcc/config/microblaze/microblaze-protos.h b/gcc/config/microblaze/microblaze-protos.h
index 4cbba0c639f6..515b713a3d79 100644
--- a/gcc/config/microblaze/microblaze-protos.h
+++ b/gcc/config/microblaze/microblaze-protos.h
@@ -24,6 +24,7 @@
 
 #ifdef RTX_CODE
 extern int pic_address_needs_scratch (rtx);
+extern bool microblaze_constant_address_p (rtx x);
 extern void expand_block_move        (rtx *);
 extern void microblaze_expand_prologue (void);
 extern void microblaze_expand_epilogue (void);
diff --git a/gcc/config/microblaze/microblaze.c b/gcc/config/microblaze/microblaze.c
index 9a4a287be234..06aa50e25560 100644
--- a/gcc/config/microblaze/microblaze.c
+++ b/gcc/config/microblaze/microblaze.c
@@ -91,7 +91,8 @@ enum microblaze_address_type
   ADDRESS_SYMBOLIC,
   ADDRESS_GOTOFF,
   ADDRESS_PLT,
-  ADDRESS_TLS
+  ADDRESS_TLS,
+  ADDRESS_SYMBOLIC_TXT_REL
 };
 
 /* Classifies symbols
@@ -650,6 +651,10 @@ microblaze_classify_unspec (struct microblaze_address_info *info, rtx x)
       info->type = ADDRESS_TLS;
       info->tls_type = tls_reloc (INTVAL (XVECEXP (x, 0, 1)));
     }
+  else if (XINT (x, 1) == UNSPEC_TEXT)
+    {
+      info->type = ADDRESS_SYMBOLIC_TXT_REL;
+    }
   else
     {
       return false;
@@ -701,8 +706,10 @@ get_base_reg (rtx x)
 }
 
 /* Return true if X is a valid address for machine mode MODE.  If it is,
-   fill in INFO appropriately.  STRICT is true if we should only accept
-   hard base registers.  
+   fill in INFO appropriately.
+   STRICT > 0 if we should only accept hard base registers.
+   STRICT = 2 if the operand address is being printed thus
+   function has been called by print_operand_address.
 
       type                     regA      regB    offset      symbol
 
@@ -728,6 +735,7 @@ microblaze_classify_address (struct microblaze_address_info *info, rtx x,
 {
   rtx xplus0;
   rtx xplus1;
+  rtx offset;
 
   info->type = ADDRESS_INVALID;
   info->regA = NULL;
@@ -735,6 +743,7 @@ microblaze_classify_address (struct microblaze_address_info *info, rtx x,
   info->offset = NULL;
   info->symbol = NULL;
   info->symbol_type = SYMBOL_TYPE_INVALID;
+  offset = NULL;
 
   switch (GET_CODE (x))
     {
@@ -795,8 +804,13 @@ microblaze_classify_address (struct microblaze_address_info *info, rtx x,
 		/* for (plus x const_int) just look at x.  */
 		if (GET_CODE (xconst0) == PLUS
 		    && GET_CODE (XEXP (xconst0, 1)) == CONST_INT
-		    && SMALL_INT (XEXP (xconst0, 1)))
+		    && (SMALL_INT (XEXP (xconst0, 1))
+		       || GET_CODE (XEXP (xconst0, 0)) == UNSPEC))
 		  {
+		    /* Hold CONST_INT Value in offset in case of
+		       UNSPEC + CONST_INT.  */
+		    offset = XEXP (xconst0, 1);
+
 		    /* This is ok as info->symbol is set to xplus1 the full
 		       const-expression below.  */
 		    xconst0 = XEXP (xconst0, 0);
@@ -814,6 +828,15 @@ microblaze_classify_address (struct microblaze_address_info *info, rtx x,
 		    return true;
 		  }
 
+		if (GET_CODE (xconst0) == UNSPEC && TARGET_PIC_DATA_TEXT_REL)
+		  {
+		    if (GET_MODE_SIZE (mode) > UNITS_PER_WORD)
+		      return false;
+
+		    info->offset = offset;
+		    return microblaze_classify_unspec (info, xconst0);
+		  }
+
 		/* Not base + symbol || base + UNSPEC.  */
 		return false;
 
@@ -858,6 +881,15 @@ microblaze_classify_address (struct microblaze_address_info *info, rtx x,
 	     return !(flag_pic && pic_address_needs_scratch (x));
 	  }
 
+	/* Avoid error in print_operand_address in case UNSPEC
+	 is removed from SYMBOL or LABEL REFS during optimization.  */
+	if ((GET_CODE (x) == SYMBOL_REF || GET_CODE (x) == LABEL_REF)
+	    && flag_pic && TARGET_PIC_DATA_TEXT_REL && strict == 2)
+	  {
+	    info->type = ADDRESS_SYMBOLIC_TXT_REL;
+	    return true;
+	  }
+
 	if (flag_pic == 2)
 	  return false;
 	else if (microblaze_tls_symbol_p(x))
@@ -893,6 +925,15 @@ microblaze_legitimate_address_p (machine_mode mode, rtx x, bool strict)
   return microblaze_classify_address (&addr, x, mode, strict);
 }
 
+bool
+microblaze_constant_address_p (rtx x)
+{
+  return ((GET_CODE (x) == LABEL_REF) || (GET_CODE (x) == SYMBOL_REF)
+	  || GET_CODE (x) == CONST_INT
+	  || (GET_CODE (x) == CONST
+	  && ! (flag_pic && pic_address_needs_scratch (x))));
+}
+
 int
 microblaze_valid_pic_const (rtx x)
 {
@@ -910,7 +951,8 @@ microblaze_valid_pic_const (rtx x)
 int
 microblaze_legitimate_pic_operand (rtx x)
 {
-  if (flag_pic == 2 && (symbol_mentioned_p(x) || label_mentioned_p(x)))
+  if (flag_pic == 2 && (symbol_mentioned_p (x) || label_mentioned_p (x))
+      && !(TARGET_PIC_DATA_TEXT_REL && call_insn_operand (x,VOIDmode)))
     return 0;
 
   if (microblaze_tls_referenced_p(x))
@@ -1024,17 +1066,35 @@ microblaze_legitimize_address (rtx x, rtx oldx ATTRIBUTE_UNUSED,
 		}
 	      else if (flag_pic == 2)
 		{
-		  rtx pic_ref, reg;
-		  reg = gen_reg_rtx (Pmode);
-
-		  pic_ref = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, xplus1),
-					    UNSPEC_GOTOFF);
-		  pic_ref = gen_rtx_CONST (Pmode, pic_ref);
-		  pic_ref = gen_rtx_PLUS (Pmode, pic_offset_table_rtx, pic_ref);
-		  pic_ref = gen_const_mem (Pmode, pic_ref);
-		  emit_move_insn (reg, pic_ref);
-		  result = gen_rtx_PLUS (Pmode, xplus0, reg);
-		  return result;
+		  if (!TARGET_PIC_DATA_TEXT_REL)
+		    {
+		      rtx pic_ref, reg;
+		      reg = gen_reg_rtx (Pmode);
+
+		      pic_ref = gen_rtx_UNSPEC (Pmode,
+						gen_rtvec (1, xplus1),
+						UNSPEC_GOTOFF);
+		      pic_ref = gen_rtx_CONST (Pmode, pic_ref);
+		      pic_ref = gen_rtx_PLUS (Pmode,
+					      pic_offset_table_rtx, pic_ref);
+		      pic_ref = gen_const_mem (Pmode, pic_ref);
+		      emit_move_insn (reg, pic_ref);
+		      result = gen_rtx_PLUS (Pmode, xplus0, reg);
+		      return result;
+		    }
+		  else
+		    {
+		      rtx pic_ref, reg;
+		      reg = gen_reg_rtx (Pmode);
+		      pic_ref = gen_rtx_UNSPEC (Pmode,
+						gen_rtvec (1, xplus1),
+						UNSPEC_TEXT);
+		      pic_ref = gen_rtx_CONST (Pmode, pic_ref);
+		      emit_insn (gen_addsi3 (reg,
+				 pic_offset_table_rtx, xplus0));
+		      result = gen_rtx_PLUS (Pmode, reg, pic_ref);
+		      return result;
+		    }
 		}
 	    }
 	}
@@ -1047,19 +1107,31 @@ microblaze_legitimize_address (rtx x, rtx oldx ATTRIBUTE_UNUSED,
         {
           reg = microblaze_legitimize_tls_address (xinsn, NULL_RTX);
         }
-      else
+      else if (flag_pic == 2)
         {
-          rtx pic_ref;
+	  if (reload_in_progress)
+	    df_set_regs_ever_live (PIC_OFFSET_TABLE_REGNUM, true);
 
-          if (reload_in_progress)
-            df_set_regs_ever_live (PIC_OFFSET_TABLE_REGNUM, true);
+	  if (!TARGET_PIC_DATA_TEXT_REL)
+	    {
+	      rtx pic_ref;
 
-          pic_ref = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, xinsn), UNSPEC_GOTOFF);
-          pic_ref = gen_rtx_CONST (Pmode, pic_ref);
-          pic_ref = gen_rtx_PLUS (Pmode, pic_offset_table_rtx, pic_ref);
-          pic_ref = gen_const_mem (Pmode, pic_ref);
-          reg = pic_ref;
-        }
+	      pic_ref = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, xinsn), UNSPEC_GOTOFF);
+	      pic_ref = gen_rtx_CONST (Pmode, pic_ref);
+	      pic_ref = gen_rtx_PLUS (Pmode, pic_offset_table_rtx, pic_ref);
+	      pic_ref = gen_const_mem (Pmode, pic_ref);
+	      reg = pic_ref;
+	    }
+	  else
+	    {
+	      rtx pic_ref;
+
+	      pic_ref = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, xinsn), UNSPEC_TEXT);
+	      pic_ref = gen_rtx_CONST (Pmode, pic_ref);
+	      pic_ref = gen_rtx_PLUS (Pmode, pic_offset_table_rtx, pic_ref);
+	      reg = pic_ref;
+	    }
+	}
       return reg;
     }
 
@@ -1388,6 +1460,7 @@ microblaze_address_insns (rtx x, machine_mode mode)
 	case ADDRESS_REG_INDEX:
 	  return 1;
 	case ADDRESS_SYMBOLIC:
+	case ADDRESS_SYMBOLIC_TXT_REL:
 	case ADDRESS_GOTOFF:
 	  return 2;
 	case ADDRESS_TLS:
@@ -2066,7 +2139,7 @@ compute_frame_size (HOST_WIDE_INT size)
 
   total_size = var_size + args_size;
 
-  if (flag_pic == 2)
+  if (flag_pic == 2 && !TARGET_PIC_DATA_TEXT_REL)
     /* force setting GOT.  */
     df_set_regs_ever_live (MB_ABI_PIC_ADDR_REGNUM, true);
 
@@ -2322,6 +2395,7 @@ print_operand (FILE * file, rtx op, int letter)
 	    case ADDRESS_REG:
 	    case ADDRESS_CONST_INT:
 	    case ADDRESS_SYMBOLIC:
+	    case ADDRESS_SYMBOLIC_TXT_REL:
 	    case ADDRESS_GOTOFF:
 	    case ADDRESS_TLS:
 	      fputs ("i", file);
@@ -2489,7 +2563,7 @@ print_operand_address (FILE * file, rtx addr)
 {
   struct microblaze_address_info info;
   enum microblaze_address_type type;
-  if (!microblaze_classify_address (&info, addr, GET_MODE (addr), 1))
+  if (!microblaze_classify_address (&info, addr, GET_MODE (addr), 2))
     fatal_insn ("insn contains an invalid address !", addr);
 
   type = info.type;
@@ -2515,6 +2589,7 @@ print_operand_address (FILE * file, rtx addr)
       output_addr_const (file, info.offset);
       break;
     case ADDRESS_SYMBOLIC:
+    case ADDRESS_SYMBOLIC_TXT_REL:
     case ADDRESS_GOTOFF:
     case ADDRESS_PLT:
     case ADDRESS_TLS:
@@ -2529,6 +2604,16 @@ print_operand_address (FILE * file, rtx addr)
 	{
 	  fputs ("@PLT", file);
 	}
+      else if (type == ADDRESS_SYMBOLIC_TXT_REL)
+    {
+      if (info.offset != NULL && CONST_INT_P (info.offset)
+	  && INTVAL (info.offset) > 0)
+	{
+	  fprintf (file, "+");
+	  output_addr_const (file, info.offset);
+	}
+      fputs ("@TXTREL", file);
+    }
       else if (type == ADDRESS_TLS)
 	{
 	  switch (info.tls_type)
@@ -2888,7 +2973,6 @@ microblaze_expand_prologue (void)
   if (flag_stack_usage_info)
     current_function_static_stack_size = fsiz;
 
-
   /* If this function is a varargs function, store any registers that
      would normally hold arguments ($5 - $10) on the stack.  */
   if (((TYPE_ARG_TYPES (fntype) != 0
@@ -2913,7 +2997,6 @@ microblaze_expand_prologue (void)
 
 	  offset += GET_MODE_SIZE (SImode);
 	}
-
     }
 
   if (fsiz > 0)
@@ -2960,8 +3043,18 @@ microblaze_expand_prologue (void)
   if ((flag_pic == 2 || TLS_NEEDS_GOT )
       && df_regs_ever_live_p (MB_ABI_PIC_ADDR_REGNUM))
     {
-      SET_REGNO (pic_offset_table_rtx, MB_ABI_PIC_ADDR_REGNUM);
-      emit_insn (gen_set_got (pic_offset_table_rtx));	/* setting GOT.  */
+      if ((flag_pic == 2 && !TARGET_PIC_DATA_TEXT_REL) || TLS_NEEDS_GOT)
+	{
+	  SET_REGNO (pic_offset_table_rtx, MB_ABI_PIC_ADDR_REGNUM);
+	  /* setting GOT.  */
+	  emit_insn (gen_set_got (pic_offset_table_rtx));
+	}
+      else
+	{
+	  SET_REGNO (pic_offset_table_rtx, MB_ABI_PIC_ADDR_REGNUM);
+	  /* setting start of text.  */
+	  emit_insn (gen_set_text (pic_offset_table_rtx));
+	}
     }
 
   /* If we are profiling, make sure no instructions are scheduled before
@@ -3154,6 +3247,14 @@ microblaze_elf_in_small_data_p (const_tree decl)
   return (size > 0 && size <= microblaze_section_threshold);
 }
 
+/* We need to disable address diff vectors in
+case of pic data text relative mode.  */
+
+static bool
+microblaze_gen_pic_addr_dif_vec (void)
+{
+  return (flag_pic && !TARGET_PIC_DATA_TEXT_REL);
+}
 
 static section *
 microblaze_select_section (tree decl, int reloc, unsigned HOST_WIDE_INT align)
@@ -3187,10 +3288,19 @@ static rtx
 expand_pic_symbol_ref (machine_mode mode ATTRIBUTE_UNUSED, rtx op)
 {
   rtx result;
-  result = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, op), UNSPEC_GOTOFF);
+  bool isFunc = (GET_CODE (op) == SYMBOL_REF
+		 && (SYMBOL_REF_FLAGS (op) & SYMBOL_FLAG_FUNCTION));
+  result = (!TARGET_PIC_DATA_TEXT_REL)
+	    ? gen_rtx_UNSPEC (Pmode, gen_rtvec (1, op), UNSPEC_GOTOFF)
+	    : gen_rtx_UNSPEC (Pmode, gen_rtvec (1, op), UNSPEC_TEXT);
   result = gen_rtx_CONST (Pmode, result);
-  result = gen_rtx_PLUS (Pmode, pic_offset_table_rtx, result);
-  result = gen_const_mem (Pmode, result);
+  result = (TARGET_PIC_DATA_TEXT_REL && isFunc)
+	    ? gen_rtx_PLUS (Pmode, gen_raw_REG (Pmode,
+			    get_base_reg (op)), result)
+	    : gen_rtx_PLUS (Pmode, pic_offset_table_rtx, result);
+  result = (!TARGET_PIC_DATA_TEXT_REL)
+	    ? gen_const_mem (Pmode, result) : result;
+
   return result;
 }
 
@@ -3294,10 +3404,37 @@ microblaze_expand_move (machine_mode mode, rtx operands[])
 	  if (reload_in_progress)
 	    df_set_regs_ever_live (PIC_OFFSET_TABLE_REGNUM, true);
 	  result = expand_pic_symbol_ref (mode, op1);
+
+	  if (TARGET_PIC_DATA_TEXT_REL && GET_CODE (op0) == REG
+	      && REGNO (op0) >= FIRST_PSEUDO_REGISTER)
+	    result = force_reg (SImode, result);
+
 	  emit_move_insn (op0, result);
 	  return true;
 	}
     }
+  if (GET_CODE (op1) == PLUS && GET_CODE (XEXP (op1,1)) == CONST)
+    {
+      rtx p0, p1, result, temp;
+
+      p0 = XEXP (XEXP (op1,1), 0);
+
+      if (GET_CODE (p0) == PLUS)
+	{
+	  p1 = XEXP (p0, 1);
+	  p0 = XEXP (p0, 0);
+	}
+
+      if (GET_CODE (p0) == UNSPEC && GET_CODE (p1) == CONST_INT
+	  && flag_pic && TARGET_PIC_DATA_TEXT_REL)
+	{
+	  result = gen_rtx_CONST (Pmode, p0);
+	  result = gen_rtx_PLUS (Pmode, pic_offset_table_rtx, result);
+	  temp = force_reg (SImode, result);
+	  emit_move_insn (op0, gen_rtx_PLUS (SImode, temp, p1));
+	  return true;
+	}
+    }
   /* Handle Case of (const (plus symbol const_int)).  */
   if (GET_CODE (op1) == CONST && GET_CODE (XEXP (op1,0)) == PLUS)
     {
@@ -3912,6 +4049,9 @@ microblaze_starting_frame_offset (void)
 #undef TARGET_LEGITIMATE_CONSTANT_P
 #define TARGET_LEGITIMATE_CONSTANT_P microblaze_legitimate_constant_p
 
+#undef  TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC
+#define TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC	microblaze_gen_pic_addr_dif_vec
+
 #undef TARGET_MACHINE_DEPENDENT_REORG
 #define TARGET_MACHINE_DEPENDENT_REORG microblaze_machine_dependent_reorg
 
diff --git a/gcc/config/microblaze/microblaze.h b/gcc/config/microblaze/microblaze.h
index 0d3718f417ba..c05bed6e323b 100644
--- a/gcc/config/microblaze/microblaze.h
+++ b/gcc/config/microblaze/microblaze.h
@@ -518,11 +518,7 @@ typedef struct microblaze_args
 
 /* Identify valid constant addresses.  Exclude if PIC addr which 
    needs scratch register.  */
-#define CONSTANT_ADDRESS_P(X)						\
-  (GET_CODE (X) == LABEL_REF || GET_CODE (X) == SYMBOL_REF		\
-    || GET_CODE (X) == CONST_INT 		                        \
-    || (GET_CODE (X) == CONST						\
-	&& ! (flag_pic && pic_address_needs_scratch (X))))
+#define CONSTANT_ADDRESS_P(X)	microblaze_constant_address_p(X)
 
 /* Define this, so that when PIC, reload won't try to reload invalid
    addresses which require two reload registers.  */
diff --git a/gcc/config/microblaze/microblaze.md b/gcc/config/microblaze/microblaze.md
index f698e541c238..bec346f60ff6 100644
--- a/gcc/config/microblaze/microblaze.md
+++ b/gcc/config/microblaze/microblaze.md
@@ -41,6 +41,8 @@
   (UNSPEC_CMP		104)    ;; signed compare
   (UNSPEC_CMPU		105)    ;; unsigned compare
   (UNSPEC_TLS           106)    ;; jump table
+  (UNSPEC_SET_TEXT      107)    ;; set text start
+  (UNSPEC_TEXT          108)    ;; data text relative
 ])
 
 (define_c_enum "unspec" [
@@ -1848,7 +1850,7 @@
   {
     gcc_assert (GET_MODE (operands[0]) == Pmode);
 
-    if (!flag_pic)
+    if (!flag_pic || TARGET_PIC_DATA_TEXT_REL)
       emit_jump_insn (gen_tablejump_internal1 (operands[0], operands[1]));
     else
       emit_jump_insn (gen_tablejump_internal3 (operands[0], operands[1]));
@@ -2053,7 +2055,8 @@
   {
     rtx addr = XEXP (operands[0], 0);
 
-    if (flag_pic == 2 && GET_CODE (addr) == SYMBOL_REF 
+    if (flag_pic == 2 && !TARGET_PIC_DATA_TEXT_REL
+    && GET_CODE (addr) == SYMBOL_REF
 	&& !SYMBOL_REF_LOCAL_P (addr)) 
       {
         rtx temp = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, addr), UNSPEC_PLT);
@@ -2156,7 +2159,8 @@
   {
     rtx addr = XEXP (operands[1], 0);
 
-    if (flag_pic == 2 && GET_CODE (addr) == SYMBOL_REF
+    if (flag_pic == 2 && !TARGET_PIC_DATA_TEXT_REL
+    && GET_CODE (addr) == SYMBOL_REF
 	&& !SYMBOL_REF_LOCAL_P (addr)) 
       {
         rtx temp = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, addr), UNSPEC_PLT);
@@ -2313,6 +2317,18 @@
   [(set_attr "type" "multi")
    (set_attr "length" "12")])
 
+;; The insn to set TEXT.
+;; The hardcoded number "8" accounts for $pc difference
+;; between "mfs" and "addik" instructions.
+(define_insn "set_text"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+    (unspec:SI[(const_int 0)] UNSPEC_SET_TEXT))]
+  ""
+  "mfs\t%0,rpc\n\taddik\t%0,%0,8@TXTPCREL"
+  [(set_attr "type" "multi")
+   (set_attr "length" "12")])
+
+
 ;; This insn gives the count of leading number of zeros for the second
 ;; operand and stores the result in first operand.
 (define_insn "clzsi2"
diff --git a/gcc/config/microblaze/microblaze.opt b/gcc/config/microblaze/microblaze.opt
index 824299823335..2f34541c2251 100644
--- a/gcc/config/microblaze/microblaze.opt
+++ b/gcc/config/microblaze/microblaze.opt
@@ -127,5 +127,9 @@ mxl-prefetch
 Target Mask(PREFETCH)
 Use hardware prefetch instruction
 
+mpic-data-is-text-relative
+Target Mask(PIC_DATA_TEXT_REL)
+Data referenced by offset from start of text instead of GOT (with -fPIC/-fPIE).
+
 mxl-mode-xilkernel
 Target
diff --git a/gcc/doc/invoke.texi b/gcc/doc/invoke.texi
index 444159178a76..e45f467155a7 100644
--- a/gcc/doc/invoke.texi
+++ b/gcc/doc/invoke.texi
@@ -867,7 +867,8 @@ Objective-C and Objective-C++ Dialects}.
 -mmemcpy  -mxl-soft-mul  -mxl-soft-div  -mxl-barrel-shift @gol
 -mxl-pattern-compare  -mxl-stack-check  -mxl-gp-opt  -mno-clearbss @gol
 -mxl-multiply-high  -mxl-float-convert  -mxl-float-sqrt @gol
--mbig-endian  -mlittle-endian  -mxl-reorder  -mxl-mode-@var{app-model}}
+-mbig-endian  -mlittle-endian  -mxl-reorder  -mxl-mode-@var{app-model}
+-mpic-data-is-text-relative}
 
 @emph{MIPS Options}
 @gccoptlist{-EL  -EB  -march=@var{arch}  -mtune=@var{arch} @gol
@@ -20113,6 +20114,12 @@ Select application model @var{app-model}.  Valid models are
 @item executable
 normal executable (default), uses startup code @file{crt0.o}.
 
+@item -mpic-data-is-text-relative
+@opindex mpic-data-is-text-relative
+Assume that the displacement between the text and data segments is fixed
+at static link time.  This allows data to be referenced by offset from start of
+text address instead of GOT since PC-relative addressing is not supported.
+
 @item xmdstub
 for use with Xilinx Microprocessor Debugger (XMD) based
 software intrusive debug agent called xmdstub. This uses startup file
diff --git a/gcc/doc/tm.texi b/gcc/doc/tm.texi
index bd8b917ba829..9d92ed1c3d38 100644
--- a/gcc/doc/tm.texi
+++ b/gcc/doc/tm.texi
@@ -7491,6 +7491,14 @@ when the target cannot support (some kinds of) dynamic relocations
 in read-only sections even in executables.
 @end deftypefn
 
+@deftypefn {Target Hook} bool TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC (void)
+Return true to generate ADDR_DIF_VEC table
+or false to generate ADDR_VEC table for jumps in case of -fPIC.
+
+The default version of this function returns true if flag_pic
+equals true and false otherwise
+@end deftypefn
+
 @deftypefn {Target Hook} {section *} TARGET_ASM_SELECT_SECTION (tree @var{exp}, int @var{reloc}, unsigned HOST_WIDE_INT @var{align})
 Return the section into which @var{exp} should be placed.  You can
 assume that @var{exp} is either a @code{VAR_DECL} node or a constant of
diff --git a/gcc/doc/tm.texi.in b/gcc/doc/tm.texi.in
index b0207146e8c2..5732a2a4515a 100644
--- a/gcc/doc/tm.texi.in
+++ b/gcc/doc/tm.texi.in
@@ -4922,6 +4922,8 @@ This macro is irrelevant if there is no separate readonly data section.
 
 @hook TARGET_ASM_RELOC_RW_MASK
 
+@hook TARGET_ASM_GENERATE_PIC_ADDR_DIFF_VEC
+
 @hook TARGET_ASM_SELECT_SECTION
 
 @defmac USE_SELECT_SECTION_FOR_FUNCTIONS
diff --git a/gcc/stmt.c b/gcc/stmt.c
index 9493dccf734b..b8df18181377 100644
--- a/gcc/stmt.c
+++ b/gcc/stmt.c
@@ -853,7 +853,8 @@ emit_case_dispatch_table (tree index_expr, tree index_type,
   /* Output the table.  */
   emit_label (table_label);
 
-  if (CASE_VECTOR_PC_RELATIVE || flag_pic)
+  if (CASE_VECTOR_PC_RELATIVE
+	  || (flag_pic && targetm.asm_out.generate_pic_addr_diff_vec ()))
     emit_jump_table_data (gen_rtx_ADDR_DIFF_VEC (CASE_VECTOR_MODE,
 						 gen_rtx_LABEL_REF (Pmode,
 								    table_label),
diff --git a/gcc/target.def b/gcc/target.def
index c5b2a1e7e71f..2f7bca99ec24 100644
--- a/gcc/target.def
+++ b/gcc/target.def
@@ -507,6 +507,18 @@ in read-only sections even in executables.",
  int, (void),
  default_reloc_rw_mask)
 
+ /* Return a flag for either generating ADDR_DIF_VEC table
+ or ADDR_VEC table for jumps in case of -fPIC/-fPIE.  */
+DEFHOOK
+(generate_pic_addr_diff_vec,
+"Return true to generate ADDR_DIF_VEC table\n\
+or false to generate ADDR_VEC table for jumps in case of -fPIC.\n\
+\n\
+The default version of this function returns true if flag_pic\n\
+equals true and false otherwise",
+ bool, (void),
+ default_generate_pic_addr_diff_vec)
+
  /* Return a section for EXP.  It may be a DECL or a constant.  RELOC
     is nonzero if runtime relocations must be applied; bit 1 will be
     set if the runtime relocations require non-local name resolution.
diff --git a/gcc/targhooks.c b/gcc/targhooks.c
index fafcc6c51966..749e24ae1787 100644
--- a/gcc/targhooks.c
+++ b/gcc/targhooks.c
@@ -1196,6 +1196,15 @@ default_reloc_rw_mask (void)
   return flag_pic ? 3 : 0;
 }
 
+/* By default, address diff vectors are generated
+for jump tables when flag_pic is true.  */
+
+bool
+default_generate_pic_addr_diff_vec (void)
+{
+  return flag_pic;
+}
+
 /* By default, do no modification. */
 tree default_mangle_decl_assembler_name (tree decl ATTRIBUTE_UNUSED,
 					 tree id)
diff --git a/gcc/targhooks.h b/gcc/targhooks.h
index 8a4393f2ba40..56951556525e 100644
--- a/gcc/targhooks.h
+++ b/gcc/targhooks.h
@@ -175,6 +175,7 @@ extern machine_mode default_secondary_memory_needed_mode (machine_mode);
 extern void default_target_option_override (void);
 extern void hook_void_bitmap (bitmap);
 extern int default_reloc_rw_mask (void);
+extern bool default_generate_pic_addr_diff_vec (void);
 extern tree default_mangle_decl_assembler_name (tree, tree);
 extern tree default_emutls_var_fields (tree, tree *);
 extern tree default_emutls_var_init (tree, tree, tree);
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index c41d69b4a212..093cd3656624 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,23 @@
+2018-04-30 Andrew Sadek  <andrew.sadek.se@gmail.com>
+
+	Microblaze Target: PIC data text relative
+
+	* gcc.target/microblaze/others/data_var1.c: Include
+	PIC case of r20 base register.
+	* gcc.target/microblaze/others/data_var2.c: Ditto.
+	* gcc.target/microblaze/others/picdtr.c: Add new
+	test case for -mpic-is-data-text-relative.
+	* gcc.target/microblaze/others/sdata_var1.c: Add
+	* gcc.target/microblaze/others/sdata_var2.c: Ditto.
+	* gcc.target/microblaze/others/sdata_var3.c: Ditto.
+	* gcc.target/microblaze/others/sdata_var4.c: Ditto.
+	* gcc.target/microblaze/others/sdata_var5.c: Ditto.
+	* gcc.target/microblaze/others/sdata_var6.c: Ditto.
+	* gcc.target/microblaze/others/string_cst1_gpopt.c:
+	Ditto.
+	* gcc.target/microblaze/others/string_cst2_gpopt.c:
+	Ditto.
+
 2018-04-30  Richard Biener  <rguenther@suse.de>
 
 	PR tree-optimization/28364
diff --git a/gcc/testsuite/gcc.target/microblaze/others/data_var1.c b/gcc/testsuite/gcc.target/microblaze/others/data_var1.c
index 15b85ca77808..5826913d5d03 100644
--- a/gcc/testsuite/gcc.target/microblaze/others/data_var1.c
+++ b/gcc/testsuite/gcc.target/microblaze/others/data_var1.c
@@ -3,6 +3,6 @@ int global;
 
 int testfunc ()
 {
-/* { dg-final { scan-assembler "\lwi\tr(\[0-9]\|\[1-2]\[0-9]\|3\[0-1]),r0" } } */
+/* { dg-final { scan-assembler "\lwi\tr(\[0-9]\|\[1-2]\[0-9]\|3\[0-1]),r(0|20)" } } */
     return global;
 }
diff --git a/gcc/testsuite/gcc.target/microblaze/others/data_var2.c b/gcc/testsuite/gcc.target/microblaze/others/data_var2.c
index 9fb7347bab4c..97b091f10fc5 100644
--- a/gcc/testsuite/gcc.target/microblaze/others/data_var2.c
+++ b/gcc/testsuite/gcc.target/microblaze/others/data_var2.c
@@ -3,6 +3,6 @@ int global = 10;
 
 int testfunc ()
 {
-/* { dg-final { scan-assembler "\lwi\tr(\[0-9]\|\[1-2]\[0-9]\|3\[0-1]),r0" } } */
+/* { dg-final { scan-assembler "\lwi\tr(\[0-9]\|\[1-2]\[0-9]\|3\[0-1]),r(0|20)" } } */
     return global;
 }
diff --git a/gcc/testsuite/gcc.target/microblaze/others/sdata_var1.c b/gcc/testsuite/gcc.target/microblaze/others/sdata_var1.c
index 2337f5a1e786..d79034e1a07d 100644
--- a/gcc/testsuite/gcc.target/microblaze/others/sdata_var1.c
+++ b/gcc/testsuite/gcc.target/microblaze/others/sdata_var1.c
@@ -1,4 +1,4 @@
-/* { dg-options "-mxl-gp-opt" } */
+/* { dg-options "-mxl-gp-opt -fno-pic" } */
 
 /* { dg-final { scan-assembler "\.sbss\[^2]+" } } */
 typedef int Boolean;
diff --git a/gcc/testsuite/gcc.target/microblaze/others/sdata_var2.c b/gcc/testsuite/gcc.target/microblaze/others/sdata_var2.c
index 1c91d004305f..21b9115d795b 100644
--- a/gcc/testsuite/gcc.target/microblaze/others/sdata_var2.c
+++ b/gcc/testsuite/gcc.target/microblaze/others/sdata_var2.c
@@ -1,4 +1,4 @@
-/* { dg-options "-mxl-gp-opt" } */
+/* { dg-options "-mxl-gp-opt -fno-pic" } */
 
 /* { dg-final { scan-assembler "\.sdata\[^2]+" } } */
 int global = 10;
diff --git a/gcc/testsuite/gcc.target/microblaze/others/sdata_var3.c b/gcc/testsuite/gcc.target/microblaze/others/sdata_var3.c
index 07c80041c72e..2f233138fc16 100644
--- a/gcc/testsuite/gcc.target/microblaze/others/sdata_var3.c
+++ b/gcc/testsuite/gcc.target/microblaze/others/sdata_var3.c
@@ -1,4 +1,4 @@
-/* { dg-options "-mxl-gp-opt" } */
+/* { dg-options "-mxl-gp-opt -fno-pic" } */
 
 extern int a;
 
diff --git a/gcc/testsuite/gcc.target/microblaze/others/sdata_var4.c b/gcc/testsuite/gcc.target/microblaze/others/sdata_var4.c
index 4dfa337d5384..dc74e2d7d2ce 100644
--- a/gcc/testsuite/gcc.target/microblaze/others/sdata_var4.c
+++ b/gcc/testsuite/gcc.target/microblaze/others/sdata_var4.c
@@ -1,4 +1,4 @@
-/* { dg-options "-mxl-gp-opt -G 16" } */
+/* { dg-options "-mxl-gp-opt -G 16 -fno-pic" } */
 
 /* { dg-final { scan-assembler "\.sbss\[^2]+" } } */
 struct test_s {
diff --git a/gcc/testsuite/gcc.target/microblaze/others/sdata_var5.c b/gcc/testsuite/gcc.target/microblaze/others/sdata_var5.c
index 5c61962bf4e2..c0c3cb3bbba1 100644
--- a/gcc/testsuite/gcc.target/microblaze/others/sdata_var5.c
+++ b/gcc/testsuite/gcc.target/microblaze/others/sdata_var5.c
@@ -1,4 +1,4 @@
-/* { dg-options "-mxl-gp-opt -G 16" } */
+/* { dg-options "-mxl-gp-opt -G 16 -fno-pic" } */
 
 /* { dg-final { scan-assembler "\.sdata\[^2]+" } } */
 struct test_s {
diff --git a/gcc/testsuite/gcc.target/microblaze/others/sdata_var6.c b/gcc/testsuite/gcc.target/microblaze/others/sdata_var6.c
index 0c8fe431f5d0..a23a2c76fe8c 100644
--- a/gcc/testsuite/gcc.target/microblaze/others/sdata_var6.c
+++ b/gcc/testsuite/gcc.target/microblaze/others/sdata_var6.c
@@ -1,5 +1,4 @@
-/* { dg-options "-mxl-gp-opt -G 16" } */
-
+/* { dg-options "-mxl-gp-opt -G 16 -fno-pic" } */
 struct test_s {
     int a;
     int b;
diff --git a/gcc/testsuite/gcc.target/microblaze/others/string_cst1_gpopt.c b/gcc/testsuite/gcc.target/microblaze/others/string_cst1_gpopt.c
index 5b5d3db18df5..5bf390b3ea72 100644
--- a/gcc/testsuite/gcc.target/microblaze/others/string_cst1_gpopt.c
+++ b/gcc/testsuite/gcc.target/microblaze/others/string_cst1_gpopt.c
@@ -1,4 +1,4 @@
-/* { dg-options "-mxl-gp-opt" } */
+/* { dg-options "-mxl-gp-opt -fno-pic" } */
 
 #include <string.h>
 
diff --git a/gcc/testsuite/gcc.target/microblaze/others/string_cst2_gpopt.c b/gcc/testsuite/gcc.target/microblaze/others/string_cst2_gpopt.c
index 057e8c4479bb..2ad6673d2ef6 100644
--- a/gcc/testsuite/gcc.target/microblaze/others/string_cst2_gpopt.c
+++ b/gcc/testsuite/gcc.target/microblaze/others/string_cst2_gpopt.c
@@ -1,4 +1,4 @@
-/* { dg-options "-mxl-gp-opt" } */
+/* { dg-options "-mxl-gp-opt -fno-pic" } */
 
 #include <string.h>
 
-- 
GitLab