diff --git a/gcc/ChangeLog b/gcc/ChangeLog index b91bf89652c2a5637574c4b9beab5b95bd2ea897..1bc0f809858f4ae83f0667fadabaa067f27961a8 100644 --- a/gcc/ChangeLog +++ b/gcc/ChangeLog @@ -1,3 +1,65 @@ +2016-11-15 Claudiu Zissulescu <claziss@synopsys.com> + + * config/arc/arc-arch.h: New file. + * config/arc/arc-arches.def: Likewise. + * config/arc/arc-cpus.def: Likewise. + * config/arc/arc-options.def: Likewise. + * config/arc/t-multilib: Likewise. + * config/arc/genmultilib.awk: Likewise. + * config/arc/genoptions.awk: Likewise. + * config/arc/arc-tables.opt: Likewise. + * config/arc/driver-arc.c: Likewise. + * testsuite/gcc.target/arc/nps400-cpu-flag.c: Likewise. + * common/config/arc/arc-common.c (arc_handle_option): Trace + toggled options. + * config.gcc (arc*-*-*): Add arc-tables.opt to arc's extra + options; check for supported cpu against arc-cpus.def file. + (arc*-*-elf*, arc*-*-linux-uclibc*): Use new make fragment; define + TARGET_CPU_BUILD macro; add driver-arc.o as an extra object. + * config/arc/arc-c.def: Add emacs local variables. + * config/arc/arc-opts.h (processor_type): Use arc-cpus.def file. + (FPU_FPUS, FPU_FPUD, FPU_FPUDA, FPU_FPUDA_DIV, FPU_FPUDA_FMA) + (FPU_FPUDA_ALL, FPU_FPUS_DIV, FPU_FPUS_FMA, FPU_FPUS_ALL) + (FPU_FPUD_DIV, FPU_FPUD_FMA, FPU_FPUD_ALL): New defines. + (DEFAULT_arc_fpu_build): Define. + (DEFAULT_arc_mpy_option): Define. + * config/arc/arc-protos.h (arc_init): Delete. + * config/arc/arc.c (arc_cpu_name): New variable. + (arc_selected_cpu, arc_selected_arch, arc_arcem, arc_archs) + (arc_arc700, arc_arc600, arc_arc601): New variable. + (arc_init): Add static; remove selection of default tune value, + cleanup obsolete error messages. + (arc_override_options): Make use of .def files for selecting the + right cpu and option configurations. + * config/arc/arc.h (stdbool.h): Include. + (TARGET_CPU_DEFAULT): Define. + (CPP_SPEC): Remove mcpu=NPS400 handling. + (arc_cpu_to_as): Declare. + (EXTRA_SPEC_FUNCTIONS): Define. + (OPTION_DEFAULT_SPECS): Likewise. + (ASM_DEFAULT): Remove. + (ASM_SPEC): Use arc_cpu_to_as. + (DRIVER_SELF_SPECS): Remove deprecated options. + (arc_base_cpu): Declare. + (TARGET_ARC600, TARGET_ARC601, TARGET_ARC700, TARGET_EM) + (TARGET_HS, TARGET_V2, TARGET_ARC600): Make them use arc_base_cpu + variable. + (MULTILIB_DEFAULTS): Use ARC_MULTILIB_CPU_DEFAULT. + * config/arc/arc.md (attr_cpu): Remove. + * config/arc/arc.opt (mno-mpy): Deprecate. + (mcpu=ARC600, mcpu=ARC601, mcpu=ARC700, mcpu=NPS400, mcpu=ARCEM) + (mcpu=ARCHS): Remove. + (mcrc, mdsp-packa, mdvbf, mmac-d16, mmac-24, mtelephony, mrtsc): + Deprecate. + (mbarrel_shifte, mspfp_, mdpfp_, mdsp_pack, mmac_): Remove. + (arc_fpu): Use new defines. + (mpy-option): Change to use numeric or string like inputs. + * config/arc/t-arc (driver-arc.o): New target. + (arc-cpus, t-multilib, arc-tables.opt): Likewise. + * config/arc/t-arc-newlib: Delete. + * config/arc/t-arc-uClibc: Renamed to t-uClibc. + * doc/invoke.texi (ARC): Update arc options. + 2016-11-15 Maciej W. Rozycki <macro@imgtec.com> * config/mips/mips.c (mips16_emit_constants): Emit `consttable' diff --git a/gcc/common/config/arc/arc-common.c b/gcc/common/config/arc/arc-common.c index 5b687fb16ad5e869e160391fa2a4fdd1c9fd7c91..1dbddae388a6955a3540f706478f4bc3da25e3fa 100644 --- a/gcc/common/config/arc/arc-common.c +++ b/gcc/common/config/arc/arc-common.c @@ -2,6 +2,7 @@ Copyright (C) 1994-2016 Free Software Foundation, Inc. Contributor: Joern Rennecke <joern.rennecke@embecosm.com> on behalf of Synopsys Inc. + Claudiu Zissulescu <Claudiu.Zissulescu@synopsys.com> This file is part of GCC. @@ -61,17 +62,19 @@ static const struct default_options arc_option_optimization_table[] = /* Process options. */ static bool -arc_handle_option (struct gcc_options *opts, struct gcc_options *opts_set, +arc_handle_option (struct gcc_options *opts, + struct gcc_options *opts_set ATTRIBUTE_UNUSED, const struct cl_decoded_option *decoded, location_t loc) { size_t code = decoded->opt_index; int value = decoded->value; const char *arg = decoded->arg; + static int mcpu_seen = PROCESSOR_NONE; + char *p; switch (code) { - static int mcpu_seen = PROCESSOR_NONE; case OPT_mcpu_: /* N.B., at this point arc_cpu has already been set to its new value by our caller, so comparing arc_cpu with PROCESSOR_NONE is pointless. */ @@ -79,71 +82,33 @@ arc_handle_option (struct gcc_options *opts, struct gcc_options *opts_set, if (mcpu_seen != PROCESSOR_NONE && mcpu_seen != value) warning_at (loc, 0, "multiple -mcpu= options specified."); mcpu_seen = value; - - switch (value) - { - case PROCESSOR_NPS400: - if (! (opts_set->x_TARGET_CASE_VECTOR_PC_RELATIVE) ) - opts->x_TARGET_CASE_VECTOR_PC_RELATIVE = 1; - /* Fall through */ - case PROCESSOR_ARC600: - case PROCESSOR_ARC700: - if (! (opts_set->x_target_flags & MASK_BARREL_SHIFTER) ) - opts->x_target_flags |= MASK_BARREL_SHIFTER; - break; - case PROCESSOR_ARC601: - if (! (opts_set->x_target_flags & MASK_BARREL_SHIFTER) ) - opts->x_target_flags &= ~MASK_BARREL_SHIFTER; - break; - case PROCESSOR_ARCHS: - if ( !(opts_set->x_target_flags & MASK_BARREL_SHIFTER)) - opts->x_target_flags |= MASK_BARREL_SHIFTER; /* Default: on. */ - if ( !(opts_set->x_target_flags & MASK_CODE_DENSITY)) - opts->x_target_flags |= MASK_CODE_DENSITY; /* Default: on. */ - if ( !(opts_set->x_target_flags & MASK_NORM_SET)) - opts->x_target_flags |= MASK_NORM_SET; /* Default: on. */ - if ( !(opts_set->x_target_flags & MASK_SWAP_SET)) - opts->x_target_flags |= MASK_SWAP_SET; /* Default: on. */ - if ( !(opts_set->x_target_flags & MASK_DIVREM)) - opts->x_target_flags |= MASK_DIVREM; /* Default: on. */ - break; - - case PROCESSOR_ARCEM: - if ( !(opts_set->x_target_flags & MASK_BARREL_SHIFTER)) - opts->x_target_flags |= MASK_BARREL_SHIFTER; /* Default: on. */ - if ( !(opts_set->x_target_flags & MASK_CODE_DENSITY)) - opts->x_target_flags &= ~MASK_CODE_DENSITY; /* Default: off. */ - if ( !(opts_set->x_target_flags & MASK_NORM_SET)) - opts->x_target_flags &= ~MASK_NORM_SET; /* Default: off. */ - if ( !(opts_set->x_target_flags & MASK_SWAP_SET)) - opts->x_target_flags &= ~MASK_SWAP_SET; /* Default: off. */ - if ( !(opts_set->x_target_flags & MASK_DIVREM)) - opts->x_target_flags &= ~MASK_DIVREM; /* Default: off. */ - break; - default: - gcc_unreachable (); - } break; case OPT_mmpy_option_: - if (value < 0 || value > 9) - error_at (loc, "bad value %qs for -mmpy-option switch", arg); + if (opts->x_arc_mpy_option == 1) + warning_at (loc, 0, "Unsupported value for mmpy-option"); + break; + + default: break; } return true; } +#undef TARGET_OPTION_INIT_STRUCT #define TARGET_OPTION_INIT_STRUCT arc_option_init_struct + +#undef TARGET_OPTION_OPTIMIZATION_TABLE #define TARGET_OPTION_OPTIMIZATION_TABLE arc_option_optimization_table -#define TARGET_HANDLE_OPTION arc_handle_option #define DEFAULT_NO_SDATA (TARGET_SDATA_DEFAULT ? 0 : MASK_NO_SDATA_SET) -/* We default to ARC700, which has the barrel shifter enabled. */ -#define TARGET_DEFAULT_TARGET_FLAGS \ - (MASK_BARREL_SHIFTER|MASK_VOLATILE_CACHE_SET|DEFAULT_NO_SDATA) +#undef TARGET_DEFAULT_TARGET_FLAGS +#define TARGET_DEFAULT_TARGET_FLAGS (DEFAULT_NO_SDATA | MASK_VOLATILE_CACHE_SET) +#undef TARGET_HANDLE_OPTION +#define TARGET_HANDLE_OPTION arc_handle_option #include "common/common-target-def.h" diff --git a/gcc/config.gcc b/gcc/config.gcc index 3e0be2297652f527ebfc3559a996e2362aa95051..595563b40ee78f0558059b197892f4f2e4e8d02a 100644 --- a/gcc/config.gcc +++ b/gcc/config.gcc @@ -318,6 +318,7 @@ arc*-*-*) cpu_type=arc c_target_objs="arc-c.o" cxx_target_objs="arc-c.o" + extra_options="${extra_options} arc/arc-tables.opt" ;; arm*-*-*) cpu_type=arm @@ -999,13 +1000,12 @@ alpha*-dec-*vms*) ;; arc*-*-elf*) extra_headers="arc-simd.h" - tm_file="dbxelf.h elfos.h newlib-stdint.h ${tm_file}" - tmake_file="arc/t-arc-newlib arc/t-arc" - case x"${with_cpu}" in - xarc600|xarc601|xarc700) - target_cpu_default="TARGET_CPU_$with_cpu" - ;; - esac + tm_file="arc/arc-arch.h dbxelf.h elfos.h newlib-stdint.h ${tm_file}" + tmake_file="arc/t-multilib arc/t-arc" + extra_gcc_objs="driver-arc.o" + if test "x$with_cpu" != x; then + tm_defines="${tm_defines} TARGET_CPU_BUILD=PROCESSOR_$with_cpu" + fi if test x${with_endian} = x; then case ${target} in arc*be-*-* | arc*eb-*-*) with_endian=big ;; @@ -1022,15 +1022,14 @@ arc*-*-elf*) ;; arc*-*-linux-uclibc*) extra_headers="arc-simd.h" - tm_file="dbxelf.h elfos.h gnu-user.h linux.h glibc-stdint.h ${tm_file}" - tmake_file="${tmake_file} arc/t-arc-uClibc arc/t-arc" + tm_file="arc/arc-arch.h dbxelf.h elfos.h gnu-user.h linux.h glibc-stdint.h ${tm_file}" + tmake_file="${tmake_file} arc/t-uClibc arc/t-arc" tm_defines="${tm_defines} TARGET_SDATA_DEFAULT=0" tm_defines="${tm_defines} TARGET_MMEDIUM_CALLS_DEFAULT=1" - case x"${with_cpu}" in - xarc600|xarc601|xarc700) - target_cpu_default="TARGET_CPU_$with_cpu" - ;; - esac + extra_gcc_objs="driver-arc.o" + if test "x$with_cpu" != x; then + tm_defines="${tm_defines} TARGET_CPU_BUILD=PROCESSOR_$with_cpu" + fi if test x${with_endian} = x; then case ${target} in arc*be-*-* | arc*eb-*-*) with_endian=big ;; @@ -3624,15 +3623,19 @@ case "${target}" in done ;; - arc*-*-*) # was: arc*-*-linux-uclibc) + arc*-*-*) supported_defaults="cpu" - case $with_cpu in - arc600|arc601|arc700) - ;; - *) echo "Unknown cpu type" - exit 1 - ;; - esac + + if [ x"$with_cpu" = x ] \ + || grep "^ARC_CPU ($with_cpu," \ + ${srcdir}/config/arc/arc-cpus.def \ + > /dev/null; then + # Ok + true + else + echo "Unknown cpu used in --with-cpu=$with_cpu" 1>&2 + exit 1 + fi ;; arm*-*-*) diff --git a/gcc/config/arc/arc-arch.h b/gcc/config/arc/arc-arch.h new file mode 100644 index 0000000000000000000000000000000000000000..bfd3f234f32a7f6a9331ab5010ccaee923f3e700 --- /dev/null +++ b/gcc/config/arc/arc-arch.h @@ -0,0 +1,123 @@ +/* Definitions of types that are used to store ARC architecture and + device information. + Copyright (C) 2016 Free Software Foundation, Inc. + Contributed by Claudiu Zissulescu (claziss@synopsys.com) + +This file is part of GCC. + +GCC is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 3, or (at your option) +any later version. + +GCC is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with GCC; see the file COPYING3. If not see +<http://www.gnu.org/licenses/>. */ + +#ifndef GCC_ARC_ARCH_H +#define GCC_ARC_ARCH_H + +#ifndef IN_LIBGCC2 +/* Architecture selection types. */ + +enum cpu_flags + { +#define ARC_OPT(NAME, CODE, MASK, DOC) NAME = CODE, +#define ARC_OPTX(NAME, CODE, VAR, VAL, DOC) NAME = CODE, +#include "arc-options.def" +#undef ARC_OPT +#undef ARC_OPTX + FL_END + }; + + +/* ARC architecture variants. */ + +enum base_architecture + { + BASE_ARCH_NONE, +#define ARC_ARCH(NAME, ARCH, FLAGS, DFLAGS) BASE_ARCH_##ARCH, +#include "arc-arches.def" +#undef ARC_ARCH + BASE_ARCH_END + }; + + +/* Tune variants. Needs to match the attr_tune enum. */ + +enum arc_tune_attr + { + ARC_TUNE_NONE, + ARC_TUNE_ARC600, + ARC_TUNE_ARC700_4_2_STD, + ARC_TUNE_ARC700_4_2_XMAC + }; + +/* CPU specific properties. */ + +typedef struct +{ + /* CPU name. */ + const char *const name; + + /* Architecture class. */ + enum base_architecture arch; + + /* Specific processor type. */ + enum processor_type processor; + + /* Specific flags. */ + const unsigned long long flags; + + /* Tune value. */ + enum arc_tune_attr tune; +} arc_cpu_t; + + +/* Architecture specific propoerties. */ + +typedef struct +{ + /* Architecture name. */ + const char *const name; + + /* Architecture class. */ + enum base_architecture arch; + + /* All allowed flags for this architecture. */ + const unsigned long long flags; + + /* Default flags for this architecture. It is a subset of + FLAGS. */ + const unsigned long long dflags; +} arc_arch_t; + + + +const arc_arch_t arc_arch_types[] = + { + {"none", BASE_ARCH_NONE, 0, 0}, +#define ARC_ARCH(NAME, ARCH, FLAGS, DFLAGS) \ + {NAME, BASE_ARCH_##ARCH, FLAGS, DFLAGS}, +#include "arc-arches.def" +#undef ARC_ARCH + {NULL, BASE_ARCH_END, 0, 0} + }; + +const arc_cpu_t arc_cpu_types[] = + { + {"none", BASE_ARCH_NONE, PROCESSOR_NONE, 0, ARC_TUNE_NONE}, +#define ARC_CPU(NAME, ARCH, FLAGS, TUNE) \ + {#NAME, BASE_ARCH_##ARCH, PROCESSOR_##NAME, FLAGS, ARC_TUNE_##TUNE}, +#include "arc-cpus.def" +#undef ARC_CPU + {NULL, BASE_ARCH_END, PROCESSOR_NONE, 0, ARC_TUNE_NONE} + }; + +#endif +#endif /* GCC_ARC_ARCH_H */ diff --git a/gcc/config/arc/arc-arches.def b/gcc/config/arc/arc-arches.def new file mode 100644 index 0000000000000000000000000000000000000000..f24babb4d5325d18ad0f8c8ae2aaa1451da554af --- /dev/null +++ b/gcc/config/arc/arc-arches.def @@ -0,0 +1,56 @@ +/* ARC ARCH architectures. + Copyright (C) 2016 Free Software Foundation, Inc. + + This file is part of GCC. + + GCC is free software; you can redistribute it and/or modify it + under the terms of the GNU General Public License as published + by the Free Software Foundation; either version 3, or (at your + option) any later version. + + GCC is distributed in the hope that it will be useful, but WITHOUT + ANY WARRANTY; without even the implied warranty of MERCHANTABILITY + or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public + License for more details. + + You should have received a copy of the GNU General Public License + along with GCC; see the file COPYING3. If not see + <http://www.gnu.org/licenses/>. */ + +/* List of all known ARC base architectures. These defines are used + to check if command line given options are valid for a specific + architecture, and to set default architecture options, if needed. + + Before including this file, define a macro: + + ARC_ARCH (NAME, ARCH, DEV_HW_FACILITIES, DEF_HW_FACILITIES) + + where the arguments are the fields of arc_arch_t: + + NAME Architecture given name; + + ARCH Architecture class as in enum base_architecture; + + DEV_HW_FACILITIES All allowed architecture hardware facilities. + These facilities are represented as compiler + options, defined in arc_options.def file. + + DEF_HW_FACILITIES Default flags for this architecture. It is a + subset of DEV_HW_FACILITIES. */ + +ARC_ARCH ("arcem", em, FL_MPYOPT_1_6 | FL_DIVREM | FL_CD | FL_NORM \ + | FL_BS | FL_SWAP | FL_FPUS | FL_SPFP | FL_DPFP \ + | FL_SIMD | FL_FPUDA, 0) +ARC_ARCH ("archs", hs, FL_MPYOPT_7_9 | FL_DIVREM | FL_NORM | FL_CD \ + | FL_ATOMIC | FL_LL64 | FL_BS | FL_SWAP \ + | FL_FPUS | FL_FPUD, \ + FL_CD | FL_ATOMIC | FL_BS | FL_NORM | FL_SWAP) +ARC_ARCH ("arc6xx", 6xx, FL_BS | FL_NORM | FL_SWAP | FL_MUL64 | FL_MUL32x16 \ + | FL_SPFP | FL_ARGONAUT | FL_DPFP, 0) +ARC_ARCH ("arc700", 700, FL_ATOMIC | FL_BS | FL_NORM | FL_SWAP | FL_EA \ + | FL_SIMD | FL_SPFP | FL_ARGONAUT | FL_DPFP, \ + FL_BS | FL_NORM | FL_SWAP) + +/* Local Variables: */ +/* mode: c */ +/* End: */ diff --git a/gcc/config/arc/arc-c.def b/gcc/config/arc/arc-c.def index 065e97360dedd8760111789bf06e5b1a27da2b32..4cfd7b6e35fd55273e68f54bf26f2d1db302f57f 100644 --- a/gcc/config/arc/arc-c.def +++ b/gcc/config/arc/arc-c.def @@ -66,3 +66,7 @@ ARC_C_DEF ("__EM__", TARGET_EM) ARC_C_DEF ("__HS__", TARGET_HS) ARC_C_DEF ("__Xnorm", TARGET_NORM) ARC_C_DEF ("__Xbarrel_shifter", TARGET_BARREL_SHIFTER) + +/* Local Variables: */ +/* mode: c */ +/* End: */ diff --git a/gcc/config/arc/arc-cpus.def b/gcc/config/arc/arc-cpus.def new file mode 100644 index 0000000000000000000000000000000000000000..0ceb7344a8397dff3eedc276f601c993ea690962 --- /dev/null +++ b/gcc/config/arc/arc-cpus.def @@ -0,0 +1,75 @@ +/* ARC CPU architectures. + Copyright (C) 2016 Free Software Foundation, Inc. + + This file is part of GCC. + + GCC is free software; you can redistribute it and/or modify it + under the terms of the GNU General Public License as published + by the Free Software Foundation; either version 3, or (at your + option) any later version. + + GCC is distributed in the hope that it will be useful, but WITHOUT + ANY WARRANTY; without even the implied warranty of MERCHANTABILITY + or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public + License for more details. + + You should have received a copy of the GNU General Public License + along with GCC; see the file COPYING3. If not see + <http://www.gnu.org/licenses/>. */ + +/* List of various ARC CPU configurations. If updated, cd to + $(builddir)/gcc and run + + $ make arc-cpus + + This will regenerate / update the following source files: + + - $(srcdir)/config/arc/t-multilib + - $(srcdir)/config/arc/arc-tables.opt + + After that, rebuild everything and check-in the new sources to the + repo. This file defines the accepted values for -mcpu=<CPU> + option. + + Before including this file, define a macro: + + ARC_CPU (NAME, ARCH, FLAGS, TUNE) + + where the arguments are the fields of arc_cpu_t: + + NAME A given arbitrary name. + ARCH Base architecture for the given CPU. + FLAGS Specific hardware flags that are enabled by this CPU configuration, + as defined in arc-options.def file, and allowed by arc-arches.def + file. The specific hardware flags are enumerated without using + spaces between the '|' character and consequtive flags. + TUNE Tune value for the given configuration, otherwise NONE. */ + +ARC_CPU (em, em, 0, NONE) +ARC_CPU (arcem, em, FL_MPYOPT_2|FL_CD|FL_BS, NONE) +ARC_CPU (em4, em, FL_CD, NONE) +ARC_CPU (em4_dmips, em, FL_MPYOPT_2|FL_CD|FL_DIVREM|FL_NORM|FL_SWAP|FL_BS, NONE) +ARC_CPU (em4_fpus, em, FL_MPYOPT_2|FL_CD|FL_DIVREM|FL_NORM|FL_SWAP|FL_BS|FL_FPU_FPUS, NONE) +ARC_CPU (em4_fpuda, em, FL_MPYOPT_2|FL_CD|FL_DIVREM|FL_NORM|FL_SWAP|FL_BS|FL_FPU_FPUDA, NONE) + +ARC_CPU (hs, hs, 0, NONE) +ARC_CPU (archs, hs, FL_MPYOPT_2|FL_DIVREM|FL_LL64, NONE) +ARC_CPU (hs34, hs, FL_MPYOPT_2, NONE) +ARC_CPU (hs38, hs, FL_MPYOPT_9|FL_DIVREM|FL_LL64, NONE) +ARC_CPU (hs38_linux, hs, FL_MPYOPT_9|FL_DIVREM|FL_LL64|FL_FPU_FPUD_ALL, NONE) + +ARC_CPU (arc600, 6xx, FL_BS, ARC600) +ARC_CPU (arc600_norm, 6xx, FL_BS|FL_NORM, ARC600) +ARC_CPU (arc600_mul64, 6xx, FL_BS|FL_NORM|FL_MUL64, ARC600) +ARC_CPU (arc600_mul32x16, 6xx, FL_BS|FL_NORM|FL_MUL32x16, ARC600) +ARC_CPU (arc601, 6xx, 0, ARC600) +ARC_CPU (arc601_norm, 6xx, FL_NORM, ARC600) +ARC_CPU (arc601_mul64, 6xx, FL_NORM|FL_MUL64, ARC600) +ARC_CPU (arc601_mul32x16, 6xx, FL_NORM|FL_MUL32x16, ARC600) + +ARC_CPU (arc700, 700, 0, ARC700_4_2_STD) +ARC_CPU (nps400, 700, 0, ARC700_4_2_STD) + +/* Local Variables: */ +/* mode: c */ +/* End: */ diff --git a/gcc/config/arc/arc-options.def b/gcc/config/arc/arc-options.def new file mode 100644 index 0000000000000000000000000000000000000000..0f9d36ccc84df0fee23d625044516042ebef7aac --- /dev/null +++ b/gcc/config/arc/arc-options.def @@ -0,0 +1,109 @@ +/* ARC options. + Copyright (C) 2016 Free Software Foundation, Inc. + + This file is part of GCC. + + GCC is free software; you can redistribute it and/or modify it + under the terms of the GNU General Public License as published + by the Free Software Foundation; either version 3, or (at your + option) any later version. + + GCC is distributed in the hope that it will be useful, but WITHOUT + ANY WARRANTY; without even the implied warranty of MERCHANTABILITY + or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public + License for more details. + + You should have received a copy of the GNU General Public License + along with GCC; see the file COPYING3. If not see + <http://www.gnu.org/licenses/>. */ + +/* List of all known ARC hardware modifier options (i.e., compiler + options that are selecting a hardware facility). There can be two + types options: simple switches (e.g. code-density option can be + on/off), or can accept multiple values (e.g., fpu options). + + For any valid HW option, define a macro: + + ARC_OPT (NAME, CODE, MASK, DOC) + + where: + NAME Name (identifier) of a particular hardware modifier option, + as in enum cpu_flags. + + CODE 64-bit mask used to encode NAME. + + MASK Corresponding GCC's MASK_<option> macro. + + DOC A string used when emitting compiler errors or warnings. + + For a multi-value option, define a macro for a valid value: + + ARC_OPTX (NAME, CODE, VAR, VAL, DOC) + + where: + NAME Name (identifier) of a particular hardware modifier + configuration. + + CODE 64-bit mask used to encode NAME. It will be encoded in the + same variable like options given via ARC_OPT. + + VAR Corresponding GCC's option variable. + + VAL Value to be set in VAR. + + DOC A string used when emitting compiler errors or warnings. + + All multi-value options are defined using ARC_OPTX and ARC_OPT. + ARC_OPT contains a mask with all valid values for the given + option. */ + +ARC_OPT (FL_CD, (1ULL << 0), MASK_CODE_DENSITY, "code density") +ARC_OPT (FL_DIVREM, (1ULL << 1), MASK_DIVREM, "div/rem") +ARC_OPT (FL_NORM, (1ULL << 2), MASK_NORM_SET, "norm") + +ARC_OPT (FL_ATOMIC, (1ULL << 4), MASK_ATOMIC, "atomic") +ARC_OPT (FL_LL64, (1ULL << 5), MASK_LL64, "double load/store") +ARC_OPT (FL_BS, (1ULL << 6), MASK_BARREL_SHIFTER, "barrel shifter") +ARC_OPT (FL_SWAP, (1ULL << 7), MASK_SWAP_SET, "swap") +ARC_OPT (FL_MUL64, (1ULL << 8), MASK_MUL64_SET, "mul64") +ARC_OPT (FL_MUL32x16, (1ULL << 9), MASK_MULMAC_32BY16_SET, "mul32x16") + +ARC_OPT (FL_EA, (1ULL << 11), MASK_EA_SET, "extended arithmetics") +ARC_OPT (FL_SPFP, (1ULL << 12), MASK_SPFP_COMPACT_SET, "single precission FPX") +ARC_OPT (FL_DPFP, (1ULL << 13), MASK_DPFP_COMPACT_SET, "double precission FPX") +ARC_OPT (FL_ARGONAUT, (1ULL << 14), MASK_ARGONAUT_SET, "argonaut") +ARC_OPT (FL_SIMD, (1ULL << 15), MASK_SIMD_SET, "simd") + +ARC_OPTX (FL_MPYOPT_1, (1ULL << 17), arc_mpy_option, 1, "mpy option w") +ARC_OPTX (FL_MPYOPT_2, (1ULL << 18), arc_mpy_option, 2, "mpy option wlh1") +ARC_OPTX (FL_MPYOPT_3, (1ULL << 19), arc_mpy_option, 3, "mpy option wlh2") +ARC_OPTX (FL_MPYOPT_4, (1ULL << 20), arc_mpy_option, 4, "mpy option wlh3") +ARC_OPTX (FL_MPYOPT_5, (1ULL << 21), arc_mpy_option, 5, "mpy option wlh4") +ARC_OPTX (FL_MPYOPT_6, (1ULL << 22), arc_mpy_option, 6, "mpy option wlh5") +ARC_OPTX (FL_MPYOPT_7, (1ULL << 23), arc_mpy_option, 7, "mpy option plus_dmpy") +ARC_OPTX (FL_MPYOPT_8, (1ULL << 24), arc_mpy_option, 8, "mpy option plus_macd") +ARC_OPTX (FL_MPYOPT_9, (1ULL << 25), arc_mpy_option, 9, "mpy option plus_qmacw") + +ARC_OPT (FL_MPYOPT_7_9, (0x01c2ULL << 17), 0, "mpy option") +ARC_OPT (FL_MPYOPT_1_6, (0x003fULL << 17), 0, "mpy option") + +ARC_OPTX (FL_FPU_FPUS, (1ULL << 26), arc_fpu_build, FPU_FPUS, "mfpu=fpus") +ARC_OPTX (FL_FPU_FPUS_DIV, (1ULL << 27), arc_fpu_build, FPU_FPUS_DIV, "mfpu=fpus_div") +ARC_OPTX (FL_FPU_FPUS_FMA, (1ULL << 28), arc_fpu_build, FPU_FPUS_FMA, "mfpu=fpus_fma") +ARC_OPTX (FL_FPU_FPUS_ALL, (1ULL << 29), arc_fpu_build, FPU_FPUS_ALL, "mfpu=fpus_all") +ARC_OPTX (FL_FPU_FPUDA, (1ULL << 30), arc_fpu_build, FPU_FPUDA, "mfpu=fpuda") +ARC_OPTX (FL_FPU_FPUDA_DIV, (1ULL << 31), arc_fpu_build, FPU_FPUDA_DIV, "mfpu=fpuda_div") +ARC_OPTX (FL_FPU_FPUDA_FMA, (1ULL << 32), arc_fpu_build, FPU_FPUDA_FMA, "mfpu=fpuda_fma") +ARC_OPTX (FL_FPU_FPUDA_ALL, (1ULL << 33), arc_fpu_build, FPU_FPUDA_ALL, "mfpu=fpuda_all") +ARC_OPTX (FL_FPU_FPUD, (1ULL << 34), arc_fpu_build, FPU_FPUD, "mfpu=fpud") +ARC_OPTX (FL_FPU_FPUD_DIV, (1ULL << 35), arc_fpu_build, FPU_FPUD_DIV, "mfpu=fpud_div") +ARC_OPTX (FL_FPU_FPUD_FMA, (1ULL << 36), arc_fpu_build, FPU_FPUD_FMA, "mfpu=fpud_fma") +ARC_OPTX (FL_FPU_FPUD_ALL, (1ULL << 37), arc_fpu_build, FPU_FPUD_ALL, "mfpu=fpud_all") + +ARC_OPT (FL_FPUS, (0xFULL << 26), 0, "single precission floating point") +ARC_OPT (FL_FPUDA, (0xFFULL << 26), 0, "double precission fp assist") +ARC_OPT (FL_FPUD, (0xF0FULL << 26), 0, "double precission floating point") + +/* Local Variables: */ +/* mode: c */ +/* End: */ diff --git a/gcc/config/arc/arc-opts.h b/gcc/config/arc/arc-opts.h index cbd78985dd8bbbc5fb53c24200633e724af1ed1c..e5bca8494f1b10e1f7dce713d3ca7a7988725817 100644 --- a/gcc/config/arc/arc-opts.h +++ b/gcc/config/arc/arc-opts.h @@ -18,15 +18,16 @@ along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#ifndef ARC_OPTS_H +#define ARC_OPTS_H + enum processor_type { - PROCESSOR_NONE, - PROCESSOR_ARC600, - PROCESSOR_ARC601, - PROCESSOR_ARC700, - PROCESSOR_NPS400, - PROCESSOR_ARCEM, - PROCESSOR_ARCHS + PROCESSOR_NONE = 0, +#define ARC_CPU(NAME, ARCH, FLAGS, TUNE) PROCESSOR_##NAME, +#include "arc-cpus.def" +#undef ARC_CPU + PROCESSOR_generic }; /* Single precision floating point. */ @@ -48,3 +49,37 @@ enum processor_type /* Double precision floating point assist operations. */ #define FPX_DP 0x0100 +/* fpus option combi. */ +#define FPU_FPUS (FPU_SP | FPU_SC) +/* fpud option combi. */ +#define FPU_FPUD (FPU_SP | FPU_SC | FPU_DP | FPU_DC) +/* fpuda option combi. */ +#define FPU_FPUDA (FPU_SP | FPU_SC | FPX_DP) +/* fpuda_div option combi. */ +#define FPU_FPUDA_DIV (FPU_SP | FPU_SC | FPU_SD | FPX_DP) +/* fpuda_fma option combi. */ +#define FPU_FPUDA_FMA (FPU_SP | FPU_SC | FPU_SF | FPX_DP) +/* fpuda_all option combi. */ +#define FPU_FPUDA_ALL (FPU_SP | FPU_SC | FPU_SF | FPU_SD | FPX_DP) +/* fpus_div option combi. */ +#define FPU_FPUS_DIV (FPU_SP | FPU_SC | FPU_SD) +/* fpus_fma option combi. */ +#define FPU_FPUS_FMA (FPU_SP | FPU_SC | FPU_SF) +/* fpus_all option combi. */ +#define FPU_FPUS_ALL (FPU_SP | FPU_SC | FPU_SF | FPU_SD) +/* fpud_div option combi. */ +#define FPU_FPUD_DIV (FPU_FPUS_DIV | FPU_DP | FPU_DC | FPU_DD) +/* fpud_fma option combi. */ +#define FPU_FPUD_FMA (FPU_FPUS_FMA | FPU_DP | FPU_DC | FPU_DF) +/* fpud_all option combi. */ +#define FPU_FPUD_ALL (FPU_FPUS_ALL | FPU_DP | FPU_DC | FPU_DF | FPU_DD) + +/* Default FPU option value needed to mark if the variable in question + is changed by a command line option or not. This is required when + we set the cpu's specific configuration. */ +#define DEFAULT_arc_fpu_build 0x10000000 + +/* Default MPY option value. */ +#define DEFAULT_arc_mpy_option -1 + +#endif /* ARC_OPTS_H */ diff --git a/gcc/config/arc/arc-protos.h b/gcc/config/arc/arc-protos.h index ad5d4d347ec5e6f8a9c5e7d6990c2746d3cc9c0e..d1266b4a6dbf92635d03257c8a792c711d1bc6c4 100644 --- a/gcc/config/arc/arc-protos.h +++ b/gcc/config/arc/arc-protos.h @@ -52,7 +52,6 @@ extern enum arc_function_type arc_compute_function_type (struct function *); #endif /* TREE_CODE */ -extern void arc_init (void); extern unsigned int arc_compute_frame_size (int); extern bool arc_ccfsm_branch_deleted_p (void); extern void arc_ccfsm_record_branch_deleted (void); diff --git a/gcc/config/arc/arc-tables.opt b/gcc/config/arc/arc-tables.opt new file mode 100644 index 0000000000000000000000000000000000000000..0e7c50c7be78553956fb4b35ab0f2ce698e21312 --- /dev/null +++ b/gcc/config/arc/arc-tables.opt @@ -0,0 +1,90 @@ +; Auto-generated Makefile Snip +; Generated by : ./gcc/config/arc/genoptions.awk +; Generated from : ./gcc/config/arc/arc-cpu.def +; +; Copyright (C) 2016 Free Software Foundation, Inc. +; +; This file is part of GCC. +; +; GCC is free software; you can redistribute it and/or modify it under +; the terms of the GNU General Public License as published by the Free +; Software Foundation; either version 3, or (at your option) any later +; version. +; +; GCC is distributed in the hope that it will be useful, but WITHOUT ANY +; WARRANTY; without even the implied warranty of MERCHANTABILITY or +; FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License +; for more details. +; +; You should have received a copy of the GNU General Public License +; along with GCC; see the file COPYING3. If not see +; <http://www.gnu.org/licenses/>. + +Enum +Name(processor_type) Type(enum processor_type) +Known ARC CPUs (for use with the -mcpu= option): + +EnumValue +Enum(processor_type) String(em) Value(PROCESSOR_em) + +EnumValue +Enum(processor_type) String(arcem) Value(PROCESSOR_arcem) + +EnumValue +Enum(processor_type) String(em4) Value(PROCESSOR_em4) + +EnumValue +Enum(processor_type) String(em4_dmips) Value(PROCESSOR_em4_dmips) + +EnumValue +Enum(processor_type) String(em4_fpus) Value(PROCESSOR_em4_fpus) + +EnumValue +Enum(processor_type) String(em4_fpuda) Value(PROCESSOR_em4_fpuda) + +EnumValue +Enum(processor_type) String(hs) Value(PROCESSOR_hs) + +EnumValue +Enum(processor_type) String(archs) Value(PROCESSOR_archs) + +EnumValue +Enum(processor_type) String(hs34) Value(PROCESSOR_hs34) + +EnumValue +Enum(processor_type) String(hs38) Value(PROCESSOR_hs38) + +EnumValue +Enum(processor_type) String(hs38_linux) Value(PROCESSOR_hs38_linux) + +EnumValue +Enum(processor_type) String(arc600) Value(PROCESSOR_arc600) + +EnumValue +Enum(processor_type) String(arc600_norm) Value(PROCESSOR_arc600_norm) + +EnumValue +Enum(processor_type) String(arc600_mul64) Value(PROCESSOR_arc600_mul64) + +EnumValue +Enum(processor_type) String(arc600_mul32x16) Value(PROCESSOR_arc600_mul32x16) + +EnumValue +Enum(processor_type) String(arc601) Value(PROCESSOR_arc601) + +EnumValue +Enum(processor_type) String(arc601_norm) Value(PROCESSOR_arc601_norm) + +EnumValue +Enum(processor_type) String(arc601_mul64) Value(PROCESSOR_arc601_mul64) + +EnumValue +Enum(processor_type) String(arc601_mul32x16) Value(PROCESSOR_arc601_mul32x16) + +EnumValue +Enum(processor_type) String(arc700) Value(PROCESSOR_arc700) + +EnumValue +Enum(processor_type) String(nps400) Value(PROCESSOR_nps400) + + diff --git a/gcc/config/arc/arc.c b/gcc/config/arc/arc.c index 5ba7ccc776f6b7cab812f091bbd9108c7c992618..3bce7ef3661078473536ddcd1dd6c2c45a6373b1 100644 --- a/gcc/config/arc/arc.c +++ b/gcc/config/arc/arc.c @@ -65,7 +65,8 @@ along with GCC; see the file COPYING3. If not see #include "alias.h" /* Which cpu we're compiling for (ARC600, ARC601, ARC700). */ -static const char *arc_cpu_string = ""; +static char arc_cpu_name[10] = ""; +static const char *arc_cpu_string = arc_cpu_name; /* ??? Loads can handle any constant, stores can only handle small ones. */ /* OTOH, LIMMs cost extra, so their usefulness is limited. */ @@ -242,6 +243,12 @@ static bool arc_use_by_pieces_infrastructure_p (unsigned HOST_WIDE_INT, enum by_pieces_operation op, bool); +static const arc_cpu_t *arc_selected_cpu; +static const arc_arch_t *arc_selected_arch; + +/* Global var which sets the current compilation architecture. */ +enum base_architecture arc_base_cpu; + /* Implements target hook vector_mode_supported_p. */ static bool @@ -669,47 +676,9 @@ make_pass_arc_predicate_delay_insns (gcc::context *ctxt) /* Called by OVERRIDE_OPTIONS to initialize various things. */ -void +static void arc_init (void) { - enum attr_tune tune_dflt = TUNE_NONE; - - switch (arc_cpu) - { - case PROCESSOR_ARC600: - arc_cpu_string = "ARC600"; - tune_dflt = TUNE_ARC600; - break; - - case PROCESSOR_ARC601: - arc_cpu_string = "ARC601"; - tune_dflt = TUNE_ARC600; - break; - - case PROCESSOR_ARC700: - arc_cpu_string = "ARC700"; - tune_dflt = TUNE_ARC700_4_2_STD; - break; - - case PROCESSOR_NPS400: - arc_cpu_string = "NPS400"; - tune_dflt = TUNE_ARC700_4_2_STD; - break; - - case PROCESSOR_ARCEM: - arc_cpu_string = "EM"; - break; - - case PROCESSOR_ARCHS: - arc_cpu_string = "HS"; - break; - - default: - gcc_unreachable (); - } - - if (arc_tune == TUNE_NONE) - arc_tune = tune_dflt; /* Note: arc_multcost is only used in rtx_cost if speed is true. */ if (arc_multcost < 0) switch (arc_tune) @@ -740,18 +709,10 @@ arc_init (void) break; } - /* Support mul64 generation only for ARC600. */ - if (TARGET_MUL64_SET && (!TARGET_ARC600_FAMILY)) - error ("-mmul64 not supported for ARC700 or ARCv2"); - /* MPY instructions valid only for ARC700 or ARCv2. */ if (TARGET_NOMPY_SET && TARGET_ARC600_FAMILY) error ("-mno-mpy supported only for ARC700 or ARCv2"); - /* mul/mac instructions only for ARC600. */ - if (TARGET_MULMAC_32BY16_SET && (!TARGET_ARC600_FAMILY)) - error ("-mmul32x16 supported only for ARC600 or ARC601"); - if (!TARGET_DPFP && TARGET_DPFP_DISABLE_LRSR) error ("-mno-dpfp-lrsr supported only with -mdpfp"); @@ -764,23 +725,11 @@ arc_init (void) if (TARGET_SPFP_FAST_SET && TARGET_ARC600_FAMILY) error ("-mspfp_fast not available on ARC600 or ARC601"); - /* FPX-3. No FPX extensions on pre-ARC600 cores. */ - if ((TARGET_DPFP || TARGET_SPFP) - && (!TARGET_ARCOMPACT_FAMILY && !TARGET_EM)) - error ("FPX extensions not available on pre-ARC600 cores"); - - /* FPX-4. No FPX extensions mixed with FPU extensions for ARC HS - cpus. */ - if ((TARGET_DPFP || TARGET_SPFP) - && TARGET_HARD_FLOAT - && TARGET_HS) + /* FPX-4. No FPX extensions mixed with FPU extensions. */ + if ((TARGET_DPFP_FAST_SET || TARGET_DPFP_COMPACT_SET || TARGET_SPFP) + && TARGET_HARD_FLOAT) error ("No FPX/FPU mixing allowed"); - /* Only selected multiplier configurations are available for HS. */ - if (TARGET_HS && ((arc_mpy_option > 2 && arc_mpy_option < 7) - || (arc_mpy_option == 1))) - error ("This multiplier configuration is not available for HS cores"); - /* Warn for unimplemented PIC in pre-ARC700 cores, and disable flag_pic. */ if (flag_pic && TARGET_ARC600_FAMILY) { @@ -790,26 +739,6 @@ arc_init (void) flag_pic = 0; } - if (TARGET_ATOMIC && !(TARGET_ARC700 || TARGET_HS)) - error ("-matomic is only supported for ARC700 or ARC HS cores"); - - /* ll64 ops only available for HS. */ - if (TARGET_LL64 && !TARGET_HS) - error ("-mll64 is only supported for ARC HS cores"); - - /* FPU support only for V2. */ - if (TARGET_HARD_FLOAT) - { - if (TARGET_EM - && (arc_fpu_build & ~(FPU_SP | FPU_SF | FPU_SC | FPU_SD | FPX_DP))) - error ("FPU double precision options are available for ARC HS only"); - if (TARGET_HS && (arc_fpu_build & FPX_DP)) - error ("FPU double precision assist " - "options are not available for ARC HS"); - if (!TARGET_HS && !TARGET_EM) - error ("FPU options are available for ARCv2 architecture only"); - } - arc_init_reg_tables (); /* Initialize array for PRINT_OPERAND_PUNCT_VALID_P. */ @@ -854,7 +783,89 @@ static void arc_override_options (void) { if (arc_cpu == PROCESSOR_NONE) - arc_cpu = PROCESSOR_ARC700; + arc_cpu = TARGET_CPU_DEFAULT; + + /* Set the default cpu options. */ + arc_selected_cpu = &arc_cpu_types[(int) arc_cpu]; + arc_selected_arch = &arc_arch_types[(int) arc_selected_cpu->arch]; + arc_base_cpu = arc_selected_arch->arch; + + /* Set the architectures. */ + switch (arc_selected_arch->arch) + { + case BASE_ARCH_em: + arc_cpu_string = "EM"; + break; + case BASE_ARCH_hs: + arc_cpu_string = "HS"; + break; + case BASE_ARCH_700: + if (arc_selected_cpu->processor == PROCESSOR_nps400) + arc_cpu_string = "NPS400"; + else + arc_cpu_string = "ARC700"; + break; + case BASE_ARCH_6xx: + arc_cpu_string = "ARC600"; + break; + default: + gcc_unreachable (); + } + + /* Set cpu flags accordingly to architecture/selected cpu. The cpu + specific flags are set in arc-common.c. The architecture forces + the default hardware configurations in, regardless what command + line options are saying. The CPU optional hw options can be + turned on or off. */ +#define ARC_OPT(NAME, CODE, MASK, DOC) \ + do { \ + if ((arc_selected_cpu->flags & CODE) \ + && ((target_flags_explicit & MASK) == 0)) \ + target_flags |= MASK; \ + if (arc_selected_arch->dflags & CODE) \ + target_flags |= MASK; \ + } while (0); +#define ARC_OPTX(NAME, CODE, VAR, VAL, DOC) \ + do { \ + if ((arc_selected_cpu->flags & CODE) \ + && (VAR == DEFAULT_##VAR)) \ + VAR = VAL; \ + if (arc_selected_arch->dflags & CODE) \ + VAR = VAL; \ + } while (0); + +#include "arc-options.def" + +#undef ARC_OPTX +#undef ARC_OPT + + /* Check options against architecture options. Throw an error if + option is not allowed. */ +#define ARC_OPTX(NAME, CODE, VAR, VAL, DOC) \ + do { \ + if ((VAR == VAL) \ + && (!(arc_selected_arch->flags & CODE))) \ + { \ + error ("%s is not available for %s architecture", \ + DOC, arc_selected_arch->name); \ + } \ + } while (0); +#define ARC_OPT(NAME, CODE, MASK, DOC) \ + do { \ + if ((target_flags & MASK) \ + && (!(arc_selected_arch->flags & CODE))) \ + error ("%s is not available for %s architecture", \ + DOC, arc_selected_arch->name); \ + } while (0); + +#include "arc-options.def" + +#undef ARC_OPTX +#undef ARC_OPT + + /* Set Tune option. */ + if (arc_tune == TUNE_NONE) + arc_tune = (enum attr_tune) arc_selected_cpu->tune; if (arc_size_opt_level == 3) optimize_size = 1; diff --git a/gcc/config/arc/arc.h b/gcc/config/arc/arc.h index a4adce0812e69f8bee8c8b62871926a8bcaa6f6f..6188a4f81ad4447b71b815661fa5b5a3513809cc 100644 --- a/gcc/config/arc/arc.h +++ b/gcc/config/arc/arc.h @@ -28,6 +28,8 @@ along with GCC; see the file COPYING3. If not see #ifndef GCC_ARC_H #define GCC_ARC_H +#include <stdbool.h> + /* Things to do: - incscc, decscc? @@ -39,6 +41,10 @@ along with GCC; see the file COPYING3. If not see #define SYMBOL_FLAG_LONG_CALL (SYMBOL_FLAG_MACH_DEP << 2) #define SYMBOL_FLAG_CMEM (SYMBOL_FLAG_MACH_DEP << 3) +#ifndef TARGET_CPU_DEFAULT +#define TARGET_CPU_DEFAULT PROCESSOR_arc700 +#endif + /* Check if this symbol has a long_call attribute in its declaration */ #define SYMBOL_REF_LONG_CALL_P(X) \ ((SYMBOL_REF_FLAGS (X) & SYMBOL_FLAG_LONG_CALL) != 0) @@ -74,9 +80,11 @@ along with GCC; see the file COPYING3. If not see GNU_USER_TARGET_OS_CPP_BUILTINS (); \ } \ while (0) -#endif -/* Match the macros used in the assembler. */ +#endif /* DEFAULT_LIBC == LIBC_UCLIBC */ + +/* Macros enabled by specific command line option. FIXME: to be + deprecatd. */ #define CPP_SPEC "\ %{msimd:-D__Xsimd} %{mno-mpy:-D__Xno_mpy} %{mswap:-D__Xswap} \ %{mmin-max:-D__Xmin_max} %{mEA:-D__Xea} \ @@ -85,34 +93,22 @@ along with GCC; see the file COPYING3. If not see %{mdsp-packa:-D__Xdsp_packa} %{mcrc:-D__Xcrc} %{mdvbf:-D__Xdvbf} \ %{mtelephony:-D__Xtelephony} %{mxy:-D__Xxy} %{mmul64: -D__Xmult32} \ %{mlock:-D__Xlock} %{mswape:-D__Xswape} %{mrtsc:-D__Xrtsc} \ -%{mcpu=NPS400:-D__NPS400__} \ -%{mcpu=nps400:-D__NPS400__} \ -" +%{mcpu=nps400:-D__NPS400__}" #define CC1_SPEC "\ %{EB:%{EL:%emay not use both -EB and -EL}} \ %{EB:-mbig-endian} %{EL:-mlittle-endian} \ " +extern const char *arc_cpu_to_as (int argc, const char **argv); + +#define EXTRA_SPEC_FUNCTIONS \ + { "cpu_to_as", arc_cpu_to_as }, + +#define ASM_SPEC "%{mbig-endian|EB:-EB} %{EL} " \ + "%:cpu_to_as(%{mcpu=*:%*}) %{mspfp*} %{mdpfp*} %{mfpu=fpuda*:-mfpuda}" -#define ASM_DEFAULT "-mARC700 -mEA" - -#define ASM_SPEC "\ -%{mbig-endian|EB:-EB} %{EL} \ -%{mcpu=ARC600:-mARC600} \ -%{mcpu=ARC601:-mARC601} \ -%{mcpu=ARC700:-mARC700} \ -%{mcpu=ARC700:-mEA} \ -%{!mcpu=*:" ASM_DEFAULT "} \ -%{mbarrel-shifter} %{mno-mpy} %{mmul64} %{mmul32x16:-mdsp-packa} %{mnorm} \ -%{mswap} %{mEA} %{mmin-max} %{mspfp*} %{mdpfp*} %{mfpu=fpuda*:-mfpuda} \ -%{msimd} \ -%{mmac-d16} %{mmac-24} %{mdsp-packa} %{mcrc} %{mdvbf} %{mtelephony} %{mxy} \ -%{mcpu=ARC700|!mcpu=*:%{mlock}} \ -%{mcpu=ARC700|!mcpu=*:%{mswape}} \ -%{mcpu=ARC700|!mcpu=*:%{mrtsc}} \ -%{mcpu=ARCHS:-mHS} \ -%{mcpu=ARCEM:-mEM} \ -%{matomic:-mlock}" +#define OPTION_DEFAULT_SPECS \ + {"cpu", "%{!mcpu=*:%{!mARC*:%{!marc*:%{!mA7:%{!mA6:-mcpu=%(VALUE)}}}}}" } #if DEFAULT_LIBC == LIBC_UCLIBC /* Note that the default is to link against dynamic libraries, if they are @@ -178,17 +174,11 @@ along with GCC; see the file COPYING3. If not see #define TARGET_MMEDIUM_CALLS_DEFAULT 0 #endif -#define DRIVER_SELF_SPECS DRIVER_ENDIAN_SELF_SPECS \ - "%{mARC600|mA6: -mcpu=ARC600 %<mARC600 %<mA6}" \ - "%{mARC601: -mcpu=ARC601 %<mARC601}" \ - "%{mARC700|mA7: -mcpu=ARC700 %<mARC700 %<mA7}" \ - "%{mbarrel_shifte*: -mbarrel-shifte%* %<mbarrel_shifte*}" \ - "%{mEA: -mea %<mEA}" \ - "%{mspfp_*: -mspfp-%* %<mspfp_*}" \ - "%{mdpfp_*: -mdpfp-%* %<mdpfp_*}" \ - "%{mdsp_pack*: -mdsp-pack%* %<mdsp_pack*}" \ - "%{mmac_*: -mmac-%* %<mmac_*}" \ - "%{multcost=*: -mmultcost=%* %<multcost=*}" +#define DRIVER_SELF_SPECS DRIVER_ENDIAN_SELF_SPECS \ + "%{mARC600|mA6: -mcpu=arc600 %<mARC600 %<mA6 %<mARC600}" \ + "%{mARC601: -mcpu=arc601 %<mARC601}" \ + "%{mARC700|mA7: -mcpu=arc700 %<mARC700 %<mA7}" \ + "%{mEA: -mea %<mEA}" /* Run-time compilation parameters selecting different hardware subsets. */ @@ -234,20 +224,21 @@ along with GCC; see the file COPYING3. If not see use conditional execution? */ #define TARGET_AT_DBR_CONDEXEC (!TARGET_ARC700 && !TARGET_V2) -#define TARGET_ARC600 (arc_cpu == PROCESSOR_ARC600) -#define TARGET_ARC601 (arc_cpu == PROCESSOR_ARC601) -#define TARGET_ARC700 (arc_cpu == PROCESSOR_ARC700 \ - || arc_cpu == PROCESSOR_NPS400) -#define TARGET_EM (arc_cpu == PROCESSOR_ARCEM) -#define TARGET_HS (arc_cpu == PROCESSOR_ARCHS) -#define TARGET_V2 \ - ((arc_cpu == PROCESSOR_ARCHS) || (arc_cpu == PROCESSOR_ARCEM)) - -/* Recast the cpu class to be the cpu attribute. */ -#define arc_cpu_attr ((enum attr_cpu)arc_cpu) - -#ifndef MULTILIB_DEFAULTS -#define MULTILIB_DEFAULTS { "mARC700" } +extern enum base_architecture arc_base_cpu; + +#define TARGET_ARC600 ((arc_base_cpu == BASE_ARCH_6xx) \ + && (TARGET_BARREL_SHIFTER)) +#define TARGET_ARC601 ((arc_base_cpu == BASE_ARCH_6xx) \ + && (!TARGET_BARREL_SHIFTER)) +#define TARGET_ARC700 (arc_base_cpu == BASE_ARCH_700) +#define TARGET_EM (arc_base_cpu == BASE_ARCH_em) +#define TARGET_HS (arc_base_cpu == BASE_ARCH_hs) +#define TARGET_V2 (TARGET_EM || TARGET_HS) + +#ifdef ARC_MULTILIB_CPU_DEFAULT +# ifndef MULTILIB_DEFAULTS +# define MULTILIB_DEFAULTS { "mcpu=" ARC_MULTILIB_CPU_DEFAULT } +# endif #endif #ifndef UNALIGNED_ACCESS_DEFAULT diff --git a/gcc/config/arc/arc.md b/gcc/config/arc/arc.md index 7147fbdb244ae06118ca606f4978b6c1517bc119..429611e4a30d284621dcb318c1504e536cef7f93 100644 --- a/gcc/config/arc/arc.md +++ b/gcc/config/arc/arc.md @@ -231,11 +231,6 @@ (eq_attr "is_CALL" "yes") (const_string "yes")] (const_string "no"))) - -;; Attribute describing the processor -(define_attr "cpu" "none,ARC600,ARC700,ARCEM,ARCHS" - (const (symbol_ref "arc_cpu_attr"))) - ;; true for compact instructions (those with _s suffix) ;; "maybe" means compact unless we conditionalize the insn. (define_attr "iscompact" "true,maybe,true_limm,maybe_limm,false" diff --git a/gcc/config/arc/arc.opt b/gcc/config/arc/arc.opt index 4caf366095cd111bd6005db7f5129e3e9d073486..56851003eaa0726a597ef87ea677d6563fd0e538 100644 --- a/gcc/config/arc/arc.opt +++ b/gcc/config/arc/arc.opt @@ -54,8 +54,74 @@ Target Report Same as -mA7. mmpy-option= -Target RejectNegative Joined UInteger Var(arc_mpy_option) Init(2) --mmpy-option={0,1,2,3,4,5,6,7,8,9} Compile ARCv2 code with a multiplier design option. Option 2 is default on. +Target RejectNegative Joined Enum(arc_mpy) Var(arc_mpy_option) Init(DEFAULT_arc_mpy_option) +-mmpy-option=MPY Compile ARCv2 code with a multiplier design option. + +Enum +Name(arc_mpy) Type(int) + +EnumValue +Enum(arc_mpy) String(0) Value(0) + +EnumValue +Enum(arc_mpy) String(none) Value(0) Canonical + +EnumValue +Enum(arc_mpy) String(1) Value(1) + +EnumValue +Enum(arc_mpy) String(w) Value(1) Canonical + +EnumValue +Enum(arc_mpy) String(2) Value(2) + +EnumValue +Enum(arc_mpy) String(mpy) Value(2) + +EnumValue +Enum(arc_mpy) String(wlh1) Value(2) Canonical + +EnumValue +Enum(arc_mpy) String(3) Value(3) + +EnumValue +Enum(arc_mpy) String(wlh2) Value(3) Canonical + +EnumValue +Enum(arc_mpy) String(4) Value(4) + +EnumValue +Enum(arc_mpy) String(wlh3) Value(4) Canonical + +EnumValue +Enum(arc_mpy) String(5) Value(5) + +EnumValue +Enum(arc_mpy) String(wlh4) Value(5) Canonical + +EnumValue +Enum(arc_mpy) String(6) Value(6) + +EnumValue +Enum(arc_mpy) String(wlh5) Value(6) Canonical + +EnumValue +Enum(arc_mpy) String(7) Value(7) + +EnumValue +Enum(arc_mpy) String(plus_dmpy) Value(7) Canonical + +EnumValue +Enum(arc_mpy) String(8) Value(8) + +EnumValue +Enum(arc_mpy) String(plus_macd) Value(8) Canonical + +EnumValue +Enum(arc_mpy) String(9) Value(9) + +EnumValue +Enum(arc_mpy) String(plus_qmacw) Value(9) Canonical mdiv-rem Target Report Mask(DIVREM) @@ -100,7 +166,7 @@ Target Report Mask(MUL64_SET) Generate mul64 and mulu64 instructions. mno-mpy -Target Report Mask(NOMPY_SET) +Target Report Mask(NOMPY_SET) Warn(%qs is deprecated) Do not generate mpy instructions for ARC700. mea @@ -167,45 +233,6 @@ mcpu= Target RejectNegative Joined Var(arc_cpu) Enum(processor_type) Init(PROCESSOR_NONE) -mcpu=CPU Compile code for ARC variant CPU. -Enum -Name(processor_type) Type(enum processor_type) - -EnumValue -Enum(processor_type) String(ARC600) Value(PROCESSOR_ARC600) - -EnumValue -Enum(processor_type) String(arc600) Value(PROCESSOR_ARC600) - -EnumValue -Enum(processor_type) String(ARC601) Value(PROCESSOR_ARC601) - -EnumValue -Enum(processor_type) String(arc601) Value(PROCESSOR_ARC601) - -EnumValue -Enum(processor_type) String(ARC700) Value(PROCESSOR_ARC700) - -EnumValue -Enum(processor_type) String(arc700) Value(PROCESSOR_ARC700) - -EnumValue -Enum(processor_type) String(nps400) Value(PROCESSOR_NPS400) - -EnumValue -Enum(processor_type) String(NPS400) Value(PROCESSOR_NPS400) - -EnumValue -Enum(processor_type) String(ARCEM) Value(PROCESSOR_ARCEM) - -EnumValue -Enum(processor_type) String(arcem) Value(PROCESSOR_ARCEM) - -EnumValue -Enum(processor_type) String(ARCHS) Value(PROCESSOR_ARCHS) - -EnumValue -Enum(processor_type) String(archs) Value(PROCESSOR_ARCHS) - msize-level= Target RejectNegative Joined UInteger Var(arc_size_opt_level) Init(-1) size optimization level: 0:none 1:opportunistic 2: regalloc 3:drop align, -Os. @@ -308,25 +335,25 @@ Expand adddi3 and subdi3 at rtl generation time into add.f / adc etc. ; Flags used by the assembler, but for which we define preprocessor ; macro symbols as well. mcrc -Target Report +Target Report Warn(%qs is deprecated) Enable variable polynomial CRC extension. mdsp-packa -Target Report +Target Report Warn(%qs is deprecated) Enable DSP 3.1 Pack A extensions. mdvbf -Target Report +Target Report Warn(%qs is deprecated) Enable dual viterbi butterfly extension. mmac-d16 -Target Report Undocumented +Target Report Undocumented Warn(%qs is deprecated) mmac-24 -Target Report Undocumented +Target Report Undocumented Warn(%qs is deprecated) mtelephony -Target Report RejectNegative +Target Report RejectNegative Warn(%qs is deprecated) Enable Dual and Single Operand Instructions for Telephony. mxy @@ -343,7 +370,7 @@ Target Report Enable swap byte ordering extension instruction. mrtsc -Target Report +Target Report Warn(%qs is deprecated) Enable 64-bit Time-Stamp Counter extension instruction. EB @@ -394,24 +421,6 @@ Target multcost= Target RejectNegative Joined -; Unfortunately, listing the full option name gives us clashes -; with OPT_opt_name being claimed for both opt_name and opt-name, -; so we leave out the last character or more. -mbarrel_shifte -Target Joined - -mspfp_ -Target Joined - -mdpfp_ -Target Joined - -mdsp_pack -Target Joined - -mmac_ -Target Joined - matomic Target Report Mask(ATOMIC) Enable atomic instructions. @@ -421,47 +430,47 @@ Target Report Mask(LL64) Enable double load/store instructions for ARC HS. mfpu= -Target RejectNegative Joined Enum(arc_fpu) Var(arc_fpu_build) Init(0) +Target RejectNegative Joined Enum(arc_fpu) Var(arc_fpu_build) Init(DEFAULT_arc_fpu_build) Specify the name of the target floating point configuration. Enum Name(arc_fpu) Type(int) EnumValue -Enum(arc_fpu) String(fpus) Value(FPU_SP | FPU_SC) +Enum(arc_fpu) String(fpus) Value(FPU_FPUS) EnumValue -Enum(arc_fpu) String(fpud) Value(FPU_SP | FPU_SC | FPU_DP | FPU_DC) +Enum(arc_fpu) String(fpud) Value(FPU_FPUD) EnumValue -Enum(arc_fpu) String(fpuda) Value(FPU_SP | FPU_SC | FPX_DP) +Enum(arc_fpu) String(fpuda) Value(FPU_FPUDA) EnumValue -Enum(arc_fpu) String(fpuda_div) Value(FPU_SP | FPU_SC | FPU_SD | FPX_DP) +Enum(arc_fpu) String(fpuda_div) Value(FPU_FPUDA_DIV) EnumValue -Enum(arc_fpu) String(fpuda_fma) Value(FPU_SP | FPU_SC | FPU_SF | FPX_DP) +Enum(arc_fpu) String(fpuda_fma) Value(FPU_FPUDA_FMA) EnumValue -Enum(arc_fpu) String(fpuda_all) Value(FPU_SP | FPU_SC | FPU_SF | FPU_SD | FPX_DP) +Enum(arc_fpu) String(fpuda_all) Value(FPU_FPUDA_ALL) EnumValue -Enum(arc_fpu) String(fpus_div) Value(FPU_SP | FPU_SC | FPU_SD) +Enum(arc_fpu) String(fpus_div) Value(FPU_FPUS_DIV) EnumValue -Enum(arc_fpu) String(fpud_div) Value(FPU_SP | FPU_SC | FPU_SD | FPU_DP | FPU_DC | FPU_DD) +Enum(arc_fpu) String(fpud_div) Value(FPU_FPUD_DIV) EnumValue -Enum(arc_fpu) String(fpus_fma) Value(FPU_SP | FPU_SC | FPU_SF) +Enum(arc_fpu) String(fpus_fma) Value(FPU_FPUS_FMA) EnumValue -Enum(arc_fpu) String(fpud_fma) Value(FPU_SP | FPU_SC | FPU_SF | FPU_DP | FPU_DC | FPU_DF) +Enum(arc_fpu) String(fpud_fma) Value(FPU_FPUD_FMA) EnumValue -Enum(arc_fpu) String(fpus_all) Value(FPU_SP | FPU_SC | FPU_SF | FPU_SD) +Enum(arc_fpu) String(fpus_all) Value(FPU_FPUS_ALL) EnumValue -Enum(arc_fpu) String(fpud_all) Value(FPU_SP | FPU_SC | FPU_SF | FPU_SD | FPU_DP | FPU_DC | FPU_DF | FPU_DD) +Enum(arc_fpu) String(fpud_all) Value(FPU_FPUD_ALL) mtp-regno= Target RejectNegative Joined UInteger Var(arc_tp_regno) Init(25) diff --git a/gcc/config/arc/driver-arc.c b/gcc/config/arc/driver-arc.c new file mode 100644 index 0000000000000000000000000000000000000000..0c24cdaf08d2871021943d016e76bfbc342aeea7 --- /dev/null +++ b/gcc/config/arc/driver-arc.c @@ -0,0 +1,81 @@ +/* Subroutines for the gcc driver. + Copyright (C) 2016 Free Software Foundation, Inc. + Contributed by Claudiu Zissulescu <claziss@synopsys.com> + + This file is part of GCC. + + GCC is free software; you can redistribute it and/or modify it + under the terms of the GNU General Public License as published by + the Free Software Foundation; either version 3, or (at your option) + any later version. + + GCC is distributed in the hope that it will be useful, but WITHOUT + ANY WARRANTY; without even the implied warranty of MERCHANTABILITY + or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public + License for more details. + + You should have received a copy of the GNU General Public License + along with GCC; see the file COPYING3. If not see + <http://www.gnu.org/licenses/>. */ + +#include "config.h" +#include "system.h" +#include "coretypes.h" +#include "tm.h" + +/* Returns command line parameters to pass to as. */ + +const char* +arc_cpu_to_as (int argc, const char **argv) +{ + const char *name = NULL; + const arc_cpu_t *arc_selected_cpu; + + /* No argument, check what is the default cpu. */ + if (argc == 0) + { + arc_selected_cpu = &arc_cpu_types[(int) TARGET_CPU_DEFAULT]; + } + else + { + name = argv[0]; + for (arc_selected_cpu = arc_cpu_types; arc_selected_cpu->name; + arc_selected_cpu++) + { + if (strcmp (arc_selected_cpu->name, name) == 0) + break; + } + } + + switch (arc_selected_cpu->arch) + { + case BASE_ARCH_em: + if (arc_selected_cpu->flags & FL_CD) + name = "-mcode-density"; + else + name = ""; + if (arc_selected_cpu->flags & FL_FPUDA) + name = concat ("-mfpuda ", name, NULL); + if (arc_selected_cpu->flags & FL_SPFP) + name = concat ("-mspfp ", name, NULL); + if (arc_selected_cpu->flags & FL_DPFP) + name = concat ("-mdpfp ", name, NULL); + return concat ("-mcpu=arcem ", name, NULL); + case BASE_ARCH_hs: + return "-mcpu=archs"; + case BASE_ARCH_700: + if (arc_selected_cpu->processor == PROCESSOR_nps400) + return "-mcpu=nps400 -mEA"; + else + return "-mcpu=arc700 -mEA"; + case BASE_ARCH_6xx: + if (arc_selected_cpu->flags & FL_MUL64) + return "-mcpu=arc600 -mmul64 -mnorm"; + if (arc_selected_cpu->flags & FL_MUL32x16) + return "-mcpu=arc600 -mdsp-packa -mnorm"; + return "-mcpu=arc600 -mnorm"; + default: + gcc_unreachable (); + } + return NULL; +} diff --git a/gcc/config/arc/genmultilib.awk b/gcc/config/arc/genmultilib.awk new file mode 100644 index 0000000000000000000000000000000000000000..5934f4fcb3f21ed6bc41162a13c4644d4ae7ea27 --- /dev/null +++ b/gcc/config/arc/genmultilib.awk @@ -0,0 +1,203 @@ +# Copyright (C) 2016 Free Software Foundation, Inc. +# +# This file is part of GCC. +# +# GCC is free software; you can redistribute it and/or modify it under +# the terms of the GNU General Public License as published by the Free +# Software Foundation; either version 3, or (at your option) any later +# version. +# +# GCC is distributed in the hope that it will be useful, but WITHOUT ANY +# WARRANTY; without even the implied warranty of MERCHANTABILITY or +# FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License +# for more details. +# +# You should have received a copy of the GNU General Public License +# along with GCC; see the file COPYING3. If not see +# <http://www.gnu.org/licenses/>. + +################################################################## +# +# This file is using AVR's genmultilib.awk idea. +# Transform CPU Information from arc-cpu.def to a +# Representation that is understood by GCC's multilib Machinery. +# +# The Script works as a Filter from STDIN to STDOUT. +# +# FORMAT = "Makefile": Generate Makefile Snipet that sets some +# MULTILIB_* Variables as needed. +# +################################################################## + +BEGIN { + FS ="[(, \t)]+" + comment = 1 + n_cores = 0 + n_reuse = 0 +} + +################################################################## +# Add some Comments to the generated Files and copy-paste +# Copyright Notice from above. +################################################################## +/^#/ { + if (!comment) + next + else if (comment == 1) + { + if (FORMAT == "Makefile") + { + print "# Auto-generated Makefile Snip" + print "# Generated by : ./gcc/config/arc/genmultilib.awk" + print "# Generated from : ./gcc/config/arc/arc-cpu.def" + print "# Used by : tmake_file from Makefile and genmultilib" + print "" + } + } + + comment = 2; + + print +} + +/^$/ { + # The first empty line stops copy-pasting the GPL comments + # from this file to the generated file. + + comment = 0 +} + + +/^ARC_CPU/ { + name = $2 + # gsub ("\"", "", name) + + if ($4 != "0") + { + arch = $3 + if (arch == "6xx") + arch = 601 + + n = split ($4, cpu_flg, "|") + + line = "mcpu." arch + for (i = 1; i <= n; i++) + { + if (cpu_flg[i] == "FL_MPYOPT_0") + line = line "/mmpy-option.0" + else if (cpu_flg[i] == "FL_MPYOPT_1") + line = line "/mmpy-option.1" + else if (cpu_flg[i] == "FL_MPYOPT_2") + line = line "/mmpy-option.2" + else if (cpu_flg[i] == "FL_MPYOPT_3") + line = line "/mmpy-option.3" + else if (cpu_flg[i] == "FL_MPYOPT_4") + line = line "/mmpy-option.4" + else if (cpu_flg[i] == "FL_MPYOPT_5") + line = line "/mmpy-option.5" + else if (cpu_flg[i] == "FL_MPYOPT_6") + line = line "/mmpy-option.6" + else if (cpu_flg[i] == "FL_MPYOPT_7") + line = line "/mmpy-option.7" + else if (cpu_flg[i] == "FL_MPYOPT_8") + line = line "/mmpy-option.8" + else if (cpu_flg[i] == "FL_MPYOPT_9") + line = line "/mmpy-option.9" + else if (cpu_flg[i] == "FL_CD") + line = line "/mcode-density" + else if (cpu_flg[i] == "FL_BS") + line = line "/mbarrel-shifter" + else if (cpu_flg[i] == "FL_DIVREM") + line = line "/mdiv-rem" + else if (cpu_flg[i] == "FL_NORM" \ + || cpu_flg[i] == "FL_SWAP") + line = line "/mnorm" + else if (cpu_flg[i] == "FL_FPU_FPUS") + line = line "/mfpu.fpus" + else if (cpu_flg[i] == "FL_FPU_FPUDA") + line = line "/mfpu.fpuda" + else if (cpu_flg[i] == "FL_FPU_FPUD_ALL") + line = line "/mfpu.fpud_all" + else if (cpu_flg[i] == "FL_LL64") + line = line "/mll64" + else if (cpu_flg[i] == "FL_MUL64") + line = line "/mmul64" + else if (cpu_flg[i] == "FL_MUL32x16") + line = line "/mmul32x16" + else if (cpu_flg[i] == "FL_FPX_QUARK") + line = line "/quark" + else if (cpu_flg[i] == "FL_SPFP") + line = line "/spfp" + else if (cpu_flg[i] == "FL_DPFP") + line = line "/dpfp" + else + { + print "Don't know the flag " cpu_flg[i] > "/dev/stderr" + exit 1 + } + } + line = "mcpu." name "=" line + reuse[n_reuse] = line + n_reuse++ + } + + core = name + cores[n_cores] = core + n_cores++ +} + +################################################################## +# +# We gathered all the Information, now build/output the following: +# +# awk Variable target Variable FORMAT +# ----------------------------------------------------------- +# m_options <-> MULTILIB_OPTIONS Makefile +# m_dirnames <-> MULTILIB_DIRNAMES " +# +################################################################## + +END { + m_options = "\nMULTILIB_OPTIONS = " + m_dirnames = "\nMULTILIB_DIRNAMES =" + m_reuse = "\nMULTILIB_REUSE =" + + sep = "" + for (c = 0; c < n_cores; c++) + { + m_options = m_options sep "mcpu=" cores[c] + m_dirnames = m_dirnames " " cores[c] + sep = "/" + } + + sep = "" + for (c = 0; c < n_reuse; c++) + { + m_reuse = m_reuse sep reuse[c] + sep = "\nMULTILIB_REUSE +=" + } + ############################################################ + # Output that Stuff + ############################################################ + + if (FORMAT == "Makefile") + { + # Intended Target: ./gcc/config/arc/t-multilib + + print m_options + print m_dirnames + + ############################################################ + # Legacy Aliases + ############################################################ + + print "" + print "# Aliases:" + print "MULTILIB_MATCHES = mcpu?arc600=mcpu?ARC600" + print "MULTILIB_MATCHES += mcpu?arc600=mARC600" + print "MULTILIB_MATCHES += mcpu?arc600=mA6" + print "MULTILIB_MATCHES += mcpu?arc601=mcpu?ARC601" + print "MULTILIB_MATCHES += mcpu?arc700=mA7" + print "MULTILIB_MATCHES += mcpu?arc700=mARC700" + } +} diff --git a/gcc/config/arc/genoptions.awk b/gcc/config/arc/genoptions.awk new file mode 100644 index 0000000000000000000000000000000000000000..24a93eb5e1fe7cd3b40df53a3e72d86ac6838491 --- /dev/null +++ b/gcc/config/arc/genoptions.awk @@ -0,0 +1,86 @@ +# Copyright (C) 2016 Free Software Foundation, Inc. +# +# This file is part of GCC. +# +# GCC is free software; you can redistribute it and/or modify it under +# the terms of the GNU General Public License as published by the Free +# Software Foundation; either version 3, or (at your option) any later +# version. +# +# GCC is distributed in the hope that it will be useful, but WITHOUT ANY +# WARRANTY; without even the implied warranty of MERCHANTABILITY or +# FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License +# for more details. +# +# You should have received a copy of the GNU General Public License +# along with GCC; see the file COPYING3. If not see +# <http://www.gnu.org/licenses/>. + +################################################################## +# +# This file is using AVR's genmultilib.awk idea. +# +################################################################## + +BEGIN { + FS ="[(, \t)]+" + comment = 1 + n_cores = 0 +} + +################################################################## +# Add some Comments to the generated Files and copy-paste +# Copyright Notice from above. +################################################################## +/^#/ { + if (!comment) + next + else if (comment == 1) + { + if (FORMAT == "Makefile") + { + print "; Auto-generated Makefile Snip" + print "; Generated by : ./gcc/config/arc/genoptions.awk" + print "; Generated from : ./gcc/config/arc/arc-cpu.def" + print ";" + } + } + + comment = 2; + + gsub ("^#", ";", $0) + print +} + +/^$/ { + # The first empty line stops copy-pasting the GPL comments + # from this file to the generated file. + comment = 0 +} + +/^ARC_CPU/ { + name = $2 + cores[n_cores] = name; + n_cores++ +} + +END { + m_option = "" + for (c = 0; c < n_cores; c++) + { + m_options = m_options "EnumValue\nEnum(processor_type) String(" \ + cores[c] ") Value(PROCESSOR_" cores[c] ")\n\n" + } + + ############################################################ + # Output that Stuff + ############################################################ + + if (FORMAT == "Makefile") + { + print "\nEnum" + print "Name(processor_type) Type(enum processor_type)" + print "Known ARC CPUs (for use with the -mcpu= option):\n" + print m_options + } +} diff --git a/gcc/config/arc/t-arc b/gcc/config/arc/t-arc index 4252e73cabb5190476c307ac5b376a3192364211..bdb1328c64e56d5baea481c7956db27b85f31a30 100644 --- a/gcc/config/arc/t-arc +++ b/gcc/config/arc/t-arc @@ -19,11 +19,30 @@ TM_H += $(srcdir)/config/arc/arc-c.def +driver-arc.o: $(srcdir)/config/arc/driver-arc.c \ + $(CONFIG_H) $(SYSTEM_H) coretypes.h $(TM_H) + $(COMPILER) -c $(ALL_COMPILERFLAGS) $(ALL_CPPFLAGS) $(INCLUDES) $< + arc-c.o: $(srcdir)/config/arc/arc-c.c $(CONFIG_H) $(SYSTEM_H) \ $(TREE_H) $(TM_H) $(TM_P_H) coretypes.h $(COMPILER) -c $(ALL_COMPILERFLAGS) $(ALL_CPPFLAGS) $(INCLUDES) \ $(srcdir)/config/arc/arc-c.c +#Run `arc-cpus` if you changed something in arc-cpus.def + +.PHONY: arc-cpus + +arc-cpus: $(srcdir)/config/arc/t-multilib \ + $(srcdir)/config/arc/arc-tables.opt + +$(srcdir)/config/arc/t-multilib: $(srcdir)/config/arc/genmultilib.awk \ + $(srcdir)/config/arc/arc-cpus.def + $(AWK) -f $< -v FORMAT=Makefile $< $(srcdir)/config/arc/arc-cpus.def > $@ + +$(srcdir)/config/arc/arc-tables.opt: $(srcdir)/config/arc/genoptions.awk \ + $(srcdir)/config/arc/arc-cpus.def + $(AWK) -f $< -v FORMAT=Makefile $< $(srcdir)/config/arc/arc-cpus.def > $@ + # Local Variables: # mode: Makefile # End: diff --git a/gcc/config/arc/t-arc-newlib b/gcc/config/arc/t-arc-newlib deleted file mode 100644 index c49a3fcc146fe77e3a04dc773d2536276373383f..0000000000000000000000000000000000000000 --- a/gcc/config/arc/t-arc-newlib +++ /dev/null @@ -1,46 +0,0 @@ -# GCC Makefile fragment for Synopsys DesignWare ARC with newlib. - -# Copyright (C) 2007-2016 Free Software Foundation, Inc. - -# This file is part of GCC. - -# GCC is free software; you can redistribute it and/or modify it under the -# terms of the GNU General Public License as published by the Free Software -# Foundation; either version 3, or (at your option) any later version. - -# GCC is distributed in the hope that it will be useful, but WITHOUT ANY -# WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS -# FOR A PARTICULAR PURPOSE. See the GNU General Public License for more -# details. - -# You should have received a copy of the GNU General Public License along -# with GCC; see the file COPYING3. If not see -# <http://www.gnu.org/licenses/>. - -MULTILIB_OPTIONS=mcpu=ARC600/mcpu=ARC601/mcpu=ARC700/mcpu=ARCEM/mcpu=ARCHS mmul64/mmul32x16 mnorm -MULTILIB_DIRNAMES=arc600 arc601 arc700 em hs mul64 mul32x16 norm -# -# Aliases: -MULTILIB_MATCHES = mcpu?ARC600=mcpu?arc600 -MULTILIB_MATCHES += mcpu?ARC600=mARC600 -MULTILIB_MATCHES += mcpu?ARC600=mA6 -MULTILIB_MATCHES += mcpu?ARC600=mno-mpy -MULTILIB_MATCHES += mcpu?ARC601=mcpu?arc601 -MULTILIB_MATCHES += mcpu?ARC700=mA7 -MULTILIB_MATCHES += mcpu?ARC700=mARC700 -MULTILIB_MATCHES += mcpu?ARC700=mcpu?arc700 -MULTILIB_MATCHES += mcpu?ARCEM=mcpu?arcem -MULTILIB_MATCHES += mcpu?ARCHS=mcpu?archs -MULTILIB_MATCHES += EL=mlittle-endian -MULTILIB_MATCHES += EB=mbig-endian -# -# These don't make sense for the ARC700 default target: -MULTILIB_EXCEPTIONS=mmul64* mmul32x16* norm* -# And neither of the -mmul* options make sense without -mnorm: -MULTILIB_EXCLUSIONS=mARC600/mmul64/!mnorm mcpu=ARC601/mmul64/!mnorm mARC600/mmul32x16/!mnorm -# Exclusions for ARC700 -MULTILIB_EXCEPTIONS += mcpu=ARC700/mnorm* mcpu=ARC700/mmul64* mcpu=ARC700/mmul32x16* -# Exclusions for ARCv2EM -MULTILIB_EXCEPTIONS += mcpu=ARCEM/mmul64* mcpu=ARCEM/mmul32x16* -# Exclusions for ARCv2HS -MULTILIB_EXCEPTIONS += mcpu=ARCHS/mmul64* mcpu=ARCHS/mmul32x16* mcpu=ARCHS/mnorm* diff --git a/gcc/config/arc/t-multilib b/gcc/config/arc/t-multilib new file mode 100644 index 0000000000000000000000000000000000000000..5a36af6571e48dd109dd5650f20020fe432f3714 --- /dev/null +++ b/gcc/config/arc/t-multilib @@ -0,0 +1,34 @@ +# Auto-generated Makefile Snip +# Generated by : ./gcc/config/arc/genmultilib.awk +# Generated from : ./gcc/config/arc/arc-cpu.def +# Used by : tmake_file from Makefile and genmultilib + +# Copyright (C) 2016 Free Software Foundation, Inc. +# +# This file is part of GCC. +# +# GCC is free software; you can redistribute it and/or modify it under +# the terms of the GNU General Public License as published by the Free +# Software Foundation; either version 3, or (at your option) any later +# version. +# +# GCC is distributed in the hope that it will be useful, but WITHOUT ANY +# WARRANTY; without even the implied warranty of MERCHANTABILITY or +# FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License +# for more details. +# +# You should have received a copy of the GNU General Public License +# along with GCC; see the file COPYING3. If not see +# <http://www.gnu.org/licenses/>. + +MULTILIB_OPTIONS = mcpu=em/mcpu=arcem/mcpu=em4/mcpu=em4_dmips/mcpu=em4_fpus/mcpu=em4_fpuda/mcpu=hs/mcpu=archs/mcpu=hs34/mcpu=hs38/mcpu=hs38_linux/mcpu=arc600/mcpu=arc600_norm/mcpu=arc600_mul64/mcpu=arc600_mul32x16/mcpu=arc601/mcpu=arc601_norm/mcpu=arc601_mul64/mcpu=arc601_mul32x16/mcpu=arc700/mcpu=nps400 + +MULTILIB_DIRNAMES = em arcem em4 em4_dmips em4_fpus em4_fpuda hs archs hs34 hs38 hs38_linux arc600 arc600_norm arc600_mul64 arc600_mul32x16 arc601 arc601_norm arc601_mul64 arc601_mul32x16 arc700 nps400 + +# Aliases: +MULTILIB_MATCHES = mcpu?arc600=mcpu?ARC600 +MULTILIB_MATCHES += mcpu?arc600=mARC600 +MULTILIB_MATCHES += mcpu?arc600=mA6 +MULTILIB_MATCHES += mcpu?arc601=mcpu?ARC601 +MULTILIB_MATCHES += mcpu?arc700=mA7 +MULTILIB_MATCHES += mcpu?arc700=mARC700 diff --git a/gcc/config/arc/t-arc-uClibc b/gcc/config/arc/t-uClibc similarity index 100% rename from gcc/config/arc/t-arc-uClibc rename to gcc/config/arc/t-uClibc diff --git a/gcc/doc/invoke.texi b/gcc/doc/invoke.texi index 8e2f46617b8e44ccf16941c31029ab5625322867..7176037a6249f4f725621a7c214450ca8f1e54a6 100644 --- a/gcc/doc/invoke.texi +++ b/gcc/doc/invoke.texi @@ -14174,29 +14174,92 @@ values for @var{cpu} are @table @samp @opindex mA6 @opindex mARC600 -@item ARC600 @item arc600 Compile for ARC600. Aliases: @option{-mA6}, @option{-mARC600}. -@item ARC601 @item arc601 @opindex mARC601 Compile for ARC601. Alias: @option{-mARC601}. -@item ARC700 @item arc700 @opindex mA7 @opindex mARC700 Compile for ARC700. Aliases: @option{-mA7}, @option{-mARC700}. This is the default when configured with @option{--with-cpu=arc700}@. -@item ARCEM @item arcem Compile for ARC EM. -@item ARCHS @item archs Compile for ARC HS. + +@item em +@opindex em +Compile for ARC EM cpu with no hardware extension. + +@item em4 +@opindex em4 +Compile for ARC EM4 cpu. + +@item em4_dmips +@opindex em4_dmips +Compile for ARC EM4 DMIPS cpu. + +@item em4_fpus +@opindex em4_fpus +Compile for ARC EM4 DMIPS cpu with single precision floating point +extension. + +@item em4_fpuda +@opindex em4_fpuda +Compile for ARC EM4 DMIPS cpu with single precision floating point and +double assists instructions. + +@item hs +@opindex hs +Compile for ARC HS cpu with no hardware extension, except the atomic +instructions. + +@item hs34 +@opindex hs34 +Compile for ARC HS34 cpu. + +@item hs38 +@opindex hs38 +Compile for ARC HS38 cpu. + +@item hs38_linux +@opindex hs38_linux +Compile for ARC HS38 cpu with all hardware extensions on. + +@item arc600_norm +@opindex arc600_norm +Compile for ARC 600 cpu with norm instruction enabled. + +@item arc600_mul32x16 +@opindex arc600_mul32x16 +Compile for ARC 600 cpu with norm and mul32x16 instructions enabled. + +@item arc600_mul64 +@opindex arc600_mul64 +Compile for ARC 600 cpu with norm and mul64 instructions enabled. + +@item arc601_norm +@opindex arc601_norm +Compile for ARC 601 cpu with norm instruction enabled. + +@item arc601_mul32x16 +@opindex arc601_mul32x16 +Compile for ARC 601 cpu with norm and mul32x16 instructions enabled. + +@item arc601_mul64 +@opindex arc601_mul64 +Compile for ARC 601 cpu with norm and mul64 instructions enabled. + +@item nps400 +@opindex nps400 +Compile for ARC 700 on NPS400 chip. + @end table @item -mdpfp @@ -14223,7 +14286,8 @@ supported. This is always enabled for @option{-mcpu=ARC700}. @item -mno-mpy @opindex mno-mpy -Do not generate mpy instructions for ARC700. +Do not generate mpy instructions for ARC700. This instruction is +deprecated. @item -mmul32x16 @opindex mmul32x16 @@ -14430,12 +14494,14 @@ define preprocessor macro symbols. @item -mdsp-packa @opindex mdsp-packa Passed down to the assembler to enable the DSP Pack A extensions. -Also sets the preprocessor symbol @code{__Xdsp_packa}. +Also sets the preprocessor symbol @code{__Xdsp_packa}. This option is +deprecated. @item -mdvbf @opindex mdvbf Passed down to the assembler to enable the dual viterbi butterfly -extension. Also sets the preprocessor symbol @code{__Xdvbf}. +extension. Also sets the preprocessor symbol @code{__Xdvbf}. This +option is deprecated. @c ARC700 4.10 extension instruction @item -mlock @@ -14447,19 +14513,19 @@ Conditional extension. Also sets the preprocessor symbol @item -mmac-d16 @opindex mmac-d16 Passed down to the assembler. Also sets the preprocessor symbol -@code{__Xxmac_d16}. +@code{__Xxmac_d16}. This option is deprecated. @item -mmac-24 @opindex mmac-24 Passed down to the assembler. Also sets the preprocessor symbol -@code{__Xxmac_24}. +@code{__Xxmac_24}. This option is deprecated. @c ARC700 4.10 extension instruction @item -mrtsc @opindex mrtsc Passed down to the assembler to enable the 64-bit Time-Stamp Counter extension instruction. Also sets the preprocessor symbol -@code{__Xrtsc}. +@code{__Xrtsc}. This option is deprecated. @c ARC700 4.10 extension instruction @item -mswape @@ -14472,7 +14538,7 @@ extension instruction. Also sets the preprocessor symbol @opindex mtelephony Passed down to the assembler to enable dual and single operand instructions for telephony. Also sets the preprocessor symbol -@code{__Xtelephony}. +@code{__Xtelephony}. This option is deprecated. @item -mxy @opindex mxy diff --git a/gcc/testsuite/gcc.target/arc/nps400-cpu-flag.c b/gcc/testsuite/gcc.target/arc/nps400-cpu-flag.c new file mode 100644 index 0000000000000000000000000000000000000000..fe80ce52e33e66421cf77a7db58982fec344401e --- /dev/null +++ b/gcc/testsuite/gcc.target/arc/nps400-cpu-flag.c @@ -0,0 +1,4 @@ +/* { dg-do compile } */ +/* { dg-options "-mcpu=nps400" } */ + +/* { dg-final { scan-assembler ".cpu NPS400" } } */