Skip to content
Snippets Groups Projects
  1. Feb 20, 2006
    • Paolo Bonzini's avatar
      re PR bootstrap/25670 (build fail with 'make all-gcc') · cc11cc9b
      Paolo Bonzini authored
      2006-02-20  Paolo Bonzini  <bonzini@gnu.org>
      
      	PR bootstrap/25670
      
      	* Makefile.tpl ([+compare-target+]): Print explanation messages.
      
      	* Makefile.def (ADAFLAGS, BOOT_ADAFLAGS, LANGUAGES): New flags_to_pass.
      	* Makefile.tpl (BASE_FLAGS_TO_PASS): Support optional flags_to_pass.
      	(EXTRA_GCC_FLAGS): Remove ADAFLAGS, BOOT_ADAFLAGS, LANGUAGES,
      	BUILD_PREFIX, BUILD_PREFIX_1.
      	* configure.in: (BUILD_PREFIX, BUILD_PREFIX_1): Don't substitute.
      
      	* Makefile.def (bootstrap stage 1): Pass LIBCFLAGS too.
      	* Makefile.tpl (POSTSTAGE1_FLAGS_TO_PASS): Override LIBCFLAGS too.
      
      	* Makefile.tpl (configure-stage[+id+]-[+prefix+][+module+],
      	all-stage[+id+]-[+prefix+][+module+], : Use $(current_stage) instead
      	of `cat stage_current`.  Always provide the `r' and `s' variables.
      	(clean-stage[+id+]-[+prefix+][+module+]): Likewise, and make it into
      	a single shell execution.
      	(configure-[+prefix+][+module+], all-[+prefix+][+module+]): For
      	bootstrapped modules, make the stage1 module if the build was not
      	started yet, else build the current stage.
      	(all-host, all-target): Omit bootstrapped modules (if bootstrapping).
      	(all-build, all-host, all-target, [+make_target+]-host,
      	[+make_target+]-target): Do not use \-continued lines.
      	(target modules): Depend on stage_last, not all-gcc, if bootstrapping.
      	(current_stage, restrap, stage_last): New.
      
      	* Makefile.in: Regenerate.
      	* configure: Regenerate.
      
      gcc:
      2006-02-20  Paolo Bonzini  <bonzini@gnu.org>
      
      	PR bootstrap/25476
      
      	* Makefile.in (LDFLAGS): Define from autoconf substitution.
      
      	* Makefile.in (BOOTSTRAPPING): New.
      	(quickstrap): New definition if BOOTSTRAPPING=yes.
      
      	* Makefile.in (CONFIG_LANGUAGES): Substitute all_selected_languages.
      	* configure.ac: Substitute all_selected_languages with the languages
      	that were configured.  For all the other variables except
      	lang_specs_files, include all the languages in the tree.
      	* configure: Regenerate.
      	
      	* Makefile.in (stmp-fixinc): Copy includes from the prev-gcc directory,
      	if there is one.  Run the commands to run fixincludes in the same
      	subshell.
      
      	* doc/makefile.texi: Document new makefile targets from toplevel bootstrap.
      	* doc/install.texi: Document exact conventions for searching target tools.
      	Document --with-build-time-tools.  Document toplevel bootstrap.  Document
      	something more about building an Ada cross-compiler.  Don't list GNU Make
      	requirements which affect all platforms.
      
      From-SVN: r111295
      cc11cc9b
    • Roger Sayle's avatar
      re PR middle-end/19543 ([4.1 only] fortran LOGICAL*8 not consistently... · 6a34c788
      Roger Sayle authored
      re PR middle-end/19543 ([4.1 only] fortran LOGICAL*8 not consistently distinguished from 32 bit integers)
      
      
      	PR middle-end/19543
      	* varasm.c (compare_constant) <INTEGER_CST>: Integer constants are
      	only equivalent if the have both the same mode and precision.
      
      	* gfortran.dg/logical_1.f90: New test case.
      
      From-SVN: r111294
      6a34c788
    • GCC Administrator's avatar
      Daily bump. · 3cdab266
      GCC Administrator authored
      From-SVN: r111292
      3cdab266
  2. Feb 19, 2006
    • Ben Elliston's avatar
      * doc/tree-ssa.texi (Interfaces): Describe low vs. high GIMPLE. · 9c603f8f
      Ben Elliston authored
      From-SVN: r111286
      9c603f8f
    • Roger Sayle's avatar
      gcse.c (want_to_gcse_p): On STACK_REGS targets... · 3d8504ac
      Roger Sayle authored
      
      
      	* gcse.c (want_to_gcse_p): On STACK_REGS targets, look through
      	constant pool references to identify stack mode constants.
      	* rtlanal.c (constant_pool_constant_p): New predicate to check
      	whether operand is a floating point constant in the pool.
      	* rtl.h (constant_pool_constant_p): Prototype here.
      	* loop.c (scan_loop): Avoid hoisting constants from the constant
      	pool on STACK_REGS targets.
      	(load_mems): Likewise.
      	* loop-invariant.c (get_inv_cost): Make hoisting constant pool
      	loads into x87 registers expensive in terms of register pressure.
      
      
      Co-Authored-By: default avatarSteven Bosscher <stevenb.gcc@gmail.com>
      
      From-SVN: r111283
      3d8504ac
    • Roger Sayle's avatar
      gthr-posix.h: On Tru64... · c2a8530e
      Roger Sayle authored
      	* gthr-posix.h: On Tru64, map __gthr_foo as a weak reference to
      	__foo and not foo when _PTHREAD_USE_MANGLED_NAMES_ is defined.
      
      From-SVN: r111282
      c2a8530e
    • François-Xavier Coudert's avatar
      re PR libfortran/21303 (L edit descriptor without a width) · 8f0d39a8
      François-Xavier Coudert authored
      	PR libfortran/21303
      
      	* gfortran.h (notification): New enumeration.
      	(gfc_notification_std): Prototype for the new function.
      	* error.c (gfc_notification_std): New function.
      	* io.c (check_format): Handle the case of a L format descriptor
      	without a width.
      
      	* runtime/error.c (notification_std): New function.
      	* libgfortran.h (notification): New enumeration.
      	* io/io.h (notification_std): Prototype for the new function. 
      	* io/format.c (parse_format_list): Handle the case of a L format
      	descriptor without a width.
      
      	* gcc/testsuite/gfortran.dg/fmt_l.f90: New test.
      
      From-SVN: r111281
      8f0d39a8
    • Thomas Koenig's avatar
      gfortran.texi: Document environment variables which influence runtime behavior. · f5dc42bb
      Thomas Koenig authored
      2006-02-19  Thomas Koenig  <Thomas.Koenig@online.de>
      
              * gfortran.texi:  Document environment variables which
              influence runtime behavior.
      
      From-SVN: r111280
      f5dc42bb
    • Jakub Jelinek's avatar
      re PR middle-end/26334 (ICE in lhd_set_decl_assembler_name) · 0d84c7ab
      Jakub Jelinek authored
      	PR middle-end/26334
      	* gcc.dg/20060218-1.c: Moved to...
      	* gcc.target/i386/20060218-1.c: ... here.  New test.
      
      From-SVN: r111279
      0d84c7ab
    • David Edelsohn's avatar
      xcoff.h (TARGET_ASM_OUTPUT_ANCHOR): Define. · 0d5817b2
      David Edelsohn authored
              * config/rs6000/xcoff.h (TARGET_ASM_OUTPUT_ANCHOR): Define.
              * config/rs6000/rs6000.c (rs6000_xcoff_asm_output_anchor): Define.
      
      From-SVN: r111275
      0d5817b2
    • Paolo Carlini's avatar
      std_sstream.h (basic_stringbuf<>::setbuf): Simply clear the internal... · 62448787
      Paolo Carlini authored
      std_sstream.h (basic_stringbuf<>::setbuf): Simply clear the internal _M_string, adjust _M_sync call.
      
      2006-02-19  Paolo Carlini  <pcarlini@suse.de>
      
      	* include/std/std_sstream.h (basic_stringbuf<>::setbuf): Simply
      	clear the internal _M_string, adjust _M_sync call.
      	* include/bits/sstream.tcc (basic_stringbuf<>::_M_sync): Adjust
      	consistently for calls from setbuf.
      
      From-SVN: r111274
      62448787
    • Daniel Berlin's avatar
      invoke.texi: Document -fipa-pta. · 4cf4d6a3
      Daniel Berlin authored
      2006-02-19  Daniel Berlin  <dberlin@dberlin.org>
      
      	* doc/invoke.texi: Document -fipa-pta.
      	* common.opt: Add ipa-pta option.
      	* tree-ssa-structalias.c (DONT_PROPAGATE_WITH_ANYTHING): Removed.
      	(do_sd_constraint): Enable DONT_PROPAGATE_WITH_ANYTHING code.
      	(do_ds_constraint): Ditto.
      	(get_constraint_for): Only add to referenced_vars if
      	referenced_vars exists.
      	(insert_into_field_list): Rewrite to do this unsorted.
      	(insert_into_field_list_sorted): Rename old insert_into_field_list
      	to this.
      	(create_function_info_for): Use insert_into_field_list_sorted.
      	(create_variable_info_for): Rewrite so it uses unsorted version,
      	since the field list is sorted.
      	(intra_create_variable_infos): Only add to referenced_vars if
      	referenced_vars exists.
      	(ipa_pta_execute): Init heapvars, and delete when done.
      	* passes.c (init_optimization_passes): Add call to pass_ipa_pta.
      
      From-SVN: r111273
      4cf4d6a3
    • John David Anglin's avatar
      install.texi: Add missing `@samp'. · 353f74e8
      John David Anglin authored
      	* doc/install.texi: Add missing `@samp'.
      
      From-SVN: r111272
      353f74e8
    • H.J. Lu's avatar
      resolve.c (resolve_contained_functions): Call resolve_entries first. · caf0eced
      H.J. Lu authored
      2006-02-19  H.J. Lu  <hongjiu.lu@intel.com>
      
      	* resolve.c (resolve_contained_functions): Call resolve_entries
      	first.
      	(resolve_types): Remove calls to resolve_entries and
      	resolve_contained_functions.
      	(gfc_resolve): Call resolve_contained_functions.
      
      From-SVN: r111271
      caf0eced
    • Erik Edelmann's avatar
      re PR fortran/26201 (__convert_i4_i8 written to a module.) · 3431818f
      Erik Edelmann authored
      fortran/
      2006-02-19  Erik Edelmann  <eedelman@gcc.gnu.org>
      
              PR fortran/26201
              * intrinsic.c (gfc_convert_type_warn): Call
              gfc_intrinsic_symbol() on the newly created symbol.
      
      testsuite/
      2006-02-19  Erik Edelmann  <eedelman@gcc.gnu.org>
      
              PR fortran/26201
              * gfortran.dg/convert_1.f90: New.
      
      From-SVN: r111270
      3431818f
    • Bud Davis's avatar
      MAINTAINERS (Write After Approval): Remove myself. · 63a7c9ef
      Bud Davis authored
      2006-02-19  Bud Davis  <jmdavis@link.com>
      
              * MAINTAINERS (Write After Approval):  Remove myself.
              (Language Front End Maintainers):  Add myself as fortran 95
              maintainer and update e-mail address.
      
      From-SVN: r111269
      63a7c9ef
    • Paul Thomas's avatar
      re PR fortran/25054 (nonconstant bounds array cannot appear in a namelist) · 3e1cf500
      Paul Thomas authored
      2005-02-19  Paul Thomas  <pault@gcc.gnu.org>
      
      	PR fortran/25054
      	* resolve.c (is_non_constant_shape_array): New function.
      	(resolve_fl_variable): Remove code for the new function and call it.
      	(resolve_fl_namelist): New function.  Add test for namelist array
      	with non-constant shape, using is_non_constant_shape_array.
      	(resolve_symbol): Remove code for resolve_fl_namelist and call it.
      
      	PR fortran/25089
      	* match.c (match_namelist): Increment the refs field of an accepted
      	namelist object symbol.
      	* resolve.c (resolve_fl_namelist): Test namelist objects for a conflict
      	with contained or module procedures.
      
      2005-02-19  Paul Thomas  <pault@gcc.gnu.org>
      
      	PR fortran/25054
      	* gfortran.dg/namelist_5.f90: New test.
      
      	PR fortran/25089
      	* gfortran.dg/namelist_4.f90: New test.
      
      From-SVN: r111268
      3e1cf500
    • Francois-Xavier Coudert's avatar
      * io/open.c (edit_modes): Correct abusive copy-pasting. · c05f6d04
      Francois-Xavier Coudert authored
      From-SVN: r111266
      c05f6d04
    • Andrew Pinski's avatar
      darwin.h (ASM_OUTPUT_SPECIAL_POOL_ENTRY_P): Use the arguments. · 69b61bb1
      Andrew Pinski authored
      2006-02-18  Andrew Pinski <pinskia@physics.uc.edu>
      
              * config/rs6000/darwin.h (ASM_OUTPUT_SPECIAL_POOL_ENTRY_P):
              Use the arguments.
      
      From-SVN: r111265
      69b61bb1
    • GCC Administrator's avatar
      Daily bump. · 94f19b11
      GCC Administrator authored
      From-SVN: r111263
      94f19b11
    • Mark Wielaard's avatar
      contrib.texi (Contributors): Add classpath/libgcj hackers who added new 4.1 features... · 43e96d00
      Mark Wielaard authored
             * doc/contrib.texi (Contributors): Add classpath/libgcj hackers
             who added new 4.1 features, bug fixes and integration support.
      
      From-SVN: r111256
      43e96d00
  3. Feb 18, 2006
    • David Edelsohn's avatar
      re PR target/26350 (ICE in extract_insn, at recog.c:2084, -fPIC -mlong-double-128) · aa9cf005
      David Edelsohn authored
              PR target/26350
              * config/rs6000/rs6000.md (extenddftf2): Force 0.0 to validized
              MEM for ABI_V4 pic.
      
      From-SVN: r111255
      aa9cf005
    • Richard Sandiford's avatar
      re PR target/9703 ([arm] Accessing data through constant pool more times could... · aacd3885
      Richard Sandiford authored
      re PR target/9703 ([arm] Accessing data through constant pool more times could be solved in less instructions)
      
      	* cselib.c (cselib_init): Change RTX_SIZE to RTX_CODE_SIZE.
      	* emit-rtl.c (copy_rtx_if_shared_1): Use shallow_copy_rtx.
      	(copy_insn_1): Likewise.  Don't copy each field individually.
      	Reindent.
      	* read-rtl.c (apply_macro_to_rtx): Use RTX_CODE_SIZE instead
      	of RTX_SIZE.
      	* reload1.c (eliminate_regs): Use shallow_copy_rtx.
      	* rtl.c (rtx_size): Rename variable to...
      	(rtx_code_size): ...this.
      	(rtx_size): New function.
      	(rtx_alloc_stat): Use RTX_CODE_SIZE instead of RTX_SIZE.
      	(copy_rtx): Use shallow_copy_rtx.  Don't copy each field individually.
      	Reindent.
      	(shallow_copy_rtx_stat): Use rtx_size instead of RTX_SIZE.
      	* rtl.h (rtx_code_size): New variable.
      	(rtx_size): Change from a variable to a function.
      	(RTX_SIZE): Rename to...
      	(RTX_CODE_SIZE): ...this.
      
      	PR target/9703
      	PR tree-optimization/17106
      	* doc/tm.texi (TARGET_USE_BLOCKS_FOR_CONSTANT_P): Document.
      	(Anchored Addresses): New section.
      	* doc/invoke.texi (-fsection-anchors): Document.
      	* doc/rtl.texi (SYMBOL_REF_IN_BLOCK_P, SYMBOL_FLAG_IN_BLOCK): Likewise.
      	(SYMBOL_REF_ANCHOR_P, SYMBOL_FLAG_ANCHOR): Likewise.
      	(SYMBOL_REF_BLOCK, SYMBOL_REF_BLOCK_OFFSET): Likewise.
      	* hooks.c (hook_bool_mode_rtx_false): New function.
      	* hooks.h (hook_bool_mode_rtx_false): Declare.
      	* gengtype.c (create_optional_field): New function.
      	(adjust_field_rtx_def): Add the "block_sym" field for SYMBOL_REFs when
      	SYMBOL_REF_IN_BLOCK_P is true.
      	* target.h (output_anchor, use_blocks_for_constant_p): New hooks.
      	(min_anchor_offset, max_anchor_offset): Likewise.
      	(use_anchors_for_symbol_p): New hook.
      	* toplev.c (compile_file): Call output_object_blocks.
      	(target_supports_section_anchors_p): New function.
      	(process_options): Check that -fsection-anchors is only used on
      	targets that support it and when -funit-at-a-time is in effect.
      	* tree-ssa-loop-ivopts.c (prepare_decl_rtl): Only create DECL_RTL
      	if the decl doesn't have one.
      	* dwarf2out.c: Remove instantiations of VEC(rtx,gc).
      	* expr.c (emit_move_multi_word, emit_move_insn): Pass the result
      	of force_const_mem through use_anchored_address.
      	(expand_expr_constant): New function.
      	(expand_expr_addr_expr_1): Call it.  Use the same modifier when
      	calling expand_expr for INDIRECT_REF.
      	(expand_expr_real_1): Pass DECL_RTL through use_anchored_address
      	for all modifiers except EXPAND_INITIALIZER.  Use expand_expr_constant.
      	* expr.h (use_anchored_address): Declare.
      	* loop-unroll.c: Don't declare rtx vectors here.
      	* explow.c: Include output.h.
      	(validize_mem): Call use_anchored_address.
      	(use_anchored_address): New function.
      	* common.opt (-fsection-anchors): New switch.
      	* varasm.c (object_block_htab, anchor_labelno): New variables.
      	(hash_section, object_block_entry_eq, object_block_entry_hash)
      	(use_object_blocks_p, get_block_for_section, create_block_symbol)
      	(use_blocks_for_decl_p, change_symbol_section): New functions.
      	(get_variable_section): New function, split out from assemble_variable.
      	(make_decl_rtl): Create a block symbol if use_object_blocks_p and
      	use_blocks_for_decl_p say so.  Use change_symbol_section if the
      	symbol has already been created.
      	(assemble_variable_contents): New function, split out from...
      	(assemble_variable): ...here.  Don't output any code for
      	block symbols; just pass them to place_block_symbol.
      	Use get_variable_section and assemble_variable_contents.
      	(get_constant_alignment, get_constant_section, get_constant_size): New
      	functions, split from output_constant_def_contents.
      	(build_constant_desc): Create a block symbol if use_object_blocks_p
      	says so.  Or into SYMBOL_REF_FLAGS.
      	(assemble_constant_contents): New function, split from...
      	(output_constant_def_contents): ...here.  Don't output any code
      	for block symbols; just pass them to place_section_symbol.
      	Use get_constant_section and get_constant_alignment.
      	(force_const_mem): Create a block symbol if use_object_blocks_p and
      	use_blocks_for_constant_p say so.  Or into SYMBOL_REF_FLAGS.
      	(output_constant_pool_1): Add an explicit alignment argument.
      	Don't switch sections here.
      	(output_constant_pool): Adjust call to output_constant_pool_1.
      	Switch sections here instead.  Don't output anything for block symbols;
      	just pass them to place_block_symbol.
      	(init_varasm_once): Initialize object_block_htab.
      	(default_encode_section_info): Keep the old SYMBOL_FLAG_IN_BLOCK.
      	(default_asm_output_anchor, default_use_aenchors_for_symbol_p)
      	(place_block_symbol, get_section_anchor, output_object_block)
      	(output_object_block_htab, output_object_blocks): New functions.
      	* target-def.h (TARGET_ASM_OUTPUT_ANCHOR): New macro.
      	(TARGET_ASM_OUT): Include it.
      	(TARGET_USE_BLOCKS_FOR_CONSTANT_P): New macro.
      	(TARGET_MIN_ANCHOR_OFFSET, TARGET_MAX_ANCHOR_OFFSET): New macros.
      	(TARGET_USE_ANCHORS_FOR_SYMBOL_P): New macro.
      	(TARGET_INITIALIZER): Include them.
      	* rtl.c (rtl_check_failed_block_symbol): New function.
      	* rtl.h: Include vec.h.  Declare heap and gc rtx vectors.
      	(block_symbol, object_block): New structures.
      	(rtx_def): Add a block_symbol field to the union.
      	(BLOCK_SYMBOL_CHECK): New macro.
      	(rtl_check_failed_block_symbol): Declare.
      	(SYMBOL_FLAG_IN_BLOCK, SYMBOL_FLAG_ANCHOR): New SYMBOL_REF flags.
      	(SYMBOL_REF_IN_BLOCK_P, SYMBOL_REF_ANCHOR_P): New predicates.
      	(SYMBOL_FLAG_MACH_DEP_SHIFT): Bump by 2.
      	(SYMBOL_REF_BLOCK, SYMBOL_REF_BLOCK_OFFSET): New accessors.
      	* output.h (output_section_symbols): Declare.
      	(object_block): Name structure.
      	(place_section_symbol, get_section_anchor, default_asm_output_anchor)
      	(default_use_anchors_for_symbol_p): Declare.
      	* Makefile.in (RTL_BASE_H): Add vec.h.
      	(explow.o): Depend on output.h.
      	* config/rs6000/rs6000.c (TARGET_MIN_ANCHOR_OFFSET): Override default.
      	(TARGET_MAX_ANCHOR_OFFSET): Likewise.
      	(TARGET_USE_BLOCKS_FOR_CONSTANT_P): Likewise.
      	(rs6000_use_blocks_for_constant_p): New function.
      
      From-SVN: r111254
      aacd3885
    • John David Anglin's avatar
      install.texi (hppa*-hp-hpux*): Update for 4.1.0. · dcf966bd
      John David Anglin authored
      	* doc/install.texi (hppa*-hp-hpux*): Update for 4.1.0.
      
      From-SVN: r111253
      dcf966bd
    • Andrew Pinski's avatar
      re PR tree-optimization/25680 (Store CCP does not understand REALPART_EXPR < COMPLEX_CST >) · add9e6d3
      Andrew Pinski authored
      2006-02-18  Andrew Pinski  <pinskia@physics.uc.edu>
      
              PR tree-opt/25680
              * tree-ssa-ccp.c (ccp_fold): Handle store CCP of REALPART_EXPR and
              IMAGPART_EXPR.
      2006-02-18  Andrew Pinski  <pinskia@physics.uc.edu>
      
              PR tree-opt/25680
              * testsuite/gcc.dg/tree-ssa/complex-3.c: New test.
      
      From-SVN: r111251
      add9e6d3
    • Andrew Pinski's avatar
      20031106-1.c: Fix the final scan of the variable to take into account the variable name in... · c8ca29f1
      Andrew Pinski authored
      2006-02-18  Andrew Pinski  <pinskia@physics.uc.edu>
      
              * gcc.dg/tree-ssa/20031106-1.c: Fix the final scan of the
              variable to take into account the variable name in the
              function header.
              * gcc.dg/tree-ssa/20031106-2.c: Likewise.
      
      From-SVN: r111250
      c8ca29f1
    • Diego Novillo's avatar
      tree-flow.h (struct var_ann_d): Rename field is_alias_tag to is_aliased. · faf7c678
      Diego Novillo authored
      	* tree-flow.h (struct var_ann_d): Rename field is_alias_tag to
      	is_aliased.
      	Update all users.
      
      From-SVN: r111249
      faf7c678
    • Jakub Jelinek's avatar
      re PR middle-end/26334 (ICE in lhd_set_decl_assembler_name) · 3f2de3dc
      Jakub Jelinek authored
      	PR middle-end/26334
      	* stmt.c (decl_overlaps_hard_reg_set_p): Use DECL_HARD_REGISTER
      	instead of DECL_REGISTER.
      
      	* gcc.c-torture/compile/20060217-1.c: New test.
      	* gcc.dg/20060218-1.c: New test.
      
      From-SVN: r111247
      3f2de3dc
    • Roger Sayle's avatar
      trans-stmt.c (struct temporary_list): Delete. · 3891cee2
      Roger Sayle authored
      	* trans-stmt.c (struct temporary_list): Delete.
      	(gfc_trans_where_2): Major reorganization.  Remove no longer needed
      	TEMP argument.  Allocate and deallocate the control mask and
      	pending control mask locally.
      	(gfc_trans_forall_1): Delete TEMP local variable, and update
      	call to gfc_trans_where_2.  No need to deallocate arrays after.
      	(gfc_evaluate_where_mask): Major reorganization.  Change return
      	type to void.  Pass in parent execution mask, MASK, and two
      	already allocated mask arrays CMASK and PMASK.  On return
      	CMASK := MASK & COND, PMASK := MASK & !COND.  MASK, CMASK and
      	CMASK may all be NULL, or refer to the same temporary arrays.
      	(gfc_trans_where): Update call to gfc_trans_where_2.  We no
      	longer need a TEMP variable or to deallocate temporary arrays
      	allocated by gfc_trans_where_2.
      
      From-SVN: r111245
      3891cee2
    • Olivier Hainque's avatar
      re PR ada/13408 (acats numeric tests cxg* fail on pa/hpux) · 4ea42eba
      Olivier Hainque authored
      	PR ada/13408
      	* pa.h (WIDEST_HARDWARE_FP_SIZE): Define.
      
      From-SVN: r111241
      4ea42eba
    • Danny Smith's avatar
      gfortran.h (gfc_add_attribute): Change uint to unsigned int. · ef6a0629
      Danny Smith authored
      2006-02-18   Danny Smith  <dannysmith@users.sourceforeg.net>
      
          * gfortran.h (gfc_add_attribute): Change uint to unsigned int.
          * symbol.c (gfc_add_attribute): Likewise for definition.
          * resolve.c (resolve_global_procedure): Likewise for variable 'type'.
      
      From-SVN: r111239
      ef6a0629
    • Steve Ellcey's avatar
      re PR target/26189 (Bug in vendor /usr/include/net/if.h needs fixincluding on HPUX) · e084430d
      Steve Ellcey authored
      	PR target/26189
      	* inclhack.def (hpux_spu_info): New.
      	* fixincl.x: Regenerate
      
      From-SVN: r111237
      e084430d
    • Joseph Myers's avatar
      re PR target/24837 (move dynamic linker names out of LINK_SPEC and into new DYNAMIC_LINKER) · 7bd85ce0
      Joseph Myers authored
      	PR target/24837
      	* config.gcc: Define UCLIBC_DEFAULT to 0 or 1.
      	* opth-gen.awk: Handle Var and InverseMask together.
      	* config/linux.opt (muclibc, mglibc): Use Var(linux_uclibc).
      	* config/linux.h: Use #if not #ifdef for testing UCLIBC_DEFAULT.
      	(TARGET_C99_FUNCTIONS): Test OPTION_GLIBC not TARGET_GLIBC.
      	(CHOOSE_DYNAMIC_LINKER): Give an error for -mglibc and -muclibc
      	used together.
      	(UCLIBC_DYNAMIC_LINKER32, UCLIBC_DYNAMIC_LINKER64,
      	LINUX_DYNAMIC_LINKER32, LINUX_DYNAMIC_LINKER64): Define.
      	* config/alpha/linux-elf.h (GLIBC_DYNAMIC_LINKER,
      	UCLIBC_DYNAMIC_LINKER, CHOOSE_DYNAMIC_LINKER,
      	LINUX_DYNAMIC_LINKER): Define.
      	(ELF_DYNAMIC_LINKER): Define to LINUX_DYNAMIC_LINKER.
      	* config/alpha/linux.h (TARGET_C99_FUNCTIONS): Define to
      	TARGET_GLIBC.
      	* config/cris/linux.h (GLIBC_DYNAMIC_LINKER): Define.
      	(CRIS_LINK_SUBTARGET_SPEC): Pass a -dynamic-linker option.
      	* config/frv/linux.h (GLIBC_DYNAMIC_LINKER): Define.
      	(LINK_SPEC): Use LINUX_DYNAMIC_LINKER.
      	(TARGET_C99_FUNCTIONS): Don't define.
      	* config/i386/linux.h (DYNAMIC_LINKER): Rename to
      	GLIBC_DYNAMIC_LINKER.
      	(SUBTARGET_EXTRA_SPECS): Use LINUX_DYNAMIC_LINKER.
      	* config/i386/linux64.h (GLIBC_DYNAMIC_LINKER32,
      	GLIBC_DYNAMIC_LINKER64): Define.
      	(LINK_SPEC): Use LINUX_DYNAMIC_LINKER32 and
      	LINUX_DYNAMIC_LINKER64.
      	* config/ia64/linux.h (GLIBC_DYNAMIC_LINKER): Define.
      	(LINK_SPEC): Use LINUX_DYNAMIC_LINKER.
      	* config/m32r/linux.h (GLIBC_DYNAMIC_LINKE): Define.
      	(LINK_SPEC): Use LINUX_DYNAMIC_LINKER.
      	* config/m68k/linux.h (GLIBC_DYNAMIC_LINKER): Define.
      	(LINK_SPEC): Use LINUX_DYNAMIC_LINKER.
      	* config/mips/linux64.h (GLIBC_DYNAMIC_LINKER32,
      	GLIBC_DYNAMIC_LINKER64, GLIBC_DYNAMIC_LINKERN32,
      	UCLIBC_DYNAMIC_LINKERN32, LINUX_DYNAMIC_LINKERN32): Define.
      	(LINK_SPEC): Use LINUX_DYNAMIC_LINKERN32, LINUX_DYNAMIC_LINKER64
      	and LINUX_DYNAMIC_LINKER32.
      	* config/mn10300/linux.h (GLIBC_DYNAMIC_LINKER): Define.
      	(LINK_SPEC): Use LINUX_DYNAMIC_LINKER.
      	* config/pa/pa-linux.h (GLIBC_DYNAMIC_LINKER): Define.
      	(LINK_SPEC): Use LINUX_DYNAMIC_LINKER.
      	* config/rs6000/linux.h (TARGET_C99_FUNCTIONS): Define to
      	TARGET_GLIBC.
      	* config/rs6000/linux64.h (TARGET_C99_FUNCTIONS): Likewise.
      	(GLIBC_DYNAMIC_LINKER32, GLIBC_DYNAMIC_LINKER64,
      	UCLIBC_DYNAMIC_LINKER32, UCLIBC_DYNAMIC_LINKER64,
      	CHOOSE_DYNAMIC_LINKER, CHOOSE_DYNAMIC_LINKER,
      	LINUX_DYNAMIC_LINKER32, LINUX_DYNAMIC_LINKER64): Define.
      	(LINK_OS_LINUX_SPEC32): Use LINUX_DYNAMIC_LINKER32.
      	(LINK_OS_LINUX_SPEC64): Use LINUX_DYNAMIC_LINKER64.
      	* config/rs6000/sysv4.h (GLIBC_DYNAMIC_LINKER,
      	UCLIBC_DYNAMIC_LINKER, CHOOSE_DYNAMIC_LINKER,
      	LINUX_DYNAMIC_LINKER): Define.
      	(LINK_OS_LINUX_SPEC): Use LINUX_DYNAMIC_LINKE.
      	* config/s390/linux.h (GLIBC_DYNAMIC_LINKER32,
      	GLIBC_DYNAMIC_LINKER64): Define.
      	(LINK_SPEC): Use LINUX_DYNAMIC_LINKER32 and
      	LINUX_DYNAMIC_LINKER64.
      	* config/sh/linux.h (GLIBC_DYNAMIC_LINKER): Define.
      	(SUBTARGET_LINK_SPEC): Use LINUX_DYNAMIC_LINKER.
      	* config/sparc/linux.h (GLIBC_DYNAMIC_LINKER,
      	UCLIBC_DYNAMIC_LINKER, CHOOSE_DYNAMIC_LINKER,
      	LINUX_DYNAMIC_LINKER): Define.
      	(LINK_SPEC): Use LINUX_DYNAMIC_LINKER.
      	(TARGET_C99_FUNCTIONS): Define to TARGET_GLIBC.
      	* config/sparc/linux64.h (GLIBC_DYNAMIC_LINKER32,
      	GLIBC_DYNAMIC_LINKER64, UCLIBC_DYNAMIC_LINKER32,
      	UCLIBC_DYNAMIC_LINKER64, CHOOSE_DYNAMIC_LINKER,
      	LINUX_DYNAMIC_LINKER32, LINUX_DYNAMIC_LINKER64): Define.
      	(LINK_ARCH32_SPEC): Use LINUX_DYNAMIC_LINKER32.
      	(LINK_ARCH64_SPEC, LINK_SPEC): Use LINUX_DYNAMIC_LINKER64.
      	(TARGET_C99_FUNCTIONS): Define to TARGET_GLIBC.
      	* config/xtensa/linux.h (GLIBC_DYNAMIC_LINKER): Define.
      	(LINK_SPEC): Use LINUX_DYNAMIC_LINKER.
      	* doc/invoke.texi (-muclibc): Remove caveat about supported
      	targets.
      
      testsuite:
      	* gcc.dg/glibc-uclibc-1.c, gcc.dg/glibc-uclibc-2.c: New tests.
      
      From-SVN: r111235
      7bd85ce0
    • Grigory Zagorodnev's avatar
      cpp.texi (__TIMESTAMP__): Document. · be8ac3e2
      Grigory Zagorodnev authored
      2006-02-17  Grigory Zagorodnev <grigory_zagorodnev@linux.intel.com>
      
      gcc/ChangeLog:
           * doc/cpp.texi (__TIMESTAMP__): Document.
      
      libcpp/ChangeLog:
           * macro.c (_cpp_builtin_macro_text): Handle BT_TIMESTAMP.
           * files.c (_cpp_get_file_stat): New function.
           * include/cpplib.h (builtin_type): Add BT_TIMESTAMP.
           * init.c (builtin_array): Add support for __TIMESTAMP__/BT_TIMESTAMP.
           * internal.h (_cpp_get_file_stat): Prototype.
           (struct cpp_buffer): Add timestamp.
      
      gcc/testsuite/ChangeLog:
           * gcc.dg/cpp/undef3.c: New test.
           * gcc.dg/cpp/trad/builtins2.c: New test.
      
      From-SVN: r111232
      be8ac3e2
    • Mark Mitchell's avatar
      re PR c++/26266 (Trouble with static const data members in template classes) · 8d08b2d7
      Mark Mitchell authored
      	PR c++/26266
      	* g++.dg/template/static22.C: New test.
      	* g++.dg/template/static23.C: New test.
      	* g++.dg/template/static24.C: New test.
      	* g++.dg/template/non-dependent13.C: New test.
      	* g++.dg/init/member1.C: Tweak error markers.
      
      From-SVN: r111230
      8d08b2d7
    • Mark Mitchell's avatar
      re PR c++/26266 (Trouble with static const data members in template classes) · d174af6c
      Mark Mitchell authored
      	PR c++/26266
      	* cp-tree.h (cp_finish_decl): Adjust declaration.
      	(grokbitfield): Likewise.
      	(finish_static_data_member_decl): Likewise.
      	* init.c (constant_value_1): Ensure processing_template_decl when
      	folding non-dependent initializers for static data members of
      	dependent types.  Return error_mark_node for erroneous
      	initailizers.
      	* class.c (get_vtable_decl): Use finish_decl, not cp_finish_decl.
      	* decl.c (cp_make_fname_decl): Adjust call to cp_finish_decl.
      	(cp_finish_decl): Add init_const_expr_p parameter.  Set
      	DECL_INITIALIZED_BY_CONSTANT_EXPRESSION_P here.
      	(finish_decl): Adjust call to cp_finish_decl.
      	(compute_array_index_type): Robustify.
      	(start_method): Use finish_decl, not cp_finish_decl.
      	* rtti.c (emit_tinfo_decl): Likewise.
      	* except.c (initialize_handler_parm): Adjust call to
      	cp_finish_decl.
      	(expand_start_catch_block): Likewise.
      	* cvt.c (build_up_reference): Adjust call to cp_finish_decl.
      	* pt.c (instantiate_class_template): Adjust call to
      	finish_static_data_member_decl.
      	(tsubst_expr): Use finish_decl, not cp_finish_decl.
      	(instantiate_decl): Adjust call to cp_finish_decl.
      	* name-lookup.c (pushdecl_top_level_1): Use finish_decl, not
      	cp_finish_decl.
      	* decl2.c (finish_static_data_member_decl): Add init_const_expr_p
      	parameter.
      	(grokfield): Likewise.
      	* parser.c (cp_parser_condition): Check for constant initializers.
      	(cp_parser_init_declarator): Adjust calls to grokfield and
      	cp_finish_decl.  Don't set
      	DECL_INITIALIZED_BY_CONSTANT_EXPRESSION_P here.
      	(cp_parser_member_declaration): Likewise.
      	(cp_parser_objc_class_ivars): Likewise.
      	PR c++/26266
      	* g++.dg/template/static22.C: New test.
      	* g++.dg/template/static23.C: New test.
      	* g++.dg/template/static24.C: New test.
      	* g++.dg/template/non-dependent13.C: New test.
      
      From-SVN: r111229
      d174af6c
    • Roger Sayle's avatar
      re PR rtl-optimization/25600 (unsigned>>31?-1:0 should be optimized to int>>31) · 8305d786
      Roger Sayle authored
      	PR middle-end/25600
      	* fold-const.c (fold_binary): Fold (X >> C) != 0 into X < 0 when
      	C is one less than the width of X (and related transformations).
      	* simplify_rtx.c (simplify_unary_operation_1): Transform 
      	(neg (lt x 0)) into either (ashiftrt X C) or (lshiftrt X C)
      	depending on STORE_FLAG_VALUE, were C is one less then the
      	width of X.
      
      From-SVN: r111226
      8305d786
    • Kaz Kojima's avatar
      ffi.c (ffi_closure_helper_SYSV): Remove unused variable and cast integer to void * if needed. · e097f887
      Kaz Kojima authored
      	* src/sh/ffi.c (ffi_closure_helper_SYSV): Remove unused variable
      	and cast integer to void * if needed.  Update the pointer to
      	the FP register saved area correctly.
      
      From-SVN: r111225
      e097f887
    • GCC Administrator's avatar
      Daily bump. · a3042501
      GCC Administrator authored
      From-SVN: r111223
      a3042501
    • Daniel Berlin's avatar
      re PR tree-optimization/26341 (930217-1.c and 931013-3.c ICE at -O2 and above... · dd7b13d8
      Daniel Berlin authored
      re PR tree-optimization/26341 (930217-1.c and 931013-3.c ICE at -O2 and above in add_virtual_operand)
      
      2006-02-17  Daniel Berlin  <dberlin@dberlin.org>
      
      	Fix PR tree-optimization/26341
      	* tree-ssa-operands.c (add_virtual_operand): Remove assert 
      	about NAME_MEMORY_TAG's.
      
      From-SVN: r111217
      dd7b13d8
Loading