diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index ff0670569f62efbf6a2f32ef57cdfee5ff0e497b..5220337f50777a8620a6b5d301f692df49698128 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,20 @@
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* exp_ch9.adb, exp_sel.adb, restrict.ads, exp_disp.adb, erroutc.ads,
+	exp_ch3.adb: Minor reformatting.
+
+2011-08-02  Emmanuel Briot  <briot@adacore.com>
+
+	* adaint.c (__gnat_locate_exec_on_path): only returns executable
+	files, not any regular file.
+	(__gnat_locate_file_with_predicate): new subprogram.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* sinfo.adb, sinfo.ads: Restrict the use of flags
+	Has_Dynamic_Length_Check and Has_Dynamic_Range_Check to expression
+	nodes, plus N_Subtype_Declaration for the 2nd one.
+
 2011-08-02  Sergey Rybin  <rybin@adacore.com>
 
 	* gnat_rm.texi: Ramification of pragma Eliminate documentation
@@ -3185,6 +3202,3198 @@
 	variables that are referenced in exception handlers volatile.
 
 
+
+Copyright (C) 2011 Free Software Foundation, Inc.
+
+Copying and distribution of this file, with or without modification,
+are permitted in any medium without royalty provided the copyright
+notice and this notice are preserved.
+
+	* gnat_rm.texi: Ramification of pragma Eliminate documentation
+	 - fix bugs in the description of Source_Trace;
+	 - get rid of UNIT_NAME;
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* exp_ch9.adb
+	(Build_Dispatching_Requeue): Adding support for VM targets
+	since we cannot directly reference the Tag entity.
+	* exp_sel.adb (Build_K): Adding support for VM targets.
+	(Build_S_Assignment): Adding support for VM targets.
+	* exp_disp.adb
+	(Default_Prim_Op_Position): In VM targets do not restrict availability
+	of predefined interface primitives to compiling in Ada 2005 mode.
+	(Is_Predefined_Interface_Primitive): In VM targets this service is not
+	restricted to compiling in Ada 2005 mode.
+	(Make_VM_TSD): Generate code that declares and initializes the OSD
+	record. Needed to support dispatching calls through synchronized
+	interfaces.
+	* exp_ch3.adb
+	(Make_Predefined_Primitive_Specs): Enable generation of predefined
+	primitives associated with synchronized interfaces.
+	(Make_Predefined_Primitive_Bodies): Enable generation of predefined
+	primitives associated with synchronized interfaces.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* par-ch11.adb (P_Handled_Sequence_Of_Statements): mark a sequence of
+	statements hidden in SPARK if preceded by the HIDE directive
+	(Parse_Exception_Handlers): mark each exception handler in a sequence of
+	exception handlers as hidden in SPARK if preceded by the HIDE directive
+	* par-ch6.adb (P_Subprogram): mark a subprogram body hidden in SPARK
+	if starting with the HIDE directive
+	* par-ch7.adb (P_Package): mark a package body hidden in SPARK if
+	starting with the HIDE directive; mark the declarations in a private
+	part as hidden in SPARK if the private part starts with the HIDE
+	directive
+	* restrict.adb, restrict.ads
+	(Set_Hidden_Part_In_SPARK): record a range of slocs as hidden in SPARK
+	(Is_In_Hidden_Part_In_SPARK): new function which returns whether its
+	argument node belongs to a part which is hidden in SPARK
+	(Check_SPARK_Restriction): do not issue violations on nodes in hidden
+	parts in SPARK; protect the possibly costly call to
+	Is_In_Hidden_Part_In_SPARK by a check that the SPARK restriction is on
+	* scans.ads (Token_Type): new value Tok_SPARK_Hide in enumeration
+	* scng.adb (Accumulate_Token_Checksum_GNAT_6_3,
+	Accumulate_Token_Checksum_GNAT_5_03): add case for new token
+	Tok_SPARK_Hide.
+	(Scan): recognize special comment starting with '#' and followed by
+	SPARK keyword "hide" as a HIDE directive.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* types.ads, erroutc.ads: Minor reformatting.
+
+2011-08-02  Vincent Celier  <celier@adacore.com>
+
+	* link.c: Add response file support for cross platforms.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_aggr.adb (Resolve_Array_Aggregate): when copying the expression
+	in an association, set parent field of copy before partial analysis.
+	* sem_res.adb (Resolve_Slice): create reference to itype only when
+	expansion is enabled.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* einfo.adb, einfo.ads (Body_Is_In_ALFA, Set_Body_Is_In_ALFA): get/set
+	for new flag denoting which subprogram bodies are in ALFA
+	* restrict.adb, sem_ch7.adb: Update comment
+	* sem_ch11.adb, sem_ch2.adb, sem_ch3.adb, sem_ch4.adb, sem_ch5.adb,
+	sem_ch9.adb, sem_res.adb: Add calls to
+	Current_Subprogram_Body_Is_Not_In_ALFA on unsupported constructs.
+	* sem_ch6.adb (Analyze_Function_Return): add calls to
+	Current_Subprogram_Body_Is_Not_In_ALFA on return statement in the
+	middle of the body, and extended return.
+	(Check_Missing_Return): add calls to Set_Body_Is_In_ALFA with argument
+	False when missing return.
+	(Analyze_Subprogram_Body_Helper): initialize the flag Body_Is_In_ALFA
+	to True for subprograms whose spec is in ALFA. Remove later on the flag
+	on the entity used for a subprogram body when there exists a separate
+	declaration.
+	* sem_util.adb, sem_util.ads (Current_Subprogram_Body_Is_Not_In_ALFA):
+	if Current_Subprogram is not Empty, set its flag Body_Is_In_ALFA to
+	False, otherwise do nothing.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* inline.adb, stand.ads, sem_ch6.adb, sem_ch8.adb: Minor reformatting.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* sem_ch4.ads: minor formatting.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* sem_aggr.adb, err_vars.ads, sem_ch3.adb, sem_ch5.adb, sem_ch9.adb,
+	debug.adb, sem_util.adb, sem_res.adb, sem_attr.adb, gnat1drv.adb,
+	errout.adb, errout.ads, exp_ch6.adb, sem_ch4.adb, restrict.adb,
+	restrict.ads, sem_ch6.adb, sem_ch8.adb, sem_ch11.adb,
+	opt.ads: cleanup of SPARK mode
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* cstand.adb (Create_Standard): sets Is_In_ALFA component of standard
+	types.
+	* einfo.adb, einfo.ads (Is_In_ALFA): add flag for all entities
+	(Is_In_ALFA, Set_Is_In_ALFA): new subprograms to access flag Is_In_ALFA
+	* sem_ch3.adb
+	(Analyze_Object_Declaration): set Is_In_ALFA flag for objects
+	(Constrain_Enumeration): set Is_In_ALFA flag for enumeration subtypes
+	(Constrain_Integer): set Is_In_ALFA flag for integer subtypes
+	(Enumeration_Type_Declaration): set Is_In_ALFA flag for enumeration
+	types.
+	(Set_Scalar_Range_For_Subtype): unset Is_In_ALFA flag for subtypes with
+	non-static range.
+	* sem_ch6.adb (Analyze_Return_Type): unset Is_In_ALFA flag for
+	functions whose return type is not in ALFA.
+	(Analyze_Subprogram_Specification): set Is_In_ALFA flag for subprogram
+	specifications.
+	(Process_Formals): unset Is_In_ALFA flag for subprograms if a
+	parameter's type is not in ALFA.
+	* stand.ads (Standard_Type_Is_In_ALFA): array defines which standard
+	types are in ALFA.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch6 (Analyze_Expression_Function): treat the function as
+	Inline_Always, and introduce a subprogram declaration for it when it is
+	not a completion.
+	* inline.adb (Add_Inlined_Body): recognize bodies that come from
+	expression functions, so that the back-end can determine whether they
+	can in fact be inlined.
+	* sem_util.adb (Is_Expression_Function): predicate to determine whether
+	a function body comes from an expression function.
+
+2011-08-02  Gary Dismukes  <dismukes@adacore.com>
+
+	* sem_ch6.adb (Check_Conformance): Revise the check for nonconforming
+	null exclusions to test Can_Never_Be_Null on the anonymous access types
+	of the formals rather than testing the formals themselves. Exclude this
+	check in cases where the Old_Formal is marked as a controlling formal,
+	to avoid issuing spurious errors for bodies completing dispatching
+	operations (due to the flag not getting set on controlling access
+	formals in body specs).
+	(Find_Corresponding_Spec): When checking full and subtype conformance of
+	subprogram bodies in instances, pass Designated and E in that order, for
+	consistency with the expected order of the formals (New_Id followed by
+	Old_Id).
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch8.adb: Minor reformatting.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch8.adb (Analyze_Subprogram_Renaming): new procedure
+	Check_Class_Wide_Actual, to implement AI05-0071, on defaulted
+	primitive operations of class-wide actuals.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* exp_atag.ads, exp_atag.adb
+	(Build_Common_Dispatching_Select_Statements): Remove argument Loc
+	since its value is implicitly passed in argument Typ.
+	* exp_disp.adb (Make_Disp_Conditional_Select_Body,
+	Make_Disp_Timed_Select_Body): Remove Loc in calls to routine
+	Build_Common_Dispatching_Select_Statements.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch3.adb, exp_atag.ads, get_scos.adb, get_scos.ads,
+	exp_disp.adb, lib-xref.adb, lib-xref.ads: Update comments.
+	Minor reformatting.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_res.adb: Minor reformatting.
+	* sem_prag.adb: Minor reformatting.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* exp_atag.adb, exp_atags.ads
+	(Build_Common_Dispatching_Select_Statement): Replace argument DT_Ptr
+	by the tagged type Entity. Required to use this routine in the VM
+	targets since we do not have available the Tag entity in the VM
+	platforms.
+	* exp_ch6.adb
+	(Expand_N_Subprogram_Body): Do not invoke Build_VM_TSDs if package
+	Ada.Tags has not been previously loaded.
+	* exp_ch7.adb
+	(Expand_N_Package_Declaration, Expand_N_Package_Body): Do not invoke
+	Build_VM_TSDs if package Ada.Tags has not been previously loaded.
+	* sem_aux.adb
+	(Enclosing_Dynamic_Scope): Add missing support to handle the full
+	view of enclosing scopes. Required to handle enclosing scopes that
+	are synchronized types whose full view is a task type.
+	* exp_disp.adb
+	(Build_VM_TSDs): Minor code improvement to avoid generating and
+	analyzing lists with empty nodes.
+	(Make_Disp_Asynchronous_Select_Body): Add support for VM targets.
+	(Make_Disp_Conditional_Select_Body): Add support for VM targets.
+	(Make_Disp_Get_Prim_Op_Kind): Add support for VM targets.
+	(Make_Disp_Timed_Select_Body): Add support for VM targets.
+	(Make_Select_Specific_Data_Table): Add support for VM targets.
+	(Make_VM_TSD): Generate code to initialize the SSD structure of
+	the TSD.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* lib-writ.adb (Write_ALI): when ALFA mode is set, write local
+	cross-references section in ALI.
+	* lib-xref.adb, lib-xref.ads (Xref_Entry): add components Sub
+	(enclosing subprogram), Slc (location of Sub) and Sun (unit number of
+	Sub).
+	(Enclosing_Subprogram_Or_Package): new function to return the enclosing
+	subprogram or package entity of a node
+	(Is_Local_Reference_Type): new function returns True for references
+	selected in local cross-references.
+	(Lt): function extracted from Lt in Output_References
+	(Write_Entity_Name): function extracted from Output_References
+	(Generate_Definition): generate reference with type 'D' for definition
+	of objects (object declaration and parameter specification), with
+	appropriate locations and units, for use in local cross-references.
+	(Generate_Reference): update fields Sub, Slc and Sun. Keep newly created
+	references of type 'I' for initialization in object definition.
+	(Output_References): move part of function Lt and procedure
+	Write_Entity_Name outside of the body. Ignore references of types 'D'
+	and 'I' introduced for local cross-references.
+	(Output_Local_References): new procedure to output the local
+	cross-references sections.
+	(Lref_Entity_Status): new array defining whether an entity is a local
+	* sem_ch3.adb (Analyze_Object_Declaration): call Generate_Reference
+	with 'I' type when initialization expression is present.
+	* get_scos.adb, get_scos.ads: Correct comments and typos
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* exp_ch6.adb (Expand_N_Subprogram_Body): Enable generation of TSDs in
+	the JVM target.
+	* exp_ch7.adb (Expand_N_Package_Body): Enable generation of TSDs in
+	the JVM target.
+	* exp_disp.adb (Build_VM_TSDs): No action needed if the runtime has no
+	TSD support.
+
+2011-08-02  Vincent Celier  <celier@adacore.com>
+
+	* prj-nmsc.adb (File_Found): New components Excl_File and Excl_Line
+	(No_Space_Img): New function
+	(Find_Excluded_Sources): When reading from a file, record the file name
+	and the line number for each excluded source.
+	(Mark_Excluded_Sources): When reporting an error, if the excluded
+	sources were read from a file, include file name and line number in
+	the error message.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_res.adb (Resolve_Call): implement rule in RM 12.5.1 (23.3/2).
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* exp_ch7.adb exp_ch6.adb, exp_disp.adb: Minor reformatting
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* exp_ch6.adb (Expand_N_Subprogram_Body): Temporarily restrict the
+	generation of TSDs to the DOTNET compiler.
+	* exp_ch7.adb (Expand_N_Package_Body): Temporarily restrict the
+	generation of TSDs to the DOTNET compiler.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* exp_disp.ads (Build_VM_TSDs): Build the runtime Type Specific Data
+	record of all the tagged types declared inside library level package
+	declarations, library level package bodies or library level subprograms.
+	* exp_disp.adb (Make_VM_TSD): New subprogram that builds the TSD
+	associated with a given tagged type.
+	(Build_VM_TSDs): New subprogram.
+	* exp_ch6.adb (Expand_N_Subprogram_Body): Generate TSDs records of main
+	compilation units that are subprograms.
+	* exp_ch7.adb (Expand_N_Package_Body): Generate TSDs of main
+	compilation units that are package bodies.
+	(Expand_N_Package_Declaration): Generate TSDs of the main compilation
+	units that are a package declaration or a package instantiation.
+	* exp_intr.adb (Expand_Dispatching_Constructor_Call): Minor code
+	reorganization to improve the error generated by the frontend when the
+	function Ada.Tags.Secondary_Tag is not available.
+	* rtsfind.ads (RE_Register_TSD): New runtime entity.
+	* exp_ch4.adb (Expand_N_Type_Conversion): Minor code cleanup.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* exp_disp.adb (Make_DT): Generate call to Check_TSD in Ada 2005 mode.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* s-imenne.ads: Minor reformatting.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* a-stunau.ads: Add pragma Suppress_Initialization for Big_String
+	* freeze.adb (Warn_Overlay): Don't warn if initialization suppressed
+	* s-stalib.ads: Add pragma Suppress_Initialization for Big_String
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* einfo.ads (Materialize_Entity): Document this is only for renamings
+	* exp_ch3.adb (Expand_N_Object_Declaration): Make sure we generate
+	required debug information in the case where we transform the object
+	declaration into a renaming declaration.
+	* exp_ch4.adb (Expand_Concatenate): Generate debug info for result
+	object
+	* exp_dbug.ads (Debug_Renaming_Declaration): Document setting of
+	Materialize_Entity.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* einfo.ads, einfo.adb (Suppress_Initialization): Replaces
+	Suppress_Init_Procs.
+	* exp_ch3.adb, exp_disp.adb, freeze.adb: Use
+	Suppress_Initialization/Initialization_Suppressed.
+	* gnat_rm.texi: New documentation for pragma Suppress_Initialization
+	* sem_aux.ads, sem_aux.adb (Initialization_Suppressed): New function
+	* sem_dist.adb: Use Suppress_Initialization/Initialization_Suppressed
+	* sem_prag.adb: New processing for pragma Suppress_Initialization.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* gnat_rm.texi, a-tags.ads, sem_prag.adb, sem_ch12.adb, exp_disp.adb:
+	Minor reformatting.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_prag.adb (Chain_PPC): Implement AI04-0230: null procedures can
+	only have inheritable classwide pre/postconditions.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* a-tags.ads, a-tags.adb (Check_TSD): New subprogram.
+	* rtsfind.ads (RE_Check_TSD): New runtime entity.
+	* exp_disp.adb (Make_DT): Generate call to the new runtime routine that
+	checks if the external tag of a type is the same as the external tag
+	of some other declaration.
+
+2011-08-02  Thomas Quinot  <quinot@adacore.com>
+
+	* s-taskin.ads: Minor reformatting.
+
+2011-08-02  Emmanuel Briot  <briot@adacore.com>
+
+	* g-comlin.adb (Display_Help): swap the order in which it prints the
+	short help and the general usage.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch12.adb (Analyze_Generic_Subprogram_Declaration): copy properly
+	the aspect declarations and attach them to the generic copy for
+	subsequent analysis.
+	(Analyze_Subprogram_Instantiation): copy explicitly the aspect
+	declarations of the generic tree to the new subprogram declarations.
+	* sem_attr.adb (Check_Precondition_Postcondition): recognize
+	conditions that apply to a subprogram instance.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* gnat_rm.texi: Clarify doc on pragma Source_File_Name[_Project].
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch3.adb (Derived_Type_Declaration): When checking that a untagged
+	private type with a tagged full view is not derived in the immediate
+	scope of the partial view, (RM 7.3 (7)) use the scope of the base type.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* exp_ch4.adb: Minor reformatting.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch5.adb (Analyze_Loop_Statement):  If the iteration scheme is an
+	Ada2012 iterator, the loop will be rewritten during expansion into a
+	while loop with a cursor and an element declaration. Do not analyze the
+	body in this case, because if the container is for indefinite types the
+	actual subtype of the elements will only be determined when the cursor
+	declaration is analyzed.
+
+2011-08-02  Arnaud Charlet  <charlet@adacore.com>
+
+	* sem_ch13.adb (Analyze_Attribute_Definition_Clause): Ignore
+	size/alignment related attributes in CodePeer_Mode.
+
+2011-08-02  Gary Dismukes  <dismukes@adacore.com>
+
+	* sem_ch3.adb (Check_Ops_From_Incomplete_Type): Remove call to
+	Prepend_Element, since this can result in the operation getting the
+	wrong slot in the full type's dispatch table if the full type has
+	inherited operations. The incomplete type's operation will get added
+	to the proper position in the full type's primitives
+	list later in Sem_Disp.Check_Operation_From_Incomplete_Type.
+	(Process_Incomplete_Dependents): Add Is_Primitive test when checking for
+	dispatching operations, since there are cases where nonprimitive
+	subprograms can get added to the list of incomplete dependents (such
+	as subprograms in nested packages).
+	* sem_ch6.adb (Process_Formals): First, remove test for being in a
+	private part when determining whether to add a primitive with a
+	parameter of a tagged incomplete type to the Private_Dependents list.
+	Such primitives can also occur in the visible part, and should not have
+	been excluded from being private dependents.
+	* sem_ch7.adb (Uninstall_Declarations): When checking the rule of
+	RM05-3.10.1(9.3/2), test that a subprogram in the Private_Dependents
+	list of a Taft-amendment incomplete type is a primitive before issuing
+	an error that the full type must appear in the same unit. There are
+	cases where nonprimitives can be in the list (such as subprograms in
+	nested packages).
+	* sem_disp.adb (Derives_From): Use correct condition for checking that
+	a formal's type is derived from the type of the corresponding formal in
+	the parent subprogram (the condition was completely wrong). Add
+	checking that was missing for controlling result types being derived
+	from the result type of the parent operation.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* errout.adb (First_Node): minor renaming
+	* restrict.adb (Check_Formal_Restriction): put restriction warning on
+	first node.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* sem_res.adb (Resolve_Logical_Op): ensure N is a binary operator
+	before accessing operands.
+	* sem_util.adb (Is_SPARK_Initialization_Expr): follow original nodes to
+	decide whether an initialization expression respects SPARK rules, as
+	the plain node is the expanded one. This allows for more valid warnings
+	to be issued.
+	* gnat_rm.texi: Minor update.
+
+2011-08-02  Arnaud Charlet  <charlet@adacore.com>
+
+	* sem_ch13.adb (Analyze_Enumeration_Representation_Clause): Revert
+	previous change.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch3.adb, sem_ch4.adb: Minor reformatting.
+
+2011-08-02  Hristian Kirtchev  <kirtchev@adacore.com>
+
+	* exp_ch5.adb (Expand_Iterator_Loop): Reformatting. Wrap the original
+	loop statements and the element renaming declaration with a block when
+	the element type is controlled.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* sinfo.ads: Minor formatting.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_aggr.adb (Add_Association): if the association has a box and no
+	expression, use the Sloc of the aggregate itself for the new
+	association.
+	* errout.adb (First_Node): Exclude nodes with no Sloc, and always use
+	the Original_Node.
+
+2011-08-02  Hristian Kirtchev  <kirtchev@adacore.com>
+
+	* exp_ch5.adb (Expand_Iterator_Loop): Code cleanup and refactoring.
+	When a container is provided via a function call, generate a renaming
+	of the function result. This avoids the creation of a transient scope
+	and the premature finalization of the container.
+	* exp_ch7.adb (Is_Container_Cursor): Removed.
+	(Wrap_Transient_Declaration): Remove the supression of the finalization
+	of the list controller when the declaration denotes a container cursor,
+	it is not needed.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* restrict.adb (Check_Formal_Restriction): only issue a warning if the
+	node is from source, instead of the original node being from source.
+	* sem_aggr.adb
+	(Resolve_Array_Aggregate): refine the check for a static expression, to
+	recognize also static ranges
+	* sem_ch3.adb, sem_ch3.ads (Analyze_Component_Declaration,
+	Array_Type_Declaration): postpone the test for the type being a subtype
+	mark after the type has been resolved, so that component-selection and
+	expanded-name are discriminated.
+	(Make_Index, Process_Range_Expr_In_Decl): add a parameter In_Iter_Schm
+	to distinguish the case of an iteration scheme, so that an error is
+	issed on a non-static range in SPARK except in an iteration scheme.
+	* sem_ch5.adb (Analyze_Iteration_Scheme): call Make_Index with
+	In_Iter_Schm = True.
+	* sem_ch6.adb (Analyze_Subprogram_Specification): refine the check for
+	user-defined operators so that they are allowed in renaming
+	* sem_ch8.adb
+	(Find_Selected_Component): refine the check for prefixing of operators
+	so that they are allowed in renaming. Move the checks for restrictions
+	on selector name after analysis discriminated between
+	component-selection and expanded-name.
+	* sem_res.adb (Resolve_Op_Concat_Arg): do not issue a warning on
+	concatenation argument of string type if it is static.
+	* sem_util.adb, sem_util.ads
+	(Check_Later_Vs_Basic_Declarations): add a new function
+	Is_Later_Declarative_Item to decice which declarations are allowed as
+	later items, in the two different modes Ada 83 and SPARK. In the SPARK
+	mode, add that renamings are considered as later items.
+	(Enclosing_Package): new function to return the enclosing package
+	(Enter_Name): correct the rule for homonyms in SPARK
+	(Is_SPARK_Initialization_Expr): default to returning True on nodes not
+	from source (result of expansion) to avoid issuing wrong warnings.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* errout.adb: On anything but an expression First_Node returns its
+	argument.
+
+2011-08-02  Pascal Obry  <obry@adacore.com>
+
+	* prj-proc.adb, make.adb, makeutl.adb: Minor reformatting.
+
+2011-08-02  Hristian Kirtchev  <kirtchev@adacore.com>
+
+	* exp_ch5.adb (Expand_Iterator_Loop): Code cleanup and reorganization.
+	Set the associated loop as the related expression of internally
+	generated cursors.
+	* exp_ch7.adb (Is_Container_Cursor): New routine.
+	(Wrap_Transient_Declaration): Supress the finalization of the list
+	controller when the declaration denotes a container cursor.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* opt.ads (SPARK_Mode): update comment, SPARK_Mode only set through
+	command line now.
+	* par-ch3.adb (P_Delta_Constraint): remove check in SPARK mode that the
+	expression is a simple expression. This check cannot be performed in
+	the semantics, so just drop it.
+	(P_Index_Or_Discriminant_Constraint): move check that the index or
+	discriminant is a subtype mark to Analyze_Subtype_Declaration in the
+	semantics. Other cases were previously checked in the semantics.
+	* par-ch4.adb (P_Name): move checks that a selector name is not
+	character literal or an operator symbol to Find_Selected_Component in
+	the semantics
+	* par-ch5.adb (Parse_Decls_Begin_End): move check that basic
+	declarations are not placed after later declarations in a separate
+	procedure in Sem_Util (possibly not the best choice?), to be used both
+	during parsing, for Ada 83 mode, and during semantic analysis, for
+	SPARK mode.
+	* par-endh.adb (Check_End): move check that end label is not missing
+	to Process_End_Label in the semantics
+	* par-prag.adb (Process_Restrictions_Or_Restriction_Warnings): remove
+	the special case for SPARK restriction
+	* par.adb: use and with Sem_Util, for use in Parse_Decls_Begin_End
+	* restrict.adb, restrict.ads (Check_Formal_Restriction): add a
+	parameter Force to issue the error message even on internal node (used
+	for generated end label). Call Check_Restriction to check when an error
+	must be issued. In SPARK mode, issue an error message even if the
+	restriction is not set.
+	(Check_Restriction): new procedure with an additional out parameter to
+	inform the caller that a message has been issued
+	* sem_aggr.adb: Minor modification of message
+	* sem_attr.adb (Analyze_Attribute): call Check_Formal_Restriction
+	instead of issuing an error message directly
+	* sem_ch3.adb (Analyze_Declarations): move here the check that basic
+	declarations are not placed after later declarations, by calling
+	Check_Later_Vs_Basic_Declarations
+	(Analyze_Subtype_Declaration): move here the check that an index or
+	discriminant constraint must be a subtype mark. Change the check that
+	a subtype of String must start at one so that it works on subtype marks.
+	* sem_ch4.adb (Analyze_Call): move here the check that a named
+	association cannot follow a positional one in a call
+	* sem_ch5.adb (Check_Unreachable_Code): call Check_Formal_Restriction
+	instead of issuing an error message directly
+	* sem_ch8.adb (Find_Selected_Component): move here the check that a
+	selector name is not a character literal or an operator symbol. Move
+	here the check that the prefix of an expanded name cannot be a
+	subprogram or a loop statement.
+	* sem_util.adb, sem_util.ads (Check_Later_Vs_Basic_Declarations): new
+	procedure called from parsing and semantics to check that basic
+	declarations are not placed after later declarations
+	(Process_End_Label): move here the check that end label is not missing
+
+2011-08-02  Arnaud Charlet  <charlet@adacore.com>
+
+	* sem_ch13.adb (Analyze_Enumeration_Representation_Clause): Ignore enum
+	representation clause in codepeer mode, since it confuses CodePeer and
+	does not bring useful info.
+
+2011-08-02  Ed Falis  <falis@adacore.com>
+
+	* init.c: initialize fp hw on MILS.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* errout.adb (First_Node): for bodies, return the node itself (small
+	optimization). For other nodes, do not check source_unit if the node
+	comes from Standard.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* exp_ch3.adb: Minor comment additions.
+	* sem_ch13.adb: Minor reformatting.
+
+2011-08-02  Pascal Obry  <obry@adacore.com>
+
+	* make.adb, makeutl.adb: Removes some superfluous directory separator.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_attr.adb: Minor reformatting.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* einfo.adb (Has_Default_Aspect): Replaces Has_Default_Value
+	(Has_Default_Component_Value): Removed
+	* einfo.ads Comment updates
+	(Has_Default_Aspect): Replaces Has_Default_Value
+	(Has_Default_Component_Value): Removed
+	* exp_ch13.adb
+	(Expand_N_Freeze_Entity): Handle Default[_Component]_Value aspects
+	* exp_ch3.adb
+	(Build_Array_Init_Proc): Handle Default_[Component_]Value aspects
+	(Get_Simple_Init_Val): Handle Default_Value aspect
+	(Needs_Simple_Initialization): Handle Default_Value aspect
+	* exp_ch3.ads: Needs_Simple_Initialization
+	* freeze.adb (Freeze_Entity): Handle Default_[Component_]Value aspect
+	* par-prag.adb (Pragma_Default[_Component]Value) Removed
+	* sem_ch13.adb
+	(Analyze_Aspect_Specifications): Fix Default[_Component]_Value aspects
+	* sem_prag.adb (Pragma_Default[_Component]Value) Removed
+	* snames.ads-tmpl (Pragma_Default[_Component]Value) Removed
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch5.adb (Analyze_Iterator_Specification): use base type to locate
+	package containing iteration primitives.
+	exp_ch5.adb (Expand_Iterator_Loop): ditto.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch5.adb (Analyze_Iteration_Scheme): For an Ada2012 iterator with
+	"of", pre-analyze expression in case it is a function call with
+	finalization actions that must be placed ahead of the loop.
+	* exp_ch5.adb (Expand_Iterator_Loop): If condition_actions are present
+	on an Ada2012 iterator, insert them ahead of the rewritten loop.
+
+2011-08-02  Geert Bosch  <bosch@adacore.com>
+
+	* cstand.adb (Create_Float_Types): Only consider C's long double for
+	Long_Long_Float, in addition to double.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch3.adb, sem_ch5.adb, sem_type.adb, switch-c.adb, switch-c.ads,
+	sem_prag.adb, sem_util.adb, sem_util.ads, sem_res.adb, warnsw.ads,
+	prepcomp.ads, cstand.adb, stand.ads, a-calfor.adb, s-stusta.adb:
+	Minor reformatting.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_attr.adb: handle properly 'Result when it is a prefix of an
+	indexed component.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* einfo.ads, einfo.adb
+	(Original_Access_Type): Move this attribute to Node26 since there was
+	an undocumented use of Node21 in E_Access_Subprogram_Type entities
+	which causes conflicts and breaks the generation of the .NET compiler.
+	(Interface_Name): Add missing documentation on JGNAT only uses of
+	this attribute.
+
+2011-08-02  Geert Bosch  <bosch@adacore.com>
+
+	* cstand.adb (Back_End_Float_Types): Use Elist instead of Nlist
+	(Find_Back_End_Float_Type): Likewise
+	(Create_Back_End_Float_Types): Likewise
+	(Create_Float_Types): Likewise
+	(Register_Float_Type): Likewise
+	* sem_ch3.adb (Floating_Point_Type_Declaration): Use Elist instead of
+	Nlist and split out type selection in new local Find_Base_Type function.
+	* sem_prag.adb (Process_Import_Predefined_Type): Use Elist instead of
+	Nlist
+	* stand.ads (Predefined_Float_Types): Use Elist instead of Nlist
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* inline.adb: Minor code reorganization (put Get_Code_Unit_Entity in
+	alpha order).
+	* opt.ads: Minor comment change.
+	* sem_ch12.adb: Minor code reorganization.
+
+2011-08-02  Gary Dismukes  <dismukes@adacore.com>
+
+	* sem_ch3.adb (Complete_Private_Subtype): Don't append the private
+	subtype's list of rep items to the list on the full subtype in the case
+	where the lists are the same.
+
+2011-08-02  Geert Bosch  <bosch@adacore.com>
+
+	* switch-c.adb (Free): New deallocation procedure to avoid implicitly
+	using the one from System.Strings, which also deallocates all strings.
+
+2011-08-02  Geert Bosch  <bosch@adacore.com>
+
+	* gcc-interface/gigi.h, gcc-interface/misc.c (enumerate_modes): New
+	function.
+	* gcc-interface/Make-lang.in: Update dependencies.
+
+2011-08-02  Olivier Hainque  <hainque@adacore.com>
+
+	* gcc-interface/trans.c (Subprogram_Body_to_gnu): Set the function
+	end_locus.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* sem_ch3.adb (Check_Anonymous_Access_Components): Create extra formals
+	associated with anonymous access to subprograms.
+
+2011-08-02  Geert Bosch  <bosch@adacore.com>
+
+	* opt.ads
+	(Preprocessing_Symbol_Defs): Move from Prepcomp.Symbol_Definitions.
+	(Preprocessing_Symbol_Last): Move from Prepcomp.Last_Definition.
+	* prepcomp.adb (Symbol_Definitions, Last_Definition): Move to opt.ads
+	(Add_Symbol_Definition): Move to switch-c.adb
+	(Process_Command_Line_Symbol_Definitions): Adjust references to above.
+	* prepcomp.ads: Remove dependency on Ada.Unchecked_Deallocation.
+	(Add_Symbol_Definition): Move to switch-c.adb.
+	* sem_ch13.adb, sem_prag.adb: Add dependency on Warnsw.
+	* sem_warn.adb
+	(Set_Dot_Warning_Switch, Set_GNAT_Mode_Warnings, Set_Warning_Switch):
+	Move to warnsw.adb.
+	* sem_warn.ads (Warn_On_Record_Holes, Warn_On_Overridden_Size,
+	Set_Dot_Warning_Switch, Set_GNAT_Mode_Warnings, Set_Warning_Switch):
+	Move to warnsw.adb.
+	* switch-c.adb: Replace dependency on Prepcomp and Sem_Warn by Warnsw.
+	(Add_Symbol_Definition): Moved from Prepcomp.
+	* switch-c.ads: Update copyright notice. Use String_List instead of
+	Argument_List, removing dependency on System.OS_Lib.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* sem_ch3.adb (Analyze_Object_Declaration): issue an error in formal
+	mode on initialization expression which does not respect SPARK
+	restrictions.
+	* sem_util.adb, sem_util.ads (Is_SPARK_Initialization_Expr): determines
+	if the tree referenced by its argument represents an initialization
+	expression in SPARK, suitable for initializing an object in an object
+	declaration.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* exp_ch9.adb (Expand_Access_Protected_Subprogram_Type): Link the
+	internally generated access to subprogram with its associated protected
+	subprogram type.
+	* einfo.ads, einfo.adb (Original_Access_Type): New attribute.
+
+2011-08-02  Geert Bosch  <bosch@adacore.com>
+
+	* cstand.adb (Register_Float_Type): Print information about type to
+	register, if the Debug_Flag_Dot_B is set.
+	* debug.adb (Debug_Flag_Dot_B): Document d.b debug option.
+	* rtsfind.ads (RE_Max_Base_Digits): New run time entity.
+	* sem_ch3.adb (Floating_Point_Type_Declaration): Allow declarations
+	with a requested precision of more than Max_Digits digits and no more
+	than Max_Base_Digits digits, if a range specification is present and the
+	Predefined_Float_Types list has a suitable type to derive from.
+	* sem_ch3.adb (Rep_Item_Too_Early): Avoid generating error in the
+	case of type completion with pragma Import
+	* sem_prag.adb
+	(Process_Import_Predefined_Type): Processing to complete a type
+	with pragma Import. Currently supports floating point types only.
+	(Set_Convention_From_Pragma): Do nothing without underlying type.
+	(Process_Convention): Guard against absence of underlying type,
+	which may happen when importing incomplete types.
+	(Process_Import_Or_Interface): Handle case of importing predefined
+	types. Tweak error message.
+
+2011-08-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* inline.adb (Add_Inlined_Body): Adjust check for library-level inlined
+	functions to previous change.  Reorganize code slightly.
+
+2011-08-02  Geert Bosch  <bosch@adacore.com>
+
+	* back_end.ads (Register_Type_Proc): New call back procedure type for
+	allowing the back end to provide information about available types.
+	(Register_Back_End_Types): New procedure to register back end types.
+	* back_end.adb (Register_Back_End_Types): Call the back end to enumerate
+	available types.
+	* cstand.adb (Back_End_Float_Types): New list for floating point types
+	supported by the back end.
+	(Build_Float_Type): Add extra parameter for Float_Rep_Kind.
+	(Copy_Float_Type): New procedure to make new copies of predefined types.
+	(Register_Float_Type): New call back procedure to populate the BEFT list
+	(Find_Back_End_Float_Type): New procedure to find a BEFT by name
+	(Create_Back_End_Float_Types): New procedure to populate the BEFT list.
+	(Create_Float_Types): New procedure to create entities for floating
+	point types predefined in Standard, and put these and any remaining
+	BEFTs on the Predefined_Float_Types list.
+	* stand.ads (Predefined_Float_Types): New list for predefined floating
+	point types that do not have declarations in package Standard.
+
+2011-08-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* inline.adb (Get_Code_Unit_Entity): New local function.  Returns the
+	entity node for the unit containing the parameter.
+	(Add_Inlined_Body): Use it to find the unit containing the subprogram.
+	(Add_Inlined_Subprogram): Likewise.
+	* gcc-interface/Make-lang.in: Update dependencies.
+
+2011-08-02  Thomas Quinot  <quinot@adacore.com>
+
+	* s-stusta.adb (Print): Make sure Pos is always initialized to a
+	suitable value.
+
+2011-08-02  Geert Bosch  <bosch@adacore.com>
+
+	* a-calfor.adb (Image): Simplify, removing unnecessary uses of 'Image.
+
+2011-08-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* sem_type.adb (Covers): Move trivial case to the top and reuse the
+	computed value of Base_Type.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* restrict.adb (Check_Restriction): issue an error for any use of
+	class-wide, even if the No_Dispatch restriction is not set.
+	* sem_aggr.adb: Correct typos in comments and messages in formal mode
+	* sem_ch3.adb (Process_Full_View): issue an error in formal mode is,
+	when completing a private extension, the type named in the private part
+	is not the same as that named in the visible part.
+	* sem_res.adb (Resolve_Call): issue an error in formal mode on the use
+	of an inherited primitive operations of a tagged type or type extension
+	that returns the tagged type.
+	* sem_util.adb, sem_util.ads (Is_Inherited_Operation_For_Type): new
+	function which returns True for an implicit operation inherited by the
+	derived type declaration for the argument type.
+	(Is_SPARK_Object_Reference): move to appropriate place in alphabetic
+	order.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch5.adb (Pre_Analyze_Range): new procedure extracted from
+	Process_Bounds, to perform analysis with expansion of a range or an
+	expression that is the iteration scheme for a loop.
+	(Analyze_Iterator_Specification): If domain of iteration is given by a
+	function call with a controlled result, as is the case if call returns
+	a predefined container, ensure that finalization actions are properly
+	generated.
+	* par-ch3.adb: accept Ada2012 iterator form in P_Discrete_Range.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* sem_ch5.adb (Analyze_Iteration_Scheme): Fix typo.
+	* gcc-interface/Make-lang.in: Update dependencies.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* sem_util.ads, sem_util.adb (Is_Variable): Add a new formal to
+	determine if the analysis is performed using N or Original_Node (N).
+	* exp_util.adb (Side_Effect_Free): Code cleanup since the new
+	functionality of routine Is_Variable avoids code duplication.
+	* checks.adb (Determine_Range): Handle temporaries generated by
+	Remove_Side_Effects.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* exp_ch4.adb (Expand_N_Quantified_Expression): Force reanalysis and
+	expansion of the condition. Required since the previous analysis was
+	done with expansion disabled (see Resolve_Quantified_Expression) and
+	hence checks were not inserted and record comparisons have not been
+	expanded.
+
+2011-08-02  Ed Falis  <falis@adacore.com>
+
+	* s-taprop-vxworks.adb, s-intman-vxworks.adb, s-intman-vxworks.ads:
+	Update header.
+
+2011-08-02  Bob Duff  <duff@adacore.com>
+
+	* opt.ads: Minor comment fix.
+
+2011-08-02  Bob Duff  <duff@adacore.com>
+
+	* sem_ch12.adb (Analyze_Package_Instantiation,
+	Analyze_Subprogram_Instantiation): Turn off style checking while
+	analyzing an instance. Whatever style checks that apply to the generic
+	unit should apply, so it makes no sense to apply them in an instance.
+	This was causing trouble when compiling an instance of a runtime
+	unit that violates the -gnatyO switch.
+	* stylesw.adb (Set_Style_Check_Options): "when 'O' =>" was missing from
+	one of the two case statements, causing spurious errors.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* uname.adb: Minor reformatting.
+	* gnatcmd.adb: Minor reformatting.
+	* exp_attr.adb: Minor reformatting.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* exp_ch5.adb (Expand_N_Assignment_Statement): under restriction
+	No_Dispatching_Calls, do not look for the Assign primitive, because
+	predefined primitives are not created in this case.
+
+2011-08-02  Bob Duff  <duff@adacore.com>
+
+	* stylesw.ads: Minor comment fixes.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* freeze.adb (Add_To_Result): New procedure.
+
+2011-08-02  Jose Ruiz  <ruiz@adacore.com>
+
+	* exp_attr.adb (Find_Stream_Subprogram): When using a configurable run
+	time, if the specific run-time routines for handling streams of strings
+	are not available, use the default mechanism.
+
+2011-08-02  Arnaud Charlet  <charlet@adacore.com>
+
+	* s-regpat.ads: Fix typo.
+
+2011-08-02  Vincent Celier  <celier@adacore.com>
+
+	* prj-conf.adb (Get_Or_Create_Configuration_File): If On_Load_Config is
+	not null, call it to create the in memory config project file without
+	parsing an existing default config project file.
+
+2011-08-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* atree.adb (Allocate_Initialize_Node): Remove useless temporaries.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_elim.adb: an abstract subprogram does not need an eliminate
+	pragma for its descendant to be eliminable.
+
+2011-08-02  Ed Falis  <falis@adacore.com>
+
+	* init.c: revert to handling before previous checkin for VxWorks
+	* s-intman-vxworks.adb: delete unnecessary declarations related to
+	using Ada interrupt facilities for handling signals.
+	Delete Initialize_Interrupts. Use __gnat_install_handler instead.
+	* s-intman-vxworks.ads: Import __gnat_install_handler as
+	Initialize_Interrupts.
+	* s-taprop-vxworks.adb: Delete Signal_Mask.
+	(Abort_Handler): change construction of mask to unblock exception
+	signals.
+
+2011-08-02  Jerome Guitton  <guitton@adacore.com>
+
+	* a-except-2005.adb (Raise_From_Signal_Handler): Call
+	Debug_Raise_Exception before propagation starts.
+
+2011-08-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* exp_ch6.adb (Expand_Call): Guard restriction checks with a call
+	to Restriction_Check_Required.
+	* sem_ch3.adb (Analyze_Object_Declaration): Likewise.
+	* sem_res.adb (Resolve_Call): Likewise.
+	* sem_attr.adb (Check_Stream_Attribute): Likewise.
+
+2011-08-02  Bob Duff  <duff@adacore.com>
+
+	* stylesw.ads: Update comment.
+	* style.adb: Minor: Use Error_Msg_NE instead of Error_Msg_N.
+	* errout.ads: Remove obsolete comment.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* einfo.ads, einfo.adb (Is_Safe_To_Reevaluate): new function.
+	(Set_Is_Safe_To_Reevaluate): new procedure.
+	* sem_ch5.adb (Analyze_Assignment): Add one assertion to ensure that no
+	assignment is allowed on safe-to-reevaluate variables.
+	(Analyze_Iteration_Schine.Process_Bounds.One_Bound): Decorate the
+	temporary created to remove side effects in expressions that use
+	the secondary stack as safe-to-reevaluate.
+	* exp_util.adb (Side_Effect_Free): Add missing code to handle well
+	variables that are not true constants.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch5.adb, sem_ch7.adb, einfo.ads, sem_util.adb, sem_util.ads,
+	sem_res.adb, sem_ch6.adb: Minor reformatting.
+
+2011-08-02  Jerome Guitton  <guitton@adacore.com>
+
+	* a-except-2005.adb (Raise_Current_Excep): Remove obsolete dead code.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch6.adb (New_Overloaded_Entity, Check_Overriding_Indicator): Do
+	not set Overridden_Operation if subprogram is an initialization
+	procedure.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* par-ch6.adb: Correct obsolete name in comments
+	* restrict.adb, restrict.ads (Check_Formal_Restriction): new function
+	which takes two message arguments (existing function takes one), with
+	second message used for continuation.
+	* sem_ch5.adb (Analyze_Block_Statement): in formal mode, only reject
+	block statements that originate from a source block statement, not
+	generated block statements
+	* sem_ch6.adb (Analyze_Function_Call): rename L into Actuals, for
+	symmetry with procedure case
+	* sem_ch7.adb (Check_One_Tagged_Type_Or_Extension_At_Most): new
+	function to issue an error in formal mode if a package specification
+	contains more than one tagged type or type extension.
+	* sem_res.adb (Resolve_Actuals): in formal mode, check that actual
+	parameters matching formals of tagged types are objects (or ancestor
+	type conversions of objects), not general expressions. Issue an error
+	on view conversions that are not involving ancestor conversion of an
+	extended type.
+	(Resolve_Type_Conversion): in formal mode, issue an error on the
+	operand of an ancestor type conversion which is not an object
+	* sem_util.adb, sem_util.ads (Find_Actual): extend the behavior of the
+	procedure so that it works also for actuals of function calls
+	(Is_Actual_Tagged_Parameter): new function which determines if its
+	argument is an actual parameter of a formal of tagged type in a
+	subprogram call
+	(Is_SPARK_Object_Reference): new function which determines if the tree
+	referenced by its argument represents an object in SPARK
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch3.adb: Minor reformatting
+	Minor comment addition
+	Minor error msg text change
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* sem_ch5.adb (Analyze_Iteration_Scheme.Uses_Secondary_Stack): New
+	function. Used to be more precise when we generate a variable plus one
+	assignment to remove side effects in the evaluation of the Bound
+	expressions.
+	(Analyze_Iteration_Scheme): Clean attribute analyzed in all the nodes
+	of the bound expression to force its re-analysis and thus expand the
+	associated transient scope (if required). Code cleanup replacing the
+	previous code that declared the constant entity by an invocation to
+	routine Force_Evaluation which centralizes this work in the frontend.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* einfo.adb (Is_Base_Type): Improve efficiency by using a flag table
+	(Base_Type): Now uses improved Is_Base_Type function
+	* einfo.ads (Base_Type): Inline this function
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_prag.adb (Analyze_Pragma): Defend against infinite recursion
+	(Analyze_Aspect_Specifications): Fix Sloc values for constructed pragmas
+
+2011-08-02  Arnaud Charlet  <charlet@adacore.com>
+
+	* gcc-interface/Make-lang.in: Update dependencies.
+	* gcc-interface/Makefile.in: Use s-inmapop-vxworks.adb for all VxWorks
+	targets.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* par-ch3.adb (P_Delta_Constraint): issue an error in formal mode on
+	non-simple expression used in delta constraint
+	(P_Index_Or_Discriminant_Constraint): issue an error in formal mode on
+	index constraint which is not a subtype mark
+	* par.adb: With and use Restrict
+	* sem_ch3.adb (Analyze_Component_Declaration): issue an error in formal
+	mode on component type which is not a subtype mark and default
+	expression on component
+	(Analyze_Subtype_Declaration): issue an error in formal mode on subtype
+	of string which does not have a lower index bound equal to 1
+	(Array_Type_Declaration): issue an error in formal mode on index or
+	component type which is not a subtype mark, and on aliased keyword on
+	component
+	(Derived_Type_Declaration): issue an error in formal mode on interface,
+	limited or abstract type
+	(Record_Type_Declaration): issue an error in formal mode on interface
+	(Record_Type_Definition): issue an error in formal mode on tagged types
+	and type extensions not declared in the specification of a library unit
+	package; on null non-tagged record; on variant part
+
+2011-08-02  Vincent Celier  <celier@adacore.com>
+
+	* prj-nmsc.adb (Check_Library_Attributes): Do not report Library_Dir
+	not declared for qualified library project when Library_Name is not
+	declared, but Library_Dir is.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch13.adb (Analyze_Aspect_Specification): Fix slocs on generated
+	pragmas (affects aspects [Component_]Default_Value
+	(Check_Aspect_At_Freeze_Point): For Component_Default_Value, use
+	component type for the resolution
+
+2011-08-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* einfo.adb (Base_Type): Tune implementation for speed.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* freeze.adb: Minor reformatting.
+
+2011-08-02  Thomas Quinot  <quinot@adacore.com>
+
+	* scos.ads: Update comments.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch3.adb (Build_Derived_Type): Inherit the convention from the
+	base type, because the parent may be a subtype of a private type whose
+	convention is established in a private part.
+
+2011-08-02  Hristian Kirtchev  <kirtchev@adacore.com>
+
+	* exp_ch6.adb (Expand_N_Extended_Return_Statement): Wrap the return
+	statement in a block when the expansion of the return expression has
+	created a finalization chain.
+	* freeze.adb (Freeze_Expression): Alphabetize all choices associated
+	with the parent node.
+	Add N_Extended_Return_Statement to handle the case where a transient
+	object declaration appears in the Return_Object_Declarations list of
+	an extended return statement.
+
+2011-08-02  Matthew Gingell  <gingell@adacore.com>
+
+	* adaint.c (__gnat_is_symbolic_link_attr): Supress warning on possibly
+	unused parameter 'name'.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_elim.adb (Set_Eliminated): If the overridden operation is an
+	inherited operation, check whether its alias, which is the source
+	operastion that it renames, has been marked eliminated.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* exp_util.adb (Safe_Prefixed_Reference): Do not consider safe an
+	in-mode parameter whose type is an access type since it can be used to
+	modify its designated object. Enforce code that handles as safe an
+	access type that is not access-to-constant but it is the result of a
+	previous removal of side-effects.
+	(Remove_Side_Effects): Minor code reorganization of cases which require
+	no action. Done to incorporate documentation on new cases uncovered
+	working in this ticket: no action needed if this routine was invoked
+	too early and the nodes are not yet decorated.
+	* sem_res.adb (Resolve_Slice): Minor code cleanup replacling two calls
+	to routine Remove_Side_Effects by calls to Force_Evaluation since they
+	were issued with actuals that are implicitly provided by
+	Force_Evaluation.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch3.adb, sem_res.adb: Minor reformatting.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* sem_attr.adb (Check_Formal_Restriction_On_Attribute): new procedure
+	to issue an error in formal mode on attribute not supported in this mode
+	(Analyze_Attribute): issue errors on standard attributes not supported
+	in formal mode.
+	* sem_ch3.adb (Modular_Type_Declaration): remove obsolete part of
+	comment, and issue error in formal mode on modulus which is not a power
+	of 2.
+	(Process_Range_Expr_In_Decl): issue error in formal mode on non-static
+	range.
+	* sem_ch8.adb (Find_Type): issue error in formal mode on 'Base in
+	subtype mark.
+	* sem_res.adb (Resolve_Unary_Op): issue error in formal mode on unary
+	operator on modular type (except 'not').
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* gnat_rm.texi: Minor reformatting.
+
+2011-08-02  Arnaud Charlet  <charlet@adacore.com>
+
+	* s-osinte-linux.ads: Minor comment update and reformatting.
+	* i-cexten.ads: Make this unit pure, as for its parent.
+	Will allow its usage in more contexts if needed.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* s-utf_32.ads: Minor comment fix.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_res.adb (Resolve_Actuals): if the subprogram is a primitive
+	operation of a tagged synchronized type, handle the case where the
+	controlling argument is overloaded.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* gnat_rm.texi, opt.ads, sem_prag.adb, snames.ads-tmpl:
+	Replace pragma SPARK_95 with pragma Restrictions (SPARK)
+	* par-prag.adb (Process_Restrictions_Or_Restriction_Warnings): set
+	SPARK mode and formal verification mode on processing SPARK restriction
+	* s-rident.ads (Restriction_Id): add SPARK restriction in those not
+	requiring consistency checking.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_res.adb: Minor reformatting.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* a-cfdlli.ads, a-cfhase.ads, a-cforma.ads, a-cfhama.ads,
+	a-cforse.ads: Remove unneeded with of Ada.Containers
+	Remove commented out pragma Inline's
+	Move specifications of new subprograms to the actual specs
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* a-cfdlli.ads, a-cfhase.ads, a-cforma.ads, a-cfhama.ads,
+	a-cforse.ads: Update comments.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_attr.adb: add attribute name when 'Result has the wrong prefix.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* a-cfdlli.ads, a-cfhase.ads, a-cforma.ads, a-cfhama.ads,
+	a-cforse.ads, a-cofove.ads: Minor reformatting.
+
+2011-08-02  Claire Dross  <dross@adacore.com>
+
+	* a-cfdlli.ads, a-cfhase.ads, a-cforma.ads, a-cfhama.ads, a-cforse.ads,
+	a-cofove.ads: Add comments.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* gnat_rm.texi: Document formal containers.
+
+2011-08-02  Emmanuel Briot  <briot@adacore.com>
+
+	* g-comlin.adb (Goto_Section, Getopt): fix handling of "*" when there
+	are empty sections.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* mlib-prj.adb, restrict.ads, sem_aggr.adb, sem_ch12.adb: Minor
+	reformatting.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* aspects.adb: New aspects Default_Value and Default_Component_Value
+	New format of Aspect_Names table checks for omitted entries
+	* aspects.ads: Remove mention of Aspect_Cancel and add documentation on
+	handling of boolean aspects for derived types.
+	New aspects Default_Value and Default_Component_Value
+	New format of Aspect_Names table checks for omitted entries
+	* einfo.ads, einfo.adb (Has_Default_Component_Value): New flag
+	(Has_Default_Value): New flag
+	(Has_Default_Component_Value): New flag
+	(Has_Default_Value): New flag
+	* par-ch13.adb (P_Aspect_Specifications): New format of Aspect_Names
+	table.
+	* par-prag.adb: New pragmas Default_Value and Default_Component_Value
+	* sem_ch13.adb (Analyze_Aspect_Specifications): New aspects
+	Default_Value and Default_Component_Value
+	* sem_prag.adb: New pragmas Default_Value and Default_Component_Value
+	New aspects Default_Value and Default_Component_Value
+	* snames.ads-tmpl: New pragmas Default_Value and Default_Component_Value
+	* sprint.adb: Print N_Aspect_Specification node when called from gdb
+
+2011-08-02  Vincent Celier  <celier@adacore.com>
+
+	* prj-nmsc.adb (Check_Library_Attributes): For virtual library project,
+	inherit library kind.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_res.adb: Add guards in calls to Matching_Static_Array_Bounds.
+	Minor reformatting.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* i-cstrin.ads: Updates to make Interfaces.C.Strings match RM
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* sem_aggr.adb (Resolve_Aggregate): Fix thinko.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* impunit.adb: Add comment.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* sem_aggr.adb (Check_Qualified_Aggregate): new procedure which checks
+	qualification of aggregates in formal mode
+	(Is_Top_Level_Aggregate): returns True for an aggregate not contained in
+	another aggregate
+	(Resolve_Aggregate): complete the test that an aggregate is adequately
+	qualified in formal mode
+
+2011-08-02  Pascal Obry  <obry@adacore.com>
+
+	* make.adb, bindgen.adb, gnatbind.adb: Minor reformatting.
+	* mlib-prj.adb: Supress warning when compiling binder generated file.
+	(Build_Library): Supress all warnings when compiling the binder
+	generated file.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* errout.adb, errout.ads (Check_Formal_Restriction): move procedure
+	from here...
+	* restrict.adb, restrict.ads (Check_Formal_Restriction): ...to here
+	* sem_aggr.adb, sem_ch5.adb, sem_util.adb:
+	Add with/use clauses to make Check_Formal_Restriction visible
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch12.adb (Check_Generic_Actuals): handle properly actual
+	in-parameters when type of the generic formal is private in the generic
+	spec and non-private in the body.
+
+2011-08-02  Claire Dross  <dross@adacore.com>
+
+	* a-cfdlli.adb, a-cfdlli.ads, a-cfhase.adb, a-cfhase.ads, a-cfhama.adb,
+	a-cfhama.ads, a-cforse.adb, a-cforse.ads, a-cforma.adb, a-cforma.ads,
+	a-cofove.adb, a-cofove.ads: New files implementing formal containers.
+	* impunit.adb, Makefile.rtl: Take new files into account.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_aggr.adb, sem_ch3.adb, sem_ch5.adb, make.adb, sem_res.adb,
+	sem_attr.adb, sem_ch6.adb, sem_ch8.adb: Minor reformatting.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* sem_aggr.adb (Resolve_Aggregate): disable incorrectly placed check in
+	formal mode
+	* sem_util.adb (Matching_Static_Array_Bounds): proper detection of
+	matching static array bounds, taking into account the special case of
+	string literals
+	* sem_ch3.adb: Typo in comment.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* errout.adb, errout.ads (Check_Formal_Restriction): new procedure
+	which issues an error in formal mode if its argument node is originally
+	from source
+	* sem_ch3.adb (Analyze_Full_Type_Declaration): move test that a type
+	has a discriminant specification so that it does not include the case
+	of derived types
+	(Derived_Type_Declaration): move here the test that a derived type has a
+	discriminant specification
+	* sem_aggr.adb (Resolve_Record_Aggregate): test the presence of the
+	first element of a component association before accessing its choices
+	(presence of component association is not enough)
+	* exp_ch6.adb (Expand_N_Subprogram_Declaration): test if a subprogram
+	declaration is a library item before accessing the next element in a
+	list, as library items are not member of lists
+	* sem_attr.adb, sem_ch11.adb, sem_ch4.adb, sem_ch5.adb, sem_ch6.adb,
+	sem_ch8.adb, sem_ch9.adb, sem_res.adb, sem_util.adb: use
+	Check_Formal_Restriction whenever possible.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch3.adb (Find_Type_Of_Object): In ASIS mode, create an itype
+	reference when needed.
+
+2011-08-02  Bob Duff  <duff@adacore.com>
+
+	* gnat_ugn.texi: Fix typo.
+
+2011-08-02  Vincent Celier  <celier@adacore.com>
+
+	* make.adb (Gnatmake): Use MLib.Tgt.Archive_Ext as the extension of
+	archive file name. Do not use the full path name of archives for Open
+	VMS.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch12.adb, sem_ch11.adb: New calling sequence for
+	Analyze_Aspect_Specifications
+	* sem_ch13.adb
+	(Analyze_Aspect_Specifications): New handling for boolean aspects
+	* sem_ch13.ads (Analyze_Aspect_Specifications): New calling sequence
+	* sem_ch3.adb, sem_ch6.adb, sem_ch7.adb, sem_ch9.adb: New calling
+	sequence for Analyze_Aspect_Specifications
+	* sem_prag.adb (Analyze_Pragma): Remove use of Aspect_Cancel entirely
+	* sinfo.ads, sinfo.adb (Aspect_Cancel): Remove, no longer used
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* freeze.adb (Freeze_Entity): Remove handling of delayed boolean
+	aspects, since these no longer exist.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* par-ch13.adb (Aspect_Specifications_Present): Always return false on
+	semicolon, do not try to see if there are aspects following it.
+	* par-ch3.adb (P_Declarative_Items): Better message for unexpected
+	aspect spec.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch8.adb, aspects.ads: Minor reformatting.
+
+2011-08-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* sem_ch13.ads (Analyze_Aspect_Specification): Add pragma Inline.
+	* sem_ch13.adb (Analyze_Non_Null_Aspect_Specifications): New procedure
+	extracted from...
+	(Analyze_Aspect_Specifications): ...here.  Call above procedure.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* exp_ch6.adb (Expand_N_Subprogram_Declaration): issue error in formal
+	mode on subprogram declaration outside of package specification, unless
+	it is followed by a pragma Import
+	* sem_ch3.adb (Access_Definition, Access_Subprogram_Declaration,
+	Access_Type_Declaration): issue error in formal mode on access type
+	(Analyze_Incomplete_Type_Decl): issue error in formal mode on
+	incomplete type
+	(Analyze_Object_Declaration): issue error in formal mode on object
+	declaration which does not respect SPARK restrictions
+	(Analyze_Subtype_Declaration): issue error in formal mode on subtype
+	declaration which does not respect SPARK restrictions
+	(Constrain_Decimal, Constrain_Float, Constrain_Ordinary_Fixed): issue
+	error in formal mode on digits or delta constraint
+	(Decimal_Fixed_Point_Type_Declaration): issue error in formal mode on
+	decimal fixed point type
+	(Derived_Type_Declaration): issue error in formal mode on derived type
+	other than type extensions of tagged record types
+	* sem_ch6.adb (Process_Formals): remove check in formal mode, redundant
+	with check on access definition
+	* sem_ch9.adb (Analyze_Protected_Definition): issue error in formal
+	mode on protected definition.
+	(Analyze_Task_Definition): issue error in formal mode on task definition
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* make.adb, sem_ch8.adb, s-inmaop-vxworks.adb: Minor reformatting.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* sem_ch6.adb (Can_Override_Operator): New function.
+	(Verify_Overriding_Indicator): Add missing code to check overriding
+	indicator in operators. Fixes regression.
+	(Check_Overriding_Indicator): Minor reformating after replacing the
+	code that evaluates if the subprogram can override an operator by
+	invocations to the above new function.
+	* einfo.adb
+	(Write_Field26_Name): Add missing code to ensure that, following
+	the documentation in einfo.ads, this field is not shown as attribute
+	"Static_Initialization" on non-dispatching functions.
+
+2011-08-02  Jose Ruiz  <ruiz@adacore.com>
+
+	* sem_res.adb (Resolve_Call): A call to
+	Ada.Real_Time.Timing_Events.Set_Handler violates restriction
+	No_Relative_Delay (AI-0211) only when it sets a relative timing event,
+	i.e., when the second parameter is of type Time_Span.
+
+2011-08-02  Vincent Celier  <celier@adacore.com>
+
+	* make.adb (Gnatmake): use <library dir>/lib<library name>.a to link
+	with an archive instead of -L<library dir> -l<library name>.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch8.adb (Analyze_Use_Type): If the clause is being re-analyzed,
+	mark the base types In_Use in addition to making the operations
+	use_visible.
+
+2011-08-02  Ed Falis  <falis@adacore.com>
+
+	* init.c: add and setup __gnat_signal_mask for the exception signals
+	* s-inmaop-vxworks.adb: new file.
+	* s-intman-vxworks.adb: remove unnecessary initializations and
+	simplify remaining
+	* s-intman-vxworks.ads: remove unnecessary variable
+	* s-taprop-vxworks.adb: simplify signal initialization
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch8.adb: Minor code reorganization, comment updates.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* sem_res.adb (Matching_Static_Array_Bounds): Moved to Sem_Util
+	* sem_util.ads, sem_util.adb (Matching_Static_Array_Bounds): Moved
+	here from Sem_Res.
+	(Matching_Static_Array_Bounds): Use Is_Ok_Static_Expression
+	(Matching_Static_Array_Bounds): Moved here from Sem_Res
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* atree.h, atree.ads, atree.adb: New subprograms to manipulate Elist5.
+	* par_ch8.adb (P_Use_Type): initialize Used_Operations for node.
+	* sinfo.ads, sinfo.adb (Used_Operations): new attribute of
+	use_type_clauses, to handle more efficiently use_type and use_all_type
+	constructs.
+	* sem_ch8.adb: Rewrite Use_One_Type and End_Use_Type to handle the
+	Ada2012 Use_All_Type clause.
+	(Use_Class_Wide_Operations): new procedure.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* exp_util.adb, par-ch10.adb, par-ch6.adb, sem.adb, sem_ch6.adb,
+	sem_ch6.ads, sinfo.adb, sinfo.ads, sprint.adb: Change parameterized
+	expression to expression function.
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch4.adb: transform simple Ada2012 membership into equality only
+	if types are compatible.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* sem_res.adb (Matching_Static_Array_Bounds): new function which
+	returns True if its argument array types have same dimension and same
+	static bounds at each index.
+	(Resolve_Actuals): issue an error in formal mode on actuals passed as
+	OUT or IN OUT paramaters which are not view conversions in SPARK.
+	(Resolve_Arithmetic_Op): issue an error in formal mode on
+	multiplication or division with operands of fixed point types which are
+	not qualified or explicitly converted.
+	(Resolve_Comparison_Op): issue an error in formal mode on comparisons of
+	Boolean or array type (except String) operands.
+	(Resolve_Equality_Op): issue an error in formal mode on equality
+	operators for array types other than String with non-matching static
+	bounds.
+	(Resolve_Logical_Op): issue an error in formal mode on logical operators
+	for array types with non-matching static bounds. Factorize the code in
+	Matching_Static_Array_Bounds.
+	(Resolve_Qualified_Expression): issue an error in formal mode on
+	qualified expressions for array types with non-matching static bounds.
+	(Resolve_Type_Conversion): issue an error in formal mode on type
+	conversion for array types with non-matching static bounds
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* par-ch10.adb: Minor code reorganization (use Nkind_In).
+
+2011-08-02  Ed Schonberg  <schonberg@adacore.com>
+
+	* par-ch9.adb: save location of entry for proper error message.
+
+2011-08-02  Javier Miranda  <miranda@adacore.com>
+
+	* sem_type.ads, sem_type.adb (Is_Ancestor): Addition of a new formal
+	(Use_Full_View) which permits this routine to climb through the
+	ancestors using the full-view of private parents.
+	* sem_util.adb (Collect_Interfaces_Info, Implements_Interface): Set
+	Use_Full_View to true in calls to Is_Ancestor.
+	* sem_disp.adb (Override_Dispatching_Operation): Set Use_Full_View to
+	true in call to Is_Ancestor.
+	* exp_ch3.adb (Build_Offset_To_Top_Functions, Initialize_Tag): Set
+	Use_Full_View to true in call to Is_Ancestor.
+	* exp_ch7.adb (Controller_Component): Set Use_Full_View to true in
+	call to Is_Ancestor.
+	* exp_ch4.adb (Expand_N_Type_Conversion, Tagged_Membership): Set
+	Use_Full_View to true in calls to Is_Ancestor.
+	* exp_disp.adb (Expand_Interface_Actuals, Make_Secondary_DT, Make_DT,
+	Make_Select_Specific_Data_Table, Register_Primitive,
+	Set_All_DT_Position): Set Use_Full_View to true in calls to Is_Ancestor.
+	* exp_intr.adb (Expand_Dispatching_Constructor_Call): Set Use_Full_View
+	to true in call to Is_Ancestor.
+	* exp_util.adb (Find_Interface_ADT, Find_Interface_Tag): Set
+	Use_Full_View to true in calls to Is_Ancestor.
+	* exp_cg.adb
+	(Write_Call_Info): Set Use_Full_View to true in call to Is_Ancestor.
+	(Write_Type_Info): Set Use_Full_View to true in call to Is_Ancestor.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* gnat_rm.texi: Minor reformatting.
+	* sem_prag.adb: Minor reformatting.
+
+2011-08-02  Tristan Gingold  <gingold@adacore.com>
+
+	* vms_data.ads: Add VMS qualifier for -gnateP.
+
+2011-08-02  Robert Dewar  <dewar@adacore.com>
+
+	* par-ch13.adb (P_Aspect_Specification): New meaning of Decl = Empty
+	* par-ch7.adb (P_Package): Proper placement of aspects for package
+	decl/instantiation.
+	* par-endh.adb (Check_End): Ad Is_Sloc parameter
+	(End_Statements): Add Is_Sloc parameterr
+	* par.adb (P_Aspect_Specification): New meaning of Decl = Empty
+	(Check_End): Ad Is_Sloc parameter
+	(End_Statements): Add Is_Sloc parameterr
+
+2011-08-02  Vincent Celier  <celier@adacore.com>
+
+	* ug_words: Add VMS qualifier equivalent to -gnateP:
+	/SYMBOL_PREPROCESSING.
+
+2011-08-02  Jose Ruiz  <ruiz@adacore.com>
+
+	* gnat-style.texi: For hexadecimal numeric literals the typical
+	grouping of digits is 4 to represent 2 bytes.
+	A procedure spec which is split into several lines is indented two
+	characters.
+
+2011-08-02  Yannick Moy  <moy@adacore.com>
+
+	* exp_aggr.adb (Is_Others_Aggregate): move function to other unit.
+	* sem_aggr.adb, sem_aggr.ads (Is_Others_Aggregate): move function here
+	(Resolve_Aggregate): issue errors in formal modes when aggregate is not
+	properly qualified
+	(Resolve_Array_Aggregate): issue errors in formal modes on non-static
+	choice in array aggregate
+	(Resolve_Extension_Aggregate): issue errors in formal modes on subtype
+	mark as ancestor
+	(Resolve_Record_Aggregate): issue errors in formal modes on mixed
+	positional and named aggregate for record, or others in record
+	aggregate, or multiple choice in record aggregate
+	* sem_res.adb (Resolve_Logical_Op): issue errors in formal mode when
+	array operands to logical operations AND, OR and XOR do not have the
+	same static lower and higher bounds
+	* sem_ch5.adb, sinfo.ads: Correct typos in comments
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* sem_util.ads, sem_util.adb, sem_ch6.adb (Last_Source_Statement):
+	Replaces Last_Source_Node_In_Sequence.
+	* err_vars.ads (Error_Msg_Lang): 16 is OK, don't need 4K
+	* errout.adb (Set_Error_Msg_Lang): Takes arg with no parens, but stores
+	parens and blank in string (this was inconsistently implemented).
+	* errout.ads
+	(Set_Error_Msg_Lang): Takes arg with no parens, but stores parens and
+	blank in string (this was inconsistently implemented).
+	* gnat1drv.adb
+	(Set_Global_Switches): Set formal mode switches appropriately
+	* opt.ads, opt.adb: Formal mode is now global switches, more consistent
+	* par-prag.adb
+	(Analyze_Pragma, case SPARK_95): Set opt switches appropriately and
+	call Set_Error_Msg_Lang to set "spark" as language name.
+	* par.adb: Remove unnecessary call to set formal language for errout
+	* sem_prag.adb (P_Pragma, case SPARK_95): Set opt switches
+	appropriately and call Set_Error_Msg_Lang to set "spark" as language
+	name.
+	* sem_ch4.adb (Analyze_Concatenation_Operand): remove procedure and
+	calls to it, moved after resolution so that types are known
+	* sem_res.adb (Resolve_Op_Concat): issue an error in formal mode if
+	result of concatenation is not of type String
+	(Resolve_Op_Concat_Arg): issue an error in formal mode if an operand of
+	concatenation is not properly restricted
+	* gnat_rm.texi: Add doc on pragma Spark_95.
+	* gcc-interface/Makefile.in: Remove obsolete target pairs for
+	Interfaces.C.* on VMS. Remove s-parame-vms-restrict.ads.
+	* gcc-interface/Make-lang.in: Update dependencies.
+
+2011-08-01  Javier Miranda  <miranda@adacore.com>
+
+	* sem_disp.adb (Override_Dispatching_Operation): Enforce strictness of
+	condition that detects if the overridden operation must replace an
+	existing entity.
+
+2011-08-01  Javier Miranda  <miranda@adacore.com>
+
+	* exp_ch4.adb (Expand_N_Case_Expression): Propagate to the expanded
+	code declarations inserted by Insert_Actions in each alternative of the
+	N_Case_Expression node.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch6.adb: Minor code reorganization.
+	* sem_util.adb: Minor reformatting.
+
+2011-08-01  Pascal Obry  <obry@adacore.com>
+
+	* prj-env.adb: Remove <prefix>/lib/gpr/<target> project search path.
+	* gnat_ugn.texi: Add documentation for VERSIONINFO Windows resource.
+
+2011-08-01  Yannick Moy  <moy@adacore.com>
+
+	* par-ch4.adb (P_Name): issue a syntax error in SPARK mode on character
+	literal or operator symbol which is prefixed
+	* sem_attr.adb (Analyze_Access_Attribute): issue an error in formal
+	mode on access attributes.
+	* sem_ch4.adb (Analyze_Concatenation_Operand): new procedure to check
+	that concatenation operands are properly restricted in formal mode
+	(Analyze_Concatenation, Analyze_Concatenation_Rest): call new procedure
+	Analyze_Concatenation_Operand. Issue an error in formal mode if the
+	result of the concatenation has a type different from String.
+	(Analyze_Conditional_Expression, Analyze_Explicit_Dereference,
+	Analyze_Quantified_Expression, Analyze_Slice,
+	Analyze_Null): issue an error in formal mode on unsupported constructs
+	* sem_ch5.adb
+	(Analyze_Block_Statement): only issue error on source block statement
+	* sem_util.ads, sem_util.adb (Last_Source_Node_In_Sequence): new
+	function which returns the last node in a list of nodes for which
+	Comes_From_Source returns True, if any
+	* sem_ch6.adb (Check_Missing_Return): minor refactoring to use
+	Last_Source_Node_In_Sequence
+	* sem_ch8.adb (Analyze_Exception_Renaming, Analyze_Generic_Renaming,
+	Analyze_Object_Renaming, Analyze_Use_Package): issue an error in formal
+	mode on unsupported constructs
+	* sem_ch9.adb Do not return after issuing error in formal mode, as the
+	rest of the actions may be needed later on since the error is marked as
+	not serious.
+	* sinfo.ads: Typos in comments.
+
+2011-08-01  Pascal Obry  <obry@adacore.com>
+
+	* projects.texi: Minor editing.
+
+2011-08-01  Yannick Moy  <moy@adacore.com>
+
+	* err_vars.ads (Error_Msg_Lang, Error_Msg_Langlen): new variables for
+	insertion character ~~
+	* errout.ads, errout.adb (Formal_Error_Msg_...): remove procedures
+	(Set_Error_Msg_Lang): new procedure which fixes the language for use
+	with insertion character ~~
+	(Set_Msg_Text): treat insertion character ~~
+	* par-ch4.adb, par-ch5.adb, par-endh.adb, sem_attr.adb, sem_ch11.adb,
+	sem_ch3.adb, sem_ch5.adb, sem_ch9.adb, sem_util.adb: Replace calls to
+	Formal_Error_Msg_... procedures by equivalent Error_Msg_...
+	procedures. Favor calls to Error_Msg_F(E) over Error_Msg_N(E). Make
+	errors related to the formal language restriction not serious
+	(insertion character |).
+	* par.adb (Par): set formal language for error messages if needed
+	* sem_ch6.adb (Check_Missing_Return): take into account possible
+	generated statements at the end of the function
+	* snames.ads-tmpl (Name_SPARK_95, Pragma_SPARK_95): new variable and
+	enumeration value to define a new pragma SPARK_95
+	* opt.ads, opt.adb (SPARK_Version_Type, SPARK_Version_Default,
+	SPARK_Version): new type and variables to store the SPARK version
+	(none by default).
+	(SPARK_Mode): return True when SPARK_Version is set
+	* par-prag.adb: Correct indentation
+	(Prag): take Pragma_SPARK_95 into account
+	* sem_prag.adb (Set_Mechanism_Value, Sig_Flags): take Pragma_SPARK_95
+	into account.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* sem_ch3.adb, sem_ch3.ads, sem_ch5.adb, prj-part.adb, par-ch4.adb,
+	sem_util.adb, sem_ch4.adb, sem_ch6.adb, sem_ch6.ads, sem_ch8.adb,
+	sem_ch8.ads, sem_ch13.ads, par-ch5.adb, prj-env.ads: Minor reformatting
+
+2011-08-01  Pascal Obry  <obry@adacore.com>
+
+	* prj-part.ads, prj-part.adb (Parse): Add Target_Name parameter. Pass
+	Target_Name to Get_Path call.
+	(Parse_Single_Project): Likewise.
+	(Post_Parse_Context_Clause): Likewise.
+	* prj-env.ads, prj-env.adb (Find_Project): Add Target_Name parameter.
+	Call Initialise_Project_Path with the proper Target_Name.
+	(Initialize_Project_Path): Add <gnat_root>/<target_name>/lib/gnat
+	search path.
+	(Get_Path): Add Target_Name parameter. Call Initialise_Project_Path
+	with the proper Target_Name.
+	* prj-conf.adb (Get_Or_Create_Configuration_File): Pass Target_Name to
+	Part.Parse routine.
+	(Parse_Project_And_Apply_Config): Likewise.
+	* prj-makr.adb (Initialize): Pass empty Target_Name to Parse routine.
+	This is fine as this part of the code is supporting only native
+	compilation.
+	* prj-pars.adb (Parse): Pass empty Target_Name to Parse routine. This
+	is fine as this part of the code is supporting only native compilation.
+
+2011-08-01  Yannick Moy  <moy@adacore.com>
+
+	* sem_util.adb (Enter_Name): issue error in formal mode on declaration
+	of homonym, unless the homonym is one of the cases allowed in SPARK
+	* par-ch5.adb (Parse_Decls_Begin_End): issue error in SPARK mode for
+	package declaration occurring after a body.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* checks.adb, exp_ch4.adb: Minor reformatting.
+
+2011-08-01  Javier Miranda  <miranda@adacore.com>
+
+	* einfo.ads (Access_Disp_Table): Fix documentation.
+	(Dispatch_Table_Wrappers): Fix documentation.
+
+2011-08-01  Pascal Obry  <obry@adacore.com>
+
+	* prj-env.adb, prj-env.ads: Minor reformatting.
+
+2011-08-01  Yannick Moy  <moy@adacore.com>
+
+	* sem_util.ads, sem_util.adb, par.adb, par_util.adb
+	(Formal_Error_Msg, Formal_Error_Msg_N, Formal_Error_Msg_SP): move
+	procedures out of these packages.
+	* errout.ads, errout.adb 
+	(Formal_Error_Msg, Formal_Error_Msg_N, Formal_Error_Msg_SP): move
+	procedures in of this package
+	(Formal_Error_Msg_NE): new procedure for wrapper on Error_Msg_NE
+	* par-ch5.adb (Parse_Decls_Begin_End): issue syntax error in SPARK mode
+	on misplaced later vs initial declarations, like in Ada 83
+	* sem_attr.adb (Processing for Analyze_Attribute): issue error in
+	formal mode on attribute of private type whose full type declaration
+	is not visible
+	* sem_ch3.adb (Analyze_Declarations): issue error in formal mode on a
+	package declaration inside a package specification
+	(Analyze_Full_Type_Declaration): issue error in formal mode on
+	controlled type or discriminant type
+	* sem_ch6.adb (Analyze_Subprogram_Specification): only issue error on
+	user-defined operator means that it should come from the source
+	(New_Overloaded_Entity): issue error in formal mode on overloaded
+	entity.
+	* sem_ch6.ads, sem_ch13.ads: typos in comments.
+
+2011-08-01  Thomas Quinot  <quinot@adacore.com>
+
+	* atree.adb: Minor reformatting.
+	* checks.adb: Minor reformatting.
+
+2011-08-01  Vincent Celier  <celier@adacore.com>
+
+	* s-parame-vms-ia64.ads: Fix typo in comment
+	Minor reformatting
+	* s-parame-vms-restrict.ads: Removed, unused.
+
+2011-08-01  Javier Miranda  <miranda@adacore.com>
+
+	* exp_ch3.adb
+	(Is_Variable_Size_Array): Remove local subprogram Is_Constant_Bound.
+	* sem_ch3.adb
+	(Constrain_Index): Remove side effects in the evaluation of the bounds.
+	* sem_ch3.ads, sem_ch3.adb
+	(Is_Constant_Bound): New extended version of the subprogram that was
+	previously located inside function Exp_Ch3.Is_Variable_Size_Array.
+	Moved here since it is shared by routines of sem_ch3 and exp_ch3.
+	* sem_aux.ads (Constant_Value): Fix typo in comment.
+	* checks.adb (Generate_Index_Checks): New implementation which, for
+	array objects with constant bounds, generates the runtime check
+	referencing the bounds of the array type. For other cases this routine
+	provides its previous behavior obtaining such values from the array
+	object.
+	* sem_res.adb (Set_Slice_Subtype): Link a copied range subtree with its
+	parent type.
+	* atree.adb (New_Copy): Reset flag Is_Overloaded in the new copy since
+	we cannot have semantic interpretations of the new node.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch6.adb (Fully_Conformant_Expressions): handle quantified
+	expressions.
+
+2011-08-01  Arnaud Charlet  <charlet@adacore.com>
+
+	* sem_ch8.adb: Minor code editing.
+	* s-vxwext.adb: Remove trailing space.
+	* freeze.adb, freeze.ads, errout.ads, erroutc.adb: Fix GPLv3 header for
+	consistency with other files.
+
+2011-08-01  Thomas Quinot  <quinot@adacore.com>
+
+	* s-auxdec.ads, s-auxdec-vms_64.ads: Minor reformatting.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* par-ch10.adb: reject parameterized expressions as compilation unit.
+	* sem_ch4.adb: handle properly conditional expression with overloaded
+	then_clause and no else_clause.
+
+2011-08-01  Tristan Gingold  <gingold@adacore.com>
+
+	* s-parame-vms-alpha.ads, s-parame-vms-ia64.ads: Redeclare C_Address
+	like done by System.Aux_DEC.
+	* env.c (__gnat_setenv) [VMS]: Put logicals into LNM$PROCESS table.
+
+2011-08-01  Yannick Moy  <moy@adacore.com>
+
+	* par-endh.adb (Check_End): issue a syntax error in SPARK mode for
+	missing label at end of declaration (subprogram or package)
+	* par-ch4.adb (P_Name): issue a syntax error in SPARK mode for mixing
+	of positional and named parameter association
+	* par.adb, par-util.adb (Formal_Error_Msg_SP): new wrapper on
+	Error_Msg_SP which adds a prefix to the error message giving the name
+	of the formal language analyzed
+	* sem_ch6.adb (Analyze_Return_Type): issue an error in formal mode for
+	access result type in subprogram, unconstrained array as result type,.
+	(Analyze_Subprogram_Declaration): issue an error in formal mode for null
+	procedure
+	* sem_ch8.adb: Code clean up.
+
+2011-08-01  Javier Miranda  <miranda@adacore.com>
+
+	* sem_ch7.adb (Uninstall_Declarations): Remove useless code.
+	* einfo.ads (Access_Disp_Table): Fix documentation.
+	(Dispatch_Table_Wrappers): Fix documentation.
+	* einfo.adb (Access_Disp_Table, Dispatch_Table_Wrappers,
+	Set_Access_Disp_Table, Set_Dispatch_Table_Wrappers): Fix the assertions
+	to enforce the documentation of this attribute.
+	(Set_Is_Interface): Cleanup the assertion.
+	* exp_ch4.adb (Expand_Allocator_Expression, Tagged_Membership): Locate
+	the Underlying_Type entity before reading attribute Access_Disp_Table.
+	* exp_disp.adb (Expand_Dispatching_Call, Expand_Interface_Conversion):
+	Locate the Underlying_Type before reading attribute Access_Disp_Table.
+	* exp_aggr.adb (Build_Array_Aggr_Code, Build_Record_Aggr_Code): Locate
+	the Underlying_Type entity before reading attribute Access_Disp_Table.
+	* exp_ch3.adb (Build_Record_Init_Proc, Expand_N_Object_Declaration):
+	Locate the Underlying_Type entity before reading attribute
+	Access_Disp_Table.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* s-poosiz.ads: Additional overriding indicators.
+
+2011-08-01  Yannick Moy  <moy@adacore.com>
+
+	* sem_ch5.adb (Analyze_Exit_Statement): add return after error in
+	formal mode.
+	(Analyze_Iteration_Scheme): issue error in formal mode when loop
+	parameter specification does not include a subtype mark.
+	* sem_ch6.adb (Analyze_Abstract_Subprogram_Declaration): issue error in
+	formal mode on abstract subprogram.
+	(Analyze_Subprogram_Specification): issue error in formal mode on
+	user-defined operator.
+	(Process_Formals): issue error in formal mode on access parameter and
+	default expression.
+	* sem_ch9.adb (Analyze_Abort_Statement,
+	Analyze_Accept_Statement, Analyze_Asynchronous_Select,
+	Analyze_Conditional_Entry_Call, Analyze_Delay_Relative,
+	Analyze_Delay_Until, Analyze_Entry_Call_Alternative,
+	Analyze_Requeue, Analyze_Selective_Accept,
+	Analyze_Timed_Entry_Call): issue error in formal mode on such constructs
+	* sem_ch11.adb (Analyze_Raise_Statement, Analyze_Raise_xxx_Error):
+	issue error in formal mode on user-defined raise statement.
+
+2011-08-01  Thomas Quinot  <quinot@adacore.com>
+
+	* sem_ch6.adb (Enter_Overloaded_Entity): Do not warn about a
+	declaration being hidden when overriding an implicit inherited
+	subprogram.
+	* par-ch10.adb (P_Compilation_Unit): In syntax check only mode
+	(-gnats), do not complain about a source file that contains only a
+	pragma No_Body.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch5.adb (Analyze_Iterator_Scheme): Do not overwrite type of loop
+	variable if already set.
+
+2011-08-01  Arnaud Charlet  <charlet@adacore.com>
+
+	* g-socket-dummy.adb, s-osinte-linux.ads, g-socket-dummy.ads,
+	g-debuti.adb, g-tasloc.adb, g-debuti.ads, g-tasloc.ads,
+	s-osinte-hpux.ads, g-sercom.adb, g-soliop-solaris.ads, g-sercom.ads,
+	g-sptain.ads, g-curexc.ads, s-tasloc.adb, s-tasloc.ads, s-tataat.adb,
+	g-ctrl_c.adb, a-reatim.adb, s-tataat.ads, g-dirope.adb, g-ctrl_c.ads,
+	g-dirope.ads, g-boubuf.adb, g-calend.adb, g-boubuf.ads, g-souinf.ads,
+	g-table.adb, g-bytswa-x86.adb, g-wispch.adb, g-io.adb, g-table.ads,
+	g-wispch.ads, g-io.ads, g-memdum.adb, g-memdum.ads, g-busorg.adb,
+	g-busorg.ads, g-regpat.adb, g-sothco-dummy.adb, g-encstr.adb,
+	g-regpat.ads, g-sothco-dummy.ads, s-osinte-aix.ads, g-encstr.ads,
+	g-sercom-mingw.adb, s-mastop-vms.adb, g-diopit.adb, g-diopit.ads,
+	s-vxwext.adb, g-dyntab.adb, g-dyntab.ads, g-crc32.adb,
+	g-sercom-linux.adb, g-crc32.ads, s-regpat.adb, g-flocon.ads,
+	s-regpat.ads, g-stheme.adb, g-sestin.ads, s-taspri-posix-noaltstack.ads,
+	g-soliop.ads, s-inmaop-posix.adb, g-locfil.ads, g-enblsp-vms-alpha.adb,
+	g-socthi-dummy.adb, g-socthi-dummy.ads, gnat.ads, g-moreex.adb,
+	g-moreex.ads, g-dynhta.adb, g-dynhta.ads, g-deutst.ads, g-htable.adb,
+	g-cgicoo.adb, g-htable.ads, g-cgicoo.ads, a-interr.adb,
+	g-socthi-vms.adb, g-socthi-vms.ads, g-hesora.adb, g-bubsor.adb,
+	g-hesora.ads, g-bubsor.ads, g-md5.adb, g-md5.ads, s-intman-irix.adb,
+	s-htable.adb, s-osinte-vms.adb, s-htable.ads, s-osinte-vms.ads,
+	s-taprob.adb, g-bytswa.adb, g-bytswa.ads, s-osinte-solaris-posix.ads,
+	a-suenco.adb, g-comver.adb, g-comver.ads, g-exctra.adb,
+	s-osinte-solaris.adb, g-exctra.ads, s-osinte-irix.ads,
+	s-osinte-solaris.ads, a-caldel-vms.adb, g-socthi-vxworks.adb,
+	g-expect.adb, g-socthi-vxworks.ads, g-expect.ads, g-comlin.ads,
+	g-heasor.adb, g-heasor.ads, g-traceb.adb, g-traceb.ads, g-decstr.adb,
+	g-spipat.adb, g-decstr.ads, g-spipat.ads, s-mastop-tru64.adb,
+	g-except.ads, g-thread.adb, g-hesorg.adb, g-thread.ads, g-hesorg.ads,
+	g-expect-vms.adb, a-stuten.ads, g-spchge.adb, g-spchge.ads,
+	g-u3spch.adb, g-u3spch.ads, g-spitbo.adb, g-spitbo.ads,
+	s-osinte-dummy.ads, s-osinte-posix.adb, g-pehage.adb, g-pehage.ads,
+	s-gloloc-mingw.adb, g-sha1.ads, s-traceb-hpux.adb,
+	g-trasym-unimplemented.adb, g-trasym-unimplemented.ads, g-io_aux.adb,
+	g-regexp.adb, g-io_aux.ads, g-socthi-mingw.adb, g-regexp.ads,
+	s-osinte-hpux-dce.adb, g-socthi-mingw.ads, g-cgi.adb,
+	s-osinte-hpux-dce.ads, g-cgi.ads, g-byorma.adb, g-boumai.ads,
+	g-byorma.ads, a-caldel.adb, s-regexp.adb, s-regexp.ads,
+	g-soliop-mingw.ads, g-sptavs.ads, s-osinte-tru64.ads, g-speche.adb,
+	g-speche.ads, g-socthi.adb, g-stsifd-sockets.adb, g-socthi.ads,
+	s-osinte-darwin.ads, i-vxwork-x86.ads, g-awk.adb, i-vxwork.ads,
+	g-awk.ads, g-zspche.adb, g-zspche.ads, g-socket.adb, g-sptabo.ads,
+	g-socket.ads, g-semaph.adb, g-semaph.ads, s-taspri-posix.ads,
+	g-enblsp-vms-ia64.adb, g-cgideb.adb, g-cgideb.ads, g-sothco.adb,
+	s-osinte-freebsd.ads, g-sothco.ads, g-catiio.adb, g-casuti.adb,
+	g-catiio.ads, g-casuti.ads, g-trasym.adb, g-trasym.ads, s-casuti.adb,
+	g-os_lib.adb, s-traceb-mastop.adb, g-busora.adb, s-interr-dummy.adb,
+	g-busora.ads, g-enutst.ads, s-os_lib.adb, a-tasatt.adb,
+	s-osinte-mingw.ads: Update to GPLv3 run-time license.
+	Use GNAT instead of GNARL.
+
+2011-08-01  Bob Duff  <duff@adacore.com>
+
+	* a-cdlili.ads, a-cihama.ads, a-coinve.ads, a-ciorse.ads, a-coorma.ads,
+	a-cidlli.ads, a-ciormu.ads, a-cihase.ads, a-cohama.ads, a-coorse.ads,
+	a-ciorma.ads, a-coormu.ads, a-convec.ads, a-cohase.ads: Minor
+	reformatting.
+
+2011-08-01  Yannick Moy  <moy@adacore.com>
+
+	* debug.adb (d.D) reverve flag for the SPARK mode
+	(d.E) reverve flag for SPARK generation mode
+	(d.F) reverve flag for Why generation mode
+	* opt.ads, opt.adb (ALFA_Mode, ALFA_Through_SPARK_Mode, 
+	ALFA_Through_Why_Mode, Formal_Verification_Mode, SPARK_Mode):  New
+	functions which return True when the corresponding modes are set
+	(Formal_Language): return "spark" or "alfa" when in formal verification
+	mode.
+	* sem_util.ads, sem_util.adb (Formal_Error_Msg): new wrapper on
+	Error_Msg to prefix the error message with a tag giving the formal
+	language
+	(Formal_Error_Msg_N): new wrapper on Error_Msg_N to prefix the error
+	message with a tag giving the formal language
+	* sem_ch5.adb (Analyze_Block_Statement): issue error in formal mode on
+	block statement
+	(Analyze_Case_Statement): issue error in formal mode on case statement
+	with a single "others" case alternative
+	(Analyze_Exit_Statement): issue errors in formal mode on exit
+	statements which do not respect SPARK restrictions
+	(Analyze_Goto_Statement): issue error in formal mode on goto statement
+	(Check_Unreachable_Code): always issue an error (not a warning) in
+	formal mode on unreachable code (concerns both code after an infinite
+	loop and after an unconditional jump, both not allowed in SPARK)
+	* sem_ch6.adb (Analyze_Return_Statement): add call to
+	Set_Return_Present for a procedure containing a return statement
+	(already done for functions in Analyze_Function_Return)
+	(Analyze_Function_Return): issue error in formal mode on extended
+	return or if return is not last statement in function
+	(Check_Missing_Return): issue error in formal mode if function does
+	not end with return or if procedure contains a return
+	* sem_ch8.ads, sem_ch8.adb (Has_Loop_In_Inner_Open_Scopes): new
+	function to detect if there is an inner scope of its parameter S which
+	is a loop.
+
+2011-08-01  Thomas Quinot  <quinot@adacore.com>
+
+	* sem_ch6.ads: Minor reformatting.
+
+2011-08-01  Javier Miranda  <miranda@adacore.com>
+
+	* sem_util.adb (Abstract_Interface_List): Complete condition when
+	processing private type declarations to avoid reading unavailable
+	attribute.
+	(Is_Synchronized_Tagged_Type): Complete condition when processing
+	private extension declaration nodes to avoid reading unavailable
+	attribute.
+
+2011-08-01  Thomas Quinot  <quinot@adacore.com>
+
+	* sem_ch3.adb: Minor reformatting.
+
+2011-08-01  Thomas Quinot  <quinot@adacore.com>
+
+	* s-parame-ae653.ads, s-parame-vms-alpha.ads, s-parame-hpux.ads,
+	i-cpoint.adb, i-cstrin.adb, i-cpoint.ads, i-cstrin.ads,
+	s-parame-vms-ia64.ads, s-parame.ads, i-c.ads, s-parame-vxworks.ads,
+	s-parame-vms-restrict.ads: Remove duplicated Interfaces.C.* packages
+	for VMS, instead parametrize the common implementation with
+	System.Parameters declarations.
+
+2011-08-01  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gnat_rm.texi: Document limitation of Pragma No_Strict_Aliasing.
+
+2011-08-01  Tristan Gingold  <gingold@adacore.com>
+
+	* seh_init.c: Fix SEH handler installation on win64.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch3.adb (Access_Subprogram_Declaration): in Asis mode, prevent
+	double analysis of an anonymous access to subprogram, because it can
+	lead to improper sharing of profiles and a back-end crash.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* make.adb, sem_ch4.adb: Minor reformatting.
+	* gcc-interface/Make-lang.in: Update dependencies.
+	* sem_util.adb, exp_ch5.adb: Minor reformatting.
+
+2011-08-01  Arnaud Charlet  <charlet@adacore.com>
+
+	* gnat_rm.texi: Fix definition of Long_Integer.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* exp_aggr.adb: check limit size of static aggregate unconditionally,
+	to prevent storage exhaustion.
+	* exp_ch7.adb (Clean_Simple_Protected_Objects): if the scope being
+	finalized is a function body, insert the cleanup code before the final
+	return statement, to prevent spurious warnings.
+	* s-pooglo.ads: add overriding indicator.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch4.adb (Operator_Check): improve error message when both a
+	with_clause and a use_clause are needed to make operator usage legal.
+	* sem_util.ads, sem_util.adb (Unit_Is_Visible): new predicate to
+	determine whether a compilation unit is visible within an other,
+	either through a with_clause in the current unit, or a with_clause in
+	its library unit or one one of its parents.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* exp_ch5.adb (Expand_N_Iterator_Loop): handle properly an iterator
+	over an arbitrary expression of an array or container type.
+	* lib-xref.adb: clarify comment.
+
+2011-08-01  Bob Duff  <duff@adacore.com>
+
+	* einfo.ads: Minor reformatting.
+	* debug.adb: Minor comment improvement.
+
+2011-08-01  Javier Miranda  <miranda@adacore.com>
+
+	* sem_ch4.adb (Try_Object_Operation): For class-wide subprograms do not
+	consider hidden subprograms as valid candidates.
+
+2011-08-01  Arnaud Charlet  <charlet@adacore.com>
+
+	* make.adb (Compile): Strip -mxxx switches in CodePeer mode.
+
+2011-08-01  Vasiliy Fofanov  <fofanov@adacore.com>
+
+	* gnat_ugn.texi: Fix typo.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* i-cstrin.adb, sem_util.adb, exp_ch11.adb, sem_ch8.adb,
+	lib-xref.adb: Minor reformatting
+
+2011-08-01  Gary Dismukes  <dismukes@adacore.com>
+
+	* exp_ch6.adb (Expand_N_Extended_Return_Statement): Replace test of
+	when to generate a call to Move_Final_List.
+	(Has_Controlled_Parts): Remove this function.
+
+2011-08-01  Geert Bosch  <bosch@adacore.com>
+
+	* par-ch3.adb (P_Discrete_Choice_List): Improve error message for extra
+	"," in choice list.
+
+2011-08-01  Thomas Quinot  <quinot@adacore.com>
+
+	* exp_ch11.adb (Expand_N_Raise_Statement): Mark N_Raise_xxx_Error for
+	explicit raise of a predefined exception as Comes_From_Source if the
+	original N_Raise_Statement comes from source.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* sinfo.ads: Add comment.
+	* sem_ch6.adb: Minor reformatting.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* freeze.adb (Freeze_Entity): Refine check for bad component size
+	clause to avoid rejecting confirming clause when atomic/aliased present.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch8.adb (Find_Direct_Name, Analyze_Expanded_Name): use Is_LHS to
+	better determine whether an entity reference is a write.
+	* sem_util.adb (Is_LHS): refine predicate to handle assignment to a
+	subcomponent.
+	* lib-xref.adb (Output_References): Do no suppress a read reference at
+	the same location as an immediately preceeding modify-reference, to
+	handle properly in-out actuals.
+
+2011-08-01  Tristan Gingold  <gingold@adacore.com>
+
+	* env.c (__gnat_setenv) [VMS]: Refine previous change.
+
+2011-08-01  Quentin Ochem  <ochem@adacore.com>
+
+	* i-cstrin.adb (New_String): Changed implementation, now uses only the
+	heap to compute the result.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* atree.ads: Minor reformatting.
+
+2011-08-01  Emmanuel Briot  <briot@adacore.com>
+
+	* g-expect.adb (Get_Command_Output): Fix memory leak.
+
+2011-08-01  Geert Bosch  <bosch@adacore.com>
+
+	* cstand.adb (P_Float_Type): New procedure to print the definition of
+	predefined fpt types.
+	(P_Mixed_Name): New procedure to print a name using mixed case
+	(Print_Standard): Use P_Float_Type for printing floating point types
+	* einfo.adb (Machine_Emax_Value): Add preliminary support for quad
+	precision IEEE float.
+
+2011-08-01  Thomas Quinot  <quinot@adacore.com>
+
+	* sem_ch3.adb: Minor reformatting.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch6.adb (Analyze_Parameterized_Expression): If the expression is
+	the completion of a generic function, insert the new body rather than
+	rewriting the original.
+
+2011-08-01  Yannick Moy  <moy@adacore.com>
+
+	* sinfo.ads, errout.ads: Typos in comments.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* par-endh.adb: Minor reformatting.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* aspects.ads, aspects.adb: Add aspects for library unit pragmas
+	(Pre_Post_Aspects): New subtype.
+	* par-ch12.adb (P_Generic): New syntax for aspects in packages
+	* par-ch13.adb (P_Aspect_Specifications): Add Semicolon parameter
+	* par-ch7.adb (P_Package): Remove Decl parameter
+	(P_Package): Handle new syntax for aspects (before IS)
+	* par-ch9.adb (P_Protected_Definition): Remove Decl parameter, handle
+	new aspect syntax
+	(P_Task_Definition): Remove Decl parameter, handle new aspect syntax
+	* par.adb (P_Aspect_Specifications): Add Semicolon parameter
+	(P_Package): Remove Decl parameter
+	* sem_ch13.adb (Analyze_Aspect_Specifications): Handle library unit
+	aspects
+	* sem_ch7.adb (Analyze_Package_Declaration): Analyze new format aspect
+	specs
+	* sem_util.ads, sem_util.adb (Static_Boolean): New function
+	* sinfo.ads: Document new syntax for aspects in packages etc.
+	* sprint.adb: Handle new syntax of aspects before IS in package
+
+2011-08-01  Thomas Quinot  <quinot@adacore.com>
+
+	* atree.ads: Minor reformatting.
+	* sem_prag.adb: Minor reformatting.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* exp_util.adb (Insert_Actions): Fix error in handling Actions for
+	case expr alternative.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch12.adb: Fix typo.
+
+2011-08-01  Geert Bosch  <bosch@adacore.com>
+
+	* sem_prag.adb (Check_No_Link_Name): New procedure.
+	(Process_Import_Or_Interface): Use Check_No_Link_Name.
+	* cstand.adb (Create_Standard): Use Esize (Standard_Long_Long_Float)
+	instead of Standard_Long_Long_Float_Size global. Preparation for
+	eventual removal of per type constants.
+	* exp_util.ads (Get_Stream_Size): New function returning the stream
+	size value of subtype E.
+	* exp_util.adb (Get_Stream_Size): Implement new function.
+	* exp_strm.adb (Build_Elementary_Input_Call): Use Get_Stream_Size
+	function.
+	* exp_attr.adb (Attribute_Stream_Size): Use Get_Stream_Size
+	* einfo.adb:
+	(Machine_Mantissa_Value): Handle 128-bit quad precision IEEE floats
+
+2011-08-01  Geert Bosch  <bosch@adacore.com>
+
+	* cstand.adb: Fix comments.
+	* sem_prag.adb (Analyze_Pragma): Use List_Length instead of explicit
+	count of arguments.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* exp_ch4.adb, sem_cat.adb: Minor reformatting.
+
+2011-08-01  Geert Bosch  <bosch@adacore.com>
+
+	* atree.ads: Fix comment.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* aspects.ads, aspects.adb (Aspect_Names): Moved from body to spec.
+	* par-ch13.adb (P_Aspect_Specifications): Check misspelled aspect name.
+	* par.adb: Add with for Namet.Sp.
+	* par-tchk.adb: Minor reformatting.
+
+2011-08-01  Vincent Celier  <celier@adacore.com>
+
+	* mlib-tgt-specific-vms-alpha.adb, mlib-tgt-specific-vms-ia64.adb
+	(Build_Dynamic_Library): Use new function Init_Proc_Name to get the name
+	of the init procedure of a SAL.
+	* mlib-tgt-vms_common.ads, mlib-tgt-vms_common.adb (Init_Proc_Name):
+	New procedure.
+
+2011-08-01  Thomas Quinot  <quinot@adacore.com>
+
+	* exp_ch4.adb, s-tasini.ads, sem_attr.adb, s-soflin.ads: Minor
+	reformatting.
+
+2011-08-01  Richard Kenner  <kenner@vlsi1.ultra.nyu.edu>
+
+	* adaint.c (__gnat_file_time_name_attr): Get rid of warning.
+
+2011-08-01  Thomas Quinot  <quinot@adacore.com>
+
+	* sem_util.adb, sem_util.ads (Has_Overriding_Initialize): Make function
+	conformant with its spec (return True only for types that have
+	an overriding Initialize primitive operation that prevents them from
+	having preelaborable initialization).
+	* sem_cat.adb (Validate_Object_Declaration): Fix test for preelaborable
+	initialization for controlled types in Ada 2005 or later mode.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* aspects.ads, aspects.adb: Add aspect Type_Invariant, Precondition,
+	Postcondition.
+	(Same_Aspect): New function.
+	* sem_ch13.adb (Analyze_Aspect_Specifications): Add aspect
+	Type_Invariant, Precondition, Postcondition.
+	* snames.ads-tmpl: Add Name_Type_Invariant.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* freeze.adb (Freeze_Entity): Don't call Check_Aspect_At_Freeze_Point
+	here.
+	(Freeze_All_Ent): Fix error in handling inherited aspects.
+	* sem_ch13.adb (Analyze_Aspect_Specifications): Skip aspect that is
+	already analyzed, but don't skip entire processing of a declaration,
+	that's wrong in some cases of declarations being rewritten.
+	(Analyze_Aspect_Specification): Set Is_Delayed_Aspect in aspects.
+	Don't delay for integer, string literals
+	Treat predicates in usual manner for delay, remove special case code,
+	not needed.
+	(Analyze_Freeze_Entity): Make call to Check_Aspect_At_Freeze_Point
+	(Build_Predicate_Function): Update saved expression in aspect
+	(Build_Invariant_Procedure): Update saved expression in aspect
+	* exp_ch4.adb (Expand_N_Selected_Component): Only do the optimization
+	of replacement of discriminant references if the reference is simple.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* aspects.ads, aspects.adb: Add Static_Predicate and Dynamic_Predicate.
+	* sem_ch13.adb (Analyze_Aspect_Specification): Add processing for
+	Static_Predicate and Dynamic_Predicate.
+	(Build_Predicate_Function): Add processing for Static_Predicate
+	and Dynamic_Predicate.
+	* sinfo.ads, sinfo.adb (From_Dynamic_Predicate): New flag
+	(From_Static_Predicate): New flag
+	* snames.ads-tmpl: Add Name_Static_Predicate and Name_Dynamic_Predicate
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* usage.adb: Documentation cleanup for Ada version modes in usage.
+	* expander.adb: Minor reformatting.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* atree.ads: Minor comment fix.
+	* a-stwifi.adb, a-stzfix.adb, a-strfix.adb, a-ztexio.ads, a-textio.ads,
+	a-witeio.ads, sem_prag.adb: Minor reformatting.
+
+2011-08-01  Doug Rupp  <rupp@adacore.com>
+
+	* env.c (__gnat_setenv) [VMS]: Force 32bit on item list structure
+	pointers. Use descrip.h header file for convenience. Add some
+	comments.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* freeze.adb (Freeze_Entity): Call Check_Aspect_At_Freeze_Point
+	(Freeze_All): Call Check_Aspect_At_End_Of_Declarations
+	* sem_ch13.ads, sem_ch13.adb (Check_Aspect_At_Freeze_Point):
+	New procedure.
+	(Check_Aspect_At_End_Of_Declarations): New procedure
+	(Analye_Aspect_Specification): Minor changes for above procedures
+	* sinfo.ads, sinfo.adb (Is_Delayed_Aspect): Now set in aspect
+	specification node as well.
+
+2011-08-01  Pascal Obry  <obry@adacore.com>
+
+	* adaint.c (_gnat_stat): GetFilesAttributesEx() would fail on special
+	Windows files. Use GetFilesAttributes() in this case to check for file
+	existence instead of returning with an error code.
+
+2011-08-01  Vincent Celier  <celier@adacore.com>
+
+	* a-stzfix.adb, a-stwifi.adb (Replace_Slice): Fixed computation when
+	High is above Source length.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* a-ztexio.ads, a-textio.ads, a-witeio.ads: Fix comment.
+
+2011-08-01  Robert Dewar  <dewar@adacore.com>
+
+	* aspects.ads (Boolean_Aspects): New subtype.
+	* exp_ch13.adb (Expand_Freeze_Entity): Fix errors in handling aspects
+	for derived types in cases where the parent type and derived type have
+	aspects.
+	* freeze.adb (Freeze_Entity): Fix problems in handling derived type
+	with aspects when parent type also has aspects.
+	(Freeze_Entity): Deal with delay of boolean aspects (must evaluate
+	boolean expression at this point).
+	* sem_ch13.adb (Analyze_Aspect_Specifications): Delay all aspects in
+	accordance with final decision on the Ada 2012 feature.
+	* sinfo.ads, sinfo.adb (Is_Boolean_Aspect): New flag.
+
+2011-08-01  Matthew Heaney  <heaney@adacore.com>
+
+	* a-chtgbo.adb (Delete_Node_Sans_Free): Replace iterator with selector.
+
+2011-08-01  Pascal Obry  <obry@adacore.com>
+
+	* a-stzunb-shared.adb, a-strunb-shared.adb, a-stwiun-shared.adb:
+	Fix Replace_Slice when High is above current string size.
+	(Replace_Slice): Fix DL computation when High is above current
+	string length.
+
+2011-08-01  Gary Dismukes  <dismukes@adacore.com>
+
+	* gnat_rm.texi: Add documentation for pragma Static_Elaboration_Desired.
+
+2011-08-01  Matthew Heaney  <heaney@adacore.com>
+
+	* a-rbtgbo.adb (Delete_Node_Sans_Free): Fixed assignment to left child
+	of node.
+
+2011-08-01  Pascal Obry  <obry@adacore.com>
+
+	* a-stzunb-shared.adb, a-strunb-shared.adb, a-stwiun-shared.adb: Minor
+	reformatting.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_attr.adb (Analyze_Attribute, case 'Access): Handle properly named
+	access to protected subprograms in generic bodies.
+	* sem_ch6.adb (Analyze_Subprogram_Declaration): If the context is a
+	protected type, indicate that the convention of the subprogram is
+	Convention_Protected, because it may be used in subsequent declarations
+	within the protected declaration.
+
+2011-08-01  Vincent Celier  <celier@adacore.com>
+
+	* mlib-prj.adb (Build_Library): Use "ada_" as the prefix for the "init"
+	and "final" procedures when the name of the library is "ada", to avoid
+	duplicate symbols "adainit" and "adafinal" in executables.
+
+2011-08-01  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_attr.adb (Analyze_Attribute, case 'Result): Handle properly a
+	quantified expression that appears within a postcondition and uses the
+	Ada2012 'Result attribute.
+
+2011-07-28  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
+
+	* init.c (__gnat_error_handler): Cast reason to int.
+	(__gnat_install_handler): Explain sa_sigaction use.
+
+2011-07-24  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (gnat_to_gnu_entity) <E_Subprogram_Type>: If the
+	subprogram has copy-in copy-out parameters, try to promote the mode of
+	the return type if it is passed in registers.
+
+2011-07-24  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/utils2.c (build_binary_op) <ARRAY_REF>: Do not mark the
+	left operand as addressable.
+
+2011-07-24  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/gigi.h (build_function_stub): Remove.
+	(build_return_expr): Likewise.
+	(convert_vms_descriptor): Declare.
+	* gcc-interface/utils.c (convert_vms_descriptor): Make global.
+	(build_function_stub): Move to...
+	* gcc-interface/utils2.c (build_return_expr): Move to...
+	* gcc-interface/trans.c (build_function_stub): ...here.
+	(build_return_expr): ...here.
+	(Subprogram_Body_to_gnu): Add local variable for language_function.
+	Disconnect the parameter attributes cache, if any, once done with it.
+	Call end_subprog_body only after setting the end_locus.
+	Build the stub associated with the function, if any, at the very end.
+	(gnat_to_gnu) <N_Return_Statement>: Remove couple of useless local
+	variables and streamline control flow.
+
+2011-07-23  Arnaud Charlet  <charlet@adacore.com>
+
+	PR ada/49819
+	* gcc-interface/Makefile.in (powerpc-linux): Remove reference to
+	g-trasym-dwarf.adb.
+
+2011-07-22  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
+
+	PR bootstrap/49794
+	* init.c [sun && __SVR4 && !__vxworks] (__gnat_install_handler):
+	Assign to act.sa_sigaction.
+	* tracebak.c [USE_GENERIC_UNWINDER] (__gnat_backtrace): Cast
+	current->return_address to char * before arithmetic.
+
+2011-07-22  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
+
+	* init.c [sgi] (__gnat_error_handler): Update sigaction(2) citation.
+	Correct argument types.
+	Extract code from reason.
+	(__gnat_install_handler): Assign to act.sa_sigaction.
+
+2011-07-21  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/Make-lang.in (GNAT1_ADA_OBJS): Move ada/b_gnat1.o to...
+	(GNAT1_OBJS): ...here.
+
+2011-07-15  Eric Botcazou  <ebotcazou@adacore.com>
+
+	PR ada/48711
+	* g-socthi-mingw.adb (Fill): Fix formatting.
+
+	* gcc-interface/gigi.h: Move around comment.
+
+2011-07-14  John David Anglin  <dave.anglin@nrc-cnrc.gc.ca>
+
+	PR ada/46350
+	* s-taprop-hpux-dce.adb (Abort_Task): Remove unnecessary cast.
+
+2011-07-14  Florian Weimer  <fw@deneb.enyo.de>
+
+	PR ada/48711
+	* g-socthi-mingw.adb (Fill): Guard against invalid MSG_WAITALL.
+
+2011-07-13  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/utils.c (build_vms_descriptor32): Skip the 32-bit
+	range comparison if Pmode is SImode.
+
+2011-07-12  Laurent GUERBY  <laurent@guerby.net>
+	    Eric Botcazou  <ebotcazou@adacore.com>
+
+	* adadecode.c: Wrap up in extern "C" block.
+	* adadecode.h: Likewise.
+	* adaint.c: Likewise.  Remove 'const' keyword.
+	* adaint.h: Likewise.
+	* argv.c: Likewise.
+	* atree.h: Likewise.
+	* cio.c: Likewise.
+	* cstreams.c: Likewise.
+	* env.c: Likewise.
+	* exit.c: Likewise.
+	* fe.h: Likewise.
+	* final.c: Likewise.
+	* init.c: Likewise.
+	* initialize.c: Likewise.
+	* link.c: Likewise.
+	* namet.h: Likewise.
+	* nlists.h: Likewise.
+	* raise.c: Likewise.
+	* raise.h: Likewise.
+	* repinfo.h: Likewise.
+	* seh_init.c: Likewise.
+	* targext.c: Likewise.
+	* tracebak.c: Likewise.
+	* uintp.h: Likewise.
+	* urealp.h: Likewise.
+	* xeinfo.adb: Wrap up generated C code in extern "C" block.
+	* xsinfo.adb: Likewise.
+	* xsnamest.adb: Likewise.
+	* gcc-interface/gadaint.h: Wrap up in extern "C" block.
+	* gcc-interface/gigi.h: Wrap up some prototypes in extern "C" block.
+	* gcc-interface/misc.c: Likewise.
+	* gcc-interface/Make-lang.in (GCC_LINK): Use LINKER.
+	(GNAT1_C_OBJS): Remove ada/b_gnat1.o.  List ada/seh_init.o and
+	ada/targext.o here...
+	(GNAT_ADA_OBJS): ...and not here.
+	(GNAT1_ADA_OBJS): Add ada/b_gnat1.o.
+	(GNATBIND_OBJS): Reorder.
+
+2011-07-07  Richard Henderson  <rth@redhat.com>
+
+	* gcc-interface/misc.c (gnat_init_gcc_eh): Don't call
+	dwarf2out_frame_init.
+
+2011-07-07  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/misc.c (gnat_init): Tweak previous change.
+
+2011-07-07  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
+
+	PR target/39150
+	* gcc-interface/Makefile.in: Handle x86_64-solaris2.
+
+2011-07-06  Richard Guenther  <rguenther@suse.de>
+
+	* gcc-interface/misc.c (gnat_init): Merge calls to
+	build_common_tree_nodes and build_common_tree_nodes_2.
+	Re-initialize boolean_false_node.
+
+2011-07-02  Eric Botcazou  <ebotcazou@adacore.com>
+	    Olivier Hainque  <hainque@adacore.com>
+	    Nicolas Setton  <setton@adacore.com>
+
+	* gcc-interface/utils.c (record_builtin_type): Set TYPE_ARTIFICIAL on
+	the type according to the ARTIFICIAL_P parameter.
+	(create_type_decl): Likewise.
+	(create_type_stub_decl): Set TYPE_ARTIFICIAL on the type to 1.
+
+2011-07-01  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/Make-lang.in (gnat1): Prepend '+' to the command.
+	(gnatbind): Likewise.
+
+2011-06-29  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
+
+	* gcc-interface/Makefile.in (TOOLS_LIBS): Add $(LIBINTL).
+
+2011-06-18  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (gnat_to_gnu_component_type): Use GNAT_TYPE
+	local variable throughout.  Remove useless call to Base_Type.
+	(gnat_to_gnu_field): Use GNAT_FIELD_TYPE local variable throughout.
+	Take it also into account for the volatileness of the field.  Set the
+	TREE_SIDE_EFFECTS flag as well in this case.  Reorder some warnings.
+
+2011-06-18  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/trans.c (Identifier_to_gnu): Don't set TREE_THIS_NOTRAP
+	on a dereference built for a by-ref object if it has an address clause.
+
+2011-06-18  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* einfo.ads (Address_Taken): Document use for the second argument of
+	Asm_Input and Asm_Output attributes.
+	* sem_attr.adb (Analyze_Attribute) <Attribute_Asm_Input>: If the second
+	argument is an entity name, then set Address_Taken on it.
+	<Attribute_Asm_Output>: Likewise.
+	* gcc-interface/trans.c (lvalue_required_for_attribute_p): Handle the
+	Attr_Asm_Input and Attr_Asm_Output attributes explicitly.
+	(gnat_to_gnu) <N_Code_Statement>: If an operand is going to end up in
+	memory and is a CONST_DECL, retrieve its corresponding VAR_DECL.
+
+2011-06-16  Joern Rennecke  <joern.rennecke@embecosm.com>
+
+	PR middle-end/46500
+	* gcc-interface/decl.c (gnat_to_gnu_param): Use pack_cumulative_args.
+
+2011-06-14  Joseph Myers  <joseph@codesourcery.com>
+
+	* gcc-interface/Make-lang.in (gnatbind$(exeext)): Use ggc-none.o.
+	(ada/utils.o): Update dependencies.
+	* gcc-interface/Makefile.in (EXTRA_GNATTOOLS_OBJS): Add
+	../../../libcpp/libcpp.a.
+	* gcc-interface/utils.c: Include common/common-target.h.
+	(process_attributes): Use targetm_common.have_named_sections.
+
+2011-06-07  Richard Guenther  <rguenther@suse.de>
+
+	* gcc-interface/misc.c (gnat_init): Do not set size_type_node or call
+	set_sizetype.
+
+2011-06-06  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/utils2.c (gnat_stabilize_reference): Propagate the
+	TREE_THIS_NOTRAP flag.
+
+2011-06-06  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/utils2.c (gnat_stabilize_reference) <COMPOUND_EXPR>:
+	Fix thinko.
+
+2011-06-06  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/trans.c (Identifier_to_gnu): Also handle deferred
+	constants whose full view has discriminants specially.
+
+2011-06-06  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/utils.c: Include diagnostic.h.
+	(gnat_write_global_declarations): Output debug information for all
+	global type declarations before finalizing the compilation unit.
+	* gcc-interface/Make-lang.in (ada/utils.o): Add dependency.
+
+2011-05-25  Jakub Jelinek  <jakub@redhat.com>
+
+	* gcc-interface/utils.c (def_fn_type): Remove extra va_end.
+
+2011-05-25  Kai Tietz  <ktietz@redhat.com>
+
+	* adaint.c (__gnat_to_canonical_file_list_next): Use array
+	initialization instead of const/none-const pointer assignment.
+
+2011-05-24  Joseph Myers  <joseph@codesourcery.com>
+
+	* gcc-interface/Make-lang.in (GNAT1_OBJS): Don't include
+	$(EXTRA_GNAT1_OBJS).
+	(GNATBIND_OBJS): Don't include $(EXTRA_GNATBIND_OBJS).
+	(EXTRA_GNAT1_OBJS, EXTRA_GNATBIND_OBJS): Remove.
+	(gnat1$(exeext), gnatbind$(exeext)): Use libcommon-target.a.
+	* gcc-interface/Makefile.in (EXTRA_GNATTOOLS_OBJS): Use
+	libcommon-target.a instead of prefix.o.
+
+2011-05-21  Joseph Myers  <joseph@codesourcery.com>
+
+	PR ada/49097
+	* gcc-interface/Make-lang.in (gnatbind$(exeext)): Depend on $(LIBDEPS).
+
+2011-05-20  Joseph Myers  <joseph@codesourcery.com>
+
+	* gcc-interface/Make-lang.in (EXTRA_GNATBIND_OBJS): Remove version.o.
+	* gcc-interface/Makefile.in (EXTRA_GNATTOOLS_OBJS): Use libcommon.a
+	instead of version.o.
+
+2011-05-18  Kai Tietz <ktietz@redhat.com>
+
+	* gcc-interface/trans.c (Exception_Handler_to_gnu_sjlj): Use
+	boolean_false_node instead of integer_zero_node.
+	(convert_with_check): Likewise.
+	* gcc-interface/decl.c (choices_to_gnu): Likewise.
+
+2011-05-12  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/trans.c (call_to_gnu): In the by-reference case, if the
+	type of the parameter is an unconstrained array, convert the actual to
+	the type of the formal in the In Out and Out cases as well.
+
+2011-05-11  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* gcc-interface/utils.c (def_fn_type): Don't call build_function_type;
+	call build_function_type_array or build_varargs_function_type_array
+	instead.
+	(create_subprog_type): Don't call build_function_type; call
+	build_function_type_vec instead.
+
+2011-05-11  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* gcc-interface/ada-tree.h (TYPE_OBJECT_RECORD_TYPE): Use TYPE_MINVAL.
+	(TYPE_GCC_MIN_VALUE): Use TYPE_MINVAL.
+	(TYPE_GCC_MAX_VALUE): Use TYPE_MAXVAL.
+
+2011-05-07  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (intrin_arglists_compatible_p): Remove spaces.
+
+	* gcc-interface/gigi.h (global_bindings_p): Adjust prototype.
+	* gcc-interface/utils.c (global_bindings_p): Return bool and simplify.
+
+2011-05-05  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* gcc-interface/trans.c (Case_Statement_to_gnu): Call build_case_label.
+
+2011-05-05  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* gcc-interface/decl.c (intrin_arglists_compatible_p): Use iterators
+	instead of accessing TYPE_ARG_TYPES directly.
+	* gcc-interface/utils.c (handle_nonnull_attribute): Likewise.
+
+2011-05-05  Eric Botcazou  <ebotcazou@adacore.com>
+
+	PR ada/48844
+	* gcc-interface/gigi.h (get_variant_part): Declare.
+	* gcc-interface/decl.c (get_variant_part): Make global.
+	* gcc-interface/utils2.c (find_common_type): Do not return T1 if the
+	types have the same constant size, are record types and T1 has a
+	variant part while T2 doesn't.
+
+2011-05-05  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/utils.c (begin_subprog_body): Do not call
+	get_pending_sizes.
+	(end_subprog_body): Likewise.
+
+2011-05-04  Richard Guenther  <rguenther@suse.de>
+
+	* gcc-interface/trans.c (gnat_to_gnu): Remove zero notrunc argument to
+	int_const_binop.
+	(pos_to_constructor): Likewise.
+
+2011-05-03  Nathan Froyd  <froydnj@codesourcery.com>
+            Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/trans.c (gigi): Call build_function_type_list instead
+	of build_function_type.  Adjust calls to...
+	(build_raise_check): ...this.  Do not take a void_tree parameter.
+	Call build_function_type_list instead of build_function_type.
+	Fix head comment and swap couple of conditional blocks.
+
+2011-04-30  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gnatvsn.ads (Library_Version): Bump to 4.7.
+	(Current_Year): Bump to 2011.
+
+2011-04-29  Michael Matz  <matz@suse.de>
+
+	* gcc-interface/misc.c (gnat_handle_option): Set
+	warn_maybe_uninitialized.
+
+2011-04-23  Gerald Pfeifer  <gerald@pfeifer.com>
+
+	* gnat_ugn.texi (Complexity Metrics Control): Update link to
+	the Watson/McCabe paper.
+
+2011-04-23  Jim Meyering  <meyering@redhat.com>
+
+	* gnat_ugn.texi (Examples of gnatxref Usage): Fix typo: s/it it/it is/
+
+2011-04-22  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (make_packable_type): Copy DECL_PARALLEL_TYPE
+	onto the new type.
+
+2011-04-22  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/gigi.h (create_subprog_decl): Add ARTIFICIAL_FLAG
+	parameter.
+	* gcc-interface/utils.c (create_subprog_decl): Likewise.  Set
+	DECL_ARTIFICIAL and DECL_NO_INLINE_WARNING_P on the DECL accordingly.
+	* gcc-interface/decl.c (gnat_to_gnu_entity) <E_Subprogram_Type>: Add
+	ARTIFICIAL_FLAG local variable and pass it to create_subprog_decl.
+	<all>: Do not set flags on the reused DECL node coming from an alias.
+	Set DECL_IGNORED_P on the DECL node built for subprograms if they
+	don't need debug info here...
+	* gcc-interface/trans.c (Subprogram_Body_to_gnu): ...and not here.
+	(gigi): Adjust calls to create_subprog_decl.
+	(build_raise_check): Likewise.
+	(establish_gnat_vms_condition_handler): Likewise.
+	(Compilation_Unit_to_gnu): Likewise.
+	(gnat_to_gnu): Likewise.
+
+2011-04-21  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/Makefile.in (NO_SIBLING_ADAFLAGS): Always define.
+	(NO_REORDER_ADAFLAGS): New variable.
+	(EXTRA_GNATTOOLS): Always define.
+	(../stamp-gnatlib1-$(RTSDIR): Copy tsystem.h.
+	Clean up and adjust list of files compiled with special options.
+	* gcc-interface/Make-lang.in: Likewise.
+	(ada/decl.o): Cosmetical change.
+	(ada/misc.o): Remove dependency on $(PLUGIN_H).
+
+2011-04-20  Jim Meyering  <meyering@redhat.com>
+
+	* initialize.c (__gnat_initialize): Remove useless if-before-free.
+
+2011-04-17  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/Make-lang.in (gnatbind): Replace $(ALL_CFLAGS) with
+	$(CFLAGS) on the link line.
+
+2011-04-17  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (gnat_to_gnu_entity) <E_Function>: Declare the
+	padded type built for the return type if it is unconstrained.
+
+2011-04-14  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* gcc-interface/utils.c (gnat_poplevel): Use block_chainon.
+
+2011-04-12  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* gcc-interface/ada-tree.h (union lang_tree_node): Check for TS_COMMON
+	before calling TREE_CHAIN.
+	* gcc-interface/misc.c (gnat_init_ts): New function.
+	(LANG_HOOKS_INIT_TS): Define.
+
+2011-04-12  Martin Jambor  <mjambor@suse.cz>
+
+	* gcc-interface/utils.c (end_subprog_body): Call cgraph_get_create_node
+	instead of cgraph_node.
+
+2011-04-08  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (gnat_to_gnu_entity) <E_Procedure>: Set minimum
+	alignment on fields of the RETURN type built for the Copy-In Copy-Out
+	mechanism.
+
+2011-04-08  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/trans.c (Identifier_to_gnu): Do not return initializers
+	of aggregate types that contain a placeholder.
+
+2011-04-08  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* gcc-interface/utils.c (handle_sentinel_attribute): Don't use
+	TYPE_ARG_TYPES.
+	(handle_type_generic_attribute): Likewise.
+
+2011-04-04  Eric Botcazou  <ebotcazou@adacore.com>
+
+	PR ada/47163
+	* s-oscons-tmplt.c (MSG_WAITALL): Fix thinko in previous change.
+
+2011-04-04  Kai Tietz  <ktietz@redhat.com>
+
+	PR ada/47163
+	* s-oscons-tmplt.c (MSG_WAITALL): Define it for native windows targets
+	to flag value.
+
+2011-04-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/utils2.c (build_allocator): In the unconstrained array
+	type case, do not strip a padding type around the array type.
+
+2011-04-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/utils.c (update_pointer_to): Finalize named pointer
+	types.
+
+2011-04-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/lang.opt (feliminate-unused-debug-types): Delete.
+	* gcc-interface/misc.c (gnat_handle_option): Remove special handling
+	code for -feliminate-unused-debug-types.
+	(gnat_post_options): Likewise.
+
+2011-04-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/utils.c (gnat_pushdecl): If this is a non-artificial
+	declaration of a pointer type, then set DECL_ORIGINAL_TYPE to a
+	distinct copy.
+
+2011-04-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (gnat_to_gnu_entity): Do not force the
+	DECL_ARTIFICIAL flag on enumeration types.
+
+2011-04-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (gnat_to_gnu_entity) <E_Array_Type>: Do not make
+	fat pointer types artificial unconditionally.
+	<E_Array_Subtype>: Attach the base array type as a parallel type if it
+	isn't artificial.
+
+2011-04-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/gigi.h (get_dummy_type): Declare.
+	(build_dummy_unc_pointer_types): Likewise.
+	(finish_fat_pointer_type): Likewise.
+	* gcc-interface/decl.c (gnat_to_gnu_entity) <E_Array_Type>: If a dummy
+	fat pointer type has been built, complete it in place.
+	<E_Access_Type>: Call build_dummy_unc_pointer_types to build dummy fat
+	and thin pointers.  Remove useless variable.
+	(finish_fat_pointer_type): Make global and move to...
+	* gcc-interface/utils.c (finish_fat_pointer_type): ...here.
+	(get_dummy_type): New function.
+	(build_dummy_unc_pointer_types): Likewise.
+	(gnat_pushdecl): Propage the name to the anonymous variants only.
+	(update_pointer_to): Only adjust the pointer types in the unconstrained
+	array case.
+
+2011-04-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/ada-tree.h (DECL_TAFT_TYPE_P): New flag.
+	* gcc-interface/decl.c (gnat_to_gnu_entity) <E_Incomplete_Type>: Set it
+	if this is a Taft amendment type and the full declaration is available.
+	* gcc-interface/trans.c (process_type): Likewise.
+	If there is an old type, mark the new one as used if DECL_TAFT_TYPE_P.
+	(process_freeze_entity): Likewise.
+	* gcc-interface/utils.c (dummy_global): New static variable.
+	(gnat_write_global_declarations): If there are types declared as used
+	at the global level, insert them in the global hash table.
+
+2011-04-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/gigi.h (record_builtin_type): Add ARTIFICIAL_P param.
+	* gcc-interface/utils.c (gnat_pushdecl): If this is a non-artificial
+	declaration of an array type, then set DECL_ORIGINAL_TYPE to a distinct
+	copy.
+	(record_builtin_type): Add ARTIFICIAL_P parameter.  Set DECL_ARTIFICIAL
+	flag of the type accordingly.
+	* gcc-interface/trans.c (gigi): Adjust calls to record_builtin_type.
+
+2011-04-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (gnat_to_gnu_entity) <E_Access_Type>: Defer
+	finalizing types when updating the pointers to the designated type.
+	<all>: Finalize the deferred types even if we didn't defer processing
+	of incomplete types in this invocation.
+
+2011-04-01  Olivier Hainque  <hainque@adacore.com>
+            Nicolas Setton  <setton@adacore.com>
+            Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/misc.c (gnat_descriptive_type): New function.
+	(LANG_HOOKS_DESCRIPTIVE_TYPE): Redefine to gnat_descriptive_type.
+
+2011-03-28  Kai Tietz  <ktietz@redhat.com>
+
+	* gcc-interface/Makefile.in (SO_LIB): Handle multilib build for native
+	Windows targets.
+	(EH_MECHANISM): Use GCC exception mechanism for native Windows targets.
+	* system-mingw.ads (System): Change ZCX_By_Default default to True.
+
+	* raise-gcc.c (PERSONALITY_FUNCTION): Add prototype.
+
+2011-03-28  Tristan Gingold  <gingold@adacore.com>
+
+	PR ada/44431
+	* gcc-interface/Make-lang.in (ada/b_gnat1.adb): Replace ada/b_gnat1.c.
+	Use ada output of gnatbind.
+	(ada/b_gnatb.adb): Ditto.
+	(ada/b_gnat1.o, ada/b_gnatb.o): New rules.
+	(ada.mostlyclean, ada.stage1)
+	(ada.stage2, ada.stage3, ada.stage4, ada.stageprofile)
+	(ada.stagefeedback): Adjust.
+	* gcc-interface/Makefile.in (b_gnatl.adb): Replace b_gnatl.c.
+	Use ada output of gnatbind.
+	(b_gnatm.adb): Ditto.
+	(b_gnatl.o, b_gnatm.o): New rules.
+
+2011-03-26  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (gnat_to_gnu_entity) <object>: Create TYPE_DECL
+	for the padded type built to support a specified size or alignment.
+
+2011-03-26  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/gigi.h (finalize_from_with_types): Adjust comment.
+	* gcc-interface/decl.c (gnat_to_gnu_entity) <E_Access_Type>: Defer
+	unconditionally to the end of the unit when the designated type is
+	limited_with'ed.
+	<all>: Rename local variable.  Attempt to un-defer types only and do it
+	for limited_with'ed types as well.
+	(finalize_from_with_types): Adjust comment.  Rename variable and tidy.
+	* gcc-interface/trans.c (Compilation_Unit_to_gnu): Use GNAT_UNIT
+	consistently and remove redundant call to finalize_from_with_types.
+
+2011-03-26  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* inline.adb (Back_End_Cannot_Inline): Lift restriction on calls to
+	subprograms without a previous spec declared in the same unit.
+	* gcc-interface/trans.c (Compilation_Unit_to_gnu): Process inlined
+	subprograms at the end of the unit instead of at the beginning.
+	* gcc-interface/utils.c (create_subprog_decl): Check that the entity
+	isn't public for the special handling of non-inline functions nested
+	inside inline external functions.
+
+2011-03-25  Jeff Law  <law@redhat.com>
+
+	* gcc-interface/utils.c (def_fn_type): Add missing va_end.
+
+2011-03-24  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* einfo.ads (Size_Depends_On_Discriminant): Adjust description.
+	* layout.adb (Compute_Size_Depends_On_Discriminant): New procedure
+	to compute Set_Size_Depends_On_Discriminant.
+	(Layout_Type): Call it on array types in back-end layout mode.
+	* sem_util.adb (Requires_Transient_Scope): Return true for array
+	types only if the size depends on the value of discriminants.
+	* gcc-interface/utils2.c (build_binary_op) <MODIFY_EXPR>: Use the RHS
+	type if the RHS is a call to a function that returns an unconstrained
+	type with default discriminant.
+
+2011-03-24  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/trans.c (gnat_to_gnu): Remove obsolete case of
+	non-conversion to the nominal result type at the end.
+
+2011-03-23  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/trans.c (create_temporary): New function taken from...
+	(create_init_temporary): ...here.  Call it.
+	(call_to_gnu): Create the temporary for the return value early, if any.
+	Create it for a function with copy-in/copy-out parameters if there is
+	no target; in other cases of copy-in/copy-out, use another temporary.
+	Push the new binding level lazily.  Add and rename local variables.
+
+2011-03-23  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (validate_size): Improve comments and tweak
+	error message.
+	(set_rm_size): Likewise.
+
+2011-03-23  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (gnat_to_gnu_entity) <object>: Create TYPE_DECL
+	for the padded type built in order to support a specified alignment.
+	Fix incorrect formatting.
+
+2011-03-21  Eric Botcazou  <ebotcazou@adacore.com>
+
+	PR bootstrap/48216
+	* gcc-interface/decl.c (elaborate_expression_1): Localize GNU_DECL.
+
+2011-03-21  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (components_to_record): Add REORDER parameter,
+	rename DEBUG_INFO_P into DEBUG_INFO and move P_GNU_REP_LIST parameter
+	to the end of the list.  Adjust recursive call.  Rename local variable.
+	If REORDER is true, reorder components of the record type.
+	(gnat_to_gnu_entity): Pass OK_To_Reorder_Components flag as argument to
+	components_to_record and adjust the parameter list.
+
+2011-03-21  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (elaborate_expression_1): When optimization is
+	disabled, use the variable for bounds of loop iteration scheme.
+
+2011-03-21  Kai Tietz  <ktietz@redhat.com>
+
+	PR target/12171
+	* gcc-interface/utils.c (gnat_internal_attribute_table): Add column.
+
+2011-03-17  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c (elaborate_expression_1): Try harder to find
+	out whether the expression is read-only.  Short-circuit placeholder
+	case and rename a couple of local variables.
+
+2011-03-17  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/gigi.h (smaller_form_type_p): Declare.
+	* gcc-interface/trans.c (smaller_form_type_p): Make global and move...
+	* gcc-interface/utils.c (smaller_form_type_p): ...to here.
+	(convert): Deal with conversions from a smaller form type specially.
+
+2011-02-14  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/misc.c (gnat_init_options): Do not concatenate -I and
+	its argument, except for the special -I- switch.
+
+2011-02-12  Gerald Pfeifer  <gerald@pfeifer.com>
+
+	* gnat_ugn.texi (Compiling Different Versions of Ada): Update link to
+	"Ada Issues".
+
+2011-02-08  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/Makefile.in (x86-64 darwin): Handle multilibs.
+
+2011-02-03  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/gigi.h (fill_vms_descriptor): Take GNU_TYPE instead of
+	GNAT_FORMAL.
+	* gcc-interface/utils2.c (fill_vms_descriptor): Move from here to...
+	* gcc-interface/utils.c (fill_vms_descriptor): ...here.  Take GNU_TYPE
+	instead of GNAT_FORMAL.  Protect the expression against multiple uses.
+	Do not generate the check directly, instead instantiate the template
+	check present in the descriptor.
+	(make_descriptor_field): Move around.
+	(build_vms_descriptor32): Build a template check in the POINTER field.
+	(build_vms_descriptor): Remove useless suffixes.
+	* gcc-interface/trans.c (call_to_gnu): Adjust fill_vms_descriptor call.
+
+2011-01-26  Eric Botcazou  <ebotcazou@adacore.com>
+
+	PR bootstrap/47467
+	* targext.c: Include target files if IN_RTS is defined.
+
+2011-01-26  Richard Guenther  <rguenther@suse.de>
+
+	PR bootstrap/47467
+	* targext.c: Include config.h.
+	* gcc-interface/Make-lang.in (ada/targext.o): Add $(CONFIG_H)
+	dependency.
+
+2011-01-04  Pascal Obry  <obry@adacore.com>
+            Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/decl.c: Disable Stdcall convention handling for 64-bit.
+
+2011-01-04  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/trans.c (Case_Statement_to_gnu): Put the SLOC of the
+	end-of-case on the end label and its associated gotos, if any.
+
+2011-01-04  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/trans.c (Subprogram_Body_to_gnu): Evaluate the
+	expressions of the parameter cache within the statement group of
+	the CICO mechanism.
+
+2011-01-04  Olivier Hainque  <hainque@adacore.com>
+            Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/trans.c (BLOCK_SOURCE_END_LOCATION): Provide default.
+	(set_end_locus_from_node): New function.
+	(Subprogram_Body_to_gnu): Use it to mark both the inner BIND_EXPR we
+	make and the function end_locus.
+	(Compilation_Unit_to_gnu): Call it instead of a straight Sloc_to_locus
+	for the elaboration subprogram.
+	(set_gnu_expr_location_from_node) <default case>: Use it to attempt to
+	set the end_locus of the expression as well.
+
+2011-01-04  Eric Botcazou  <ebotcazou@adacore.com>
+
+	PR ada/47131
+	* gcc-interface/trans.c (Identifier_to_gnu): In SJLJ mode, do not make
+	variables that are referenced in exception handlers volatile.
+
+
 
 Copyright (C) 2011 Free Software Foundation, Inc.
 
diff --git a/gcc/ada/adaint.c b/gcc/ada/adaint.c
index fd305e67011f2674ee155ac196e965c1b4fe7ac2..446f50018dae778e7ba50535a1284d4c881a6d8d 100644
--- a/gcc/ada/adaint.c
+++ b/gcc/ada/adaint.c
@@ -2700,10 +2700,11 @@ __gnat_os_exit (int status)
   exit (status);
 }
 
-/* Locate a regular file, give a Path value.  */
+/* Locate file on path, that matches a predicate */
 
 char *
-__gnat_locate_regular_file (char *file_name, char *path_val)
+__gnat_locate_file_with_predicate
+   (char *file_name, char *path_val, int (*predicate)(char*))
 {
   char *ptr;
   char *file_path = (char *) alloca (strlen (file_name) + 1);
@@ -2733,7 +2734,7 @@ __gnat_locate_regular_file (char *file_name, char *path_val)
 
   if (absolute)
     {
-     if (__gnat_is_regular_file (file_path))
+     if (predicate (file_path))
        return xstrdup (file_path);
 
       return 0;
@@ -2746,7 +2747,7 @@ __gnat_locate_regular_file (char *file_name, char *path_val)
 
   if (*ptr != 0)
     {
-      if (__gnat_is_regular_file (file_name))
+      if (predicate (file_name))
         return xstrdup (file_name);
     }
 
@@ -2787,7 +2788,7 @@ __gnat_locate_regular_file (char *file_name, char *path_val)
 
       strcpy (++ptr, file_name);
 
-      if (__gnat_is_regular_file (file_path))
+      if (predicate (file_path))
         return xstrdup (file_path);
 
       if (*path_val == 0)
@@ -2802,6 +2803,24 @@ __gnat_locate_regular_file (char *file_name, char *path_val)
   return 0;
 }
 
+/* Locate an executable file, give a Path value.  */
+
+char *
+__gnat_locate_executable_file (char *file_name, char *path_val)
+{
+   return __gnat_locate_file_with_predicate
+      (file_name, path_val, &__gnat_is_executable_file);
+}
+
+/* Locate a regular file, give a Path value.  */
+
+char *
+__gnat_locate_regular_file (char *file_name, char *path_val)
+{
+   return __gnat_locate_file_with_predicate
+      (file_name, path_val, &__gnat_is_regular_file);
+}
+
 /* Locate an executable given a Path argument. This routine is only used by
    gnatbl and should not be used otherwise.  Use locate_exec_on_path
    instead.  */
@@ -2818,14 +2837,14 @@ __gnat_locate_exec (char *exec_name, char *path_val)
 
       strcpy (full_exec_name, exec_name);
       strcat (full_exec_name, HOST_EXECUTABLE_SUFFIX);
-      ptr = __gnat_locate_regular_file (full_exec_name, path_val);
+      ptr = __gnat_locate_executable_file (full_exec_name, path_val);
 
       if (ptr == 0)
-         return __gnat_locate_regular_file (exec_name, path_val);
+         return __gnat_locate_executable_file (exec_name, path_val);
       return ptr;
     }
   else
-    return __gnat_locate_regular_file (exec_name, path_val);
+    return __gnat_locate_executable_file (exec_name, path_val);
 }
 
 /* Locate an executable using the Systems default PATH.  */
diff --git a/gcc/ada/erroutc.ads b/gcc/ada/erroutc.ads
index df29bad07a3eda61453bdf8f72c5b59a73d64f41..a2ac46329d43a2ae854832830786ae51fa3fcd25 100644
--- a/gcc/ada/erroutc.ads
+++ b/gcc/ada/erroutc.ads
@@ -219,33 +219,33 @@ package Erroutc is
    --  error message table, since messages are not always inserted in sequence.
 
    Last_Error_Msg : Error_Msg_Id;
-   --  The last entry on the list of error messages. Note that this is not
-   --  the same as the physically last entry in the error message table, since
-   --  messages are not always inserted in sequence.
+   --  The last entry on the list of error messages. Note: this is not the same
+   --  as the physically last entry in the error message table, since messages
+   --  are not always inserted in sequence.
 
    --------------------------
    -- Warning Mode Control --
    --------------------------
 
-   --  Pragma Warnings allows warnings to be turned off for a specified
-   --  region of code, and the following tables are the data structures used
-   --  to keep track of these regions.
+   --  Pragma Warnings allows warnings to be turned off for a specified region
+   --  of code, and the following tables are the data structures used to keep
+   --  track of these regions.
 
-   --  The first table is used for the basic command line control, and for
-   --  the forms of Warning with a single ON or OFF parameter.
+   --  The first table is used for the basic command line control, and for the
+   --  forms of Warning with a single ON or OFF parameter.
 
    --  It contains pairs of source locations, the first being the start
    --  location for a warnings off region, and the second being the end
-   --  location. When a pragma Warnings (Off) is encountered, a new entry
-   --  is established extending from the location of the pragma to the
-   --  end of the current source file. A subsequent pragma Warnings (On)
-   --  adjusts the end point of this entry appropriately.
+   --  location. When a pragma Warnings (Off) is encountered, a new entry is
+   --  established extending from the location of the pragma to the end of the
+   --  current source file. A subsequent pragma Warnings (On) adjusts the end
+   --  point of this entry appropriately.
 
-   --  If all warnings are suppressed by command switch, then there is a
-   --  dummy entry (put there by Errout.Initialize) at the start of the
-   --  table which covers all possible Source_Ptr values. Note that the
-   --  source pointer values in this table always reference the original
-   --  template, not an instantiation copy, in the generic case.
+   --  If all warnings are suppressed by command switch, then there is a dummy
+   --  entry (put there by Errout.Initialize) at the start of the table which
+   --  covers all possible Source_Ptr values. Note that the source pointer
+   --  values in this table always reference the original template, not an
+   --  instantiation copy, in the generic case.
 
    type Warnings_Entry is record
       Start : Source_Ptr;
@@ -280,9 +280,9 @@ package Erroutc is
       --  Set to True if entry has been used to suppress a warning
 
       Config : Boolean;
-      --  True if pragma is configuration pragma (in which case no matching
-      --  Off pragma is required, and it is not required that a specific
-      --  warning be suppressed).
+      --  True if pragma is configuration pragma (in which case no matching Off
+      --  pragma is required, and it is not required that a specific warning be
+      --  suppressed).
    end record;
 
    package Specific_Warnings is new Table.Table (
@@ -304,10 +304,10 @@ package Erroutc is
    --     end Mumble;
 
    --  The trouble is that the first pragma is technically a configuration
-   --  pragma, and yet it is clearly being used in the context of thinking
-   --  of it as a specific case. To deal with this, what we do is that the
-   --  On entry can match a configuration pragma from the same file, and if
-   --  we find such an On entry, we cancel the indication of it being the
+   --  pragma, and yet it is clearly being used in the context of thinking of
+   --  it as a specific case. To deal with this, what we do is that the On
+   --  entry can match a configuration pragma from the same file, and if we
+   --  find such an On entry, we cancel the indication of it being the
    --  configuration case. This seems to handle all cases we run into ok.
 
    -----------------
@@ -336,16 +336,16 @@ package Erroutc is
    --  output giving node number (of node N) if the debug X switch is set.
 
    procedure Check_Duplicate_Message (M1, M2 : Error_Msg_Id);
-   --  This function is passed the Id values of two error messages. If
-   --  either M1 or M2 is a continuation message, or is already deleted,
-   --  the call is ignored. Otherwise a check is made to see if M1 and M2
-   --  are duplicated or redundant. If so, the message to be deleted and
-   --  all its continuations are marked with the Deleted flag set to True.
+   --  This function is passed the Id values of two error messages. If either
+   --  M1 or M2 is a continuation message, or is already deleted, the call is
+   --  ignored. Otherwise a check is made to see if M1 and M2 are duplicated or
+   --  redundant. If so, the message to be deleted and all its continuations
+   --  are marked with the Deleted flag set to True.
 
    procedure Output_Error_Msgs (E : in out Error_Msg_Id);
-   --  Output source line, error flag, and text of stored error message and
-   --  all subsequent messages for the same line and unit. On return E is
-   --  set to be one higher than the last message output.
+   --  Output source line, error flag, and text of stored error message and all
+   --  subsequent messages for the same line and unit. On return E is set to be
+   --  one higher than the last message output.
 
    procedure Output_Line_Number (L : Logical_Line_Number);
    --  Output a line number as six digits (with leading zeroes suppressed),
@@ -366,9 +366,9 @@ package Erroutc is
    --  including the end points) will be deleted from the error listing.
 
    function Same_Error (M1, M2 : Error_Msg_Id) return Boolean;
-   --  See if two messages have the same text. Returns true if the text
-   --  of the two messages is identical, or if one of them is the same
-   --  as the other with an appended "instance at xxx" tag.
+   --  See if two messages have the same text. Returns true if the text of the
+   --  two messages is identical, or if one of them is the same as the other
+   --  with an appended "instance at xxx" tag.
 
    procedure Set_Msg_Blank;
    --  Sets a single blank in the message if the preceding character is a
diff --git a/gcc/ada/exp_ch3.adb b/gcc/ada/exp_ch3.adb
index c54f3b08ad2d8641bdddfe526063b951afe33e1c..540d395278787790409e3b2d460af7633c06b786 100644
--- a/gcc/ada/exp_ch3.adb
+++ b/gcc/ada/exp_ch3.adb
@@ -8459,15 +8459,15 @@ package body Exp_Ch3 is
          --  they may be ancestors of synchronized interface types).
 
          elsif (not Is_Interface (Tag_Typ)
-                  and then Is_Interface (Etype (Tag_Typ))
-                  and then Is_Limited_Record (Etype (Tag_Typ)))
+                 and then Is_Interface (Etype (Tag_Typ))
+                 and then Is_Limited_Record (Etype (Tag_Typ)))
              or else
                (Is_Concurrent_Record_Type (Tag_Typ)
-                  and then Has_Interfaces (Tag_Typ))
+                 and then Has_Interfaces (Tag_Typ))
              or else
                (not Tagged_Type_Expansion
-                  and then not Is_Interface (Tag_Typ)
-                  and then Tag_Typ = Root_Type (Tag_Typ))
+                 and then not Is_Interface (Tag_Typ)
+                 and then Tag_Typ = Root_Type (Tag_Typ))
          then
             Append_To (Res,
               Make_Subprogram_Declaration (Loc,
@@ -8944,10 +8944,10 @@ package body Exp_Ch3 is
         and then not Is_Interface (Tag_Typ)
         and then
           ((Is_Interface (Etype (Tag_Typ))
-              and then Is_Limited_Record (Etype (Tag_Typ)))
+             and then Is_Limited_Record (Etype (Tag_Typ)))
            or else
              (Is_Concurrent_Record_Type (Tag_Typ)
-                and then Has_Interfaces (Tag_Typ))
+               and then Has_Interfaces (Tag_Typ))
            or else
              (not Tagged_Type_Expansion
                and then Tag_Typ = Root_Type (Tag_Typ)))
diff --git a/gcc/ada/exp_ch9.adb b/gcc/ada/exp_ch9.adb
index 986ed35092b62092a58eaedd447f9a8db3c436fb..b8a89bcb55f4724f21e0d3c770e8b32698a3dfc9 100644
--- a/gcc/ada/exp_ch9.adb
+++ b/gcc/ada/exp_ch9.adb
@@ -8698,9 +8698,7 @@ package body Exp_Ch9 is
          if Tagged_Type_Expansion then
             Prepend_To (Params,
               Make_Function_Call (Loc,
-                Name =>
-                  New_Reference_To (RTE (RE_Get_Offset_Index), Loc),
-
+                Name => New_Reference_To (RTE (RE_Get_Offset_Index), Loc),
                 Parameter_Associations => New_List (
                   Unchecked_Convert_To (RTE (RE_Tag), Concval),
                   Make_Integer_Literal (Loc, DT_Position (Entity (Ename))))));
@@ -8710,20 +8708,20 @@ package body Exp_Ch9 is
          else
             Prepend_To (Params,
               Make_Function_Call (Loc,
-                Name =>
-                  New_Reference_To (RTE (RE_Get_Offset_Index), Loc),
+                Name => New_Reference_To (RTE (RE_Get_Offset_Index), Loc),
 
                 Parameter_Associations => New_List (
+
                   --  Obj_Typ
 
                   Make_Attribute_Reference (Loc,
-                    Prefix => Concval,
+                    Prefix         => Concval,
                     Attribute_Name => Name_Tag),
 
                   --  Tag_Typ
 
                   Make_Attribute_Reference (Loc,
-                    Prefix => New_Reference_To (Etype (Concval), Loc),
+                    Prefix         => New_Reference_To (Etype (Concval), Loc),
                     Attribute_Name => Name_Tag),
 
                   --  Position
diff --git a/gcc/ada/exp_disp.adb b/gcc/ada/exp_disp.adb
index 9b9946676392f3486ec604112505e8936e782c18..85abeafdb139a606549acf6a8466381c98baf5c6 100644
--- a/gcc/ada/exp_disp.adb
+++ b/gcc/ada/exp_disp.adb
@@ -6627,7 +6627,7 @@ package body Exp_Disp is
                            --  Iface_Tag
 
                          Make_Attribute_Reference (Loc,
-                           Prefix => New_Reference_To (Iface, Loc),
+                           Prefix         => New_Reference_To (Iface, Loc),
                            Attribute_Name => Name_Tag),
 
                            --  OSD
@@ -6648,7 +6648,7 @@ package body Exp_Disp is
                      Make_Subtype_Indication (Loc,
                        Subtype_Mark =>
                          New_Reference_To (RTE (RE_Interface_Data), Loc),
-                       Constraint => Make_Index_Or_Discriminant_Constraint
+                       Constraint   => Make_Index_Or_Discriminant_Constraint
                          (Loc,
                           Constraints => New_List (
                             Make_Integer_Literal (Loc, Num_Ifaces)))),
diff --git a/gcc/ada/exp_sel.adb b/gcc/ada/exp_sel.adb
index 0c17bd16374f2ae4094b67e94d83e6c2b9c3e77b..5596f8a10f967f4334a2ca4d45c7a94b85260756 100644
--- a/gcc/ada/exp_sel.adb
+++ b/gcc/ada/exp_sel.adb
@@ -156,7 +156,7 @@ package body Exp_Sel is
       else
          Tag_Node :=
            Make_Attribute_Reference (Loc,
-             Prefix => Obj,
+             Prefix         => Obj,
              Attribute_Name => Name_Tag);
       end if;
 
@@ -205,7 +205,7 @@ package body Exp_Sel is
       if Tagged_Type_Expansion then
          return
            Make_Assignment_Statement (Loc,
-             Name => New_Reference_To (S, Loc),
+             Name       => New_Reference_To (S, Loc),
              Expression =>
                Make_Function_Call (Loc,
                  Name => New_Reference_To (RTE (RE_Get_Offset_Index), Loc),
@@ -218,10 +218,11 @@ package body Exp_Sel is
       else
          return
            Make_Assignment_Statement (Loc,
-             Name => New_Reference_To (S, Loc),
+             Name       => New_Reference_To (S, Loc),
              Expression =>
                Make_Function_Call (Loc,
                  Name => New_Reference_To (RTE (RE_Get_Offset_Index), Loc),
+
                  Parameter_Associations => New_List (
 
                      --  Obj_Typ
diff --git a/gcc/ada/restrict.ads b/gcc/ada/restrict.ads
index 001d13166bbd93ed6fa84e51bd3e1e2471d27f6e..5472d056ee103d0360d68e68089bf83e7ad23bae 100644
--- a/gcc/ada/restrict.ads
+++ b/gcc/ada/restrict.ads
@@ -185,6 +185,10 @@ package Restrict is
    --  The table contains pairs of source locations, the first being the start
    --  location for hidden region, and the second being the end location.
 
+   --  Note that the start location is included in the hidden region, while
+   --  the end location is excluded from it. (It typically corresponds to the
+   --  next token during scanning.)
+
    type SPARK_Hide_Entry is record
       Start : Source_Ptr;
       Stop  : Source_Ptr;
@@ -310,8 +314,8 @@ package Restrict is
    function Get_Restriction_Id
      (N : Name_Id) return Restriction_Id;
    --  Given an identifier name, determines if it is a valid restriction
-   --  identifier, and if so returns the corresponding Restriction_Id
-   --  value, otherwise returns Not_A_Restriction_Id.
+   --  identifier, and if so returns the corresponding Restriction_Id value,
+   --  otherwise returns Not_A_Restriction_Id.
 
    function Is_In_Hidden_Part_In_SPARK (Loc : Source_Ptr) return Boolean;
    --  Determine if given location is covered by a hidden region range in the
@@ -358,9 +362,9 @@ package Restrict is
 
    function Restricted_Profile return Boolean;
    --  Tests if set of restrictions corresponding to Profile (Restricted) is
-   --  currently in effect (set by pragma Profile, or by an appropriate set
-   --  of individual Restrictions pragmas). Returns True only if all the
-   --  required restrictions are set.
+   --  currently in effect (set by pragma Profile, or by an appropriate set of
+   --  individual Restrictions pragmas). Returns True only if all the required
+   --  restrictions are set.
 
    procedure Set_Hidden_Part_In_SPARK (Loc1, Loc2 : Source_Ptr);
    --  Insert a new hidden region range in the SPARK hides table
@@ -394,8 +398,8 @@ package Restrict is
      (Unit    : Node_Id;
       Warn    : Boolean;
       Profile : Profile_Name := No_Profile);
-   --  Sets given No_Dependence restriction in table if not there already.
-   --  Warn is True if from Restriction_Warnings, or for Restrictions if flag
+   --  Sets given No_Dependence restriction in table if not there already. Warn
+   --  is True if from Restriction_Warnings, or for Restrictions if the flag
    --  Treat_Restrictions_As_Warnings is set. False if from Restrictions and
    --  this flag is not set. Profile is set to a non-default value if the
    --  No_Dependence restriction comes from a Profile pragma.
diff --git a/gcc/ada/sinfo.adb b/gcc/ada/sinfo.adb
index 571541af26e33ab371710b30678f307dc4de8bca..fb9ab568f8b27eb05842b3c30a3714e2070bbf26 100644
--- a/gcc/ada/sinfo.adb
+++ b/gcc/ada/sinfo.adb
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---          Copyright (C) 1992-2010, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2011, Free Software Foundation, Inc.         --
 --                                                                          --
 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
 -- terms of the  GNU General Public License as published  by the Free Soft- --
@@ -1440,11 +1440,17 @@ package body Sinfo is
    function Has_Dynamic_Length_Check
       (N : Node_Id) return Boolean is
    begin
+      pragma Assert (False
+        or else NT (N).Nkind in N_Subexpr);
       return Flag10 (N);
    end Has_Dynamic_Length_Check;
+
    function Has_Dynamic_Range_Check
       (N : Node_Id) return Boolean is
    begin
+      pragma Assert (False
+        or else NT (N).Nkind =  N_Subtype_Declaration
+        or else NT (N).Nkind in N_Subexpr);
       return Flag12 (N);
    end Has_Dynamic_Range_Check;
 
@@ -4484,12 +4490,17 @@ package body Sinfo is
    procedure Set_Has_Dynamic_Length_Check
       (N : Node_Id; Val : Boolean := True) is
    begin
+      pragma Assert (False
+        or else NT (N).Nkind in N_Subexpr);
       Set_Flag10 (N, Val);
    end Set_Has_Dynamic_Length_Check;
 
    procedure Set_Has_Dynamic_Range_Check
       (N : Node_Id; Val : Boolean := True) is
    begin
+      pragma Assert (False
+        or else NT (N).Nkind =  N_Subtype_Declaration
+        or else NT (N).Nkind in N_Subexpr);
       Set_Flag12 (N, Val);
    end Set_Has_Dynamic_Range_Check;
 
diff --git a/gcc/ada/sinfo.ads b/gcc/ada/sinfo.ads
index e5ca5aae247007e520b4299296966a80e43ab6f7..88bcafbd12592fb612630090acd0af2506c6ec0b 100644
--- a/gcc/ada/sinfo.ads
+++ b/gcc/ada/sinfo.ads
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 S p e c                                  --
 --                                                                          --
---          Copyright (C) 1992-2010, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2011, Free Software Foundation, Inc.         --
 --                                                                          --
 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
 -- terms of the  GNU General Public License as published  by the Free Soft- --
@@ -424,6 +424,8 @@ package Sinfo is
    --       Raises_Constraint_Error  (Flag7-Sem)  evaluation raises CE
    --       Must_Not_Freeze          (Flag8-Sem)  set if must not freeze
    --       Do_Range_Check           (Flag9-Sem)  set if a range check needed
+   --       Has_Dynamic_Length_Check (Flag10-Sem) set if length check inserted
+   --       Has_Dynamic_Range_Check  (Flag12-Sem) set if range check inserted
    --       Assignment_OK            (Flag15-Sem) set if modification is OK
    --       Is_Controlling_Actual    (Flag16-Sem) set for controlling argument
 
@@ -485,18 +487,6 @@ package Sinfo is
    --    refers to a node or is posted on its source location, and has the
    --    effect of inhibiting further messages involving this same node.
 
-   --  Has_Dynamic_Length_Check (Flag10-Sem)
-   --    This flag is present on all nodes. It is set to indicate that one of
-   --    the routines in unit Checks has generated a length check action which
-   --    has been inserted at the flagged node. This is used to avoid the
-   --    generation of duplicate checks.
-
-   --  Has_Dynamic_Range_Check (Flag12-Sem)
-   --    This flag is present on all nodes. It is set to indicate that one of
-   --    the routines in unit Checks has generated a range check action which
-   --    has been inserted at the flagged node. This is used to avoid the
-   --    generation of duplicate checks.
-
    ------------------------------------
    -- Description of Semantic Fields --
    ------------------------------------
@@ -1125,6 +1115,19 @@ package Sinfo is
    --    handler is deleted during optimization. For further details on why
    --    this is required, see Exp_Ch11.Remove_Handler_Entries.
 
+   --  Has_Dynamic_Length_Check (Flag10-Sem)
+   --    This flag is present on all expression nodes. It is set to indicate
+   --    that one of the routines in unit Checks has generated a length check
+   --    action which has been inserted at the flagged node. This is used to
+   --    avoid the generation of duplicate checks.
+
+   --  Has_Dynamic_Range_Check (Flag12-Sem)
+   --    This flag is present in N_Subtype_Declaration nodes and on all
+   --    expression nodes. It is set to indicate that one of the routines in
+   --    unit Checks has generated a range check action which has been inserted
+   --    at the flagged node. This is used to avoid the generation of duplicate
+   --    checks.
+
    --  Has_Local_Raise (Flag8-Sem)
    --    Present in exception handler nodes. Set if the handler can be entered
    --    via a local raise that gets transformed to a goto statement. This will
@@ -2217,6 +2220,7 @@ package Sinfo is
       --  Subtype_Indication (Node5)
       --  Generic_Parent_Type (Node4-Sem) (set for an actual derived type).
       --  Exception_Junk (Flag8-Sem)
+      --  Has_Dynamic_Range_Check (Flag12-Sem)
 
       -------------------------------
       -- 3.2.2  Subtype Indication --