diff --git a/gcc/config.in b/gcc/config.in index fa40825d6d0f9fe237d4485923c626e7935889cd..b499bbfdda7522ac349c1b15e6e5d20d45147dca 100644 --- a/gcc/config.in +++ b/gcc/config.in @@ -793,6 +793,12 @@ #endif +/* Define if your assembler supports tls le relocation. */ +#ifndef USED_FOR_TARGET +#undef HAVE_AS_TLS_LE_RELAXATION +#endif + + /* Define if your assembler supports vl/vst/vlm/vstm with an optional alignment hint argument. */ #ifndef USED_FOR_TARGET diff --git a/gcc/config/loongarch/loongarch-opts.h b/gcc/config/loongarch/loongarch-opts.h index d091359300a09dd6309e2da7348f2c49e349fadb..e46f79af3907d019df08c3c16af8c0ef05850cae 100644 --- a/gcc/config/loongarch/loongarch-opts.h +++ b/gcc/config/loongarch/loongarch-opts.h @@ -114,4 +114,8 @@ struct loongarch_flags { #define HAVE_AS_TLS 0 #endif +#ifndef HAVE_AS_TLS_LE_RELAXATION +#define HAVE_AS_TLS_LE_RELAXATION 0 +#endif + #endif /* LOONGARCH_OPTS_H */ diff --git a/gcc/config/loongarch/loongarch.cc b/gcc/config/loongarch/loongarch.cc index 9f2b3e98bf0ed54c0dcdd52dcba17a8c0bef08e1..db83232884f38788b10ae58a57b3c67c8b0c924a 100644 --- a/gcc/config/loongarch/loongarch.cc +++ b/gcc/config/loongarch/loongarch.cc @@ -2997,7 +2997,29 @@ loongarch_legitimize_tls_address (rtx loc) case TLS_MODEL_LOCAL_EXEC: { - /* la.tls.le; tp-relative add. */ + /* la.tls.le; tp-relative add. + + normal: + lu12i.w $rd, %le_hi20(sym) + ori $rd, $rd, %le_lo12(sym) + add.{w/d} $rd, $rd, $tp + (st.{w/d}/ld.{w/d} $rs, $rd, 0) + + tls le relax: + lu12i.w $rd, %le_hi20_r(sym) + add.{w/d} $rd,$rd,$tp + addi.{w/d} $rd,$rd,%le_lo12_r(sym) + (st.{w/d}/ld.{w/d} $rs, $rd, 0) + + extreme (When the code model is set to extreme, the TLS le Relax + instruction sequence is not generated): + lu12i.w $rd, %le_hi20(sym) + ori $rd, $rd, %le_lo12(sym) + lu32i.d $rd, %le64_lo20(sym) + lu52i.d $rd, $rd, %le64_hi12(sym) + add.d $rd, $rd, $tp + (st.{w/d}/ld.{w/d} $rs, $rd, 0) */ + tp = gen_rtx_REG (Pmode, THREAD_POINTER_REGNUM); tmp1 = gen_reg_rtx (Pmode); dest = gen_reg_rtx (Pmode); @@ -3008,7 +3030,20 @@ loongarch_legitimize_tls_address (rtx loc) tmp3 = gen_reg_rtx (Pmode); rtx high = gen_rtx_HIGH (Pmode, copy_rtx (tmp2)); high = loongarch_force_temporary (tmp3, high); - emit_insn (gen_ori_l_lo12 (Pmode, tmp1, high, tmp2)); + + /* The assembler does not implement tls le relax support when the + code model is extreme, so when the code model is extreme, the + old symbol address acquisition method is still used. */ + if (HAVE_AS_TLS_LE_RELAXATION && !TARGET_CMODEL_EXTREME) + { + emit_insn (gen_add_tls_le_relax (Pmode, dest, high, + tp, loc)); + loongarch_emit_move (dest, + gen_rtx_LO_SUM (Pmode, dest, tmp2)); + return dest; + } + else + emit_insn (gen_ori_l_lo12 (Pmode, tmp1, high, tmp2)); if (TARGET_CMODEL_EXTREME) { @@ -5940,7 +5975,12 @@ loongarch_print_operand_reloc (FILE *file, rtx op, bool hi64_part, gcc_unreachable (); } else - reloc = hi_reloc ? "%le_hi20" : "%le_lo12"; + { + if (HAVE_AS_TLS_LE_RELAXATION && !TARGET_CMODEL_EXTREME) + reloc = hi_reloc ? "%le_hi20_r" : "%le_lo12_r"; + else + reloc = hi_reloc ? "%le_hi20" : "%le_lo12"; + } break; case SYMBOL_TLSGD: diff --git a/gcc/config/loongarch/loongarch.md b/gcc/config/loongarch/loongarch.md index 47c1c5603c1c5f9d0100581ae9c7ea10d546e5ca..4dd578bc5e455a085d893b786ce6ce7583886241 100644 --- a/gcc/config/loongarch/loongarch.md +++ b/gcc/config/loongarch/loongarch.md @@ -73,6 +73,7 @@ UNSPEC_LOAD_FROM_GOT UNSPEC_PCALAU12I UNSPEC_PCALAU12I_GR + UNSPEC_ADD_TLS_LE_RELAX UNSPEC_ORI_L_LO12 UNSPEC_LUI_L_HI20 UNSPEC_LUI_H_LO20 @@ -2503,6 +2504,17 @@ "pcalau12i\t%0,%%pc_hi20(%1)" [(set_attr "type" "move")]) +(define_insn "@add_tls_le_relax<mode>" + [(set (match_operand:P 0 "register_operand" "=r") + (unspec:P [(match_operand:P 1 "register_operand" "r") + (match_operand:P 2 "register_operand" "r") + (match_operand:P 3 "symbolic_operand")] + UNSPEC_ADD_TLS_LE_RELAX))] + "HAVE_AS_TLS_LE_RELAXATION" + "add.<d>\t%0,%1,%2,%%le_add_r(%3)" + [(set_attr "type" "move")] +) + (define_insn "@ori_l_lo12<mode>" [(set (match_operand:P 0 "register_operand" "=r") (unspec:P [(match_operand:P 1 "register_operand" "r") diff --git a/gcc/configure b/gcc/configure index de72cb1e1fe5e8f0f7627396b550f9ab19f4493c..996046f51982c396e03e138a4191ce6a25f995c6 100755 --- a/gcc/configure +++ b/gcc/configure @@ -31050,6 +31050,37 @@ if test $gcc_cv_as_loongarch_cond_branch_relax = yes; then $as_echo "#define HAVE_AS_COND_BRANCH_RELAXATION 1" >>confdefs.h +fi + + { $as_echo "$as_me:${as_lineno-$LINENO}: checking assembler for tls le relaxation support" >&5 +$as_echo_n "checking assembler for tls le relaxation support... " >&6; } +if ${gcc_cv_as_loongarch_tls_le_relaxation_support+:} false; then : + $as_echo_n "(cached) " >&6 +else + gcc_cv_as_loongarch_tls_le_relaxation_support=no + if test x$gcc_cv_as != x; then + $as_echo 'lu12i.w $t0,%le_hi20_r(a)' > conftest.s + if { ac_try='$gcc_cv_as $gcc_cv_as_flags -o conftest.o conftest.s >&5' + { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_try\""; } >&5 + (eval $ac_try) 2>&5 + ac_status=$? + $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 + test $ac_status = 0; }; } + then + gcc_cv_as_loongarch_tls_le_relaxation_support=yes + else + echo "configure: failed program was" >&5 + cat conftest.s >&5 + fi + rm -f conftest.o conftest.s + fi +fi +{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $gcc_cv_as_loongarch_tls_le_relaxation_support" >&5 +$as_echo "$gcc_cv_as_loongarch_tls_le_relaxation_support" >&6; } +if test $gcc_cv_as_loongarch_tls_le_relaxation_support = yes; then + +$as_echo "#define HAVE_AS_TLS_LE_RELAXATION 1" >>confdefs.h + fi ;; diff --git a/gcc/configure.ac b/gcc/configure.ac index 21ba631482f0eb6ee1c32153ab9fe0a964c616de..784be5bed5969d8ec91ed3850a3a47960bf221c8 100644 --- a/gcc/configure.ac +++ b/gcc/configure.ac @@ -5447,6 +5447,11 @@ x: beq $a0,$a1,a],, [AC_DEFINE(HAVE_AS_COND_BRANCH_RELAXATION, 1, [Define if your assembler supports conditional branch relaxation.])]) + gcc_GAS_CHECK_FEATURE([tls le relaxation support], + gcc_cv_as_loongarch_tls_le_relaxation_support,, + [lu12i.w $t0,%le_hi20_r(a)],, + [AC_DEFINE(HAVE_AS_TLS_LE_RELAXATION, 1, + [Define if your assembler supports tls le relocation.])]) ;; s390*-*-*) gcc_GAS_CHECK_FEATURE([.gnu_attribute support], diff --git a/gcc/testsuite/gcc.target/loongarch/tls-le-relax.c b/gcc/testsuite/gcc.target/loongarch/tls-le-relax.c new file mode 100644 index 0000000000000000000000000000000000000000..a9a404fc70abaf4b9b1a7f80a28fd45e8c38a4d4 --- /dev/null +++ b/gcc/testsuite/gcc.target/loongarch/tls-le-relax.c @@ -0,0 +1,12 @@ +/* { dg-do compile } */ +/* { dg-options "-O2 -mcmodel=normal -mexplicit-relocs" } */ +/* { dg-final { scan-assembler "%le_add_r" { target tls_le_relax } } } */ + +__attribute__ ((tls_model ("local-exec"))) __thread int a; + +void +test (void) +{ + a = 10; +} + diff --git a/gcc/testsuite/lib/target-supports.exp b/gcc/testsuite/lib/target-supports.exp index 167e630f5a5fbe07407a26468da5c33ecaeeff4b..3aa761d3e09054b23f560107b3606b49117db1dd 100644 --- a/gcc/testsuite/lib/target-supports.exp +++ b/gcc/testsuite/lib/target-supports.exp @@ -13249,6 +13249,18 @@ proc check_effective_target_loongarch_call36_support { } { } ""] } +# Returns 1 if binutils supports TLS le Relax, 0 otherwise. +proc check_effective_target_tls_le_relax { } { + if [check_effective_target_tls_native] { + return [check_no_compiler_messages loongarch_tls_le_relax object { + /* Assembly code */ + lu12i.w $r12, %le_hi20_r(a) + }] + } + + return 0; +} + # Appends necessary Python flags to extra-tool-flags if Python.h is supported. # Otherwise, modifies dg-do-what. proc dg-require-python-h { args } {