* gcc-interface/utils.c (convert) <RECORD_TYPE>: Add comment and do
[official-gcc.git] / gcc / ada / ChangeLog
blob35062ddc50fa3c70bab7407bfe35d5a7118f0688
1 2017-11-10  Eric Botcazou  <ebotcazou@adacore.com>
3         * gcc-interface/utils.c (convert) <RECORD_TYPE>: Add comment and do
4         not fall through to the next case.
5         <ARRAY_TYPE>: Deal specially with a dereference from another array
6         type with the same element type.
8 2017-11-09  Gary Dismukes  <dismukes@adacore.com>
10         * exp_util.adb, freeze.adb: Minor reformatting.
12 2017-11-09  Jerome Lambourg  <lambourg@adacore.com>
14         * gcc-interface/Makefile.in: Add rules to build aarch64-qnx runtimes.
16 2017-11-09  Hristian Kirtchev  <kirtchev@adacore.com>
18         * gcc-interface/trans.c (gnat_to_gnu): Add processing for
19         N_Variable_Reference_Marker nodes.
21 2017-11-09  Ed Schonberg  <schonberg@adacore.com>
23         * sem_ch12.adb (Analyze_Generic_Package_Declaration): Handle properly
24         the pragma Compile_Time_Error when it appears in a generic package
25         declaration and uses an expanded name to denote the current unit.
27 2017-11-09  Jerome Lambourg  <lambourg@adacore.com>
29         * libgnarl/s-taprop__qnx.adb: Fix incorrect casing for pthread_self.
30         * tracebak.c: Add support for tracebacks in QNX.
32 2017-11-09  Eric Botcazou  <ebotcazou@adacore.com>
34         * exp_aggr.adb (Aggr_Size_OK): Bump base limit from 50000 to 500000.
36 2017-11-09  Yannick Moy  <moy@adacore.com>
38         * erroutc.adb, set_targ.adb: Remove pragma Annotate for CodePeer
39         justification.
41 2017-11-09  Joel Brobecker  <brobecker@adacore.com>
43         * doc/gnat_ugn/platform_specific_information.rst: Document packages
44         needed on GNU/Linux by GNAT.
45         * gnat_ugn.texi: Regenerate.
47 2017-11-09  Hristian Kirtchev  <kirtchev@adacore.com>
49         * contracts.adb (Analyze_Contracts): Remove the three parameter
50         version. This routine now only analyzes contracts and does not perform
51         any freezing actions.
52         (Analyze_Previous_Contracts): Removed.
53         (Freeze_Previous_Contracts): New routine.
54         * contracts.ads (Analyze_Previous_Contracts): Removed.
55         (Freeze_Previous_Contracts): New routine.
56         * sem_ch3.adb (Analyze_Declarations): Analyze the contract of an
57         enclosing package spec regardless of whether the list denotes the
58         visible or private declarations.  Fix the removal of partial state
59         refinements when the context is a package spec.
60         * sem_ch6.adb (Analyze_Subprogram_Body_Helper): Freeze previous
61         contracts.
62         * sem_ch7.adb (Analyze_Package_Body_Helper): Freeze previous contracts.
63         * sem_ch9.adb (Analyze_Entry_Body): Freeze previous contracts.
64         (Analyze_Protected_Body): Freeze previous contracts.
65         (Analyze_Task_Body): Freeze previous contracts.
66         * sem_prag.adb: Comment reformatting.
68 2017-11-09  Bob Duff  <duff@adacore.com>
70         * libgnarl/g-thread.ads, libgnarl/g-thread.adb: (Make_Independent):
71         Export this so users can use it without importing
72         System.Tasking.Utilities.
73         * libgnarl/s-tassta.adb (Vulnerable_Complete_Task): Relax assertion
74         that fails when Make_Independent is called on a user task.
75         * libgnarl/s-taskin.ads (Master_Of_Task): Avoid unusual
76         capitalization style ((style) bad casing of "Master_of_Task").
78 2017-11-09  Ed Schonberg  <schonberg@adacore.com>
80         * sem_ch12.adb (Analyze_Subprogram_Instantiation): Correct use of
81         uninitialized variable uncovered by Codepeer.
83 2017-11-09  Arnaud Charlet  <charlet@adacore.com>
85         * namet.adb: Replace pragma Assume by pragma Assert to fix bootstrap.
87 2017-11-09  Javier Miranda  <miranda@adacore.com>
89         * doc/gnat_rm/standard_and_implementation_defined_restrictions.rst:
90         (Static_Dispatch_Tables): Minor rewording.
91         * gnat_rm.texi: Regenerate.
93 2017-11-09  Justin Squirek  <squirek@adacore.com>
95         * sem_ch8.adb (Analyze_Use_Package): Remove forced installation of
96         use_clauses within instances.
97         (Use_One_Package): Add condition to check for "hidden" open scopes to
98         avoid skipping over packages that have not been properly installed even
99         though they are visible.
101 2017-11-09  Ed Schonberg  <schonberg@adacore.com>
103         * sem_ch4.adb (Analyze_Selected_Component): Reject properly a call to a
104         private operation of a protected type, when the type has no visible
105         operations.
107 2017-11-09  Javier Miranda  <miranda@adacore.com>
109         * rtsfind.ads (RE_Id, RE_Unit_Table): Add RE_HT_Link.
110         * exp_disp.adb (Make_DT): Initialize the HT_Link field of the TSD only
111         if available.
113 2017-11-09  Bob Duff  <duff@adacore.com>
115         * exp_ch4.adb, exp_ch9.adb, exp_prag.adb, par-ch3.adb, sem_aggr.adb,
116         sem_ch12.adb, sem_ch13.adb, sem_ch4.adb, sem_disp.adb, sem_prag.adb,
117         sem_res.adb, sem_util.adb: Get rid of warnings about uninitialized
118         variables.
120 2017-11-09  Yannick Moy  <moy@adacore.com>
122         * exp_disp.adb (Make_DT): Default initialize Ifaces_List and
123         Ifaces_Comp_List.
125 2017-11-09  Pascal Obry  <obry@adacore.com>
127         * libgnarl/s-taprop__mingw.adb: On Windows, initialize the thead handle
128         only for foreign threads.  We initialize the thread handle only if not
129         yet initialized. This happens in Enter_Task for foreign threads only.
130         But for native threads (Ada tasking) we do want to keep the real
131         handle (from Create_Task) to be able to free the corresponding
132         resources in Finalize_TCB (CloseHandle).
134 2017-11-09  Yannick Moy  <moy@adacore.com>
136         * sem_attr.adb (Analyze_Attribute): Default initialize P_Type,
137         P_Base_Type.
138         (Error_Attr_P): Fix name in pragma No_Return.
139         (Unexpected_Argument): Add pragma No_Return.
140         (Placement_Error): Add pragma No_Return.
142 2017-11-09  Javier Miranda  <miranda@adacore.com>
144         * exp_disp.adb (Elab_Flag_Needed): Elaboration flag not needed when the
145         dispatch table is statically built.
146         (Make_DT): Declare constant the Interface_Table object associated with
147         an statically built dispatch table. For this purpose the Offset_To_Top
148         value of each interface is computed using the dummy object.
149         * exp_ch3.adb (Build_Init_Procedure): Do not generate code initializing
150         the Offset_To_Top field of secondary dispatch tables when the dispatch
151         table is statically built.
152         (Initialize_Tag): Do not generate calls to Register_Interface_Offset
153         when the dispatch table is statically built.
154         * doc/gnat_rm/standard_and_implementation_defined_restrictions.rst:
155         Document the new GNAT restriction Static_Dispatch_Tables.
156         * gnat_rm.texi: Regenerate.
158 2017-11-09  Hristian Kirtchev  <kirtchev@adacore.com>
160         * sem_aggr.adb (Resolve_Delta_Record_Aggregate): Reorder declarations
161         to avoid a dormant bug.
163 2017-11-09  Jerome Lambourg  <lambourg@adacore.com>
165         * init.c: Define missing __gnat_alternate_stack for QNX. Set it to 0,
166         as such capability is not available on the OS.
167         * link.c: Make sure linker options for QNX are correct.
168         * libgnarl/s-osinte__qnx.ads: Add some missing bindings to pthread.
169         * libgnarl/s-taprop__qnx.adb: New, derived from s-taprop__posix.adb. This brings
170         in particular a workaround with locks priority ceiling where a higher
171         priority task is allowed to lock a lower ceiling priority lock. This
172         also fixes the scheduling of FIFO tasks when the priority of a task is
173         lowered.
174         * libgnat/system-qnx-aarch64.ads: Fix priority ranges.
176 2017-11-09  Yannick Moy  <moy@adacore.com>
178         * erroutc.adb (Output_Error_Msgs): Justify CodePeer false positive
179         message.
180         * gnatbind.adb (Scan_Bind_Arg): Simplify test to remove always true
181         condition.
182         * namet.adb (Copy_One_Character): Add assumption for static analysis,
183         as knowledge that Hex(2) is in the range 0..255 is too complex for
184         CodePeer.
185         (Finalize): Add assumption for static analysis, as the fact that there
186         are symbols in the table depends on a global invariant at this point in
187         the program.
188         * set_targ.adb (Check_Spaces): Justify CodePeer false positive message.
189         * stylesw.adb (Save_Style_Check_Options): Rewrite to avoid test always
190         true.
192 2017-11-09  Javier Miranda  <miranda@adacore.com>
194         * libgnat/s-rident.ads (Static_Dispatch_Tables): New restriction name.
195         * exp_disp.adb (Building_Static_DT): Check restriction.
196         (Building_Static_Secondary_DT): Check restriction.
197         (Make_DT): Initialize the HT_Link to No_Tag.
198         * opt.ads (Static_Dispatch_Tables): Rename flag...
199         (Building_Static_Dispatch_Tables): ... into this.  This will avoid
200         conflict with the restriction name.
201         * gnat1drv.adb: Update.
202         * exp_aggr.adb (Is_Static_Dispatch_Table_Aggregate): Update.
203         * exp_ch3.adb (Expand_N_Object_Declaration): Update.
205 2017-11-09  Pascal Obry  <obry@adacore.com>
207         * libgnarl/s-taprop__mingw.adb: Minor code clean-up.  Better using a
208         named number.
210 2017-11-09  Yannick Moy  <moy@adacore.com>
212         * binde.adb (Diagnose_Elaboration_Problem): Mark procedure No_Return.
213         * checks.adb (Apply_Scalar_Range_Check): Rescope variable OK closer to
214         use.  Default initialize Hi, Lo.
215         (Selected_Range_Checks): Retype Num_Checks more precisely.
216         (Determine_Range, Determine_Range_R): Default initialize Hi_Right,
217         Lo_Right.
218         * contracts.adb (Process_Contract_Cases): Mark parameter Stmts as
219         Unmodified.
220         (Process_Postconditions): Mark parameter Stmts as Unmodified.
221         * exp_attr.adb (Expand_Loop_Entry_Attribute): Default initialize Blk.
222         * exp_ch4.adb (Expand_N_Allocator): Default initialize Typ.
223         (Expand_Concatenate): Default initialize High_Bound.
224         (Optimize_Length_Comparison): Default initialize Ent, Index.
225         * exp_ch5.adb (Expand_Predicated_Loop): Default initialize L_Hi and
226         L_Lo.
227         * exp_ch6.adb (Expand_N_Extended_Return_Statement): Default initialize
228         Return_Stmt.
229         * exp_ch9.adb (Expand_Entry_Barrier): Default initialize Func_Body and
230         remove pragma Warnings(Off).
231         * exp_imgv.adb (Expand_Image_Attribute): Default initialize Tent.
232         * exp_util.adb (Find_Interface_Tag): Default initialize AI_Tag.
233         * freeze.adb (Check_Component_Storage_Order): Default initialize
234         Comp_Byte_Aligned rather than silencing messages with pragma
235         Warnings(Off), which does not work for CodePeer initialization
236         messages, and given that here the possible read of an unitialized value
237         depends on a proper use of parameters by the caller.
238         * inline.adb (Expand_Inlined_Call): Default initialize Lab_Decl, Targ.
239         * sem_ch12.adb (Build_Operator_Wrapper): Default initialize Expr.
240         * sem_ch3.adb (Build_Derived_Array_Type): Default initialize
241         Implicit_Base.
242         * sem_ch4.adb (List_Operand_Interps): Default initialize Nam and remove
243         pragma Warnings(Off).
244         (Analyze_Case_Expression): Rescope checking block within branch where
245         Others_Present is set by the call to Check_Choices.
246         * sem_ch5.adb (Analyze_Assignment): Default initialize
247         Save_Full_Analysis.
248         * sem_ch6.adb (Analyze_Function_Return): Default initialize Obj_Decl,
249         and restructure code to defend against previous errors, so that, in
250         that case, control does not flow to the elsif condition which read an
251         uninitialized Obj_Decl.
252         * sem_ch9.adb (Analyze_Requeue): Default initialize Synch_Type.
253         (Check_Interfaces): Default initialize Full_T_Ifaces and Priv_T_Ifaces,
254         which seem to be left uninitialized and possibly read in some cases.
255         * sem_dim.adb (Analyze_Aspect_Dimension_System): Retype Position more
256         precisely.  This requires to exchange the test for exiting in case of
257         too many positions and the increment to Position, inside the loop.
258         * sem_eval.adb (Eval_Concatenation): Default initialize Folded_Val,
259         which cannot be read uninitialized, but the reasons for that are quite
260         subtle.
261         * sem_intr.adb (Check_Intrinsic_Call): Default initialize Rtyp.
262         * sem_prag.adb (Collect_Subprogram_Inputs_Outputs): Default initialize
263         Spec_Id.
264         * sem_res.adb (Make_Call_Into_Operator): Default initialize Opnd_Type,
265         and test for presence of non-null Opnd_Type before testing its scope,
266         in a test which would read its value uninitialized, and is very rarely
267         exercized (it depends on the presence of an extension of System).
268         * sem_spark.ads: Update comment to fix name of main analysis procedure.
269         * sem_warn.adb (Warn_On_Known_Condition): Default initialize
270         Test_Result.
271         * set_targ.adb (FailN): Mark procedure with No_Return.
272         * stylesw.adb (Save_Style_Check_Options): Delete useless code to
273         initialize all array Options to white space, as there is already code
274         doing the same for the remaining positions in Options at the end of the
275         procedure.
277 2017-11-09  Eric Botcazou  <ebotcazou@adacore.com>
279         * exp_ch11.adb (Possible_Local_Raise): Do not issue the warning for
280         generic instantiations either.
282 2017-11-09  Piotr Trojanek  <trojanek@adacore.com>
284         * sem_prag.adb (Analyze_Part_Of): Reword error message.
285         (Get_SPARK_Mode_Type): Do not raise Program_Error in case pragma
286         SPARK_Mode appears with an illegal mode, treat this as a non-existent
287         mode.
289 2017-11-09  Ed Schonberg  <schonberg@adacore.com>
291         * sem_ch4.adb (Analyze_Call): Reject a call to a function that returns
292         a limited view of a type T declared in unit U1, when the function is
293         declared in another unit U2 and the call appears in a procedure within
294         another unit.
296 2017-11-09  Justin Squirek  <squirek@adacore.com>
298         * sem_ch8.adb (Analyze_Use_Package): Force installation of use_clauses
299         when processing generic instances.
301 2017-11-09  Bob Duff  <duff@adacore.com>
303         * namet.ads, namet.adb (Valid_Name_Id): New subtype that excludes
304         Error_Name and No_Name.  Use this (versus Name_Id) to indicate which
305         objects can have those special values. Valid_Name_Id could usefully be
306         used all over the compiler front end, but that's too much trouble for
307         now. If we did that, we might want to rename:
308         Name_Id --> Optional_Name_Id, Valid_Name_Id --> Name_Id.
309         For parameters of type Valid_Name_Id, remove some redundant tests,
310         including the ones found by CodePeer.  Use Is_Valid_Name instead of
311         membership test when appropriate.
312         (Error_Name_Or_No_Name): Delete this; it's no longer needed.
313         * sem_ch2.adb (Analyze_Identifier): Use "not Is_Valid_Name" instead of
314         "in Error_Name_Or_No_Name".
315         (Check_Parameterless_Call): Use "not Is_Valid_Name" instead of "in
316         Error_Name_Or_No_Name".
318 2017-11-09  Arnaud Charlet  <charlet@adacore.com>
320         * gnat1drv.adb (Adjust_Global_Switches): Suppress warnings in codepeer
321         mode here unless -gnateC is specified.
322         * switch-c.adb (Scan_Front_End_Switches): Do not suppress warnings with
323         -gnatC here.
325 2017-11-09  Piotr Trojanek  <trojanek@adacore.com>
327         * lib-writ.adb (Write_ALI): Remove processing of the frontend xrefs as
328         part of the ALI writing; they are now processed directly from memory
329         when requested by the backend.
330         * lib-xref.ads (Collect_SPARK_Xrefs): Remove.
331         (Iterate_SPARK_Xrefs): New routine for iterating over frontend xrefs.
332         * lib-xref-spark_specific.adb (Traverse_Compilation_Unit): Remove.
333         (Add_SPARK_File): Remove.
334         (Add_SPARK_Xref): Refactored from removed code; filters xref entries
335         that are trivially uninteresting to the SPARK backend.
336         * spark_xrefs.ads: Remove code that is no longer needed.
337         * spark_xrefs.adb (dspark): Adapt to use Iterate_SPARK_Xrefs.
339 2017-11-09  Hristian Kirtchev  <kirtchev@adacore.com>
341         * sem_elab.adb: Update the documentation on adding a new elaboration
342         schenario. Add new hash table Recorded_Top_Level_Scenarios.
343         (Is_Check_Emitting_Scenario): Removed.
344         (Is_Recorded_Top_Level_Scenario): New routine.
345         (Kill_Elaboration_Scenario): Reimplemented.
346         (Record_Elaboration_Scenario): Mark the scenario as recorded.
347         (Set_Is_Recorded_Top_Level_Scenario): New routine.
348         (Update_Elaboration_Scenario): Reimplemented.
349         * sinfo.adb (Is_Recorded_Scenario): Removed.
350         (Set_Is_Recorded_Scenario): Removed.
351         * sinfo.ads: Remove attribute Is_Recorded_Scenario along with
352         occurrences in nodes.
353         (Is_Recorded_Scenario): Removed along with pragma Inline.
354         (Set_Is_Recorded_Scenario): Removed along with pragma Inline.
356 2017-11-09  Piotr Trojanek  <trojanek@adacore.com>
358         * sem_prag.adb (Analyze_Part_Of): Change "designate" to "denote" in
359         error message.
361 2017-11-09  Justin Squirek  <squirek@adacore.com>
363         * sem_res.adb (Resolve_Allocator): Add warning messages corresponding
364         to the allocation of an anonymous access-to-controlled object.
366 2017-11-09  Jerome Lambourg  <lambourg@adacore.com>
368         * sigtramp-qnx.c: Fix obvious typo.
370 2017-11-09  Doug Rupp  <rupp@adacore.com>
372         * libgnarl/s-taprop__linux.adb (Monotonic_Clock): Minor reformatting.
374 2017-11-09  Ed Schonberg  <schonberg@adacore.com>
376         * sem_res.adb (Resolve): If expression is an entity whose type has
377         implicit dereference, generate reference to it, because no reference is
378         generated for an overloaded entity during analysis, given that its
379         identity may not be known.
381 2017-11-09  Javier Miranda  <miranda@adacore.com>
383         * exp_disp.adb (Expand_Interface_Thunk): Replace substraction of
384         offset-to-top field by addition.
385         (Make_Secondary_DT): Initialize the offset-to-top field with a negative
386         offset.
387         * exp_ch3.adb (Build_Offset_To_Top_Function): Build functions that
388         return a negative offset-to-top value.
389         (Initialize_Tag): Invoke runtime services Set_Dynamic_Offset_To_Top and
390         Set_Static_Offset_To_Top passing a negative offet-to-top value;
391         initialize also the offset-to-top field with a negative offset.
392         * libgnat/a-tags.adb (Base_Address): Displace the pointer by means of
393         an addition since the offset-to-top field is now a negative value.
394         (Displace): Displace the pointer to the object means of a substraction
395         since it is now a negative value.
396         (Set_Dynamic_Offset_to_top): Displace the pointer to the object by
397         means of a substraction since it is now a negative value.
399 2017-11-09  Eric Botcazou  <ebotcazou@adacore.com>
401         * gnat1drv.adb (Gnat1drv): Call Errout.Finalize (Last_Call => True)
402         before Errout.Output_Messages also in the case of compilation errors.
404 2017-11-09  Javier Miranda  <miranda@adacore.com>
406         * doc/gnat_ugn/the_gnat_compilation_model.rst (Interfacing with C++ at
407         the Class Level): Fix error interfacing with C strings.
408         * gnat_ugn.texi: Regenerate.
410 2017-11-09  Jerome Lambourg  <lambourg@adacore.com>
412         * system-qnx-aarch64.ads: Fix the priority constants.
413         * s-osinte__qnx.ads: Fix constants for handling the locking protocols
414         and scheduling.
415         * s-osinte__qnx.adb: New file , prevents the use of priority 0 that
416         corresponds to an idle priority on QNX.
418 2017-11-09  Piotr Trojanek  <trojanek@adacore.com>
420         * sem_prag.adb, sem_util.adb, sem_elab.adb: Fix minor typos in
421         comments.
423 2017-11-09  Piotr Trojanek  <trojanek@adacore.com>
425         * lib-xref-spark_specific.adb (Add_SPARK_Xrefs): Ignore loop parameters
426         in expression funtions that are expanded into variables.
428 2017-11-09  Piotr Trojanek  <trojanek@adacore.com>
430         * sem_util.adb: Minor whitespace cleanup.
432 2017-11-09  Jerome Lambourg  <lambourg@adacore.com>
434         * libgnarl/s-taprop__qnx.adb: Refine aarch64-qnx. Use the POSIX
435         s-taprop version rather than a custom one.
436         * sigtramp-qnx.c (aarch64-qnx): Implement the signal trampoline.
438 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
440         * lib-xref.ads, lib-xref-spark_specific.adb
441         (Traverse_Compilation_Unit): Move declaration to package body.
443 2017-11-08  Hristian Kirtchev  <kirtchev@adacore.com>
445         * exp_spark.adb (Expand_SPARK_N_Object_Renaming_Declaration): Obtain
446         the type of the renaming from its defining entity, rather then the
447         subtype mark as there may not be a subtype mark.
449 2017-11-08  Jerome Lambourg  <lambourg@adacore.com>
451         * adaint.c, s-oscons-tmplt.c, init.c, libgnat/system-qnx-aarch64.ads,
452         libgnarl/a-intnam__qnx.ads, libgnarl/s-intman__qnx.adb,
453         libgnarl/s-osinte__qnx.ads, libgnarl/s-qnx.ads,
454         libgnarl/s-taprop__qnx.adb, s-oscons-tmplt.c, sigtramp-qnx.c,
455         terminals.c: Initial port of GNAT for aarch64-qnx
457 2017-11-08  Elisa Barboni  <barboni@adacore.com>
459         * exp_util.adb (Find_DIC_Type): Move...
460         * sem_util.ads, sem_util.adb (Find_DIC_Type): ... here.
462 2017-11-08  Justin Squirek  <squirek@adacore.com>
464         * sem_res.adb (Resolve_Allocator): Add info messages corresponding to
465         the owner and corresponding coextension.
467 2017-11-08  Ed Schonberg  <schonberg@adacore.com>
469         * sem_aggr.adb (Resolve_Delta_Aggregate): Divide into the
470         following separate procedures.
471         (Resolve_Delta_Array_Aggregate): Previous code form
472         Resolve_Delta_Aggregate.
473         (Resolve_Delta_Record_Aggregate): Extend previous code to cover latest
474         ARG decisions on the legality rules for delta aggregates for records:
475         in the case of a variant record, components from different variants
476         cannot be specified in the delta aggregate, and this must be checked
477         statically.
479 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
481         * spark_xrefs.ads (SPARK_Scope_Record): Remove File_Num component.
482         * lib-xref-spark_specific.adb (Add_SPARK_Scope): Skip initialization of
483         removed component.
485 2017-11-08  Gary Dismukes  <dismukes@adacore.com>
487         * sem_ch4.adb: Minor typo fix.
489 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
491         * spark_xrefs.ads (SPARK_Scope_Record): Remove Spec_File_Num and
492         Spec_Scope_Num components.
493         * spark_xrefs.adb (dspark): Skip pretty-printing to removed components.
494         * lib-xref-spark_specific.adb (Add_SPARK_Scope): Skip initialization of
495         removed components.
496         (Collect_SPARK_Xrefs): Skip setting proper values of removed
497         components.
499 2017-11-08  Gary Dismukes  <dismukes@adacore.com>
501         * exp_ch4.adb (Expand_N_Type_Conversion): Add test that the selector
502         name is a discriminant in check for unconditional accessibility
503         violation within instances.
505 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
507         * lib-xref-spark_specific.adb (Add_SPARK_Xrefs): Remove special-case
508         for constants (with variable input).
509         (Is_Constant_Object_Without_Variable_Input): Remove.
511 2017-11-08  Hristian Kirtchev  <kirtchev@adacore.com>
513         * exp_ch9.adb, sem_disp.adb, sem_util.adb: Minor reformatting.
515 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
517         * spark_xrefs.ads (Rtype): Remove special-casing of constants for SPARK
518         cross-references.
519         (dspark): Remove hardcoded table bound.
521 2017-11-08  Ed Schonberg  <schonberg@adacore.com>
523         * sem_ch4.adb (Analyze_Aggregate): For Ada2020 delta aggregates, use
524         the type of the base of the construct to determine the type (or
525         candidate interpretations) of the delta aggregate. This allows the
526         construct to appear in a context that expects a private extension.
527         * sem_res.adb (Resolve): Handle properly a delta aggregate with an
528         overloaded base.
530 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
532         * spark_xrefs.ads (SPARK_Xref_Record): Replace file and scope indices
533         with Entity_Id of the reference.
534         * spark_xrefs.adb (dspark): Adapt pretty-printing routine.
535         * lib-xref-spark_specific.adb (Add_SPARK_Xrefs): Store Entity_Id of the
536         reference, not the file and scope indices.
538 2017-11-08  Arnaud Charlet  <charlet@adacore.com>
540         * errout.ads (Current_Node): New.
541         * errout.adb (Error_Msg): Use Current_Node.
542         * par-ch6.adb, par-ch7.adb, par-ch9.adb, par-util.adb: Set Current_Node
543         when relevant.
544         * style.adb: Call Error_Msg_N when possible.
546 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
548         * spark_xrefs.ads (SPARK_Scope_Record): Rename Scope_Id component to
549         Entity.
550         * lib-xref-spark_specific.adb, spark_xrefs.adb: Propagate renaming of
551         the Scope_Id record component.
553 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
555         * spark_xrefs.ads (SPARK_File_Record): Remove string components.
556         * spark_xrefs.adb (dspark): Remove pretty-printing of removed
557         SPARK_File_Record components.
558         * lib-xref-spark_specific.adb (Add_SPARK_File): Do not store string
559         representation of files/units.
561 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
563         * lib-xref.ads, lib-xref-spark_specific.adb (Traverse_Declarations):
564         Remove Inside_Stubs parameter.
566 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
568         * spark_xrefs.ads (SPARK_Xref_Record): Referenced object is now
569         represented by Entity_Id.
570         (SPARK_Scope_Record): Referenced scope (e.g. subprogram) is now
571         represented by Entity_Id; this information is not repeated as
572         Scope_Entity.
573         (Heap): Moved from lib-xref-spark_specific.adb, to reside next to
574         Name_Of_Heap_Variable.
575         * spark_xrefs.adb (dspark): Adapt debug routine to above changes in
576         data types.
577         * lib-xref-spark_specific.adb: Adapt routines for populating SPARK
578         scope and xrefs tables to above changes in data types.
580 2017-11-08  Justin Squirek  <squirek@adacore.com>
582         * sem_ch8.adb (Mark_Use_Clauses): Add condition to always mark the
583         primitives of generic actuals.
584         (Mark_Use_Type): Add recursive call to properly mark class-wide type's
585         base type clauses as per ARM 8.4 (8.2/3).
587 2017-11-08  Ed Schonberg  <schonberg@adacore.com>
589         * sem_ch6.adb (Analyze_Generic_Subprobram_Body): Validate
590         categorization dependency of the body, as is done for non-generic
591         units.
592         (New_Overloaded_Entity, Visible_Part_Type): Remove linear search
593         through declarations (Simple optimization, no behavior change).
595 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
597         * spark_xrefs.ads (SPARK_Xref_Record): Remove inessential components.
598         (SPARK_Scope_Record): Remove inessential components.
599         * spark_xrefs.adb (dspark): Remove pretty-printing of removed record
600         components.
601         * lib-xref-spark_specific.adb (Add_SPARK_Scope): Remove setting of
602         removed record components.
603         (Add_SPARK_Xrefs): Remove setting of removed record components.
605 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
607         * lib-xref-spark_specific.adb (Add_SPARK_Xrefs): Remove dead check for
608         empty entities.
610 2017-11-08  Javier Miranda  <miranda@adacore.com>
612         * sem_disp.adb (Is_Inherited_Public_Operation): Extend the
613         functionality of this routine to handle multiple levels of derivations.
615 2017-11-08  Hristian Kirtchev  <kirtchev@adacore.com>
617         * einfo.adb: Elist36 is now used as Nested_Scenarios.
618         (Nested_Scenarios): New routine.
619         (Set_Nested_Scenarios): New routine.
620         (Write_Field36_Name): New routine.
621         * einfo.ads: Add new attribute Nested_Scenarios along with occurrences
622         in entities.
623         (Nested_Scenarios): New routine along with pragma Inline.
624         (Set_Nested_Scenarios): New routine along with pragma Inline.
625         * sem_elab.adb (Find_And_Process_Nested_Scenarios): New routine.
626         (Process_Nested_Scenarios): New routine.
627         (Traverse_Body): When a subprogram body is traversed for the first
628         time, find, save, and process all suitable scenarios found within.
629         Subsequent traversals of the same subprogram body utilize the saved
630         scenarios.
632 2017-11-08  Piotr Trojanek  <trojanek@adacore.com>
634         * lib-xref-spark_specific.adb (Add_SPARK_Scope): Remove detection of
635         protected operations.
636         (Add_SPARK_Xrefs): Simplify detection of empty entities.
637         * get_spark_xrefs.ads, get_spark_xrefs.adb, put_spark_xrefs.ads,
638         put_spark_xrefs.adb, spark_xrefs_test.adb: Remove code for writing,
639         reading and testing SPARK cross-references stored in the ALI files.
640         * lib-xref.ads (Output_SPARK_Xrefs): Remove.
641         * lib-writ.adb (Write_ALI): Do not write SPARK cross-references to the
642         ALI file.
643         * spark_xrefs.ads, spark_xrefs.adb (pspark): Remove, together
644         with description of the SPARK xrefs ALI format.
645         * gcc-interface/Make-lang.in (GNAT_ADA_OBJS): Remove get_spark_refs.o
646         and put_spark_refs.o.
648 2017-11-08  Hristian Kirtchev  <kirtchev@adacore.com>
650         * exp_ch4.adb (Apply_Accessibility_Check): Do not finalize the object
651         when the associated access type is subject to pragma
652         No_Heap_Finalization.
653         * exp_intr.adb (Expand_Unc_Deallocation): Use the available view of the
654         designated type in case it comes from a limited withed unit.
656 2017-11-08  Hristian Kirtchev  <kirtchev@adacore.com>
658         * exp_ch3.adb (Expand_N_Object_Declaration): Save and restore relevant
659         SPARK-related flags.  Add ??? comment.
660         * exp_util.adb (Insert_Actions): Add an entry for node
661         N_Variable_Reference_Marker.
662         * sem.adb (Analyze): Add an entry for node N_Variable_Reference_Marker.
663         * sem_ch8.adb (Find_Direct_Name): Add constant Is_Assignment_LHS. Build
664         and record a variable reference marker for the current name.
665         (Find_Expanded_Name): Add constant Is_Assignment_LHS. Build and record
666         a variable reference marker for the current name.
667         * sem_elab.adb (Build_Variable_Reference_Marker): New routine.
668         (Extract_Variable_Reference_Attributes): Reimplemented.
669         (Info_Scenario): Add output for variable references and remove output
670         for variable reads.
671         (Info_Variable_Read): Removed.
672         (Info_Variable_Reference): New routine.
673         (Is_Suitable_Scenario): Variable references are now suitable scenarios
674         while variable reads are not.
675         (Output_Active_Scenarios): Add output for variable references and
676         remove output for variable reads.
677         (Output_Variable_Read): Removed.
678         (Output_Variable_Reference): New routine.
679         (Process_Variable_Read): Removed.
680         (Process_Variable_Reference): New routine.
681         (Process_Variable_Reference_Read): New routine.
682         * sem_elab.ads (Build_Variable_Reference_Marker): New routine.
683         * sem_res.adb (Resolve_Actuals): Build and record a variable reference
684         marker for the current actual.
685         * sem_spark.adb (Check_Node): Add an entry for node
686         N_Variable_Reference_Marker.
687         * sem_util.adb (Within_Subprogram_Call): Moved to the library level.
688         * sem_util.ads (Within_Subprogram_Call): Moved to the library level.
689         * sinfo.adb (Is_Read): New routine.
690         (Is_Write): New routine.
691         (Target): Updated to handle variable reference markers.
692         (Set_Is_Read): New routine.
693         (Set_Is_Write): New routine.
694         (Set_Target): Updated to handle variable reference markers.
695         * sinfo.ads: Add new attributes Is_Read and Is_Write along with
696         occurrences in nodes. Update attribute Target. Add new node
697         kind N_Variable_Reference_Marker.
698         (Is_Read): New routine along with pragma Inline.
699         (Is_Write): New routine along with pragma Inline.
700         (Set_Is_Read): New routine along with pragma Inline.
701         (Set_Is_Write): New routine along with pragma Inline.
702         * sprint.adb (Sprint_Node_Actual): Add an entry for node
703         N_Variable_Reference_Marker.
705 2017-11-08  Arnaud Charlet  <charlet@adacore.com>
707         * sem_util.adb (Subprogram_Name): Append suffix for overloaded
708         subprograms.
710 2017-11-08  Yannick Moy  <moy@adacore.com>
712         * sem_ch8.adb (Use_One_Type, Update_Use_Clause_Chain): Do not report
713         about unused use-type or use-package clauses inside inlined bodies.
715 2017-11-08  Hristian Kirtchev  <kirtchev@adacore.com>
717         * sem_elab.adb (Ensure_Prior_Elaboration): Add new parameter
718         In_Partial_Fin along with a comment on its usage. Do not guarantee the
719         prior elaboration of a unit when the need came from a partial
720         finalization context.
721         (In_Initialization_Context): Relocated to Process_Call.
722         (Is_Partial_Finalization_Proc): New routine.
723         (Process_Access): Add new parameter In_Partial_Fin along with a comment
724         on its usage.
725         (Process_Activation_Call): Add new parameter In_Partial_Fin along with
726         a comment on its usage.
727         (Process_Activation_Conditional_ABE_Impl): Add new parameter
728         In_Partial_Fin along with a comment on its usage. Do not emit any ABE
729         diagnostics when the activation occurs in a partial finalization
730         context.
731         (Process_Activation_Guaranteed_ABE_Impl): Add new parameter
732         In_Partial_Fin along with a comment on its usage.
733         (Process_Call): Add new parameter In_Partial_Fin along with a comment
734         on its usage. A call is within a partial finalization context when it
735         targets a finalizer or primitive [Deep_]Finalize, and the call appears
736         in initialization actions. Pass this information down to the recursive
737         steps of the Processing phase.
738         (Process_Call_Ada): Add new parameter In_Partial_Fin along with a
739         comment on its usage. Remove the guard which suppresses the generation
740         of implicit Elaborate[_All] pragmas. This is now done in
741         Ensure_Prior_Elaboration.
742         (Process_Call_Conditional_ABE): Add new parameter In_Partial_Fin along
743         with a comment on its usage. Do not emit any ABE diagnostics when the
744         call occurs in a partial finalization context.
745         (Process_Call_SPARK): Add new parameter In_Partial_Fin along with a
746         comment on its usage.
747         (Process_Instantiation): Add new parameter In_Partial_Fin along with a
748         comment on its usage.
749         (Process_Instantiation_Ada): Add new parameter In_Partial_Fin along
750         with a comment on its usage.
751         (Process_Instantiation_Conditional_ABE): Add new parameter
752         In_Partial_Fin along with a comment on its usage. Do not emit any ABE
753         diagnostics when the instantiation occurs in a partial finalization
754         context.
755         (Process_Instantiation_SPARK): Add new parameter In_Partial_Fin along
756         with a comment on its usage.
757         (Process_Scenario): Add new parameter In_Partial_Fin along  with a
758         comment on its usage.
759         (Process_Single_Activation): Add new parameter In_Partial_Fin along
760         with a comment on its usage.
761         (Traverse_Body): Add new parameter In_Partial_Fin along with a comment
762         on its usage.
764 2017-11-08  Arnaud Charlet  <charlet@adacore.com>
766         * sem_ch13.adb: Add optional parameter to Error_Msg.
768 2017-11-08  Jerome Lambourg  <lambourg@adacore.com>
770         * fname.adb (Is_Internal_File_Name): Do not check the 8+3 naming schema
771         for the Interfaces.* hierarchy as longer unit names are now allowed.
773 2017-11-08  Arnaud Charlet  <charlet@adacore.com>
775         * sem_util.adb (Subprogram_Name): Emit sloc for the enclosing
776         subprogram as well.  Support more cases of entities.
777         (Append_Entity_Name): Add some defensive code.
779 2017-11-06  Eric Botcazou  <ebotcazou@adacore.com>
781         * gcc-interface/misc.c (gnat_post_options): Clear warn_return_type.
783 2017-10-31  Eric Botcazou  <ebotcazou@adacore.com>
785         PR ada/82785
786         * gcc-interface/Makefile.in (m68k/Linux): Fix typo.
788 2017-10-21  Eric Botcazou  <ebotcazou@adacore.com>
790         * gcc-interface/Makefile.in: Remove bogus settings for VxWorks.
792 2017-10-21  Eric Botcazou  <ebotcazou@adacore.com>
794         * gcc-interface/utils.c (pad_type_hash): Use hashval_t for hash value.
795         (convert): Do not use an unchecked conversion for converting from a
796         type to another type padding it.
798 2017-10-20  Doug Rupp  <rupp@adacore.com>
800         * libgnarl/s-osinte__linux.ads (Relative_Timed_Wait): Add variable
801         needed for using monotonic clock.
802         * libgnarl/s-taprop__linux.adb: Revert previous monotonic clock
803         changes.
804         * libgnarl/s-taprop__linux.adb, s-taprop__posix.adb: Unify and factor
805         out monotonic clock related functions body.
806         (Timed_Sleep, Timed_Delay, Montonic_Clock, RT_Resolution,
807         Compute_Deadline): Move to...
808         * libgnarl/s-tpopmo.adb: ... here. New separate package body.
810 2017-10-20  Ed Schonberg  <schonberg@adacore.com>
812         * sem_util.adb (Is_Controlling_Limited_Procedure): Handle properly the
813         case where the controlling formal is an anonymous access to interface
814         type.
815         * exp_ch9.adb (Extract_Dispatching_Call): If controlling actual is an
816         access type, handle properly the the constructed dereference that
817         designates the object used in the rewritten synchronized call.
818         (Parameter_Block_Pack): If the type of the actual is by-copy, its
819         generated declaration in the parameter block does not need an
820         initialization even if the type is a null-excluding access type,
821         because it will be initialized with the value of the actual later on.
822         (Parameter_Block_Pack): Do not add controlling actual to parameter
823         block when its type is by-copy.
825 2017-10-20  Justin Squirek  <squirek@adacore.com>
827         * sem_ch8.adb (Update_Use_Clause_Chain): Add sanity check to verify
828         scope stack traversal into the context clause.
830 2017-10-20  Bob Duff  <duff@adacore.com>
832         * sinfo.ads: Fix a comment typo.
834 2017-10-20  Eric Botcazou  <ebotcazou@adacore.com>
836         * doc/gnat_ugn/building_executable_programs_with_gnat.rst (-flto): Add
837         warning against usage in conjunction with -gnatn.
838         (-fdump-xref): Delete entry.
839         * doc/gnat_ugn/gnat_utility_programs.rst (--ext): Remove mention of
840         -fdump-xref switch.
841         * gnat_ugn.texi: Regenerate.
843 2017-10-20  Hristian Kirtchev  <kirtchev@adacore.com>
845         * sem_type.adb, exp_util.adb, sem_util.adb, sem_dim.adb, sem_elab.adb:
846         Minor reformatting.
848 2017-10-20  Yannick Moy  <moy@adacore.com>
850         * sem_dim.adb (Analyze_Dimension_Binary_Op): Accept with a warning to
851         compare a dimensioned expression with a literal.
852         (Dim_Warning_For_Numeric_Literal): Do not issue a warning for the
853         special value zero.
854         * doc/gnat_ugn/gnat_and_program_execution.rst: Update description of
855         dimensionality system in GNAT.
856         * gnat_ugn.texi: Regenerate.
858 2017-10-20  Yannick Moy  <moy@adacore.com>
860         * sem_ch6.adb (Analyze_Expression_Function.Freeze_Expr_Types): Remove
861         inadequate silencing of errors.
862         * sem_util.adb (Check_Part_Of_Reference): Do not issue an error when
863         checking the subprogram body generated from an expression function,
864         when this is done as part of the preanalysis done on expression
865         functions, as the subprogram body may not yet be attached in the AST.
866         The error if any will be issued later during the analysis of the body.
867         (Is_Aliased_View): Trivial rewrite with Is_Formal_Object.
869 2017-10-20  Arnaud Charlet  <charlet@adacore.com>
871         * sem_ch8.adb (Update_Chain_In_Scope): Add missing [-gnatwu] marker for
872         warning on ineffective use clause.
874 2017-10-20  Eric Botcazou  <ebotcazou@adacore.com>
876         * exp_ch11.ads (Warn_If_No_Local_Raise): Declare.
877         * exp_ch11.adb (Expand_Exception_Handlers): Use Warn_If_No_Local_Raise
878         to issue the warning on the absence of local raise.
879         (Possible_Local_Raise): Do not issue the warning for Call_Markers.
880         (Warn_If_No_Local_Raise): New procedure to issue the warning on the
881         absence of local raise.
882         * sem_elab.adb: Add with and use clauses for Exp_Ch11.
883         (Record_Elaboration_Scenario): Call Possible_Local_Raise in the cases
884         where a scenario could give rise to raising Program_Error.
885         * sem_elab.adb: Typo fixes.
886         * fe.h (Warn_If_No_Local_Raise): Declare.
887         * gcc-interface/gigi.h (get_exception_label): Change return type.
888         * gcc-interface/trans.c (gnu_constraint_error_label_stack): Change to
889         simple vector of Entity_Id.
890         (gnu_storage_error_label_stack): Likewise.
891         (gnu_program_error_label_stack): Likewise.
892         (gigi): Adjust to above changes.
893         (Raise_Error_to_gnu): Likewise.
894         (gnat_to_gnu) <N_Goto_Statement>: Set TREE_USED on the label.
895         (N_Push_Constraint_Error_Label): Push the label onto the stack.
896         (N_Push_Storage_Error_Label): Likewise.
897         (N_Push_Program_Error_Label): Likewise.
898         (N_Pop_Constraint_Error_Label): Pop the label from the stack and issue
899         a warning on the absence of local raise.
900         (N_Pop_Storage_Error_Label): Likewise.
901         (N_Pop_Program_Error_Label): Likewise.
902         (push_exception_label_stack): Delete.
903         (get_exception_label): Change return type to Entity_Id and adjust.
904         * gcc-interface/utils2.c (build_goto_raise): Change type of first
905         parameter to Entity_Id and adjust.  Set TREE_USED on the label.
906         (build_call_raise): Adjust calls to get_exception_label and also
907         build_goto_raise.
908         (build_call_raise_column): Likewise.
909         (build_call_raise_range): Likewise.
910         * doc/gnat_ugn/building_executable_programs_with_gnat.rst (-gnatw.x):
911         Document actual default behavior.
913 2017-10-20  Piotr Trojanek  <trojanek@adacore.com>
915         * einfo.ads: Minor consistent punctuation in comment.  All numbered
916         items in the comment of Is_Internal are now terminated with a period.
918 2017-10-20  Piotr Trojanek  <trojanek@adacore.com>
920         * exp_util.adb (Build_Temporary): Mark created temporary entity as
921         internal.
923 2017-10-20  Piotr Trojanek  <trojanek@adacore.com>
925         * sem_type.adb (In_Generic_Actual): Simplified.
927 2017-10-20  Justin Squirek  <squirek@adacore.com>
929         * sem_ch12.adb (Check_Formal_Package_Instance): Add sanity check to
930         verify a renaming exists for a generic formal before comparing it to
931         the actual as defaulted formals will not have a renamed_object.
933 2017-10-20  Javier Miranda  <miranda@adacore.com>
935         * exp_ch6.adb (Replace_Returns): Fix wrong management of
936         N_Block_Statement nodes.
938 2017-10-20  Bob Duff  <duff@adacore.com>
940         * exp_aggr.adb (Initialize_Array_Component): Avoid adjusting a
941         component of an array aggregate if it is initialized by a
942         build-in-place function call.
943         * exp_ch6.adb (Is_Build_In_Place_Result_Type): Use -gnatd.9 to disable
944         bip for nonlimited types.
945         * debug.adb: Document -gnatd.9.
947 2017-10-20  Bob Duff  <duff@adacore.com>
949         * sem_ch12.adb: Remove redundant setting of Parent.
951 2017-10-20  Eric Botcazou  <ebotcazou@adacore.com>
953         * sem_ch4.adb (Find_Concatenation_Types): Filter out operators if one
954         of the operands is a string literal.
956 2017-10-20  Bob Duff  <duff@adacore.com>
958         * einfo.ads: Comment fix.
960 2017-10-20  Clement Fumex  <fumex@adacore.com>
962         * switch-c.adb: Remove -gnatwm from the switches triggered by -gnateC.
964 2017-10-20  Ed Schonberg  <schonberg@adacore.com>
966         * sem_dim.adb (Extract_Power): Accept dimension values that are not
967         non-negative integers when the dimensioned base type is an Integer
968         type.
970 2017-10-20  Bob Duff  <duff@adacore.com>
972         * sinfo.ads, sinfo.adb (Alloc_For_BIP_Return): New flag to indicate
973         that an allocator came from a b-i-p return statement.
974         * exp_ch4.adb (Expand_Allocator_Expression): Avoid adjusting the return
975         object of a nonlimited build-in-place function call.
976         * exp_ch6.adb (Expand_N_Extended_Return_Statement): Set the
977         Alloc_For_BIP_Return flag on generated allocators.
978         * sem_ch5.adb (Analyze_Assignment): Move Assert to where it can't fail.
979         If the N_Assignment_Statement has been transformed into something else,
980         then Should_Transform_BIP_Assignment won't work.
981         * exp_ch3.adb (Expand_N_Object_Declaration): A previous revision said,
982         "Remove Adjust if we're building the return object of an extended
983         return statement in place." Back out that part of the change, because
984         the Alloc_For_BIP_Return flag is now used for that.
986 2017-10-19  Bob Duff  <duff@adacore.com>
988         * exp_ch6.adb (Is_Build_In_Place_Result_Type): Fix silly bug -- "Typ"
989         should be "T".  Handle case of a subtype of a class-wide type.
991 2017-10-19  Bob Duff  <duff@adacore.com>
993         * exp_util.adb: (Process_Statements_For_Controlled_Objects): Clarify
994         which node kinds can legitimately be ignored, and raise Program_Error
995         for others.
997 2017-10-19  Hristian Kirtchev  <kirtchev@adacore.com>
999         * sem_elab.adb (Compilation_Unit): Handle the case of a subprogram
1000         instantiation that acts as a compilation unit.
1001         (Find_Code_Unit): Reimplemented.
1002         (Find_Top_Unit): Reimplemented.
1003         (Find_Unit_Entity): New routine.
1004         (Process_Instantiation_SPARK): Correct the elaboration requirement a
1005         package instantiation imposes on a unit.
1007 2017-10-19  Bob Duff  <duff@adacore.com>
1009         * exp_ch6.adb (Is_Build_In_Place_Result_Type): Enable build-in-place
1010         for a narrow set of controlled types.
1012 2017-10-19  Eric Botcazou  <ebotcazou@adacore.com>
1014         * sinput.ads (Line_Start): Add pragma Inline.
1015         * widechar.ads (Is_Start_Of_Wide_Char): Likewise.
1017 2017-10-19  Bob Duff  <duff@adacore.com>
1019         * exp_attr.adb (Expand_N_Attribute_Reference): Disable
1020         Make_Build_In_Place_Call_... for F(...)'Old, where F(...) is a
1021         build-in-place function call so that the temp is declared in the right
1022         place.
1024 2017-10-18  Eric Botcazou  <ebotcazou@adacore.com>
1026         * gcc-interface/misc.c (gnat_tree_size): Move around.
1028         * gcc-interface/utils.c (max_size): Deal with SSA names.
1030 2017-10-17  Jakub Jelinek  <jakub@redhat.com>
1032         * gcc-interface/misc.c (gnat_tree_size): New function.
1033         (LANG_HOOKS_TREE_SIZE): Redefine.
1035 2017-10-14  Hristian Kirtchev  <kirtchev@adacore.com>
1037         * sem_elab.adb (In_Preelaborated_Context): A generic package subject to
1038         Remote_Call_Interface is not a suitable preelaboratd context when the
1039         call appears in the package body.
1041 2017-10-14  Eric Botcazou  <ebotcazou@adacore.com>
1043         * layout.ads (Set_Elem_Alignment): Add Align parameter defaulted to 0.
1044         * layout.adb (Set_Elem_Alignment): Likewise.  Use M name as maximum
1045         alignment for consistency.  If Align is non-zero, use the minimum of
1046         Align and M for the alignment.
1047         * cstand.adb (Build_Float_Type): Use Set_Elem_Alignment instead of
1048         setting the alignment directly.
1050 2017-10-14  Ed Schonberg  <schonberg@adacore.com>
1052         * sem_prag.adb (Analyze_Pragma, case Check): Defer evaluation of the
1053         optional string in an Assert pragma until the expansion of the pragma
1054         has rewritten it as a conditional statement, so that the string
1055         argument is only evaluaed if the assertion fails. This is mandated by
1056         RM 11.4.2.
1058 2017-10-14  Hristian Kirtchev  <kirtchev@adacore.com>
1060         * debug.adb: Switch -gnatd.v and associated flag are now used to
1061         enforce the SPARK rules for elaboration in SPARK code.
1062         * sem_elab.adb: Describe switch -gnatd.v.
1063         (Process_Call): Verify the SPARK rules only when -gnatd.v is in effect.
1064         (Process_Instantiation): Verify the SPARK rules only when -gnatd.v is
1065         in effect.
1066         (Process_Variable_Assignment): Clarify why variable assignments are
1067         processed reglardless of whether -gnatd.v is in effect.
1068         * doc/gnat_ugn/elaboration_order_handling_in_gnat.rst: Update the
1069         sections on elaboration code and compilation switches.
1070         * gnat_ugn.texi: Regenerate.
1072 2017-10-14  Gary Dismukes  <dismukes@adacore.com>
1074         * exp_util.adb, freeze.adb, sem_aggr.adb, sem_util.ads, sem_util.adb,
1075         sem_warn.adb: Minor reformattings.
1077 2017-10-14  Ed Schonberg  <schonberg@adacore.com>
1079         * doc/gnat_rm/implementation_defined_aspects.rst: Add documentation
1080         for reverse iteration over formal containers.
1081         * gnat_rm.texi: Regenerate.
1083 2017-10-14  Hristian Kirtchev  <kirtchev@adacore.com>
1085         * sem_elab.adb (Ensure_Dynamic_Prior_Elaboration): Renamed to
1086         Ensure_Prior_Elaboration_Dynamic for consistency reasons.
1087         (Ensure_Static_Prior_Elaboration): Renamed to
1088         Ensure_Prior_Elaboration_Static for consistency reasons.
1089         (Info_Variable_Reference): Renamed to Info_Variable_Read in order to
1090         reflect its new purpose.
1091         (Is_Initialized): New routine.
1092         (Is_Suitable_Variable_Reference): Renamed to Is_Suitable_Variable_Read
1093         in order to reflect its new purpose.
1094         (Is_Variable_Read): New routine.
1095         (Output_Variable_Reference): Renamed to Output_Variable_Read in order
1096         to reflect its new purpose.
1097         (Process_Variable_Assignment): This routine now acts as a top level
1098         dispatcher for variable assignments.
1099         (Process_Variable_Assignment_Ada): New routine.
1100         (Process_Variable_Assignment_SPARK): New routine.
1101         (Process_Variable_Reference): Renamed to Process_Variable_Read in order
1102         to reflects its new purpose. A reference to a variable is now suitable
1103         for ABE processing only when it is a read. The logic in the routine now
1104         reflects the latest SPARK elaboration rules.
1106 2017-10-14  Justin Squirek  <squirek@adacore.com>
1108         * sem_ch8.adb (Analyze_Subprogram_Renaming): Modify condition that
1109         triggers marking on formal subprograms.
1111 2017-10-14  Javier Miranda  <miranda@adacore.com>
1113         * checks.adb (Ensure_Valid): Do not skip adding the validity check on
1114         renamings of objects that come from the sources.
1116 2017-10-14  Eric Botcazou  <ebotcazou@adacore.com>
1118         * cstand.adb (Build_Float_Type): Move down Siz parameter, add Align
1119         parameter and set the alignment of the type to Align.
1120         (Copy_Float_Type): Adjust call to Build_Float_Type.
1121         (Register_Float_Type): Add pragma Unreferenced for Precision.  Adjust
1122         call to Build_Float_Type and do not set RM_Size and Alignment.
1124 2017-10-14  Patrick Bernardi  <bernardi@adacore.com>
1126         * Makefile.rtl (GNATRTL_NONTASKING_OBJ): Add s-soliin to
1127         GNATRTL_NONTASKING_OBJ.
1129 2017-10-14  Bob Duff  <duff@adacore.com>
1131         * exp_ch6.adb (Is_Build_In_Place_Result_Type): Include code for
1132         enabling b-i-p for nonlimited controlled types (but disabled).
1134 2017-10-14  Justin Squirek  <squirek@adacore.com>
1136         * sem_elab.adb (Is_Suitable_Variable_Assignment): Replace call to
1137         Has_Warnings_Off with Warnings_Off.
1139 2017-10-14  Piotr Trojanek  <trojanek@adacore.com>
1141         * sinfo.ads (Generic_Parent): Remove wrong (possibly obsolete) comment.
1143 2017-10-14  Hristian Kirtchev  <kirtchev@adacore.com>
1145         * sem_ch3.adb (Analyze_Declarations): Analyze the contract of an
1146         enclosing package at the end of the visible declarations.
1147         * sem_prag.adb (Analyze_Initialization_Item): Suppress the analysis of
1148         an initialization item which is undefined due to some illegality.
1150 2017-10-14  Patrick Bernardi  <bernardi@adacore.com>
1152         * ali.adb: Add new ALI line 'T' to read the number of tasks contain
1153         within each unit that require a default-sized primary and secondary
1154         stack to be generated by the binder.
1155         (Scan_ALI): Scan new 'T' lines.
1156         * ali.ads: Add Primary_Stack_Count and Sec_Stack_Count to Unit_Record.
1157         * bindgen.adb (Gen_Output_File): Count the number of default-sized
1158         stacks within the closure that are to be created by the binder.
1159         (Gen_Adainit, Gen_Output_File_Ada): Generate default-sized secondary
1160         stacks and record these in System.Secodnary_Stack.
1161         (Resolve_Binder_Options): Check if System.Secondary_Stack is in the
1162         closure of the program being bound.
1163         * bindusg.adb (Display): Add "-Q" switch. Remove rouge "--RTS" comment.
1164         * exp_ch3.adb (Count_Default_Sized_Task_Stacks): New routine.
1165         (Expand_N_Object_Declaration): Count the number of default-sized stacks
1166         used by task objects contained within the object whose declaration is
1167         being expanded.  Only performed when either the restrictions
1168         No_Implicit_Heap_Allocations or No_Implicit_Task_Allocations are in
1169         effect.
1170         * exp_ch9.adb (Create_Secondary_Stack_For_Task): New routine.
1171         (Expand_N_Task_Type_Declaration): Create a secondary stack as part of
1172         the expansion of a task type if the size of the stack is known at
1173         run-time and the restrictions No_Implicit_Heap_Allocations or
1174         No_Implicit_Task_Allocations are in effect.
1175         (Make_Task_Create_Call): If using a restricted profile provide
1176         secondary stack parameter: either the statically created stack or null.
1177         * lib-load.adb (Create_Dummy_Package_Unit, Load_Unit,
1178         Load_Main_Source): Include Primary_Stack_Count and Sec_Stack_Count in
1179         Unit_Record initialization expressions.
1180         * lib-writ.adb (Add_Preprocessing_Dependency,
1181         Ensure_System_Dependency): Include Primary_Stack_Count and
1182         Sec_Stack_Count in Unit_Record initialization expression.
1183         (Write_ALI): Write T lines.
1184         (Write_Unit_Information): Do not output 'T' lines if there are no
1185         stacks for the binder to generate.
1186         * lib-writ.ads: Updated library information documentation to include
1187         new T line entry.
1188         * lib.adb (Increment_Primary_Stack_Count): New routine.
1189         (Increment_Sec_Stack_Count): New routine.
1190         (Primary_Stack_Count): New routine.
1191         (Sec_Stack_Count): New routine.
1192         * lib.ads: Add Primary_Stack_Count and Sec_Stack_Count components to
1193         Unit_Record and updated documentation.
1194         (Increment_Primary_Stack_Count): New routine along with pragma Inline.
1195         (Increment_Sec_Stack_Count): New routine along with pragma Inline.
1196         (Primary_Stack_Count): New routine along with pragma Inline.
1197         (Sec_Stack_Count): New routine along with pragma Inline.
1198         * opt.ads: New constant No_Stack_Size.  Flag Default_Stack_Size
1199         redefined.  New flag Default_Sec_Stack_Size and
1200         Quantity_Of_Default_Size_Sec_Stacks.
1201         * rtfinal.c Fixed erroneous comment.
1202         * rtsfind.ads: Moved RE_Default_Secondary_Stack_Size from
1203         System.Secondary_Stack to System.Parameters.  Add RE_SS_Stack.
1204         * sem_util.adb (Number_Of_Elements_In_Array): New routine.
1205         * sem_util.ads (Number_Of_Elements_In_Array): New routine.
1206         * switch-b.adb (Scan_Binder_Switches): Scan "-Q" switch.
1207         * libgnarl/s-solita.adb (Get_Sec_Stack_Addr): Removed routine.
1208         (Set_Sec_Stack_Addr): Removed routine.
1209         (Get_Sec_Stack): New routine.
1210         (Set_Sec_Stack): New routine.
1211         (Init_Tasking_Soft_Links): Update System.Soft_Links reference to
1212         reflect new procedure and global names.
1213         * libgnarl/s-taprop__linux.adb, libgnarl/s-taprop__mingw.adb,
1214         libgnarl/s-taprop__posix.adb, libgnarl/s-taprop__solaris.adb,
1215         libgnarl/s-taprop__vxworks.adb (Register_Foreign_Thread): Update
1216         parameter profile to allow the secondary stack size to be specified.
1217         * libgnarl/s-tarest.adb (Create_Restricted_Task): Update the parameter
1218         profile to include Sec_Stack_Address.  Update Tasking.Initialize_ATCB
1219         call to remove Secondary_Stack_Size reference.  Add secondary stack
1220         address and size to SSL.Create_TSD call.
1221         (Task_Wrapper): Remove secondary stack creation.
1222         * libgnarl/s-tarest.ads (Create_Restricted_Task,
1223         Create_Restricted_Task_Sequential): Update parameter profile to include
1224         Sec_Stack_Address and clarify the Size parameter.
1225         * libgnarl/s-taskin.adb (Initialize_ATCB): Remove Secondary_Stack_Size
1226         from profile and body.
1227         (Initialize): Remove Secondary_Stack_Size from Initialize_ATCB call.
1228         * libgnarl/s-taskin.ads: Removed component Secondary_Stack_Size from
1229         Common_ATCB.
1230         (Initialize_ATCB): Update the parameter profile to remove
1231         Secondary_Stack_Size.
1232         * libgnarl/s-tassta.adb (Create_Task): Updated parameter profile and
1233         call to Initialize_ATCB.  Add secondary stack address and size to
1234         SSL.Create_TSD call, and catch any storage exception from the call.
1235         (Finalize_Global_Tasks): Update System.Soft_Links references to reflect
1236         new subprogram and component names.
1237         (Task_Wrapper): Remove secondary stack creation.
1238         (Vulnerable_Complete_Master): Update to reflect TSD changes.
1239         * libgnarl/s-tassta.ads: Reformat comments.
1240         (Create_Task): Update parameter profile.
1241         * libgnarl/s-tporft.adb (Register_Foreign_Thread): Update parameter
1242         profile to include secondary stack size. Remove secondary size
1243         parameter from Initialize_ATCB call and add it to Create_TSD call.
1244         * libgnat/s-parame.adb, libgnat/s-parame__rtems.adb,
1245         libgnat/s-parame__vxworks.adb (Default_Sec_Stack_Size): New routine.
1246         * libgnat/s-parame.ads, libgnat/s-parame__ae653.ads,
1247         libgnat/s-parame__hpux.ads, libgnat/s-parame__vxworks.ads: Remove type
1248         Percentage.  Remove constants Dynamic, Sec_Stack_Percentage and
1249         Sec_Stack_Dynamic.  Add constant Runtime_Default_Sec_Stack_Size and
1250         Sec_Stack_Dynamic.
1251         (Default_Sec_Stack_Size): New routine.
1252         * libgnat/s-secsta.adb, libgnat/s-secsta.ads: New implementation. Is
1253         now Preelaborate.
1254         * libgnat/s-soflin.adb: Removed unused with-clauses.  With
1255         System.Soft_Links.Initialize to initialize non-tasking TSD.
1256         (Create_TSD): Update parameter profile. Initialize the TSD and
1257         unconditionally call SS_Init.
1258         (Destroy_TSD): Update SST.SS_Free call.
1259         (Get_Sec_Stack_Addr_NT, Get_Sec_Stack_Addr_Soft, Set_Sec_Stack_Addr_NT,
1260         Set_Sec_Stack_Addr_Soft): Remove routines.
1261         (Get_Sec_Stack_NT, Get_Sec_Stack_Soft, Set_Sec_Stack_NT,
1262         Set_Sec_Stack_Soft): Add routines.
1263         (NT_TSD): Move to private part of package specification.
1264         * libgnat/s-soflin.ads: New types Get_Stack_Call and Set_Stack_Call
1265         with suppressed access checks.  Renamed *_Sec_Stack_Addr_* routines and
1266         objects to *_Sec_Stack_*.  TSD: removed warning suppression and
1267         component intialization. Changed Sec_Stack_Addr to Sec_Stack_Ptr.
1268         (Create_TSD): Update parameter profile.
1269         (NT_TSD): Move to private section from body.
1270         * libgnat/s-soliin.adb, libgnat/s-soliin.ads: New files.
1271         * libgnat/s-thread.ads (Thread_Body_Enter): Update parameter profile.
1272         * libgnat/s-thread__ae653.adb (Get_Sec_Stack_Addr, Set_Sec_Stack_Addr):
1273         Remove routine.
1274         (Get_Sec_Stack, Set_Sec_Stack): Add routine.
1275         (Thread_Body_Enter): Update parameter profile and body to adapt to new
1276         System.Secondary_Stack.
1277         (Init_RTS): Update body for new System.Soft_Links names.
1278         * gcc-interface/Make-lang.in (GNAT_ADA_OBJS, GNATBIND_OBJS): Add
1279         s-soliin.o.
1281 2017-10-10  Richard Sandiford  <richard.sandiford@linaro.org>
1283         * gcc-interface/decl.c (annotate_value): Use wi::to_wide when
1284         operating on trees as wide_ints.
1286 2017-10-09  Hristian Kirtchev  <kirtchev@adacore.com>
1288         * sem_unit.adb (Find_Enclosing_Scope): Do not treat a block statement
1289         as a scoping construct when it is byproduct of exception handling.
1291 2017-10-09  Hristian Kirtchev  <kirtchev@adacore.com>
1293         * sinfo.ads: Update table Is_Syntactic_Field to reflect the nature of
1294         semantic field Target of node N_Call_Marker.
1296 2017-10-09  Ed Schonberg  <schonberg@adacore.com>
1298         * sem_res.adb (Resolve_Allocator): Reject properly an allocator that
1299         attempts to copy a limited value, when the allocator is the expression
1300         in an expression function.
1302 2017-10-09  Joel Brobecker  <brobecker@adacore.com>
1304         * doc/share/conf.py: Tell the style checker that this is a Python
1305         fragment, and therefore that pyflakes should not be run to validate
1306         this file.
1308 2017-10-09  Eric Botcazou  <ebotcazou@adacore.com>
1310         * einfo.ads (Is_Boolean_Type): Add pragma Inline.
1311         (Is_Entity_Name): Likewise.
1312         (Is_String_Type): Likewise.
1313         * sem_type.adb (Full_View_Covers): Do not test Is_Private_Type here
1314         and remove useless comparisons on the base types.
1315         (Covers): Use simple tests for Standard_Void_Type.  Move up cheap tests
1316         on T2.  Always test Is_Private_Type before Full_View_Covers.
1318 2017-10-09  Bob Duff  <duff@adacore.com>
1320         * exp_ch4.adb: Minor refactoring.
1322 2017-10-09  Javier Miranda  <miranda@adacore.com>
1324         * sem_ch3.adb (Replace_Components): Browse the list of discriminants,
1325         not components.
1327 2017-10-09  Hristian Kirtchev  <kirtchev@adacore.com>
1329         * sem_elab.adb (Static_Elaboration_Checks): Elaboration requirements
1330         are verified only in the static model.
1332 2017-10-09  Ed Schonberg  <schonberg@adacore.com>
1334         * sem_ch5.adb (Analyze_Iterator_Specification,
1335         Check_Reverse_Iteration): Check that the domain of iteration supports
1336         reverse iteration when it is a formal container.  This requires the
1337         presence of a Previous primitive in the Iterable aspect.
1338         * sem_ch13.adb (Resolve_Iterable_Operation): Verify legality of
1339         primitives Last and Previous to support reverse iteration over formal
1340         containers.
1341         (Validate_Iterable_Aspect): Add check for reverse iteration operations.
1342         * exp_ch5.adb (Build_Formal_Container_Iteration): Add proper expansion
1343         for reverse iteration using primitives Last and Previous in generated
1344         loop.
1346 2017-10-09  Ed Schonberg  <schonberg@adacore.com>
1348         * sem_util.adb (Subprogram_Name): If this is a child unit, use the name
1349         of the Defining_Program_Unit_Name, which is an identifier, in order to
1350         construct the string for the fully qualified name.
1352 2017-10-09  Justin Squirek  <squirek@adacore.com>
1354         * sem_ch3.adb: Rename Uses_Unseen_Priv into
1355         Contains_Lib_Incomplete_Type.
1357 2017-10-09  Hristian Kirtchev  <kirtchev@adacore.com>
1359         * sem_aggr.adb, sem_spark.adb, adabkend.adb, exp_ch5.adb, frontend.adb,
1360         sem_ch12.adb, fmap.adb, exp_ch6.adb, exp_spark.adb, lib-load.adb,
1361         exp_ch9.adb, osint.adb, exp_disp.adb, sem_ch8.adb, sem_ch8.ads,
1362         prepcomp.adb, gnat1drv.adb, atree.adb, sinput-l.adb, targparm.adb,
1363         sem_ch10.adb, par-ch8.adb: Minor reformatting.
1365 2017-10-09  Hristian Kirtchev  <kirtchev@adacore.com>
1367         * sem_elab.adb (Is_Suitable_Access): This scenario is now only relevant
1368         in the static model.
1369         (Is_Suitable_Variable_Assignment): This scenario is now only relevant
1370         in the static model.
1371         (Is_Suitable_Variable_Reference): This scenario is now only relevant in
1372         the static model.
1374 2017-10-09  Ed Schonberg  <schonberg@adacore.com>
1376         * sem_ch3.adb (Analyze_Declarations): In ASIS mode, resolve aspect
1377         expressions when the enclosing scope is a subprogram body and the next
1378         declaration is a body that freezes entities previously declared in the
1379         scope.
1381 2017-10-09  Justin Squirek  <squirek@adacore.com>
1383         * sem_ch8.adb (Analyze_Use_Package): Remove checking of mixture between
1384         ghost packages and living packages in use clauses.
1385         (Use_One_Type, Note_Redundant_Use): Correct warning messages
1387 2017-10-09  Justin Squirek  <squirek@adacore.com>
1389         * osint.ads: Document new parameter FD for Read_Source_File.
1391 2017-10-09  Ed Schonberg  <schonberg@adacore.com>
1393         * exp_util.adb (Make_Predicate_Call): If the type of the expression to
1394         which the predicate check applies is tagged, convert the expression to
1395         that type. This is in most cases a no-op, but is relevant if the
1396         expression is clas-swide, because the predicate function being invoked
1397         is not a primitive of the type and cannot take a class-wide actual.
1399 2017-10-09  Gary Dismukes  <dismukes@adacore.com>
1401         * exp_disp.adb: Minor reformatting.
1403 2017-10-09  Arnaud Charlet  <charlet@adacore.com>
1405         * sem_warn.adb (Warn_On_Unreferenced_Entity): Fix typo.
1407 2017-10-09  Hristian Kirtchev  <kirtchev@adacore.com>
1409         * sem_elab.adb (Install_ABE_Check): Do not generate an ABE check for
1410         GNATprove.
1411         (Install_ABE_Failure): Do not generate an ABE failure for GNATprove.
1413 2017-10-09  Bob Duff  <duff@adacore.com>
1415         * exp_ch6.adb: (Make_Build_In_Place_Call_In_Object_Declaration): Return
1416         immediately if the call has already been processed (by a previous call
1417         to Make_Build_In_Place_Call_In_Anonymous_Context).
1418         * sem_elab.adb: Minor typo fixes.
1420 2017-10-09  Ed Schonberg  <schonberg@adacore.com>
1422         * sem_ch13.adb (Replace_Type_Ref): In the expression for a dynamic
1423         predicate, do not replace an identifier that matches the type if the
1424         identifier is a selector in a selected component, because this
1425         indicates a reference to some homograph of the type itself, and  not to
1426         the current occurence in the predicate.
1428 2017-10-09  Eric Botcazou  <ebotcazou@adacore.com>
1430         * repinfo.adb (List_Record_Layout): Tweak formatting.
1431         (Write_Val): Remove superfluous spaces in back-end layout mode.
1433 2017-10-09  Piotr Trojanek  <trojanek@adacore.com>
1435         * sem_res.adb (Property_Error): Remove.
1436         (Resolve_Actuals): check for SPARK RM 7.1.3(10) rewritten to match the
1437         current wording of the rule.
1439 2017-10-09  Justin Squirek  <squirek@adacore.com>
1441         * sem_ch3.adb (Analyze_Declarations): Add check for ghost packages
1442         before analyzing a given scope due to an expression function.
1443         (Uses_Unseen_Lib_Unit_Priv): Rename to Uses_Unseen_Priv.
1445 2017-10-09  Bob Duff  <duff@adacore.com>
1447         * exp_ch6.adb (Make_Build_In_Place_Call_In_Object_Declaration): Use
1448         Defining_Identifier (Obj_Decl) in two places, because it might have
1449         changed.
1450         * exp_ch6.adb (Make_Build_In_Place_Call_In_Allocator): Deal with cases
1451         involving 'Input on (not visibly) derived types.
1453 2017-10-09  Hristian Kirtchev  <kirtchev@adacore.com>
1455         * atree.adb: Add new soft link Rewriting_Proc.
1456         (Rewrite): Invoke the subprogram attached to the rewriting soft link.
1457         (Set_Rewriting_Proc): New routine.
1458         * attree.ads: Add new access-to-subprogram type Rewrite_Proc.
1459         (Set_Rewriting_Proc): New routine.
1460         * checks.adb (Install_Primitive_Elaboration_Check): Use 'E' character
1461         for *E*laboration flag to maintain consistency with other elaboration
1462         flag generating subprograms.
1463         * debug.adb: Document the new usage of flag -gnatdL.
1464         * einfo.adb: Node19 is now used as Receiving_Entry.  Node39 is now used
1465         as Protected_Subprogram.  Flag148 is now used as
1466         Is_Elaboration_Checks_OK_Id.  Flag302 is now used as
1467         Is_Initial_Condition_Procedure.
1468         (Is_Elaboration_Checks_OK_Id): New routine.
1469         (Is_Initial_Condition_Procedure): New routine.
1470         (Protected_Subprogram): New routine.
1471         (Receiving_Entry): New routine.
1472         (SPARK_Pragma): Update assertion.
1473         (SPARK_Pragma_Inherited): Update assertion.
1474         (Suppress_Elaboration_Warnings): Removed.
1475         (Set_Is_Elaboration_Checks_OK_Id): New routine.
1476         (Set_Is_Initial_Condition_Procedure): New routine.
1477         (Set_Protected_Subprogram): New routine.
1478         (Set_Receiving_Entry): New routine.
1479         (Set_SPARK_Pragma): Update assertion.
1480         (Set_SPARK_Pragma_Inherited): Update assertion.
1481         (Write_Entity_Flags): Update the output for Flag148 and Flag302.
1482         (Write_Field19_Name): Add output for Receiving_Entry.
1483         (Write_Field39_Name): Add output for Protected_Subprogram.
1484         (Write_Field40_Name): Update the output for SPARK_Pragma.
1485         * einfo.ads: New attributes Is_Elaboration_Checks_OK_Id,
1486         Is_Initial_Condition_Procedure, Protected_Subprogram, Receiving_Entry.
1487         Remove attribute Suppress_Elaboration_Warnings.  Update the stricture
1488         of various entities.
1489         (Is_Elaboration_Checks_OK_Id): New routine along with pragma Inline.
1490         (Is_Initial_Condition_Procedure): New routine along with pragma Inline.
1491         (Protected_Subprogram): New routine along with pragma Inline.
1492         (Receiving_Entry): New routine along with pragma Inline.
1493         (Suppress_Elaboration_Warnings): Removed.
1494         (Set_Is_Elaboration_Checks_OK_Id): New routine along with pragma
1495         Inline.
1496         (Set_Is_Initial_Condition_Procedure): New routine along with pragma
1497         Inline.
1498         (Set_Protected_Subprogram): New routine along with pragma Inline.
1499         (Set_Receiving_Entry): New routine along with pragma Inline.
1500         (Set_Suppress_Elaboration_Warnings): Removed.
1501         * exp_ch3.adb (Build_Init_Procedure): Use name _Finalizer to maintain
1502         consistency with other finalizer generating subprograms.
1503         (Default_Initialize_Object): Mark the block which wraps the call to
1504         finalize as being part of initialization.
1505         * exp_ch7.adb (Expand_N_Package_Declaration): Directly expand pragma
1506         Initial_Condition.
1507         (Expand_N_Package_Body): Directly expand pragma Initial_Condition.
1508         (Next_Suitable_Statement): Update the comment on usage. Skip over call
1509         markers generated by the ABE mechanism.
1510         * exp_ch9.adb (Activation_Call_Loc): New routine.
1511         (Add_Accept): Link the accept procedure to the original entry.
1512         (Build_Protected_Sub_Specification): Link the protected or unprotected
1513         version to the original subprogram.
1514         (Build_Task_Activation_Call): Code cleanup. Use a source location which
1515         is very close to the "begin" or "end" keywords when generating the
1516         activation call.
1517         * exp_prag.adb (Expand_Pragma_Initial_Condition): Reimplemented.
1518         * exp_spark.adb (Expand_SPARK): Use Expand_SPARK_N_Loop_Statement to
1519         process loops.
1520         (Expand_SPARK_N_Loop_Statement): New routine.
1521         (Expand_SPARK_N_Object_Declaration): Code cleanup. Partially insert the
1522         call to the Default_Initial_Condition procedure.
1523         (Expand_SPARK_Op_Ne): Renamed to Expand_SPARK_N_Op_Ne.
1524         * exp_util.adb (Build_DIC_Procedure_Body): Capture the SPARK_Mode in
1525         effect.
1526         (Build_DIC_Procedure_Declaration): Capture the SPARK_Mode in effect.
1527         (Insert_Actions): Add processing for N_Call_Marker.
1528         (Kill_Dead_Code): Explicitly kill an elaboration scenario.
1529         * exp_util.ads (Make_Invariant_Call): Update the comment on usage.
1530         * frontend.adb: Initialize Sem_Elab. Process all saved top level
1531         elaboration scenarios for ABE issues.
1532         * gcc-interface/trans.c (gnat_to_gnu): Add processing for N_Call_Marker
1533         nodes.
1534         * lib.adb (Earlier_In_Extended_Unit): New variant.
1535         * sem.adb (Analyze): Ignore N_Call_Marker nodes.
1536         (Preanalysis_Active): New routine.
1537         * sem.ads (Preanalysis_Active): New routine.
1538         * sem_attr.adb (Analyze_Access_Attribute): Save certain
1539         elaboration-related attributes. Save the scenario for ABE processing.
1540         * sem_ch3.adb (Analyze_Object_Declaration): Save the SPARK mode in
1541         effect. Save certain elaboration-related attributes.
1542         * sem_ch5.adb (Analyze_Assignment): Save certain elaboration-related
1543         attributes. Save the scenario for ABE processing.
1544         * sem_ch6.adb (Analyze_Abstract_Subprogram_Declaration): Save the SPARK
1545         mode in effect. Save certain elaboration-related attributes.
1546         (Analyze_Subprogram_Body_Helper): Skip N_Call_Marker nodes when
1547         locating the first real statement.
1548         (Analyze_Subprogram_Declaration): Save the SPARK mode in effect. Save
1549         certain elaboration-related attributes.
1550         * sem_ch7.adb (Analyze_Package_Declaration): Do not suppress
1551         elaboration warnings.
1552         * sem_ch8.adb (Attribute_Renaming): Mark a subprogram body which was
1553         generated for purposes of wrapping an attribute used as a generic
1554         actual.
1555         (Find_Direct_Name): Save certain elaboration-related attributes. Save
1556         the scenario for ABE processing.
1557         (Find_Expanded_Name): Save certain elaboration-related attributes. Save
1558         the scenario for ABE processing.
1559         * sem_ch9.adb (Analyze_Entry_Declaration): Save certain
1560         elaboration-related attributes.
1561         (Analyze_Requeue): Save certain elaboration-related attributes. Save
1562         the scenario for ABE processing.
1563         (Analyze_Single_Task_Declaration): Save certain elaboration-related
1564         attributes.
1565         (Analyze_Task_Type_Declaration): Save certain elaboration-related
1566         attributes.
1567         * sem_ch12.adb (Analyze_Generic_Package_Declaration): Save certain
1568         elaboration-related attributes.
1569         (Analyze_Generic_Subprogram_Declaration): Save the SPARK mode in
1570         effect. Save certain elaboration-related attributes.
1571         (Analyze_Package_Instantiation): Save certain elaboration-related
1572         attributes.  Save the scenario for ABE processing. Create completing
1573         bodies in case the instantiation results in a guaranteed ABE.
1574         (Analyze_Subprogram_Instantiation): Save certain elaboration-related
1575         attributes Save the scenario for ABE processing. Create a completing
1576         body in case the instantiation results in a guaranteed ABE.
1577         (Provide_Completing_Bodies): New routine.
1578         * sem_elab.ads: Brand new implementation.
1579         * sem_prag.adb (Analyze_Pragma, cases Elaborate, Elaborate_All,
1580         Elaborate_Body): Do not suppress elaboration warnings.
1581         * sem_res.adb (Make_Call_Into_Operator): Set the parent field of the
1582         operator.
1583         (Resolve_Call): Save certain elaboration-related attributes. Save the
1584         scenario for ABE processing.
1585         (Resolve_Entity_Name): Do not perform any ABE processing here.
1586         (Resolve_Entry_Call): Inherit certain attributes from the original call.
1587         * sem_util.adb (Begin_Keyword_Location): New routine.
1588         (Defining_Entity): Update the parameter profile. Add processing for
1589         concurrent subunits that are rewritten as null statements.
1590         (End_Keyword_Location): New routine.
1591         (Find_Enclosing_Scope): New routine.
1592         (In_Instance_Visible_Part): Code cleanup.
1593         (In_Subtree): Update the parameter profile. Add new version.
1594         (Is_Preelaborable_Aggregate): New routine.
1595         (Is_Preelaborable_Construct): New routine.
1596         (Mark_Elaboration_Attributes): New routine.
1597         (Scope_Within): Update the parameter profile.
1598         (Scope_Within_Or_Same): Update the parameter profile.
1599         * sem_util.ads (Begin_Keyword_Location): New routine.
1600         (Defining_Entity): Update the parameter profile and the comment on
1601         usage.
1602         (End_Keyword_Location): New routine.
1603         (Find_Enclosing_Scope): New routine.
1604         (In_Instance_Visible_Part): Update the parameter profile.
1605         (In_Subtree): Update the parameter profile. Add new version.
1606         (Is_Preelaborable_Aggregate): New routine.
1607         (Is_Preelaborable_Construct): New routine.
1608         (Mark_Elaboration_Attributes): New routine.
1609         (Scope_Within): Update the parameter profile and the comment on usage.
1610         (Scope_Within_Or_Same): Update the parameter profile and the comment on
1611         usage.
1612         * sem_warn.adb (Check_Infinite_Loop_Warning): Use Has_Condition_Actions
1613         to determine whether a loop has meaningful condition actions.
1614         (Has_Condition_Actions): New routine.
1615         * sinfo.adb (ABE_Is_Certain): Removed.
1616         (Is_Declaration_Level_Node): New routine.
1617         (Is_Dispatching_Call): New routine.
1618         (Is_Elaboration_Checks_OK_Node): New routine.
1619         (Is_Initialization_Block): New routine.
1620         (Is_Known_Guaranteed_ABE): New routine.
1621         (Is_Recorded_Scenario): New routine.
1622         (Is_Source_Call): New routine.
1623         (Is_SPARK_Mode_On_Node): New routine.
1624         (No_Elaboration_Check): Removed.
1625         (Target): New routine.
1626         (Was_Attribute_Reference): New routine.
1627         (Set_ABE_Is_Certain): Removed.
1628         (Set_Is_Declaration_Level_Node): New routine.
1629         (Set_Is_Dispatching_Call): New routine.
1630         (Set_Is_Elaboration_Checks_OK_Node): New routine.
1631         (Set_Is_Initialization_Block): New routine.
1632         (Set_Is_Known_Guaranteed_ABE): New routine.
1633         (Set_Is_Recorded_Scenario): New routine.
1634         (Set_Is_Source_Call): New routine.
1635         (Set_Is_SPARK_Mode_On_Node): New routine.
1636         (Set_No_Elaboration_Check): Removed.
1637         (Set_Target): New routine.
1638         (Set_Was_Attribute_Reference): New routine.
1639         * sinfo.ads: Remove attribute ABE_Is_Certain.  Attribute
1640         Do_Discriminant_Check now utilizes Flag3.  Attribute
1641         No_Side_Effect_Removal now utilizes Flag17.  Add new node
1642         N_Call_Marker.  Update the structure of various nodes.
1643         (ABE_Is_Certain): Removed along with pragma Inline.
1644         (Is_Declaration_Level_Node): New routine along with pragma Inline.
1645         (Is_Dispatching_Call): New routine along with pragma Inline.
1646         (Is_Elaboration_Checks_OK_Node): New routine along with pragma Inline.
1647         (Is_Initialization_Block): New routine along with pragma Inline.
1648         (Is_Known_Guaranteed_ABE): New routine along with pragma Inline.
1649         (Is_Recorded_Scenario): New routine along with pragma Inline.
1650         (Is_Source_Call): New routine along with pragma Inline.
1651         (Is_SPARK_Mode_On_Node): New routine along with pragma Inline.
1652         (No_Elaboration_Check): Removed along with pragma Inline.
1653         (Target): New routine along with pragma Inline.
1654         (Was_Attribute_Reference): New routine along with pragma Inline.
1655         (Set_ABE_Is_Certain): Removed along with pragma Inline.
1656         (Set_Is_Declaration_Level_Node): New routine along with pragma Inline.
1657         (Set_Is_Dispatching_Call): New routine along with pragma Inline.
1658         (Set_Is_Elaboration_Checks_OK_Node): New routine along with pragma
1659         Inline.
1660         (Set_Is_Initialization_Block): New routine along with pragma Inline.
1661         (Set_Is_Known_Guaranteed_ABE): New routine along with pragma Inline.
1662         (Set_Is_Recorded_Scenario): New routine along with pragma Inline.
1663         (Set_Is_Source_Call): New routine along with pragma Inline.
1664         (Set_Is_SPARK_Mode_On_Node): New routine along with pragma Inline.
1665         (Set_No_Elaboration_Check): Removed along with pragma Inline.
1666         (Set_Target): New routine along with pragma Inline.
1667         (Set_Was_Attribute_Reference): New routine along with pragma Inline.
1668         * sprint.adb (Sprint_Node_Actual): Add an entry for N_Call_Marker.
1670 2017-10-09  Bob Duff  <duff@adacore.com>
1672         * exp_ch7.adb (Create_Finalizer): Suppress checks within the finalizer.
1674 2017-10-09  Bob Duff  <duff@adacore.com>
1676         * freeze.ads: Minor comment fixed.
1678 2017-10-09  Bob Duff  <duff@adacore.com>
1680         * exp_ch6.adb: (Make_Build_In_Place_Call_In_Object_Declaration): Take
1681         care of unchecked conversions in addition to regular conversions. This
1682         takes care of a case where a type is derived from a private untagged
1683         type that is completed by a tagged controlled type.
1685 2017-10-09  Ed Schonberg  <schonberg@adacore.com>
1687         * exp_disp.adb (Build_Class_Wide_Check, Replace_Formals): When
1688         rewriting a class-wide condition, handle properly the case where the
1689         controlling argument of the operation to which the condition applies is
1690         an access to a tagged type, and the condition includes a dispatching
1691         call with an implicit dereference.
1693 2017-10-09  Bob Duff  <duff@adacore.com>
1695         * exp_ch6.adb: (Make_Build_In_Place_Call_In_Object_Declaration): Remove
1696         the code at the end of this procedure that was setting the type of a
1697         class-wide object to the specific type returned by a function call.
1698         Treat this case as indefinite instead.
1700 2017-10-09  Ed Schonberg  <schonberg@adacore.com>
1702         * sem_ch4.adb (Try_Class_Wide_Operation, Traverse_Homonyms):
1703         Suppress spurious ambiguity error when two traversals of the homonym
1704         chain (first directly, and then through an examination of relevant
1705         interfaces) retrieve the same operation, when other irrelevant homonyms
1706         of the operatioh are also present.
1708 2017-10-09  Ed Schonberg  <schonberg@adacore.com>
1710         * sem_util.adb (Object_Access_Level): If the object is the return
1711         statement of an expression function, return the level of the function.
1712         This is relevant when the object involves an implicit conversion
1713         between access types and the expression function is a completion, which
1714         forces the analysis of the expression before rewriting it as a body, so
1715         that freeze nodes can appear in the proper scope.
1717 2017-10-09  Bob Duff  <duff@adacore.com>
1719         * atree.adb: Make nnd apply to everything "interesting", including
1720         Rewrite.  Remove rrd.
1722 2017-10-09  Javier Miranda  <miranda@adacore.com>
1724         * exp_ch3.adb (Expand_N_Object_Declaration): Avoid never-ending loop
1725         processing the declaration of the dummy object internally created by
1726         Make_DT to compute the offset to the top of components referencing
1727         secondary dispatch tables.
1728         (Initialize_Tag): Do not initialize the offset-to-top field if it has
1729         been initialized initialized.
1730         * exp_disp.ads (Building_Static_Secondary_DT): New subprogram.
1731         * exp_disp.adb (Building_Static_Secondary_DT): New subprogram.
1732         (Make_DT): Create a dummy constant object if we can statically build
1733         secondary dispatch tables.
1734         (Make_Secondary_DT): For statically allocated secondary dispatch tables
1735         use the dummy object to compute the offset-to-top field value by means
1736         of the attribute 'Position.
1738 2017-10-09  Bob Duff  <duff@adacore.com>
1740         * exp_ch6.adb (Expand_N_Extended_Return_Statement): Add self-checking
1741         code so if BIPAlloc is not passed in, it will likely raise
1742         Program_Error instead of cause miscellaneous chaos.
1743         (Is_Build_In_Place_Result_Type): Return False if not Expander_Active,
1744         as for the other Is_B-I-P... functions.
1745         * sem_aggr.adb (Resolve_Extension_Aggregate): For an extension
1746         aggregate whose ancestor part is a build-in-place call returning a
1747         nonlimited type, transform the assignment to the ancestor part to use a
1748         temp.
1749         * sem_ch3.adb (Build_Itype_Reference): Handle the case where we're
1750         creating an Itype for a library unit entity.
1751         (Check_Initialization): Avoid spurious error message on
1752         internally-generated call.
1753         * sem_ch5.adb (Analyze_Assignment): Handle the case where the
1754         right-hand side is a build-in-place call. This didn't happen when b-i-p
1755         was only for limited types.
1756         * sem_ch6.adb (Create_Extra_Formals): Remove assumption that b-i-p
1757         implies >= Ada 2005.
1758         * sem_ch7.adb (Scan_Subprogram_Refs): Avoid traversing the same nodes
1759         repeatedly.
1760         * sem_util.adb (Next_Actual): Handle case of build-in-place call.
1762 2017-10-09  Arnaud Charlet  <charlet@adacore.com>
1764         * doc/gnat_ugn/gnat_and_program_execution.rst: Minor edit.
1766 2017-10-09  Piotr Trojanek  <trojanek@adacore.com>
1768         * libgnarl/s-taprob.adb: Minor whitespace fix.
1770 2017-10-09  Bob Duff  <duff@adacore.com>
1772         * namet.ads: Minor comment fix.
1774 2017-10-09  Piotr Trojanek  <trojanek@adacore.com>
1776         * sem_aux.adb (Unit_Declaration_Node): Detect protected declarations,
1777         just like other program units listed in Ada RM 10.1(1).
1779 2017-10-09  Justin Squirek  <squirek@adacore.com>
1781         * sem_ch8.adb (Update_Chain_In_Scope): Modify warning messages.
1783 2017-10-09  Ed Schonberg  <schonberg@adacore.com>
1785         * sem_ch12.adb (Analyze_Associations, Check_Generic_Parent): If an
1786         actual for a formal package is an instantiation of a child unit, create
1787         a freeze node for the instance of the parent if it appears in the same
1788         scope and is not frozen yet.
1790 2017-10-09  Pierre-Marie de Rodat  <derodat@adacore.com>
1792         * exp_atag.ads, libgnat/a-tags.adb, libgnat/a-tags.ads: Enhance
1793         in-source documentation for tagged types's Offset_To_Top.
1795 2017-10-09  Bob Duff  <duff@adacore.com>
1797         * exp_ch3.adb (Build_Assignment): Parameter name N was somewhat
1798         confusing.  Same for N_Loc.  Remove assumption that b-i-p implies
1799         limited.  This is for the case of a function call that occurs as the
1800         default for a record component.
1801         (Expand_N_Object_Declaration): Deal with the case where expansion has
1802         created an object declaration initialized with something like
1803         F(...)'Reference.
1804         * exp_ch3.adb: Minor reformatting.
1806 2017-10-09  Ed Schonberg  <schonberg@adacore.com>
1808         * exp_attr.adb (Expand_Attribute_Reference, case 'Valid): The prefix of
1809         the attribute is an object, but it may appear within a conversion. The
1810         object itself must be retrieved when generating the range test that
1811         implements the validity check on a scalar type.
1813 2017-10-05  Eric Botcazou  <ebotcazou@adacore.com>
1815         PR ada/82393
1816         * mingw32.h (_O_U8TEXT, _O_U16TEXT, _O_WTEXT): Delete.
1817         * sysdep.c (__gnat_set_mode ): Use DJGPP version for Cygwin.
1819 2017-10-02  Eric Botcazou  <ebotcazou@adacore.com>
1820             Pierre-Marie de Rodat  <derodat@adacore.com>
1822         PR ada/82384
1823         * libgnarl/s-linux__x32.ads (suseconds_t): New subtype.
1824         (time_t): Change from derived type to subtype.
1825         (timeval): Use suseconds_t for tv_usec.
1826         * libgnarl/s-osinte__x32.adb (To_Timespec): Remove use type clause.
1828 2017-10-02  Richard Sandiford  <richard.sandiford@linaro.org>
1830         * gcc-interface/decl.c (annotate_value): Use wi::to_widest when
1831         handling the form (plus/mult (convert @0) @1).
1833 2017-09-29  Bob Duff  <duff@adacore.com>
1835         * exp_ch6.adb (Expand_Call_Helper): Replace with code more similar to
1836         what we had before.
1837         (Make_Build_In_Place_Call_In_Object_Declaration): Back out previous
1838         change. Set the Etype in the class-wide case. This fixes a regression
1839         in the libadalang test suite.
1841 2017-09-29  Joel Brobecker  <brobecker@adacore.com>
1843         * doc/gnat_ugn/building_executable_programs_with_gnat.rst,
1844         doc/gnat_ugn/the_gnat_compilation_model.rst: Avoid use of single colon
1845         in comment markup.
1846         * gnat_ugn.texi: Regenerate.
1848 2017-09-29  Justin Squirek  <squirek@adacore.com>
1850         * ali-util.adb, comperr.adb, cprint.adb, errout.adb, fmap.adb,
1851         fname-sf.adb, frontend.adb, lib-xref-spark_specific.adb, gnat1drv.adb,
1852         gnatls.adb, lib.adb, lib-load.adb, lib-writ.adb, prepcomp.adb,
1853         sinput-d.adb, sinput-l.adb, sprint.adb, targparm.adb: Update comparison
1854         for checking source file status and error message and/or call to
1855         Read_Source_File.
1856         * libgnat/s-os_lib.ads: Add new potential value constant for
1857         uninitialized file descriptors.
1858         * osint.adb, osint.ads (Read_Source_File): Add extra parameter to
1859         return result of IO to encompass a read access failure in addition to a
1860         file-not-found error.
1862 2017-09-29  Bob Duff  <duff@adacore.com>
1864         * exp_ch6.adb (Expand_Call_Helper): Handle case of build-in-place
1865         functions returning nonlimited types. Allow for qualified expressions
1866         and type conversions.
1867         (Expand_N_Extended_Return_Statement): Correct the computation of
1868         Func_Bod to allow for child units.
1869         (Expand_Simple_Function_Return): Remove assumption that b-i-p implies
1870         limited (initialization of In_Place_Expansion), and implies >= Ada
1871         2005.
1872         (Is_Build_In_Place_Result_Type): New function to accompany
1873         Is_Build_In_Place_Function and Is_Build_In_Place_Function_Call, because
1874         sometimes we just have the type on our hands, not the function.  For
1875         now, does the same thing as the old version, so build-in-place is
1876         disabled for nonlimited types, except that you can use -gnatd.9 to
1877         enable it.
1878         * exp_ch6.ads (Is_Build_In_Place_Result_Type): New function to
1879         accompany Is_Build_In_Place_Function and
1880         Is_Build_In_Place_Function_Call, because sometimes we just have the
1881         type on our hands, not the function.
1882         (Make_Build_In_Place_Call_In_...): Handle nonlimited build-in-place
1883         cases.
1884         (Make_Build_In_Place_Call_In_Object_Declaration): Remove the
1885         questionable code at the end that was setting the Etype.
1886         * exp_aggr.adb (Is_Build_In_Place_Aggregate_Return): New function to
1887         determine whether "return (...agg...);" is returning from a
1888         build-in-place function.
1889         (Initialize_Ctrl_Array_Component, Initialize_Ctrl_Record_Component):
1890         Remove assumption that b-i-p implies limited (initialization of
1891         In_Place_Expansion).
1892         (Build_Record_Aggr_Code): AI-287: fix comment; it can't be wrapped in
1893         an unchecked conversion.  Add assertions.
1894         (Convert_Aggr_In_Object_Decl): Establish_Transient_Scope -- no need for
1895         secondary stack here, just because the type needs finalization.  That
1896         code is obsolete.
1897         (Convert_To_Assignments): Only set Unc_Decl if Nkind (N) = N_Aggregate.
1898         For "return (...agg...);" don't assume b-i-p implies limited.
1899         Needs_Finalization does not imply secondary stack.
1900         (Expand_Array_Aggregate): Named notation.  Reverse the sense of
1901         Component_OK_For_Backend -- more readability with fewer double
1902         negatives.
1903         * exp_attr.adb (Expand_N_Attribute_Reference): Remove assumptions that
1904         b-i-p implies >= Ada 2005.
1905         * exp_ch3.adb (Expand_N_Object_Declaration): Remove assumptions that
1906         b-i-p implies >= Ada 2005.  Remove Adjust if we're building the return
1907         object of an extended return statement in place.
1908         * exp_ch4.adb (Expand_Allocator_Expression, Expand_N_Indexed_Component,
1909         Expand_N_Selected_Component, Expand_N_Slice): Remove assumptions that
1910         b-i-p implies >= Ada 2005.
1911         * exp_ch5.adb (Expand_N_Assignment_Statement): Remove assumption that
1912         b-i-p implies >= Ada 2005.
1913         * exp_ch7.adb: Comment fix.
1914         * exp_ch8.adb (Expand_N_Object_Renaming_Declaration): Remove
1915         assumptions that b-i-p implies >= Ada 2005.
1916         * exp_disp.adb (Expand_Interface_Actuals): Remove assumptions that
1917         b-i-p implies >= Ada 2005.
1918         * exp_util.adb (Build_Allocate_Deallocate_Proc): Look at Storage_Pool
1919         (Expr), in case Pool_Id is not set.
1920         (Initialized_By_Aliased_BIP_Func_Call): Handle case where the call is
1921         qualified or converted.
1922         (Is_Secondary_Stack_BIP_Func_Call): Don't check if Nkind (Selector_Name
1923         (Param)) = N_Identifier; that's all it could be.
1924         * sinfo.ads: Comment fixes.
1925         * snames.ads-tmpl: Comment fixes.
1926         * debug.adb: Add flag gnatd.9, to enable the build-in-place machinery.
1928 2017-09-29  Justin Squirek  <squirek@adacore.com>
1930         * sem_ch8.adb (Mark_Use_Clauses): Add recursive call to properly handle
1931         all cases related to marking entity identifiers.
1933 2017-09-29  Vasiliy Fofanov  <fofanov@adacore.com>
1935         * adaint.c (win32_wait): Properly handle error and take into account
1936         the WIN32 limitation on the number of simultaneous wait objects.
1938 2017-09-29  Vasiliy Fofanov  <fofanov@adacore.com>
1940         * cal.c: Minor proofreading.
1942 2017-09-29  Vasiliy Fofanov  <fofanov@adacore.com>
1944         * doc/gnat_ugn/gnat_utility_programs.rst: Minor formatting fix.
1945         * gnat_ugn.texi: Regenerate.
1947 2017-09-29  Bob Duff  <duff@adacore.com>
1949         * lib-xref.ads: Comment fix.
1951 2017-09-29  Bob Duff  <duff@adacore.com>
1953         * exp_aggr.adb: Remove calls to Set_No_Ctrl_Actions for discriminants.
1954         Discriminants can't need finalization.
1956 2017-09-29  Ed Schonberg  <schonberg@adacore.com>
1958         * sem_ch6.adb (Analyze_Expression_Function): Do not emit freeze nodes
1959         for types in expression if the function is within a generic unit.
1960         * sem_res.adb (Resolve): In a generic context do not freeze an
1961         expression, unless it is an entity. This exception is solely for the
1962         purpose of detecting illegal uses of deferred constants in generic
1963         units.
1964         * sem_res.adb: Minor reformatting.
1966 2017-09-29  Justin Squirek  <squirek@adacore.com>
1968         * sem_ch8.adb (Note_Redundant_Use): Add guard to protect against false
1969         redundant warnings.
1971 2017-09-29  Yannick Moy  <moy@adacore.com>
1973         * sinput-c.adb: Remove unused with-clause on Ada.Unchecked_Conversion.
1975 2017-09-29  Eric Botcazou  <ebotcazou@adacore.com>
1977         * doc/gnat_rm/representation_clauses_and_pragmas.rst: Minor rewording.
1978         * doc/gnat_rm/implementation_defined_pragmas.rst (Optimize_Alignment):
1979         Document the effect of pragma Optimize_Alignment (Space) on non-packed
1980         record types.
1981         * gnat_rm.texi: Regenerate.
1983 2017-09-25  Justin Squirek  <squirek@adacore.com>
1985         * aspects.adb, bindgen.adb, clean.adb, erroutc.adb, exp_ch13.adb,
1986         exp_dbug.adb, exp_unst.adb, exp_util.adb, frontend.adb, gnat1drv.adb,
1987         gnatdll.adb, gnatlink.adb, gnatls.adb, gnatname.adb, gnatxref.adb,
1988         gnatfind.adb, libgnat/a-cfhama.ads, libgnat/a-exetim__mingw.adb,
1989         libgnat/a-strmap.adb, libgnat/a-teioed.adb, libgnat/g-alvety.ads,
1990         libgnat/g-expect.adb, libgnat/g-regist.adb, libgnat/g-socket.adb,
1991         libgnat/g-socthi__mingw.ads, libgnat/s-stausa.adb,
1992         libgnat/s-tsmona__linux.adb, libgnat/s-tsmona__mingw.adb,
1993         libgnarl/s-taenca.adb, libgnarl/s-tassta.adb, libgnarl/s-tarest.adb,
1994         libgnarl/s-tpobop.adb, make.adb, makeusg.adb, namet.adb, output.ads,
1995         put_scos.adb, repinfo.adb, rtsfind.adb, scn.ads, sem_attr.adb,
1996         sem_aux.ads, sem_warn.ads, targparm.adb, xr_tabls.adb, xref_lib.adb:
1997         Removal of ineffective use-clauses.
1998         * exp_ch9.adb (Is_Simple_Barrier_Name): Check for false positives with
1999         constant folded barriers.
2000         * ghost.adb, sprint.adb, sem_ch10.adb, sem_warn.adb: Change access to
2001         Subtype_Marks and Names list in use-clause nodes to their new singular
2002         counterparts (e.g. Subtype_Mark, Name).
2003         * par.adb, par-ch8.adb (Append_Use_Clause): Created to set
2004         Prev_Ids and More_Ids in use-clause nodes.
2005         (P_Use_Clause): Modify to take a list as a parameter.
2006         (P_Use_Package_Clause, P_Use_Type_Clause): Divide names and
2007         subtype_marks within an aggregate use-clauses into individual clauses.
2008         * par-ch3.adb, par-ch10.adb, par-ch12.adb: Trivally modify call to
2009         P_Use_Clause to match its new behavior.
2010         * sem.adb (Analyze): Mark use clauses for non-overloaded entities.
2011         * sem_ch4.adb (Try_One_Interp): Add sanity check to handle previous
2012         errors.
2013         * sem_ch6.adb (Analyze_Generic_Subprogram_Body,
2014         Analyze_Subprogram_Body_Helper): Update use clause chain at the end of
2015         the declarative region.
2016         * sem_ch7.adb (Analyze_Package_Body_Helper): Update use clause chain
2017         after analysis (Analyze_Package_Specification): Update use clause chain
2018         when there is no body.
2019         * sem_ch8.ads, sem_ch8.adb (Analyze_Use_Package, Analyze_Use_Type): Add
2020         parameter to determine weither the installation of scopes should also
2021         propagate on the use-clause "chain".
2022         (Mark_Use_Clauses): Created to traverse use-clause chains and determine
2023         what constitutes a valid "use" of a clause.
2024         (Update_Use_Clause_Chain): Created to aggregate common machinary used
2025         to clean up use-clause chains (and warn on ineffectiveness) at the end
2026         of declaritive regions.
2027         * sem_ch8.adb (Analyze_Package_Name): Created to perform analysis on a
2028         package name from a use-package clause.
2029         (Analyze_Package_Name_List): Created to perform analysis on a list of
2030         package names (similar to Analyze_Package_Name).
2031         (Find_Most_Prev): Created to traverse to the beginning of a given
2032         use-clause chain.
2033         (Most_Decendant_Use_Clause): Create to identify which clause from a
2034         given set is highest in scope (not always the most prev).
2035         (Use_One_Package, Use_One_Type): Major cleanup and reorganization to
2036         handle the new chaining algorithm, also many changes related to
2037         redundant clauses. A new parameter has also been added to force
2038         installation to handle certain cases.
2039         * sem_ch9.adb (Analyze_Entry_Body, Analyze_Protected_Body,
2040         Analyze_Task_Body): Mark use clauses on relevant entities.
2041         * sem_ch10.adb, sem_ch10.ads (Install_Context_Clauses,
2042         Install_Parents): Add parameter to determine weither the installation
2043         of scopes should also propagate on the use-clause "chain".
2044         * sem_ch12.adb (Inline_Instance_Body): Add flag in call to
2045         Install_Context to avoid redundant chaining of use-clauses.
2046         * sem_ch13.adb: Minor reformatting.
2047         * sem_res.adb (Resolve): Mark use clauses on operators.
2048         (Resolve_Call, Resolve_Entity_Name): Mark use clauses on relevant
2049         entities.
2050         * sinfo.adb, sinfo.ads (Is_Effective_Use_Clause,
2051         Set_Is_Effective_Use_Clause): Add new flag to N_Use_Clause nodes to
2052         represent any given clause's usage/reference/necessity.
2053         (Prev_Use_Clause, Set_Prev_Use_Clause): Add new field to N_Use_Clause
2054         nodes to allow loose chaining of redundant clauses.
2055         (Set_Used_Operations, Set_Subtype_Mark, Set_Prev_Ids, Set_Names,
2056         Set_More_Ids, Set_Name): Modify set procedure calls to reflect
2057         reorganization in node fields.
2058         * types.ads (Source_File_Index): Adjust index bounds.
2059         (No_Access_To_Source_File): New constant.
2061 2017-09-25  Ed Schonberg  <schonberg@adacore.com>
2063         * sem_ch13.adb (Analyze_One_Aspect): In ASIS mode make a full copy of
2064         the expression to be used in the generated attribute specification
2065         (rather than relocating it) to avoid resolving a potentially malformed
2066         tree when the expression is resolved through an ASIS-specific call to
2067         Resolve_Aspect_Expressions.  This manifests itself as a crash on a
2068         function with parameter associations.
2070 2017-09-25  Yannick Moy  <moy@adacore.com>
2072         * exp_spark.adb (Expand_SPARK_Indexed_Component,
2073         Expand_SPARK_Selected_Component): New procedures to insert explicit
2074         dereference if required.
2075         (Expand_SPARK): Call the new procedures.
2077 2017-09-25  Patrick Bernardi  <bernardi@adacore.com>
2079         * libgnat/a-stwiun.adb, libgnat/s-stchop__vxworks.adb,
2080         libgnat/g-socthi__vxworks.ads, libgnat/a-stzunb.adb,
2081         libgnat/a-strunb.adb, libgnarl/s-osinte__lynxos178.adb,
2082         libgnarl/s-intman__vxworks.adb, libgnarl/s-osinte__darwin.adb,
2083         libgnarl/a-exetim__darwin.adb: Removed ineffective use-clauses.
2085 2017-09-25  Vasiliy Fofanov  <fofanov@adacore.com>
2087         * adaint.c (win32_wait): Properly handle error and take into account
2088         the WIN32 limitation on the number of simultaneous wait objects.
2090 2017-09-25  Yannick Moy  <moy@adacore.com>
2092         * sem_ch3.adb (Constant_Redeclaration): Do not insert a call to the
2093         invariant procedure in GNATprove mode.
2094         * sem_ch5.adb (Analyze_Assignment): Likewise.
2096 2017-09-25  Piotr Trojanek  <trojanek@adacore.com>
2098         * adabkend.adb (Call_Back_End): Fix wording of "front-end" and
2099         "back-end" in comments.
2101 2017-09-25  Ed Schonberg  <schonberg@adacore.com>
2103         * exp_ch6.adb (Expand_Call_Helper): The extra accessibility check in a
2104         call that appears in a classwide precondition and that mentions an
2105         access formal of the subprogram, must use the accessibility level of
2106         the actual in the call. This is one case in which a reference to a
2107         formal parameter appears outside of the body of the subprogram.
2109 2017-09-25  Hristian Kirtchev  <kirtchev@adacore.com>
2111         * sem_res.adb (Replace_Actual_Discriminants): Replace a discriminant
2112         for GNATprove.
2113         (Resolve_Entry): Clean up predicate
2115 2017-09-25  Hristian Kirtchev  <kirtchev@adacore.com>
2117         * sem_prag.adb (Analyze_Constituent): Raise Unrecoverable_Error rather
2118         than Program_Error because U_E is more in line with respect to the
2119         intended behavior.
2121 2017-09-25  Ed Schonberg  <schonberg@adacore.com>
2123         * sem_ch13.adb (Resolve_Aspect_Expressions): The expression for aspect
2124         Storage_Size does not freeze, and thus can include references to
2125         deferred constants.
2127 2017-09-25  Hristian Kirtchev  <kirtchev@adacore.com>
2129         * exp_spark.adb (Expand_SPARK_Potential_Renaming): Do not process a
2130         reference when it appears within a pragma of no significance to SPARK.
2131         (In_Insignificant_Pragma): New routine.
2132         * sem_prag.ads: Add new table Pragma_Significant_In_SPARK.
2134 2017-09-25  Ed Schonberg  <schonberg@adacore.com>
2136         * sem_ch12.adb (Analyze_Associations, case N_Formal_Package): If the
2137         actual is a renaming, indicate that it is the renamed package that must
2138         be frozen before the instantiation.
2140 2017-09-25  Yannick Moy  <moy@adacore.com>
2142         * doc/gnat_ugn/gnat_and_program_execution.rst: Fix typo in description
2143         of dimensionality system in GNAT UG.
2144         * gnat_ugn.texi: Regenerate.
2146 2017-09-25  Yannick Moy  <moy@adacore.com>
2148         * gnat1drv.adb: Call Check_Safe_Pointers from the frontend in
2149         GNATprove_Mode when switch -gnatdF used.
2151 2017-09-25  Piotr Trojanek  <trojanek@adacore.com>
2153         * adabkend.adb (Call_Back_End): Reset Current_Error_Node when starting
2154         the backend.
2156 2017-09-25  Javier Miranda  <miranda@adacore.com>
2158         * exp_imgv.adb (Expand_Image_Attribute): Disable the optimized
2159         expansion of user-defined enumeration types when the generation of
2160         names for enumeration literals is suppressed.
2162 2017-09-25  Gary Dismukes  <dismukes@adacore.com>
2164         * libgnarl/s-taprop__linux.adb: Minor reformatting.
2166 2017-09-25  Ed Schonberg  <schonberg@adacore.com>
2168         * sem_ch13.adb (Resolve_Aspect_Expressions): Do not resolve identifiers
2169         that appear as selector names of parameter associations, as these are
2170         never resolved by visibility.
2172 2017-09-25  Justin Squirek  <squirek@adacore.com>
2174         * sem_res.adb (Resolve_Entry): Generate reference for index entities.
2176 2017-09-25  Doug Rupp  <rupp@adacore.com>
2178         * libgnarl/s-taprop__linux.adb (Compute_Base_Monotonic_Clock): Refine.
2180 2017-09-25  Javier Miranda  <miranda@adacore.com>
2182         * exp_imgv.adb (Is_User_Defined_Enumeration_Type): New subprogram.
2183         (Expand_User_Defined_Enumeration_Image): New subprogram.
2184         (Expand_Image_Attribute): Enable speed-optimized expansion of
2185         user-defined enumeration types when we are compiling with optimizations
2186         enabled.
2188 2017-09-25  Piotr Trojanek  <trojanek@adacore.com>
2190         * sem_util.adb (Has_Null_Abstract_State): Remove, as an exactly same
2191         routine is already provided by Einfo.
2192         * einfo.adb (Has_Null_Abstract_State): Replace with the body from
2193         Sem_Util, which had better comments and avoided double calls to
2194         Abstract_State.
2196 2017-09-25  Bob Duff  <duff@adacore.com>
2198         * exp_ch3.adb: Rename Comp_Type_Simple to be Comp_Simple_Init.
2200 2017-09-25  Doug Rupp  <rupp@adacore.com>
2202         * libgnarl/s-taprop__linux.adb (Base_Monotonic_Clock): New variable.
2203         (Compute_Base_Monotonic_Clock): New function.
2204         (Timed_Sleep): Adjust to use Base_Monotonic_Clock.
2205         (Timed_Delay): Likewise.
2206         (Monotonic_Clock): Likewise.
2207         * s-oscons-tmplt.c (CLOCK_MONOTONIC): Use on Linux.
2209 2017-09-25  Ed Schonberg  <schonberg@adacore.com>
2211         * sem_ch12.adb (Save_References_In_Aggregate): Small correction to
2212         previous change.
2214 2017-09-25  Hristian Kirtchev  <kirtchev@adacore.com>
2216         * exp_ch5.adb, sem_ch4.adb, sem_ch13.adb, sem_attr.adb, exp_ch3.adb:
2217         Minor reformatting.
2219 2017-09-20  Alexandre Oliva <aoliva@redhat.com>
2221         * gcc-interface/lang.opt (gant, gnatO, gnat): Add RejectNegative.
2223 2017-09-18  Bob Duff  <duff@adacore.com>
2225         * sem_ch4.adb (Complete_Object_Operation): Do not insert 'Access for
2226         reference types in the access-to-access case.
2228 2017-09-18  Eric Botcazou  <ebotcazou@adacore.com>
2230         * sem_attr.adb (Analyze_Access_Attribute): Move check for the presence
2231         of the "aliased" keyword on the prefix from here to...
2232         (Resolve_Attribute) <Attribute_Access>: ...here.  Remove useless call
2233         to Check_No_Implicit_Aliasing.
2234         * sinfo.ads (Non_Aliased_Prefix): Delete.
2235         (Set_Non_Aliased_Prefix): Likewise.
2236         * sinfo.adb (Non_Aliased_Prefix): Delete.
2237         (Set_Non_Aliased_Prefix): Likewise.
2239 2017-09-18  Bob Duff  <duff@adacore.com>
2241         * exp_ch5.adb (Build_Formal_Container_Iteration,
2242         Expand_Formal_Container_Element_Loop): Convert the container to the
2243         root type before passing it to the iteration operations, so it will be
2244         of the right type.
2246 2017-09-18  Bob Duff  <duff@adacore.com>
2248         * einfo.ads, validsw.ads, treepr.ads, sem_util.ads: Comment fixes.
2250 2017-09-18  Bob Duff  <duff@adacore.com>
2252         * exp_ch3.adb (Build_Array_Init_Proc): If validity checking is enabled,
2253         and it's a bit-packed array, pass False to the Consider_IS parameter of
2254         Needs_Simple_Initialization.
2256 2017-09-18  Hristian Kirtchev  <kirtchev@adacore.com>
2258         * sem_ch6.adb (Check_Inline_Pragma): Link the newly generated spec to
2259         the preexisting body.
2260         * sem_prag.adb (Check_Inline_Always_Placement): New routine.
2261         (Process_Inline): Verify the placement of pragma Inline_Always. The
2262         pragma must now appear on the initial declaration of the related
2263         subprogram.
2265 2017-09-18  Ed Schonberg  <schonberg@adacore.com>
2267         * sem_ch3.adb (Analyze_Declarations): In ASIS mode,  At the end of the
2268         declarative list in a subprogram body, analyze aspext specifications to
2269         provide basic semantic information, because otherwise the aspect
2270         specifications might only be snalyzed during expansion, when related
2271         subprograms are generated.
2273 2017-09-18  Bob Duff  <duff@adacore.com>
2275         * exp_ch9.adb (Is_Simple_Barrier_Name): Follow Original_Node, in case
2276         validity checks have rewritten the tree.
2278 2017-09-18  Bob Duff  <duff@adacore.com>
2280         * sem_util.adb: Comment fixes, and remove redundant Is_Itype check.
2282 2017-09-18  Ed Schonberg  <schonberg@adacore.com>
2284         * sem_ch12.adb (Save_References_In_Aggregate): When constructing a
2285         qualified exxpression for an aggregate in a generic unit, verify that
2286         the scope of the type is itself visible and not hidden, so that the
2287         qualified expression is correctly resolved in any instance.
2289 2017-09-18  Bob Duff  <duff@adacore.com>
2291         * sem_ch4.adb (Analyze_Qualified_Expression): Give an error if the type
2292         mark refers to the current instance. Set the type to Any_Type in that
2293         case, to avoid later crashes.
2295 2017-09-18  Ed Schonberg  <schonberg@adacore.com>
2297         * exp_ch3.adb (Replace_Discriminant_References): New procedure,
2298         subsidiary of Build_Assignment, used to handle the initialization code
2299         for a mutable record component whose default value is an aggregate that
2300         sets the values of the discriminants of the components.
2302 2017-09-18  Eric Botcazou  <ebotcazou@adacore.com>
2304         * sem_ch13.adb (Analyze_Attribute_Definition_Clause) <Address>: Mark
2305         the entity as being volatile for an overlay that toggles the scalar
2306         storage order.
2308 2017-09-18  Fedor Rybin  <frybin@adacore.com>
2310         * doc/gnat_ugn/gnat_utility_programs.rst: Document that gnattest
2311         options -U main and --harness-only are not compatible.
2313 2017-09-18  Hristian Kirtchev  <kirtchev@adacore.com>
2315         * freeze.adb, sem_ch6.adb, sem_res.adb: Minor reformatting.
2317 2017-09-18  Piotr Trojanek  <trojanek@adacore.com>
2319         * einfo.ads (Is_Imported): Update comment, as this
2320         routine also applies to constants.
2322 2017-09-18  Yannick Moy  <moy@adacore.com>
2324         * sem_util.adb (Find_Placement_In_State_Space): Allow generic package
2325         holding state.
2327 2017-09-18  Justin Squirek  <squirek@adacore.com>
2329         * sem_prag.adb (Is_Non_Significant_Pragma_Reference): Change the
2330         constant indication for Pragma_Linker_Section.
2332 2017-09-18  Bob Duff  <duff@adacore.com>
2334         Alternate fix for PR ada/71358
2335         * libgnat/g-comlin.adb (Getopt): Remove manual null access checks.
2336         Instead, make a local copy of Config, and if it's null, allocate an
2337         empty Command_Line_Configuration_Record, so we won't crash on null
2338         pointer dereference.
2340 2017-09-16  Eric Botcazou  <ebotcazou@adacore.com>
2342         * libgnarl/a-intnam__rtems.ads: Update copyright date.
2343         * libgnarl/s-interr__hwint.adb: Likewise.
2344         * libgnarl/s-osinte__kfreebsd-gnu.ads: Likewise.
2345         * libgnarl/s-osinte__rtems.adb: Likewise.
2346         * libgnarl/s-osinte__rtems.ads: Likewise.
2348 2017-09-13  Nicolas Roche  <roche@adacore.com>
2350         * Make-lang.in: In the fallback mechanim, parse the associated .ali
2351         file and try to guess the locations of dependencies.
2353 2017-09-13  Eric Botcazou  <ebotcazou@adacore.com>
2355         * sem_ch13.adb (Register_Address_Clause_Check): New procedure to save
2356         the suppression status of Alignment_Check on the current scope.
2357         (Alignment_Checks_Suppressed): New function to use the saved instead of
2358         the current suppression status of Alignment_Check.
2359         (Address_Clause_Check_Record): Add Alignment_Checks_Suppressed field.
2360         (Analyze_Attribute_Definition_Clause): Instead of manually appending to
2361         the table, call Register_Address_Clause_Check.
2362         (Validate_Address_Clauses): Call Alignment_Checks_Suppressed on the
2363         recorded address clause instead of its entity.
2365 2017-09-13  Jerome Guitton  <guitton@adacore.com>
2367         * libgnarl/s-tpopsp__vxworks-tls.adb,
2368         libgnarl/s-tpopsp__vxworks-rtp.adb, libgnarl/s-tpopsp__vxworks.adb
2369         (Self): Register thread if task id is null.
2371 2017-09-13  Arnaud Charlet  <charlet@adacore.com>
2373         * libgnat/s-htable.adb, libgnat/s-htable.ads: Minor style tuning.
2375 2017-09-13  Arnaud Charlet  <charlet@adacore.com>
2377         * lib-xref-spark_specific.adb (Scopes): simplify hash map; now it maps
2378         from an entity to only scope index, as a mapping from an entity to the
2379         same entity was useless.
2380         (Get_Scope_Num): refactor as a simple renaming; rename parameter from N
2381         to E.
2382         (Set_Scope_Num): refactor as a simple renaming; rename parameter from N
2383         to E.
2384         (Is_Constant_Object_Without_Variable_Input): remove local "Result"
2385         variable, just use return statements.
2387 2017-09-13  Arnaud Charlet  <charlet@adacore.com>
2389         * libgnarl/s-vxwext__kernel-smp.adb,
2390         libgnarl/s-tpopsp__vxworks-rtp.adb, libgnarl/s-vxwext__noints.adb:
2391         New file.
2393 2017-09-13  Hristian Kirtchev  <kirtchev@adacore.com>
2395         * einfo.adb: Flag42 is now Is_Controlled_Active.
2396         (Is_Controlled): This attribute is now synthesized.
2397         (Is_Controlled_Active): This attribute is now an explicit flag rather
2398         than a synthesized attribute.   (Set_Is_Controlled): Removed.
2399         (Set_Is_Controlled_Active): New routine.
2400         (Write_Entity_Flags): Update the output for Flag42.
2401         * einfo.ads: Update the documentation of the following attributes:
2402         Disable_Controlled, Is_Controlled, Is_Controlled_Active, Is_Controlled
2403         and Is_Controlled_Active have swapped their functionality.
2404         (Is_Controlled): Renamed to Is_Controlled_Active.
2405         (Is_Controlled_Active): Renamed to Is_Controlled.
2406         (Set_Is_Controlled): Renamed to Set_Is_Controlled_Active.
2407         * exp_ch3.adb (Expand_Freeze_Record_Type): Restore the original use of
2408         Is_Controlled.
2409         * exp_util.adb (Has_Some_Controlled_Component): Code clean up.
2410         (Needs_Finalization): Code clean up. Remove the tests for
2411         Disable_Controlled because a) they were incorrect as they would reject
2412         a type which is sublect to the aspect, but may contain controlled
2413         components, and b) they are no longer necessary.
2414         * exp_util.ads (Needs_Finalization): Update comment on documentation.
2415         * freeze.adb (Freeze_Array_Type): Restore the original use of
2416         Is_Controlled.
2417         (Freeze_Record_Type): Restore the original use of Is_Controlled.
2418         * sem_ch3.adb (Analyze_Object_Declaration): Restore the original use of
2419         Is_Controlled.
2420         (Array_Type_Declaration): Restore the original use of Is_Controlled.
2421         (Build_Derived_Private_Type): Restore the original use of
2422         Is_Controlled.
2423         (Build_Derived_Record_Type): Set the Is_Controlled_Active flag of a
2424         type derived from Ada.Finalization.[Limited_]Controlled.
2425         (Build_Derived_Type): Restore the original use of Is_Controlled.
2426         (Record_Type_Definition): Restore the original use of Is_Controlled.
2427         * sem_ch7.adb (Preserve_Full_Attributes): Restore the original use of
2428         Is_Controlled.
2429         * sem_ch13.adb (Analyze_Aspect_Disable_Controlled): New routine.
2430         (Analyze_Aspect_Specifications): Use routine
2431         Analyze_Aspect_Disable_Controlled to process aspect Disable_Controlled.
2433 2017-09-13  Vincent Celier  <celier@adacore.com>
2435         * clean.adb (Gnatclean): Fix error when looking for target
2436         of <target>-gnatclean
2438 2017-09-13  Javier Miranda  <miranda@adacore.com>
2439             Ed Schonberg  <schonberg@adacore.com>
2441         * sem_ch8.adb (Find_Expanded_Name): Complete code that identifies an
2442         expanded name that designates the current instance of a child unit in
2443         its own body and appears as the prefix of a reference to an entity
2444         local to the child unit.
2446 2017-09-12  Bob Duff  <duff@adacore.com>
2448         * sem_warn.adb: Minor comment.
2450 2017-09-12  Bob Duff  <duff@adacore.com>
2452         * libgnat/a-cbdlli.adb, libgnat/a-cbhama.adb,
2453         libgnat/a-cbmutr.adb, libgnat/a-cborma.adb: Rename New_Item to
2454         be Default_Initialized_Item, and apply pragma Unmodified to it,
2455         to suppress the warning.
2457 2017-09-12  Eric Botcazou  <ebotcazou@adacore.com>
2459         * exp_aggr.adb (Aggr_Assignment_OK_For_Backend): Add early return
2460         for access types.
2462 2017-09-12  Yannick Moy  <moy@adacore.com>
2464         * gnat1drv.adb (Adjust_Global_Switches): Consider Refined_Global
2465         together with Global when ignoring one in CodePeer mode.
2467 2017-09-12  Javier Miranda  <miranda@adacore.com>
2469         * sem_ch3.adb (Analyze_Declarations): In nested
2470         package declarations that have a private part enable missing check
2471         of the RM rule 13.1.1(11/3): usage names in aspect definitions are
2472         resolved at the end of the immediately enclosing declaration list.
2474 2017-09-12  Bob Duff  <duff@adacore.com>
2476         * sem_ch6.adb (Analyze_Expression_Function): Initialize Def_Id to
2477         Empty.
2479 2017-09-12  Georges-Axel Jaloyan  <jaloyan@adacore.com>
2481         * debug.adb: Reserving flag -gnatdF for safe pointer checking.
2482         * gnat1drv.adb (gnat1drv): Adding the call to the analysis on
2483         dF flag.
2484         * sem_spark.adb, sem_spark.ads: Implementation of the analysis,
2485         in preparation for the evolution of the SPARK language that
2486         includes a pointer analysis for checking non-aliasing of access
2487         types. The Check_Safe_Pointers function is the entry point, and
2488         will traverse the AST and raise compile-time errors everytime
2489         it detects non-begign aliasing.  Detailed comments are present
2490         in the sem_spark.ads file.
2491         * sem_util.adb, sem_util.ads (First_Global, Next_Global): New
2492         functions to iterate over the list of globals of a subprogram.
2493         * libgnat/system.ads: Add restriction No_Finalization.
2494         * gcc-interface/Make-lang.in: Add new file sem_spark.adb and
2495         dependency on g-dynhta.adb.
2497 2017-09-12  Bob Duff  <duff@adacore.com>
2499         * sem_ch6.adb (Analyze_Expression_Function): Call
2500         Check_Dynamically_Tagged_Expression.
2501         * sem_util.adb (Check_Dynamically_Tagged_Expression): Remove
2502         "and then Is_Tagged_Type (Typ)" because there is an earlier
2503         "Assert (Is_Tagged_Type (Typ))".
2505 2017-09-12  Eric Botcazou  <ebotcazou@adacore.com>
2507         * gcc-interface/Makefile.in (SPARC/Solaris): Remove obsolete stuff.
2509 2017-09-11  Arnaud Charlet  <charlet@adacore.com>
2511         * doc/gnat_ugn/the_gnat_compilation_model.rst: Fix sphinx warning.
2512         * doc/gnat_ugn/platform_specific_information.rst: Remove doc
2513         for no longer supported platforms.
2514         * doc/gnat_ugn/gnat_and_program_execution.rst: Added detailed
2515         description of the semantics for dimensionality analysis.
2516         * gnat_ugn.texi: Regenerated.
2518 2017-09-11  Eric Botcazou  <ebotcazou@adacore.com>
2520         * freeze.adb (Has_Incomplete_Compoent): Delete.
2521         (Freeze_Profile):
2522         Do not inhibit the freezing of the profile of an expression
2523         function here.
2524         (Freeze_Subprogram): Do not re-create extra formals.
2525         * sem_ch6.adb (Analyze_Expression_Function): Always
2526         pre-analyze the expression if the function is not a completion.
2527         (Analyze_Subprogram_Body_Helper): For the body generated
2528         from an expression function that is not a completion, do
2529         not freeze the profile and temporary mask the types declared
2530         outside the expression that are not yet frozen.
2531         * sem_res.adb (Rewrite_Renamed_Operator): Also bail out if invoked
2532         during the pre-analysis of an expression function.
2534 2017-09-11  Eric Botcazou  <ebotcazou@adacore.com>
2536         * gcc-interface/gigi.h (enum standard_datatypes): Minor tweak.
2537         (gigi): Likewise.
2539 2017-09-11  Yannick Moy  <moy@adacore.com>
2541         * lib-xref-spark_specific.adb: Minor rewrite.
2543 2017-09-11  Jerome Lambourg  <lambourg@adacore.com>
2545         * libgnat: Rename ?-[a-z]*-* into ?-[a-z]*__*
2546         * gcc-interface/Makefile.in, gcc-interface/Make-lang.in: Take this
2547         renaming into account.
2549 2017-09-11  Jerome Lambourg  <lambourg@adacore.com>
2551         * libgnarl: Rename ?-[a-z]*-* into ?-[a-z]*__*
2552         * gcc-interface/Makefile.in: Take this renaming into account.
2554 2017-09-11  Arnaud Charlet  <charlet@adacore.com>
2556         * s-auxdec-empty.ads, s-auxdec-empty.adb, 9drpc.adb: Removed, no
2557         longer used.
2559 2017-09-11  Yannick Moy  <moy@adacore.com>
2561         * sem_util.adb (Check_Result_And_Post_State):
2562         Do not issue a warning about missing reference to an outcome if
2563         the subprogram is ghost and has no outputs.
2564         * lib-xref-spark_specific.adb, sem_aggr.adb, sem_aux.ads: Minor
2565         reformatting.
2567 2017-09-11  Yannick Moy  <moy@adacore.com>
2569         * gnat1drv.adb (Adjust_Global_Switches): Set
2570         Check_Validity_Of_Parameters to False in GNATprove mode.
2571         * opt.ads (Check_Validity_Of_Parameters): Document switch to
2572         set option.
2574 2017-09-09  Pierre-Marie de Rodat  <derodat@adacore.com>
2576         * gcc-interface/decl.c (gnat_to_gnu_entity) <E_Record_Type>: Don't
2577         generate debug info for inner record types if -fgnat-encodings=minimal.
2578         (gnat_to_gnu_entity) <E_Record_Subtype>: Use the ultimate base record
2579         type as the debug type.
2581 2017-09-09  Eric Botcazou  <ebotcazou@adacore.com>
2583         * gcc-interface/decl.c (components_to_record): Do not reorder in non-
2584         packed record types if pragma Optimize_Alignment (Space) is enabled.
2586 2017-09-09  Eric Botcazou  <ebotcazou@adacore.com>
2588         * gcc-interface/trans.c (Subprogram_Body_to_gnu): Disregard inlining
2589         limits for expression functions.
2590         (gnat_to_gnu) <N_Object_Declaration>: Fix formatting.
2592 2017-09-09  Eric Botcazou  <ebotcazou@adacore.com>
2594         * gcc-interface/decl.c (gnat_to_gnu_entity) <E_Record_Type>: Copy the
2595         layout of the record from the parent type only if both are or are not
2596         unchecked unions.
2597         (is_stored_discriminant): Return false for an unchecked union.
2599 2017-09-09  Eric Botcazou  <ebotcazou@adacore.com>
2601         * gcc-interface/utils2.c (build_allocator): In type_annotate_only mode
2602         return NULL_EXPR.
2604 2017-09-09  Eric Botcazou  <ebotcazou@adacore.com>
2606         * gcc-interface/decl.c (promote_object_alignment): New function taken
2607         from...
2608         (gnat_to_gnu_entity) <E_Variable>: ...here.  Invoke it.
2609         (gnat_to_gnu_field): If the field is Atomic or VFA, invoke it and
2610         create a padding type on success before doing the atomic check.
2612 2017-09-09  Eric Botcazou  <ebotcazou@adacore.com>
2614         * gcc-interface/decl.c (gnat_to_gnu_entity) <E_Variable>: Apply the
2615         promotion to static memory earlier in the processing.
2617 2017-09-09  Eric Botcazou  <ebotcazou@adacore.com>
2619         * gcc-interface/decl.c (gnat_to_gnu_entity): Only set the TYPE_ALIGN_OK
2620         and TYPE_BY_REFERENCE_P flags on types after various promotions.
2621         * gcc-interface/trans.c (node_has_volatile_full_access) <N_Identifier>:
2622         Consider all kinds of entities.
2624 2017-09-09  Eric Botcazou  <ebotcazou@adacore.com>
2626         * gcc-interface/utils.c (convert): When converting to a padding type,
2627         reuse an existing CONSTRUCTOR if it has got the right size.
2629 2017-09-08  Nicolas Roche  <roche@adacore.com>
2631         * gcc-interface/Make-lang.in, gcc-interface/Makefile.in: Find runtime
2632         source in libgnat/
2633         * a-lfztio.ads, g-timsta.ads, g-sercom-linux.adb, s-osprim-solaris.adb,
2634         a-inteio.ads, s-stchop-rtems.adb, s-casuti.adb, s-pack39.adb,
2635         i-vxwork-x86.ads, a-strbou.adb, a-stzmap.adb, s-assert.adb,
2636         a-sfecin.ads, a-cohama.adb, s-casuti.ads, a-suenco.adb, s-pack39.ads,
2637         a-stzmap.ads, a-strbou.ads, s-stalib.adb, s-trasym.adb, g-comver.adb,
2638         s-assert.ads, s-vector.ads, g-cgi.adb, a-cohama.ads, s-wchcnv.adb,
2639         a-titest.adb, s-pack48.adb, a-suenco.ads, a-strunb.adb, s-stalib.ads,
2640         s-trasym.ads, a-nudira.adb, g-comver.ads, a-nuflra.adb, g-cgi.ads,
2641         a-chacon.adb, s-wchcnv.ads, a-excach.adb, s-pack48.ads, a-titest.ads,
2642         a-strunb.ads, s-dwalin.adb, a-nudira.ads, a-chtgbo.adb, s-resfil.adb,
2643         a-scteio.ads, a-nuflra.ads, g-soliop-mingw.ads, s-pack57.adb,
2644         a-chacon.ads, s-bytswa.ads, s-pooloc.adb, g-os_lib.adb, s-dwalin.ads,
2645         a-szuzha.adb, s-resfil.ads, a-chtgbo.ads, s-spsufi.adb, s-pack57.ads,
2646         s-pooloc.ads, g-os_lib.ads, a-stfiha.ads, a-lcteio.ads, a-wtcoau.adb,
2647         a-szuzha.ads, s-mmosin-unix.adb, a-stmaco.ads, s-spsufi.ads,
2648         s-stchop-limit.ads, a-wtcoau.ads, a-exctra.adb, s-mmosin-unix.ads,
2649         s-sequio.adb, s-conca2.adb, g-table.adb, s-imglli.adb,
2650         a-numaux-x86.adb, a-strsea.adb, s-wchstw.adb, a-clrefi.adb,
2651         a-wwboio.adb, a-exctra.ads, s-sequio.ads, s-conca2.ads, a-wwunio.ads,
2652         system-linux-hppa.ads, g-table.ads, s-dimkio.ads, s-imglli.ads,
2653         a-cofove.adb, a-numaux-x86.ads, s-wchstw.ads, a-strsea.ads,
2654         a-clrefi.ads, a-wwboio.ads, s-stratt-xdr.adb, s-crc32.adb,
2655         s-excmac-arm.adb, g-busora.adb, a-cofove.ads, s-osprim-unix.adb,
2656         g-io.adb, s-pack49.adb, s-crc32.ads, s-excmac-arm.ads, a-fzteio.ads,
2657         g-busora.ads, s-stausa.adb, system-linux-mips.ads, sequenio.ads,
2658         g-exctra.adb, g-rewdat.adb, a-cgaaso.adb, g-io.ads, s-pack49.ads,
2659         a-wtflau.adb, a-undesu.adb, s-stausa.ads, a-ztenau.adb, g-enutst.ads,
2660         calendar.ads, s-pack58.adb, g-rewdat.ads, g-exctra.ads, s-ststop.adb,
2661         a-cgaaso.ads, a-strfix.adb, a-comlin.adb, a-strunb-shared.adb,
2662         a-wtflau.ads, a-undesu.ads, a-cbhase.adb, a-ztenau.ads, s-os_lib.adb,
2663         a-coorse.adb, a-chlat1.ads, s-pack58.ads, s-ststop.ads, a-strfix.ads,
2664         a-comlin.ads, a-strunb-shared.ads, a-nscefu.ads, s-valboo.adb,
2665         directio.ads, a-chtgke.adb, a-cbhase.ads, a-wtinau.adb,
2666         system-linux-alpha.ads, s-os_lib.ads, a-coorse.ads,
2667         system-linux-s390.ads, s-imgwiu.adb, a-chtgop.adb, s-valboo.ads,
2668         a-chtgke.ads, a-tienio.adb, s-conca3.adb, a-wtinau.ads,
2669         system-darwin-ppc.ads, i-c.adb, s-expllu.adb, g-expect.adb,
2670         g-sha256.ads, s-vallld.adb, s-imgwiu.ads, a-chtgop.ads, a-strmap.adb,
2671         a-tienio.ads, s-conca3.ads, s-imgint.adb, i-c.ads, s-expllu.ads,
2672         s-osprim-darwin.adb, a-cogeso.adb, g-expect.ads, a-iwteio.ads,
2673         s-vallld.ads, a-coinho-shared.adb, g-shsh64.adb, a-strmap.ads,
2674         g-comlin.adb, a-excpol.adb, s-imgint.ads, a-ztdeau.adb, a-cogeso.ads,
2675         a-coinho-shared.ads, g-shsh64.ads, g-comlin.ads, a-stzsup.adb,
2676         a-rbtgbk.adb, a-wtmoau.adb, a-ztdeau.ads, s-exnlli.adb, g-tty.adb,
2677         g-heasor.adb, g-socthi-dummy.adb, s-llflex.ads, a-zchara.ads,
2678         a-stzsup.ads, a-ztcstr.adb, a-rbtgbk.ads, a-sfwtio.ads, a-wtmoau.ads,
2679         a-sulcin.adb, s-exnlli.ads, system-freebsd.ads, a-stunha.adb,
2680         a-charac.ads, g-tty.ads, g-heasor.ads, s-exctra.adb,
2681         g-socthi-dummy.ads, a-coboho.adb, a-ztcstr.ads, a-tideio.adb,
2682         a-sulcin.ads, a-wrstfi.adb, g-alleve.adb, s-pack59.adb, a-ngrear.adb,
2683         a-stboha.adb, a-stunau-shared.adb, a-stunha.ads, a-lfwtio.ads,
2684         s-fileio.adb, s-exctra.ads, a-coboho.ads, a-ioexce.ads, a-tideio.ads,
2685         a-ngrear.ads, a-wrstfi.ads, s-pack59.ads, g-alleve.ads, a-stboha.ads,
2686         s-poosiz.adb, g-traceb.adb, g-rannum.adb, machcode.ads, s-purexc.ads,
2687         s-fileio.ads, a-cfinve.adb, a-crbtgk.adb, system-solaris-x86.ads,
2688         s-poosiz.ads, g-rannum.ads, g-traceb.ads, a-except.adb, s-conca4.adb,
2689         a-stream.adb, a-cfinve.ads, a-crbtgk.ads, s-wchwts.adb,
2690         system-mingw.ads, a-except.ads, s-conca4.ads, a-chzla9.ads,
2691         s-valenu.adb, s-soflin.adb, a-stream.ads, a-cgarso.adb, s-valllu.adb,
2692         g-crc32.adb, s-wchwts.ads, s-fatflt.ads, s-imguns.adb, s-strcom.adb,
2693         g-decstr.adb, s-valenu.ads, s-soflin.ads, a-cgarso.ads, a-cwila1.ads,
2694         s-valllu.ads, g-crc32.ads, s-imguns.ads, g-spipat.adb, s-valwch.adb,
2695         s-strcom.ads, g-decstr.ads, text_io.ads, g-debuti.adb, s-stchop.adb,
2696         g-spipat.ads, s-valwch.ads, a-string.ads, s-exnint.adb, g-awk.adb,
2697         g-tasloc.adb, s-wwdenu.adb, s-boustr.adb, a-zchuni.adb, s-stchop.ads,
2698         g-debuti.ads, s-stopoo.adb, system-dragonfly-x86_64.ads,
2699         system-linux-x86.ads, s-exnint.ads, g-awk.ads, a-stzhas.adb,
2700         g-tasloc.ads, s-wwdenu.ads, g-debpoo.adb, g-except.ads,
2701         g-sse.ads, s-boustr.ads, a-zchuni.ads, s-bitops.adb, s-wwdwch.adb,
2702         s-stopoo.ads, a-catizo.adb, a-stzhas.ads, a-nlcefu.ads, g-debpoo.ads,
2703         i-vxwoio.adb, s-bitops.ads, g-io-put-vxworks.adb, s-wwdwch.ads,
2704         g-sehamd.adb, a-ssicst.adb, a-catizo.ads, s-mmap.adb, g-string.adb,
2705         s-traceb.adb, a-swunau.adb, s-rannum.adb, a-ticoau.adb, i-vxwoio.ads,
2706         g-sehamd.ads, a-stwiun.adb, a-ssicst.ads, s-conca5.adb, a-ssitio.ads,
2707         s-mmap.ads, a-zttest.adb, g-string.ads, g-sercom.adb, a-cdlili.adb,
2708         a-swunau.ads, s-traceb.ads, s-rannum.ads, a-ticoau.ads, system-aix.ads,
2709         a-cforma.adb, a-stwiun.ads, s-conca5.ads, s-carsi8.adb, a-zttest.ads,
2710         g-sercom.ads, a-cdlili.ads, a-cihama.adb, g-sptain.ads, a-cforma.ads,
2711         s-maccod.ads, s-carsi8.ads, a-strsup.adb, g-sha1.adb, a-cihama.ads,
2712         g-stseme.adb, s-traent.adb, s-valcha.adb, g-curexc.ads, a-strsup.ads,
2713         g-sha1.ads, a-sflcin.ads, s-traent.ads, s-pack10.adb, s-valcha.ads,
2714         a-coteio.ads, s-tasloc.adb, g-utf_32.adb, a-suteio.adb, s-except.adb,
2715         a-direct.adb, g-stsifd-sockets.adb, a-numaux-vxworks.ads, s-winext.ads,
2716         s-pack10.ads, a-ztexio.adb, a-tiflau.adb, system-vxworks-arm.ads,
2717         s-tasloc.ads, a-suteio.ads, g-utf_32.ads, s-except.ads,
2718         a-direct.ads, a-swbwha.adb, g-hesorg.adb, s-wwdcha.adb, a-wtedit.adb,
2719         a-ztexio.ads, a-wtcoio.adb, a-tiflau.ads, a-ssizti.ads, s-casi32.adb,
2720         a-swbwha.ads, s-veboop.adb, g-hesorg.ads, s-parame-rtems.adb,
2721         s-wwdcha.ads, a-wtedit.ads, a-stuten.adb, a-coinve.adb, a-wtcoio.ads,
2722         s-casi32.ads, s-string.adb, a-tiinau.adb, a-cusyqu.adb, s-conca6.adb,
2723         s-veboop.ads, a-cgcaso.adb, a-numaux-darwin.adb, a-envvar.adb,
2724         a-stuten.ads, s-secsta.adb, a-coinve.ads, s-string.ads, a-cusyqu.ads,
2725         a-tiinau.ads, s-osprim-vxworks.adb, s-conca6.ads, g-spchge.adb,
2726         s-parint.adb, a-cuprqu.adb, a-cgcaso.ads, a-numaux-darwin.ads,
2727         a-envvar.ads, s-secsta.ads, g-spchge.ads, s-parint.ads, a-cuprqu.ads,
2728         a-swuwti.adb, a-flteio.ads, a-sbhcin.adb, a-coprnu.adb, g-u3spch.adb,
2729         s-atocou.adb, g-ctrl_c.adb, a-swuwti.ads, a-calend.adb, a-sbhcin.ads,
2730         a-coprnu.ads, g-dirope.adb, g-sha512.ads, g-u3spch.ads, s-atocou.ads,
2731         g-ctrl_c.ads, a-timoau.adb, a-witeio.adb, s-pack11.adb, a-strhas.adb,
2732         a-wtflio.adb, g-spitbo.adb, a-calend.ads, a-ztenio.adb, g-dirope.ads,
2733         a-slcain.adb, g-sechas.adb, a-timoau.ads, a-witeio.ads, s-pack11.ads,
2734         s-shasto.adb, s-traceb-mastop.adb, a-ciorse.adb, s-utf_32.adb,
2735         a-strhas.ads, a-wtflio.ads, g-spitbo.ads, a-ztenio.ads, a-slcain.ads,
2736         g-sechas.ads, s-gearop.adb, a-siztio.ads, s-pack20.adb, s-shasto.ads,
2737         a-ciorse.ads, s-utf_32.ads, s-crtl.ads, a-wtinio.adb, s-elaall.adb,
2738         s-explli.adb, s-chepoo.ads, s-gearop.ads, a-einuoc.adb, s-pack20.ads,
2739         system-linux-ia64.ads, a-swunau-shared.adb, a-wtinio.ads, g-alvety.ads,
2740         a-liztio.ads, g-calend.adb, s-conca7.adb, s-elaall.ads, s-explli.ads,
2741         a-einuoc.ads, s-widboo.adb, s-imgdec.adb, a-cbhama.adb, g-calend.ads,
2742         s-conca7.ads, a-llitio.ads, i-cexten.ads, a-coorma.adb, s-widboo.ads,
2743         s-diflio.adb, g-souinf.ads, s-imgdec.ads, g-strhas.ads, a-cbhama.ads,
2744         g-shshco.adb, a-ztdeio.adb, s-gloloc.adb, a-coorma.ads, g-wispch.adb,
2745         s-pack03.adb, g-eacodu.adb, s-casi16.adb, s-diflio.ads, a-colien.adb,
2746         g-shshco.ads, a-wtmoio.adb, a-rbtgbo.adb, a-ztdeio.ads,
2747         system-rtems.ads, s-gloloc.ads, a-csquin.ads, a-cofuse.adb,
2748         g-wispch.ads, s-pack03.ads, s-casi16.ads, s-io.adb, a-colien.ads,
2749         g-alveop.adb, gnat.ads, s-diinio.adb, a-cfdlli.adb, g-pehage.adb,
2750         a-wtmoio.ads, a-stwiha.adb, a-locale.adb, a-tirsfi.adb, a-nscoty.ads,
2751         a-rbtgbo.ads, s-pack12.adb, a-cofuse.ads, a-sfteio.ads, s-io.ads,
2752         g-alveop.ads, a-cfdlli.ads, s-diinio.ads, a-stwiha.ads, g-pehage.ads,
2753         a-locale.ads, a-tirsfi.ads, s-pack12.ads, s-valuti.adb, g-cppexc.adb,
2754         system-vxworks-ppc.ads, g-memdum.adb, a-lfteio.ads, s-pack21.adb,
2755         s-unstyp.ads, s-valuti.ads, g-cppexc.ads, system-hpux-ia64.ads,
2756         g-memdum.ads, g-soccon.ads, g-altive.ads, a-crbtgo.adb, s-pack21.ads,
2757         a-llizti.ads, a-numaux-libc-x86.ads, s-expint.adb, s-conca8.adb,
2758         a-crbtgo.ads, s-pack30.adb, s-vallli.adb, s-geveop.adb, s-expint.ads,
2759         a-direio.adb, s-conca8.ads, a-widcha.ads, s-pack30.ads, s-vallli.ads,
2760         s-strhas.adb, s-geveop.ads, g-md5.adb, a-direio.ads, a-numaux.ads,
2761         s-ransee.adb, a-szbzha.adb, i-cobol.adb, g-busorg.adb, s-strhas.ads,
2762         g-md5.ads, s-widenu.adb, s-ransee.ads, s-widllu.adb, a-szbzha.ads,
2763         a-ststio.adb, i-cobol.ads, g-busorg.ads, g-regpat.adb, s-widenu.ads,
2764         a-secain.adb, s-widllu.ads, s-pack13.adb, g-encstr.adb, a-ztcoau.adb,
2765         a-ststio.ads, s-widwch.adb, g-regpat.ads, s-atacco.adb, a-cborse.adb,
2766         a-secain.ads, s-pack13.ads, g-encstr.ads, a-ztcoau.ads, s-widwch.ads,
2767         g-io_aux.adb, s-atacco.ads, a-ncelfu.ads, interfac.ads, a-cborse.ads,
2768         g-regexp.adb, s-pack22.adb, a-szuzti.adb, g-io_aux.ads, s-caun32.adb,
2769         a-nselfu.ads, g-regexp.ads, s-pack22.ads, a-ticoio.adb, a-szuzti.ads,
2770         g-diopit.adb, s-caun32.ads, s-conca9.adb, a-tags.adb, a-swmwco.ads,
2771         a-sbecin.adb, s-pack31.adb, s-expuns.adb, a-ticoio.ads, s-valint.adb,
2772         s-conca9.ads, g-diopit.ads, a-tags.ads, a-nllcef.ads, a-izteio.ads,
2773         a-sbecin.ads, s-expuns.ads, s-pack31.ads, g-dyntab.adb, s-powtab.ads,
2774         s-flocon-none.adb, s-valint.ads, a-ssiwti.ads, s-mmosin-mingw.adb,
2775         s-pack40.adb, s-pack05.adb, a-ztflau.adb, g-dyntab.ads,
2776         a-szuzti-shared.adb, g-alvevi.ads, a-stwise.adb, s-mmosin-mingw.ads,
2777         s-pack40.ads, a-diocst.adb, a-ztflau.ads, s-pack05.ads, a-nlcoty.ads,
2778         a-contai.ads, a-stwisu.adb, g-byorma.adb, a-siwtio.ads, a-stwise.ads,
2779         s-regpat.adb, g-mbdira.adb, s-pack14.adb, a-diocst.ads, g-flocon.ads,
2780         g-mbflra.adb, a-ztinau.adb, s-dim.ads, s-mantis.adb, a-stwisu.ads,
2781         g-byorma.ads, s-atopri.adb, g-wistsp.ads, a-uncdea.ads, s-widcha.adb,
2782         a-caldel.adb, s-regpat.ads, g-mbdira.ads, a-tiflio.adb, s-pack14.ads,
2783         s-parame.adb, a-liwtio.ads, s-memory.adb, g-mbflra.ads, a-ztinau.ads,
2784         a-wtgeau.adb, s-direio.adb, s-mantis.ads, s-atopri.ads, s-widcha.ads,
2785         a-caldel.ads, s-pack23.adb, a-unccon.ads, a-tiflio.ads, s-parame.ads,
2786         a-llftio.ads, s-memory.ads, s-regexp.adb, a-wtgeau.ads, a-exexda.adb,
2787         s-direio.ads, s-pack23.ads, g-stheme.adb, a-tiinio.adb, g-sestin.ads,
2788         s-regexp.ads, a-wtfiio.adb, a-comutr.adb, a-exexpr.adb, a-tiinio.ads,
2789         a-ztmoau.adb, a-cohata.ads, a-wtfiio.ads, s-imgrea.adb, ada.ads,
2790         a-szunau-shared.adb, a-comutr.ads, s-valuns.adb, a-ztmoau.ads,
2791         system-linux-arm.ads, s-osprim-x32.adb, s-pack41.adb, s-pack06.adb,
2792         s-imgrea.ads, s-valuns.ads, s-finroo.adb, s-caun16.adb, s-pooglo.adb,
2793         a-zrstfi.adb, a-suenst.adb, s-pack41.ads, g-binenv.adb, s-pack06.ads,
2794         a-calari.adb, a-nlcoar.ads, s-finroo.ads, a-timoio.adb, s-caun16.ads,
2795         s-flocon.adb, a-suenst.ads, a-zrstfi.ads, s-pooglo.ads, s-wchcon.adb,
2796         s-traceb-hpux.adb, s-pack50.adb, i-fortra.adb, s-pack15.adb,
2797         a-ngcefu.adb, g-sptavs.ads, g-binenv.ads, s-wchjis.adb, a-calari.ads,
2798         a-timoio.ads, a-decima.adb, s-flocon.ads, s-wchcon.ads, a-llfzti.ads,
2799         i-fortra.ads, s-pack50.ads, s-pack15.ads, a-ngcefu.ads, a-cfhase.adb,
2800         s-wchjis.ads, g-soliop.ads, a-decima.ads, a-chlat9.ads, s-pack24.adb,
2801         a-nlelfu.ads, a-cfhase.ads, g-locfil.adb, s-atocou-builtin.adb,
2802         s-memcop.ads, a-szunau.adb, s-pack24.ads, s-imgllb.adb, s-auxdec.adb,
2803         g-locfil.ads, s-pack33.adb, a-szunau.ads, s-parame-vxworks.adb,
2804         s-imgllb.ads, a-ciorma.adb, s-auxdec.ads, a-cobove.adb, s-dsaser.ads,
2805         a-elchha.adb, s-pack33.ads, a-cofuve.adb, s-parame-vxworks.ads,
2806         a-ciorma.ads, system-darwin-x86.ads, s-multip.adb, a-stwiun-shared.adb,
2807         a-wichun.adb, a-cobove.ads, s-imgbiu.adb, s-tsmona-mingw.adb,
2808         a-coormu.adb, a-siocst.adb, s-win32.ads, a-elchha.ads, s-pack42.adb,
2809         s-pack07.adb, a-cofuve.ads, system-hpux.ads, a-teioed.adb,
2810         a-convec.adb, g-speche.adb, s-multip.ads, a-stwiun-shared.ads,
2811         a-wichun.ads, s-imgbiu.ads, a-numeri.ads, a-siocst.ads, a-coormu.ads,
2812         a-lliwti.ads, s-pack42.ads, s-pack07.ads, a-teioed.ads, a-convec.ads,
2813         g-speche.ads, g-socthi.adb, a-nucoty.ads, a-szmzco.ads, s-pack51.adb,
2814         s-osprim-mingw.adb, s-casi64.adb, g-strspl.ads, g-socthi.ads,
2815         g-socket-dummy.adb, s-pack51.ads, s-dimmks.ads, s-casi64.ads,
2816         a-wtenau.adb, s-stchop-vxworks.adb, s-pack60.adb,
2817         system-solaris-sparc.ads, s-pack25.adb, g-socket-dummy.ads,
2818         a-exstat.adb, a-cofuma.adb, s-tsmona-linux.adb, a-wtenau.ads,
2819         s-pack60.ads, s-pack25.ads, i-cstrea.adb, a-cofuma.ads, g-exptty.adb,
2820         a-chzla1.ads, s-pack34.adb, i-cstrea.ads, s-excdeb.adb, a-iteint.ads,
2821         g-exptty.ads, i-pacdec.adb, s-pack34.ads, s-rident.ads, s-sopco3.adb,
2822         i-vxwork.ads, s-excdeb.ads, system-linux-ppc.ads, a-swuwti-shared.adb,
2823         s-widlli.adb, s-pack43.adb, i-pacdec.ads, a-cwila9.ads, s-sopco3.ads,
2824         a-fwteio.ads, s-widlli.ads, s-pack43.ads, a-suhcin.adb, a-wtdeau.adb,
2825         g-allein.ads, a-suezst.adb, a-dirval-mingw.adb, g-zspche.adb,
2826         s-bignum.adb, a-ztedit.adb, g-regist.adb, a-nllefu.ads, a-ztcoio.adb,
2827         s-pack52.adb, a-llctio.ads, a-nucoar.ads, s-pack17.adb, a-suhcin.ads,
2828         a-wtdeau.ads, a-suezst.ads, a-dirval.adb, g-zspche.ads, g-regist.ads,
2829         a-ztedit.ads, s-bignum.ads, a-wtcstr.adb, system.ads, s-pack52.ads,
2830         a-ztcoio.ads, s-pack17.ads, s-imgboo.adb, a-rbtgso.adb, a-dirval.ads,
2831         a-cohase.adb, s-pack61.adb, a-wtcstr.ads, s-pack26.adb, s-osprim.ads,
2832         a-tigeau.adb, s-imgboo.ads, a-nuelfu.ads, a-swfwha.ads, s-commun.adb,
2833         g-socthi-vxworks.adb, a-rbtgso.ads, a-cohase.ads, g-zstspl.ads,
2834         s-pack61.ads, s-pack26.ads, a-intnam-dragonfly.ads, s-imglld.adb,
2835         a-tigeau.ads, s-commun.ads, g-socthi-vxworks.ads, a-cborma.adb,
2836         a-stwifi.adb, g-moreex.adb, s-pack35.adb, s-imglld.ads, s-valdec.adb,
2837         a-tifiio.adb, a-cborma.ads, g-moreex.ads, a-stwifi.ads, s-pack35.ads,
2838         s-sopco4.adb, g-sha224.ads, g-socket.adb, a-intnam-rtems.ads,
2839         s-finmas.adb, s-valdec.ads, s-addima.adb, a-finali.adb, a-tifiio.ads,
2840         s-rpc.adb, a-ztflio.adb, s-pack44.adb, s-pack09.adb, a-sblcin.adb,
2841         s-sopco4.ads, a-textio.adb, g-socket.ads, g-sptabo.ads, s-finmas.ads,
2842         g-shsh32.adb, s-addima.ads, a-finali.ads, s-mmauni-long.ads, s-rpc.ads,
2843         a-ztflio.ads, system-djgpp.ads, s-stache.adb, s-pack44.ads,
2844         s-pack09.ads, a-sblcin.ads, a-textio.ads, a-cidlli.adb, g-shsh32.ads,
2845         a-chtgbk.adb, a-tiocst.adb, s-pack53.adb, s-pack18.adb, s-stache.ads,
2846         a-zchhan.adb, s-fatlfl.ads, a-ztinio.adb, s-strops.adb, a-siteio.ads,
2847         a-cidlli.ads, a-chtgbk.ads, g-ssvety.ads, a-tiocst.ads, s-pack53.ads,
2848         s-parame-hpux.ads, s-pack18.ads, a-zchhan.ads, s-strops.ads,
2849         a-ztinio.ads, a-wichha.adb, a-stwima.adb, a-nlrear.ads, a-liteio.ads,
2850         s-pack62.adb, s-pack27.adb, s-fore.adb, s-vercon.adb, a-wichha.ads,
2851         a-stwima.ads, s-pack62.ads, system-linux-sparc.ads, s-pack27.ads,
2852         g-dynhta.adb, s-fore.ads, s-vercon.ads, a-cofuba.adb, a-cimutr.adb,
2853         i-cpoint.adb, s-imgenu.adb, a-stwibo.adb, s-pack36.adb, i-cstrin.adb,
2854         s-imgllu.adb, a-suteio-shared.adb, g-excact.adb, s-stoele.adb,
2855         s-addope.adb, g-dynhta.ads, a-cofuba.ads, a-ztmoio.adb, a-llfwti.ads,
2856         a-cimutr.ads, i-cpoint.ads, s-imgenu.ads, a-stwibo.ads, a-wttest.adb,
2857         s-pack36.ads, a-tgdico.ads, s-sopco5.adb, s-scaval.adb, i-cstrin.ads,
2858         s-imgllu.ads, g-excact.ads, s-stoele.ads, g-deutst.ads, s-addope.ads,
2859         s-imgwch.adb, g-sha384.ads, a-ztmoio.ads, s-pack45.adb, a-wttest.ads,
2860         s-sopco5.ads, s-excmac-gcc.adb, s-scaval.ads, a-storio.adb,
2861         a-coinho.adb, a-btgbso.adb, s-imgwch.ads, s-carun8.adb, memtrack.adb,
2862         s-pack45.ads, a-sfhcin.ads, s-excmac-gcc.ads, a-storio.ads,
2863         a-coinho.ads, a-btgbso.ads, s-stratt.adb, s-carun8.ads, a-shcain.adb,
2864         s-pack54.adb, s-pack19.adb, a-colire.adb, a-tigeli.adb, s-caun64.adb,
2865         s-stratt.ads, s-fatgen.adb, a-shcain.ads, a-stzunb-shared.adb,
2866         s-pack54.ads, s-pack19.ads, a-colire.ads, a-calcon.adb, s-caun64.ads,
2867         s-fatgen.ads, s-pack63.adb, g-arrspl.adb, a-stzunb-shared.ads,
2868         s-pack28.adb, a-nllrar.ads, a-zzboio.adb, a-zzunio.ads, a-stunau.adb,
2869         a-calcon.ads, g-cgideb.adb, s-objrea.adb, s-mastop.adb, a-tienau.adb,
2870         g-altcon.adb, g-arrspl.ads, s-pack63.ads, s-restri.adb, s-pack28.ads,
2871         a-zzboio.ads, a-stunau.ads, g-cgideb.ads, g-htable.adb, g-sothco.adb,
2872         s-objrea.ads, g-soliop-solaris.ads, s-mastop.ads, a-tienau.ads,
2873         system-linux-m68k.ads, g-altcon.ads, s-dmotpr.ads, s-memory-mingw.adb,
2874         g-cgicoo.adb, s-pack37.adb, s-restri.ads, s-fatllf.ads, s-expmod.adb,
2875         a-swuwha.adb, a-exextr.adb, a-cfhama.adb, s-gloloc-mingw.adb,
2876         a-tiboio.adb, g-forstr.adb, g-sothco.ads, a-stzbou.adb, a-nllcty.ads,
2877         a-suecin.adb, g-htable.ads, s-exctab.adb, a-tiunio.ads, g-cgicoo.ads,
2878         s-osprim-posix.adb, s-pack37.ads, a-ciormu.adb, s-atocou-x86.adb,
2879         a-swuwha.ads, s-expmod.ads, a-cfhama.ads, s-ficobl.ads, a-ngcoty.adb,
2880         g-forstr.ads, a-tiboio.ads, a-calfor.adb, a-stzbou.ads, a-suecin.ads,
2881         a-conhel.adb, a-crbltr.ads, s-exctab.ads, a-dhfina.ads, s-imgcha.adb,
2882         s-pack46.adb, a-ciormu.ads, system-linux-sh4.ads, a-chahan.adb,
2883         a-ngcoty.ads, a-stzunb.adb, a-szfzha.ads, a-calfor.ads, a-cbdlli.adb,
2884         a-conhel.ads, s-imgcha.ads, s-pack46.ads, a-assert.adb, a-chahan.ads,
2885         a-stzunb.ads, a-crdlli.adb, s-pack55.adb, a-cbdlli.ads, a-tideau.adb,
2886         a-assert.ads, ioexcept.ads, s-boarop.ads, g-hesora.adb, a-crdlli.ads,
2887         s-pack55.ads, a-tideau.ads, g-bubsor.adb, a-wtenio.adb, a-cbsyqu.adb,
2888         g-hesora.ads, s-pack29.adb, a-nurear.ads, g-catiio.adb, s-stposu.adb,
2889         g-bubsor.ads, a-wtenio.ads, a-cbsyqu.ads, a-suewst.adb,
2890         system-vxworks-x86.ads, s-pack29.ads, a-cbmutr.adb, a-cbprqu.adb,
2891         s-imenne.adb, g-sothco-dummy.adb, g-casuti.adb, g-catiio.ads,
2892         s-stposu.ads, a-stzsea.adb, s-pack38.adb, a-suewst.ads, s-imgllw.adb,
2893         a-cbprqu.ads, a-cbmutr.ads, s-imenne.ads, g-sothco-dummy.ads,
2894         g-casuti.ads, s-htable.adb, s-fatsfl.ads, g-trasym.adb, unchconv.ads,
2895         a-stzsea.ads, s-arit64.adb, s-pack38.ads, a-nllcar.ads, s-valrea.adb,
2896         s-imgllw.ads, s-htable.ads, a-sequio.adb, g-trasym.ads, a-ngcoar.adb,
2897         s-exnllf.adb, s-pack47.adb, s-arit64.ads, g-sercom-mingw.adb,
2898         s-valrea.ads, g-socthi-mingw.adb, g-bytswa.adb, g-sehash.adb,
2899         unchdeal.ads, a-sequio.ads, a-ngcoar.ads, s-exnllf.ads, a-wtdeio.adb,
2900         s-pack47.ads, g-socthi-mingw.ads, a-excpol-abort.adb, a-ztgeau.adb,
2901         g-bytswa.ads, g-sehash.ads, s-pack56.adb, a-wtdeio.ads, a-ngelfu.adb,
2902         a-ztgeau.ads, a-cforse.adb, s-filatt.ads, a-stzfix.adb, a-cihase.adb,
2903         s-pack56.ads, a-sfztio.ads, a-ngelfu.ads, s-trasym-dwarf.adb,
2904         a-cforse.ads, a-ztfiio.adb, g-timsta.adb, a-stzfix.ads, a-cihase.ads,
2905         a-ztfiio.ads, system-darwin-arm.ads: Move non-tasking runtime sources
2906         to libgnat subdirectory.
2908 2017-09-08  Yannick Moy  <moy@adacore.com>
2910         * sem_aux.adb, sem_aux.ads (Get_Called_Entity): New function to
2911         return the entity associated with the call.
2912         * sem_util.adb, sem_util.ads (Check_Function_Writable_Actuals):
2913         Replace the internal Get_Function_Id with the new
2914         Sem_Aux.Get_Called_Entity.
2915         (Iterate_Call_Parameters): New
2916         procedure to iterate on formals and actuals at the same time.
2917         * sem_ch12.adb (Analyze_Subprogram_Instantiation):
2918         Set SPARK_Mode from spec when set, for analysis
2919         of instance. Restore after analysis of instance.
2920         (Instantiate_Subprogram_Body): Set SPARK_Mode from body when
2921         set, for analysis of body instance. Restored automatically at
2922         the end of the subprogram.
2923         * gnat1drv.adb (Adjust_Global_Switches): Set
2924         Check_Validity_Of_Parameters to False in GNATprove mode.
2925         * opt.ads (Check_Validity_Of_Parameters): Document switch to
2926         set option.
2928 2017-09-08  Eric Botcazou  <ebotcazou@adacore.com>
2930         * sem_util.adb (NCT_Tables_In_Use): Move to library level from...
2931         (New_Copy_Tree): ...there.  Reset the hash tables only if they
2932         were used in the previous invocation.
2933         * s-htable.adb: Fix typo.
2935 2017-09-08  Bob Duff  <duff@adacore.com>
2937         * a-ssicst.adb (Open): Set File.Last_Op to the appropriate value.
2939 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
2941         * sem_aggr.adb: minor style fix.
2943 2017-09-08  Bob Duff  <duff@adacore.com>
2945         * sprint.adb (Write_Corresponding_Source): Ignore if there is
2946         no current source file.
2947         (Write_Name_With_Col_Check, Write_Name_With_Col_Check_Sloc):
2948         Print something helpful in case N is invalid.
2949         * sprint.ads: Minor comment fix.
2951 2017-09-08  Eric Botcazou  <ebotcazou@adacore.com>
2953         * exp_aggr.adb: (Aggr_Assignment_OK_For_Backend): Add early return for
2954         access types.
2956 2017-09-08  Bob Duff  <duff@adacore.com>
2958         * par-prag.adb, sem_prag.adb, snames.ads-tmpl: Implement pragma
2959         Ada_2020, along the same lines as the other Ada version pragmas.
2961 2017-09-08  Gary Dismukes  <dismukes@adacore.com>
2963         * sem_ch12.adb: Minor typo fixes and reformatting.
2965 2017-09-08  Yannick Moy  <moy@adacore.com>
2967         * sem_aggr.adb (Resolve_Record_Aggregate):
2968         Rewrite bounds of aggregate subexpressions which may depend on
2969         discriminants of the enclosing aggregate.
2971 2017-09-08  Yannick Moy  <moy@adacore.com>
2973         * sem_ch5.adb: Prevent assertion failure on illegal code.
2975 2017-09-08  Yannick Moy  <moy@adacore.com>
2977         * lib-xref-spark_specific.adb (Add_SPARK_Xrefs.Is_SPARK_Scope): Avoid
2978         calling Renamed_Entity on an entity which cannot be a renaming.
2980 2017-09-08  Eric Botcazou  <ebotcazou@adacore.com>
2982         * exp_aggr.adb: Add with & use clause for Urealp.
2983         (Aggr_Assignment_OK_For_Backend): Accept (almost all)
2984         elementary types instead of just discrete types.
2985         * sem_eval.adb (Expr_Value): Deal with N_Null for access types.
2986         * gcc-interface/trans.c (gnat_to_gnu) <N_Assignment_Statement>:
2987         Be prepared for the FP zero value in the memset case.  Add small
2988         guard.
2990 2017-09-08  Eric Botcazou  <ebotcazou@adacore.com>
2992         * s-htable.adb (Static_HTable.Reset): Use aggregate instead
2993         of loop.
2995 2017-09-08  Hristian Kirtchev  <kirtchev@adacore.com>
2997         * exp_aggr.adb (Expand_Array_Aggregate): Use New_Copy_Tree instead
2998         of New_Copy because the latter leaves the syntactic structure of
2999         the tree inconsistent (a child is accessible through two parents)
3000         and prevents proper replication of itypes by subsequent calls
3001         to New_Copy_Tree.
3002         * exp_ch4.adb (Expand_Concatenate): Use New_Copy_Tree instead of
3003         New_Copy because the latter leaves the syntactic structure of the
3004         tree inconsistent (a child is accessible through two parents)
3005         and prevents proper replication of itypes by subsequent calls
3006         to New_Copy_Tree.
3007         * sem_util.adb (In_Subtree): New routine.
3008         (New_Copy_Tree): Reimplemented.
3009         * sem_util.ads (In_Subtree): New routine.
3010         (New_Copy_Tree): Reimplemented.
3012 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3014         * sem_ch13.adb (Resolve_Aspect_Expressions): The expression
3015         for aspect Default_Value is a static scalar value, but it does
3016         not freeze the type. Yhis allows for subsequent representation
3017         clauses for the type.
3019 2017-09-08  Javier Miranda  <miranda@adacore.com>
3021         * sem_ch8.adb (Find_Direct_Name.Undefined): Do
3022         not add entries into the undefined reference table when we are
3023         compiling with errors ignored.
3025 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3027         * sem_ch12.adb (Check_Formal_Packages): Do not apply conformance
3028         check if the instance is within an enclosing instance body. The
3029         formal package was legal in the enclosing generic, and is
3030         legal in the enclosing instantiation.  This optimisation may be
3031         applicable elsewhere, and it also removes spurious errors that
3032         may arise with on-the-fly processing  of instantiations that
3033         contain Inline_Always subprograms.
3035 2017-09-08  Vincent Celier  <celier@adacore.com>
3037         * gnatcmd.adb: Disregard empty argument of GNAT driver.
3039 2017-09-08  Justin Squirek  <squirek@adacore.com>
3041         * checks.adb (Insert_Valid_Check): Manually decorate
3042         the generated temporary for range valdity checks.
3044 2017-09-08  Eric Botcazou  <ebotcazou@adacore.com>
3046         * usage.adb (Usage): Document new -gnatw.q/-gnatw.Q switches.
3048 2017-09-08  Justin Squirek  <squirek@adacore.com>
3050         * switch-c.adb (Scan_Front_End_Switches): Add new warning switch
3051         case to handle underscore flags.
3052         * warnsw.adb, warnsw.ads (Set_Underscore_Warning_Switch): Create
3053         new procedure to handle underscores.
3055 2017-09-08  Javier Miranda  <miranda@adacore.com>
3057         * exp_ch4.adb (Expand_N_Op_Divide): Reordering code that handles
3058         divisions with fixed point results to avoid generating twice
3059         the runtime check on divide by zero.
3060         * checks.adb (Apply_Divide_Checks): Ensure that operands are
3061         not evaluated twice (once for their runtime checks and once for
3062         their regular computation).
3064 2017-09-08  Yannick Moy  <moy@adacore.com>
3066         * sem_prag.adb (Analyze_Part_Of): Add missing
3067         return statements after issuing errors.  Add detection of
3068         out-of-order item and single concurrent type.
3070 2017-09-08  Nicolas Roche  <roche@adacore.com>
3072         * gcc-interface/Makefile.in, a-extiti.ads, s-taprop-linux.adb,
3073         s-osinte-solaris.adb, a-intnam.ads, s-osinte-solaris.ads,
3074         s-tpobop.adb, s-intman-android.adb, s-tasinf.adb, s-tpobop.ads,
3075         s-tasinf.ads, i-vxinco.adb, a-exetim-posix.adb, i-vxinco.ads,
3076         a-astaco.adb, a-astaco.ads, s-tporft.adb, s-tpoaal.adb, a-taside.adb,
3077         a-taside.ads, s-tpopsp-posix.adb, s-tasdeb.adb, s-tasdeb.ads,
3078         s-tpoben.adb, a-dinopr.ads, s-inmaop-vxworks.adb, s-tpoben.ads,
3079         s-interr-vxworks.adb, s-interr-dummy.adb, s-tassta.adb,
3080         a-intnam-mingw.ads, s-tassta.ads, s-taasde.adb, a-stcoed.ads,
3081         s-taasde.ads, s-osinte-darwin.adb, s-proinf.adb, s-taprop-dummy.adb,
3082         s-osinte-darwin.ads, s-proinf.ads, s-linux.ads, a-intnam-linux.ads,
3083         s-tasren.adb, s-tasren.ads, s-mudido.adb, g-semaph.adb, s-mudido.ads,
3084         s-taprop-posix.adb, g-semaph.ads, s-osinte-mingw.ads, s-vxwork-x86.ads,
3085         s-tposen.adb, s-linux-sparc.ads, s-taprop-vxworks.adb, s-tasini.adb,
3086         s-tposen.ads, s-tasini.ads, a-etgrbu.ads, s-interr-hwint.adb,
3087         s-osinte-linux.ads, s-taprop.ads, s-tasque.adb, s-tasque.ads,
3088         s-taenca.adb, s-taspri-vxworks.ads, s-taenca.ads, a-dynpri.adb,
3089         s-tpopsp-solaris.adb, a-dynpri.ads, s-taprop-hpux-dce.adb,
3090         a-interr.adb, a-intnam-freebsd.ads, s-tarest.adb, a-interr.ads,
3091         s-intman-susv3.adb, a-synbar.adb, a-intnam-dummy.ads, s-tadeca.adb,
3092         s-osinte-vxworks.adb, s-tarest.ads, s-taskin.adb, a-synbar.ads,
3093         s-taspri-hpux-dce.ads, s-tadeca.ads, s-osinte-vxworks.ads,
3094         s-taskin.ads, s-intman-solaris.adb, a-sytaco.adb, s-vxwext-kernel.adb,
3095         s-mudido-affinity.adb, a-sytaco.ads, s-vxwext-kernel.ads, s-taprob.adb,
3096         s-intman-mingw.adb, s-taprob.ads, s-osinte-kfreebsd-gnu.ads,
3097         s-osinte-dummy.ads, s-osinte-gnu.adb, s-osinte-rtems.adb, s-interr.adb,
3098         s-inmaop.ads, s-vxwext-rtp.adb, s-osinte-gnu.ads, s-osinte-rtems.ads,
3099         a-synbar-posix.adb, s-interr.ads, s-taspri-posix-noaltstack.ads,
3100         s-vxwext-rtp.ads, a-synbar-posix.ads, a-extiin.ads, s-osinte-posix.adb,
3101         s-tpinop.adb, s-tasres.ads, s-tpinop.ads, a-disedf.ads, a-diroro.ads,
3102         s-linux-alpha.ads, a-tasatt.adb, s-solita.adb, a-intnam-solaris.ads,
3103         a-tasatt.ads, s-solita.ads, s-tasinf-solaris.adb, s-tasinf-solaris.ads,
3104         s-vxwork-arm.ads, s-tpopsp-posix-foreign.adb, s-intman-dummy.adb,
3105         s-intman.ads, s-stusta.adb, s-stusta.ads, s-intman-posix.adb,
3106         s-tpopsp-vxworks.adb, s-inmaop-dummy.adb, s-taspri-mingw.ads,
3107         a-intnam-darwin.ads, s-osinte-aix.adb, s-osinte-dragonfly.adb,
3108         s-osinte-aix.ads, s-tasinf-mingw.adb, s-osinte-dragonfly.ads,
3109         s-linux-hppa.ads, s-osinte-x32.adb, s-inmaop-posix.adb,
3110         s-tasinf-mingw.ads, s-intman-vxworks.adb, s-linux-mips.ads,
3111         s-intman-vxworks.ads, s-osinte-android.adb, s-tasinf-linux.adb,
3112         s-osinte-android.ads, s-vxwork-ppc.ads, s-tasinf-linux.ads,
3113         a-dispat.adb, a-dispat.ads, s-tadert.adb, g-thread.adb, s-tadert.ads,
3114         g-thread.ads, a-intnam-hpux.ads, s-linux-android.ads, s-tataat.adb,
3115         a-exetim.ads, s-tataat.ads, a-reatim.adb, a-reatim.ads, thread.c,
3116         g-boubuf.adb, s-osinte-freebsd.adb, g-boubuf.ads, s-osinte-freebsd.ads,
3117         s-tasuti.adb, s-taspri-dummy.ads, a-exetim-mingw.adb, s-linux-x32.ads,
3118         s-tasuti.ads, g-signal.adb, a-exetim-mingw.ads, s-interr-sigaction.adb,
3119         g-signal.ads, s-osinte-hpux.ads, a-intnam-vxworks.ads,
3120         s-osinte-hpux-dce.adb, s-taspri-posix.ads, s-osinte-hpux-dce.ads,
3121         s-tasinf-vxworks.ads, g-tastus.ads, s-tpopsp-tls.adb,
3122         s-taprop-solaris.adb, a-retide.adb, a-exetim-darwin.adb, a-retide.ads,
3123         s-vxwext.adb, s-vxwext.ads, a-rttiev.adb, a-rttiev.ads, g-boumai.ads,
3124         a-exetim-default.ads, s-taprop-mingw.adb, s-taspri-solaris.ads,
3125         a-intnam-aix.ads: Move libgnarl sources to libgnarl subdir.
3127 2017-09-08  Arnaud Charlet <charlet@adacore.com>
3129         * doc/share/conf.py, doc/share/latex_elements.py,
3130         doc/share/ada_pygments.py, doc/Makefile: Improve support for Ada
3131         highlighting.
3133 2017-09-08  Arnaud Charlet <charlet@adacore.com>
3135         * gnat_rm.texi, gnat_ugn.texi,
3136         doc/gnat_ugn/the_gnat_compilation_model.rst,
3137         doc/gnat_ugn/getting_started_with_gnat.rst,
3138         doc/gnat_ugn/inline_assembler.rst,
3139         doc/gnat_ugn/building_executable_programs_with_gnat.rst,
3140         doc/gnat_ugn/elaboration_order_handling_in_gnat.rst,
3141         doc/gnat_ugn/about_this_guide.rst,
3142         doc/gnat_ugn/platform_specific_information.rst,
3143         doc/gnat_ugn/example_of_binder_output.rst,
3144         doc/gnat_ugn/gnat_and_program_execution.rst,
3145         doc/gnat_ugn/gnat_utility_programs.rst,
3146         doc/gnat_rm/implementation_of_specific_ada_features.rst,
3147         doc/gnat_rm/interfacing_to_other_languages.rst,
3148         doc/gnat_rm/implementation_defined_aspects.rst,
3149         doc/gnat_rm/intrinsic_subprograms.rst,
3150         doc/gnat_rm/implementation_defined_characteristics.rst,
3151         doc/gnat_rm/implementation_advice.rst,
3152         doc/gnat_rm/implementation_defined_attributes.rst,
3153         doc/gnat_rm/compatibility_and_porting_guide.rst,
3154         doc/gnat_rm/standard_library_routines.rst,
3155         doc/gnat_rm/the_gnat_library.rst,
3156         doc/gnat_rm/implementation_defined_pragmas.rst,
3157         doc/gnat_rm/representation_clauses_and_pragmas.rst,
3158         doc/gnat_rm/standard_and_implementation_defined_restrictions.rst,
3159         doc/gnat_rm/obsolescent_features.rst,
3160         doc/gnat_rm/about_this_guide.rst,
3161         doc/gnat_rm/the_implementation_of_standard_i_o.rst,
3162         doc/gnat_rm/implementation_of_ada_2012_features.rst,
3163         doc/gnat_ugn.rst,
3164         doc/gnat_rm.rst: Update documentation.
3166 2017-09-08  Arnaud Charlet <charlet@adacore.com>
3168         * s-dwalin.ads, s-dwalin.adb, s-trasym-dwarf.adb, s-objrea.ads,
3169         s-objrea.adb, s-tsmona-linux.adb, s-tsmona-mingw.adb: New.
3170         * gcc-interface/Makefile.in: Enable s-trasym-dwarf.adb on x86*linux.
3172 2017-09-08  Bob Duff  <duff@adacore.com>
3174         * s-ststop.ads, s-ststop.adb, rtsfind.ads (String_Input_Tag):
3175         New routine to read the Tag robustly.
3176         * exp_attr.adb (Input): Change the expansion of 'Input,
3177         in the class-wide case, to call String_Input_Tag instead of
3178         String_Input_Blk_IO.
3180 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3182         * s-rident.ads (Restriction_Id): reorder enum
3183         literals, so that Pure_Barriers is no longer in range of the
3184         Cunit_Boolean_Restrictions subtype.
3186 2017-09-08  Nicolas Roche  <roche@adacore.com>
3188         * a-taster.ads, a-taster.adb: Move to libgnarl
3189         * gcc-interface/Makefile.in: Remove obsolete targets. Code cleanups.
3190         Add support for files in libgnarl.
3192 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3194         * exp_ch4.adb (Expand_N_Type_Conversion): Do not apply
3195         accessibility check to an interface conversion, whose purpose
3196         is to perform a pointer adjustment in a dispatching call.
3197         * exp_ch6.adb (Expand_Call_JHelper): Add accessibility checks
3198         when the actual is a construct that involves a dereference of an
3199         expression that includes a formal of the enclosing subprogram,
3200         In such cases, the accessibility level of the actual is that of
3201         the corresponding formal, which is passed in as an additional
3202         actual in the outer call.
3204 2017-09-08  Bob Duff  <duff@adacore.com>
3206         * exp_intr.adb (Add_Source_Info): Do not decode
3207         file names; they were not encoded in the first place.
3209 2017-09-08  Bob Duff  <duff@adacore.com>
3211         * a-tags.adb (Internal_Tag): Unsuppress checks, so we get
3212         exceptions instead of crashes. Check for absurdly long strings
3213         and empty strings. Empty strings cause trouble because they can
3214         have super-null ranges (e.g. 100..10), which causes Ext_Copy to
3215         be empty, which causes an array index out of bounds.
3216         * s-ststop.adb (Input): Unsuppress checks, so we get exceptions
3217         instead of crashes.
3219 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3221         * sem_util.adb (Is_CCT_Instance): allow use in
3222         the context of protected types.
3224 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3226         * a-tigeli.adb: minor remove extra whitespace.
3228 2017-09-08  Gary Dismukes  <dismukes@adacore.com>
3230         * par-ch4.adb: Reformatting of an error message.
3232 2017-09-08  Javier Miranda  <miranda@adacore.com>
3234         * sem_ch3.adb (Resolve_Name): Under ASIS mode analyze overloaded
3235         identifiers to ensure their correct decoration of names on
3236         aspect expressions.
3238 2017-09-08  Yannick Moy  <moy@adacore.com>
3240         * exp_attr.adb (Expand_Loop_Entry_Attribute): Do
3241         not skip a loop coming from source which is rewritten into a loop.
3243 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3245         * freeze.adb (Wrap_Imported_Subprogram): Indicate that the
3246         wrapper has convention Ada, to prevent spurious warnings on
3247         unconstrained array parameters.
3249 2017-09-08  Eric Botcazou  <ebotcazou@adacore.com>
3251         * sem_prag.adb (Check_Variant): Use First_Non_Pragma/Next_Non_Pragma.
3252         (Analyze_Pragma) <Pragma_Unchecked_Union>: Likewise.
3254 2017-09-08  Eric Botcazou  <ebotcazou@adacore.com>
3256         * sem_ch6.adb (Freeze_Expr_Types): Rename Spec_Id into Def_Id.
3258 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3260         * exp_intr.adb (Append_Entity_Name): Move to ...
3261         * sem_util.ads, sem_util.adb: ... here to share it.
3262         (Subprogram_Name): New subprogram, to compute the name of the enclosing
3263         subprogram/entity.
3264         * errutil.adb (Error_Msg): Fill new field Node.
3265         * erroutc.ads (Subprogram_Name_Ptr): New.
3266         (Error_Msg_Object): New field Node.
3267         * erroutc.adb (dmsg, Output_Msg_Text): Take new field Node into account.
3268         * errout.adb (Error_Msg): New variant with node id parameter.
3269         Fill new parameter Node when emitting messages. Revert previous
3270         changes for Include_Subprogram_In_Messages.
3271         * sem_ch5.adb (Check_Unreachable_Code): Supply Node parameter when
3272         generating warning message.
3274 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3276         * par-ch4.adb (P_Iterated_Component_Association): Place construct
3277         under -gnat2020 flag, given that it is a future feature of
3278         the language.
3279         * sem_aggr.adb (Resolve_Iterated_Component_Association): Mark
3280         defining identifier as referenced to prevent spurious warnings:
3281         corresponding loop is expanded into one or more loops whose
3282         variable has the same name, and the expression uses those names
3283         and not the original one.
3285 2017-09-08  Hristian Kirtchev  <kirtchev@adacore.com>
3287         * sem_elab.adb (Check_A_Call): Do not consider
3288         references to internal variables for SPARK semantics.
3290 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3292         * inline.adb (In_Package_Spec): refine type of
3293         the parameter from Node_Id to Entity_Id.
3295 2017-09-08  Justin Squirek  <squirek@adacore.com>
3297         * exp_ch5.adb (Expand_Formal_Container_Loop):
3298         Reset the scope of the loop parameter after it is reanalyzed.
3300 2017-09-08  Eric Botcazou  <ebotcazou@adacore.com>
3302         * sem_util.ads (Set_Rep_Info): New inline procedure.
3303         * sem_util.adb (Set_Rep_Info): Implement it.
3304         * sem_ch3.adb (Process_Subtype): If the case of a constraint present,
3305         always copy the representation aspects onto the subtype.
3307 2017-09-08  Georges-Alex Jaloyan  <jaloyan@adacore.com>
3309         * g-dynhta.adb, g-dynhta.ads (Get_First_Key, Get_Next_key):
3310         Correction of the return type from access type to option type.
3311         (Simple_HTable): Moving the Instance_Data to ads file.
3313 2017-09-08  Yannick Moy  <moy@adacore.com>
3315         * sem_prag.adb: Use System.Case_Util.To_Lower to simplify code.
3317 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3319         * opt.ads (Include_Subprogram_In_Messages): New variable.
3320         * errout.ads (Current_Subprogram_Ptr): New variable.
3321         * errout.adb (Error_Msg): Prepend current subprogram info
3322         in messages if Include_Subprogram_In_Messages is set.
3323         * sem_util.adb (elab code): Initialize Current_Subprogram_Ptr to
3324         Current_Subprogram.
3325         * gnat1drv.adb (Adjust_Global_Switches): Set
3326         Include_Subprogram_In_Messages when -gnatdJ is set.
3327         * debug.adb: Document and reserve -gnatdJ.
3329 2017-09-08  Georges-Axel Jaloyan  <jaloyan@adacore.com>
3331         * g-dynhta.adb, g-dynhta.ads (Get_First_Key, Get_Next_Key): New
3332         functions to iterate over simple hastables.
3333         (Load_Factor_HTable): Remove obsolete and inefficient implementation.
3335 2017-09-08  Javier Miranda  <miranda@adacore.com>
3337         * exp_ch6.adb (Unqual_BIP_Function_Call): Adding
3338         missing checks on the presence of Entity() before checking the
3339         entity attributes.
3341 2017-09-08  Eric Botcazou  <ebotcazou@adacore.com>
3343         * sem_ch6.adb (Analyze_Expression_Function): Reorder some
3344         statements, use local variable and remove unnecessary processing.
3346 2017-09-08  Javier Miranda  <miranda@adacore.com>
3348         * exp_ch6.ads (Make_Build_In_Place_Iface_Call_In_Allocator): New
3349         subprogram.
3350         (Make_Build_In_Place_Iface_Call_In_Anonymous_Context): New subprogram.
3351         (Make_Build_In_Place_Iface_Call_In_Object_Declaration): New
3352         subprogram.
3353         (Unqual_BIP_Iface_Function_Call): New subprogram.
3354         * exp_ch6.adb (Replace_Renaming_Declaration_Id): New
3355         subprogram containing code that was previously inside
3356         Make_Build_In_Place_Call_In_Object_Declaration since it is also
3357         required for one of the new subprograms.
3358         (Expand_Actuals):
3359         Invoke Make_Build_In_Place_Iface_Call_In_Anonymous_Context
3360         (Expand_N_Extended_Return_Statement): Extend the
3361         cases covered by an assertion on expected BIP object
3362         declarations.
3363         (Make_Build_In_Place_Call_In_Assignment):
3364         Removing unused code; found working on this ticket.
3365         (Make_Build_In_Place_Call_In_Object_Declaration): Move the code
3366         that replaces the internal name of the renaming declaration
3367         into the new subprogram Replace_Renaming_Declaration_Id.
3368         (Make_Build_In_Place_Iface_Call_In_Allocator): New subprogram.
3369         (Make_Build_In_Place_Iface_Call_In_Anonymous_Context):
3370         New subprogram.
3371         (Make_Build_In_Place_Iface_Call_In_Object_Declaration): New
3372         subprogram.
3373         (Unqual_BIP_Iface_Function_Call): New subprogram.
3374         * exp_ch3.adb (Expand_N_Object_Declaration): Invoke the new
3375         subprogram Make_Build_In_Place_Iface_Call_In_Object_Declaration.
3376         * exp_attr.adb (Expand_N_Attribute_Reference): Invoke the new
3377         subprogram Make_Build_In_Place_Iface_Call_In_Anonymous_Context.
3378         * exp_ch4.adb (Expand_Allocator_Expression): Invoke the new
3379         subprogram Make_Build_In_Place_Iface_Call_In_Allocator.
3380         (Expand_N_Indexed_Component): Invoke the new subprogram
3381         Make_Build_In_Place_Iface_Call_In_Anonymous_Context.
3382         (Expand_N_Selected_Component): Invoke the new subprogram
3383         Make_Build_In_Place_Iface_Call_In_Anonymous_Context.
3384         (Expand_N_Slice): Invoke the new subprogram
3385         Make_Build_In_Place_Iface_Call_In_Anonymous_Context.
3386         * exp_ch8.adb (Expand_N_Object_Renaming_Declaration):
3387         Invoke the new subprogram
3388         Make_Build_In_Place_Iface_Call_In_Anonymous_Context.
3390 2017-09-08  Javier Miranda  <miranda@adacore.com>
3392         * exp_disp.adb (Expand_Interface_Conversion): Fix handling of
3393         access to interface types.  Remove also the accessibility check.
3395 2017-09-08  Eric Botcazou  <ebotcazou@adacore.com>
3397         * sem_ch6.adb (Freeze_Expr_Types): Really freeze
3398         all the types that are referenced by the expression.
3399         (Analyze_Expression_Function): Call Freeze_Expr_Types for
3400         a completion instead of manually freezing the type of the
3401         expression.
3402         (Analyze_Subprogram_Body_Helper): Do not call Freeze_Expr_Types here.
3404 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3406         * exp_prag.adb (Replace_Discriminals_Of_Protected_Op):
3407         New procedure, auxiliary to Expand_Pragma_Check, to handle
3408         references to the discriminants of a protected type within a
3409         precondition of a protected operation. This is needed because
3410         the original precondition has been analyzed in the context of
3411         the protected declaration, but in the body of the operation
3412         references to the discriminants have been replaved by references
3413         to the discriminants of the target object, and these references
3414         are only created when expanding the protected body.
3416 2017-09-08  Yannick Moy  <moy@adacore.com>
3418         * sem_prag.adb (Analyze_Pragma): Issue more precise error messages on
3419         Loop_Variant.
3421 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3423         * exp_attr.adb (Build_Record_VS_Func): If the record is an
3424         unchecked union, do not emit checks for its (non-existent)
3425         discriminants, or for variant parts that depend on them.
3427 2017-09-08  Justin Squirek  <squirek@adacore.com>
3429         * sem_ch4.adb (Find_Equality_Types.Try_One_Interp,
3430         Find_Comparison_Type.Try_One_Interp): Add check for generic
3431         instances.
3433 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3435         * sem_ch3.adb, layout.adb, layout.ads, exp_attr.adb, debug.adb,
3436         exp_pakd.adb, sem_prag.adb, gnat1drv.adb, targparm.adb, targparm.ads,
3437         repinfo.adb, exp_ch6.adb, exp_aggr.adb, sem_eval.adb, sem_ch13.adb,
3438         exp_ch3.adb: Remove references to Frontend_Layout_On_Target and
3439         remaining references to AAMP_On_Target.
3441 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3443         * style.adb: Fix typo.
3445 2017-09-08  Javier Miranda  <miranda@adacore.com>
3447         * einfo.adb (Underlying_Type): Add missing support for class-wide
3448         types that come from the limited view.
3449         * exp_attr.adb (Attribute_Address): Check class-wide type
3450         interfaces using the underlying type to handle limited-withed
3451         types.
3452         (Attribute_Tag): Check class-wide type interfaces using
3453         the underlying type to handle limited-withed types.
3455 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3457         * exp_ch5.adb (Expand_Predicated_Loop): Handle properly a loop
3458         over a subtype of a type with a static predicate, taking into
3459         account the predicate function of the parent type and the bounds
3460         given in the loop specification.
3461         * sem_ch3.adb (Inherit_Predicate_Flags): For qn Itype created for
3462         a loop specification that is a subtype indication whose type mark
3463         is a type with a static predicate, inherit predicate function,
3464         used to build case statement for rewritten loop.
3466 2017-09-08  Justin Squirek  <squirek@adacore.com>
3468         * lib-load.adb: Modify printing of error message to exclude file
3469         line number.
3471 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3473         * inline.adb (Can_Be_Inlined_In_GNATprove_Mode):
3474         don't inline subprograms declared in both visible and private
3475         parts of a package.
3476         (In_Package_Spec): previously In_Package_Visible_Spec; now
3477         detects subprograms declared both in visible and private parts
3478         of a package spec.
3480 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3482         * exp_util.adb (Build_Invariant_Procedure_Declaration): If
3483         the type is an anonymous array in an object declaration, whose
3484         component type has an invariant, use the object declaration
3485         as the insertion point for the invariant procedure, given that
3486         there is no explicit type declaration for an anonymous array type.
3488 2017-09-08  Bob Duff  <duff@adacore.com>
3490         * a-cbprqu.ads, a-cbdlli.adb: Suppress warnings.
3492 2017-09-08  Bob Duff  <duff@adacore.com>
3494         * a-strfix.adb (Trim): Compute Low and High only if needed.
3496 2017-09-08  Justin Squirek  <squirek@adacore.com>
3498         * lib-load.adb (Load_Main_Source): Add error output in the case a
3499         source file is missing.
3501 2017-09-08  Bob Duff  <duff@adacore.com>
3503 PR ada/80888
3504         * a-textio.adb, a-witeio.adb, a-ztexio.adb (Set_WCEM): Use
3505         Default_WCEM by default (i.e. if the encoding is not specified
3506         by the Form string).
3508 2017-09-08  Bob Duff  <duff@adacore.com>
3510         * s-trasym.ads (Hexa_Traceback): If
3511         Suppress_Hex is True, print "..." instead of a hexadecimal
3512         address.
3513         * s-trasym.adb: Ignore No_Hex in this version.
3514         Misc cleanup.
3516 2017-09-08  Bob Duff  <duff@adacore.com>
3518         * debug.adb: Minor reformatting.
3520 2017-09-08  Bob Duff  <duff@adacore.com>
3522         * a-cbdlli.adb, a-cohama.adb, a-cohase.adb (Copy): Rewrite the
3523         code so it doesn't trigger an "uninit var" warning.
3525 2017-09-08  Nicolas Roche  <roche@adacore.com>
3527         * s-hibaen.ads: Remove obsolete file.
3529 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3531         * a-locale.ads: Add comment explaining the state of this package.
3533 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3535         * sem_util.adb (Is_CCT_Instance): Allow calls in the context
3536         of packages.
3537         * sem_prag.ads, sem_prag.adb (Find_Related_Declaration_Or_Body):
3538         allow calls in the context of package spec (for pragma
3539         Initializes) and bodies (for pragma Refined_State).
3541 2017-09-08  Bob Duff  <duff@adacore.com>
3543         * checks.adb (Insert_Valid_Check): Copy the Do_Range_Check flag to the
3544         new Exp.
3546 2017-09-08  Eric Botcazou  <ebotcazou@adacore.com>
3548         * debug.adb (dA): Adjust comment.
3549         * gnat1drv.adb (Gnat1drv): Likewise.
3550         * opt.ads (List_Representation_Info_Extended): New variable.
3551         * repinfo.adb (List_Record_Info): Split implementation into...
3552         (Compute_Max_Length): ...this.  Recurse on records if requested.
3553         (List_Record_Layout): Likewise.
3554         * switch-c.adb (Scan_Front_End_Switches) <'R'>: Use case
3555         statement, accept '0' and set List_Representation_Info_Extended
3556         on 'e'.
3557         * usage.adb (Usage): Document new -gnatRe variant.
3559 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3561         * sem_prag.adb (Analyze_Pragma, case Default_Storage_Pool):
3562         Do not save the given entity in the global variable Default_Pool
3563         if the pragma appears within a generic unit.
3565 2017-09-08  Bob Duff  <duff@adacore.com>
3567         * errout.adb (Delete_Warning): Do not
3568         decrement Warnings_Treated_As_Errors. This is called before
3569         Warnings_Treated_As_Errors has been incremented to account for
3570         this warning. Decrementing it here can lead to negative values
3571         of Warnings_Treated_As_Errors, raising Constraint_Error in
3572         checks-on builds, and causing the compiler to return an error
3573         code in checks-off builds.
3575 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3577         * sem_util.ads, sem_util.adb (Is_CCT_Instance): Only expect
3578         entities of named concurrent types as Ref_Id and not of anonymous
3579         concurrent objects (because callers already know when a conversion
3580         is necessary and can easily do it); also, do not expect protected
3581         types or protected objects as Context_Id (because no flow-related
3582         SPARK pragmas are attached there); reflect these changes in a
3583         more precise comment.
3585 2017-09-08  Olivier Hainque  <hainque@adacore.com>
3587         * g-altive.ads: Add documentation.
3589 2017-09-08  Bob Duff  <duff@adacore.com>
3591         * sem_util.ads, debug.adb: Minor comment fix.
3592         * erroutc.ads: Comment fix.
3594 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3596         * sem_ch12.adb (Validate_Array_Type_Instance): Suppress check
3597         for compatibility of component types of formal and actual in an
3598         instantiation of a child unit,  when the component type of the
3599         formal is itself a formal of an enclosing generic.
3601 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3603         * sem_util.ads, sem_util.adb (Is_CCT_Instance): moved from
3604         sem_prag.adb to make it available for GNATprove; for concurrent
3605         types replace custom scope climbing with Scope_Same_Or_Within; for
3606         single concurrent objects add scope climbing (with Scope_Within),
3607         which was not there (that's the primary semantic change of this
3608         commit); also, when comparing a single concurrent object with
3609         its corresponding concurrent type rely on equality of types,
3610         not of objects (because that's simpler to code).
3611         * sem_prag.adb (Is_CCT_Instance): lifted to sem_util.ads.
3612         (Analyze_Global_Item): adjust special-casing of references to the
3613         current instance of a concurrent unit in the Global contracts
3614         of task types and single tasks objects; similar for references
3615         in the protected operations and entries of protected types and
3616         single protected objects (in all these cases the current instance
3617         behaves as an implicit parameter and must not be mentioned in
3618         the Global contract).
3620 2017-09-08  Arnaud Charlet  <charlet@adacore.com>
3622         * exp_ch6.adb (Expand_Call_Helper): Introduce temporary for
3623         function calls returning a record within a subprogram call,
3624         for C generation.
3626 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3628         * sem_ch8.adb (Find_Expanded_Name): Handle properly an expanded
3629         name that designates the current instance of a child unit in its
3630         own body and appears as the prefix of a reference to an entity
3631         local to the child unit.
3632         * exp_ch6.adb, freeze.adb, sem_ch3.adb, sem_prag.adb, sem_util.adb:
3633         Minor reformatting.
3635 2017-09-08  Yannick Moy  <moy@adacore.com>
3637         * sem_res.adb (Resolve_Equality_Op): Do not warn on comparisons that
3638         may be intentional.
3640 2017-09-08  Tristan Gingold  <gingold@adacore.com>
3642         * sem_warn.adb (Check_Unused_Withs): Remove test that disabled
3643         warnings on internal units in configurable run time mode.
3645 2017-09-08  Bob Duff  <duff@adacore.com>
3647         * sem_ch3.adb (Build_Derived_Private_Type): Inherit
3648         representation items from interfaces that the derived type
3649         implements, not just from the parent type.
3650         * sem_util.ads, sem_util.adb (Abstract_Interface_List): Change
3651         this to return an empty list when there are no interfaces.
3652         * einfo.ads, sem_ch13.adb: Minor comment fixes.
3653         * sem_attr.adb: Minor comment fix.
3655 2017-09-08  Doug Rupp  <rupp@adacore.com>
3657         * sigtramp-vxworks.c [i386]: Adjust the kernel context for
3658         x86-vx7.
3660 2017-09-08  Hristian Kirtchev  <kirtchev@adacore.com>
3662         * exp_ch4.adb (Expand_N_Allocator): Generate a
3663         call to Allocate_Any_Controlled when the allocation does not
3664         require any initialization.
3666 2017-09-08  Hristian Kirtchev  <kirtchev@adacore.com>
3668         * sem_util.adb (Copy_Node_With_Replacement):
3669         Update the Renamed_Object field of a replicated object renaming
3670         declaration.
3672 2017-09-08  Patrick Bernardi  <bernardi@adacore.com>
3674         * exp_ch9.adb (Is_Pure_Barrier): Allow type
3675         conversions and components of objects. Simplified the detection
3676         of the Count attribute by identifying the corresponding run-time
3677         calls.
3679 2017-09-08  Yannick Moy  <moy@adacore.com>
3681         * exp_ch9.adb, exp_disp.adb, repinfo.adb, sem_ch12.adb, sem_dim.adb,
3682         sem_type.adb, sinfo.ads: Minor reformatting.
3684 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3686         * freeze.adb (Has_Incomplete_Compoent): New predicate, subsidiary
3687         of Freeze_Profile, used to inhibit the freezing of the profile
3688         of an expression function declared within a nested package, when
3689         some type in the profile depends on a private type declared in
3690         an enclosing package.
3692 2017-09-08  Bob Duff  <duff@adacore.com>
3694         * gnat1drv.adb (Gnat1drv): Do not set the Force_ALI_Tree_File flag in
3695         the subunit case. It's still OK to set it in the "missing subunits"
3696         case, because that won't cause the obsolete .ali files that cause
3697         confusion.
3699 2017-09-08  Bob Duff  <duff@adacore.com>
3701         * sinput-l.adb: Remove unused "with Unchecked_Conversion;". It's
3702         unclear why this didn't cause a warning.
3703         * a-uncdea.ads, a-unccon.ads: Add "Ada." to names in the
3704         pragmas. It's unclear why this didn't cause an error.
3706 2017-09-08  Hristian Kirtchev  <kirtchev@adacore.com>
3708         * exp_spark.adb (Expand_SPARK_N_Object_Renaming_Declaration):
3709         Reimplemented.
3710         (Expand_SPARK_Potential_Renaming): Code clean up.
3711         * sem_prag.adb (Analyze_Initialization_Item): Add a guard in case
3712         the item does not have a proper entity.
3713         (Analyze_Input_Item): Add a guard in case the item does not have a
3714         proper entity.
3715         (Collect_States_And_Objects): Include object renamings in the
3716         items being collected.
3717         (Resolve_State): Update the documentation of this routine.
3718         * sem_util.adb (Entity_Of): Add circuitry to handle
3719         renamings of function results.
3720         (Remove_Entity): New routine.
3721         (Remove_Overloaded_Entity): Take advantage of factorization.
3722         * sem_util.ads (Entity_Of): Update the documentation
3723         of this routine.
3724         (Remove_Entity): New routine.
3725         (Remove_Overloaded_Entity): Update the documentation of this
3726         routine.
3728 2017-09-08  Eric Botcazou  <ebotcazou@adacore.com>
3730         * repinfo.adb (List_Record_Info): During first loop,
3731         do not override the normalized position and first bit
3732         if they have already been set.  Move fallback code
3733         for the packed case to the case where it belongs.
3734         * sem_ch13.adb (Adjust_Record_For_Reverse_Bit_Order):
3735         Also adjust the normalized position of components.
3736         (Adjust_Record_For_Reverse_Bit_Order_Ada_95): Likewise.
3738 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3740         * exp_disp.adb (Make_DT, Set_All_DT_Position): Handle properly
3741         the placement of a primitive operation O that renames an operation
3742         R declared in an inner package, and which is thus not a primitive
3743         of the dispatching type of O. In this case O is a new primitive
3744         and does not inherit its dispatch table position from R (which
3745         has none).
3747 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3749         * sem_dim.adb (Analyze_Dimension_If_Expression,
3750         Analyze_Dimension_Case_Expression): new subprograms to verify
3751         the dimensional correctness of Ada2012 conditional expressions,
3752         and set properly the dimensions of the construct.
3753         * sem_res.adb (Resolve_If_Expression, Resolve_Case_Expression)):
3754         call Analyze_Dimension.
3756 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3758         * sem_type.adb (Expand_Interface_Conversion): Prevent an infinite
3759         loop on an interface declared as a private extension of another
3760         synchronized interface.
3762 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3764         * sem_ch12.adb (Check_Generic_Parent): New procedure within
3765         Analyze_Associations, to handle actual packages that depend on
3766         previous instances.  If a package IAP that is an instantiation is
3767         used as an actual in a subsequent instantiation SI in the same
3768         scope, and IAP has a body, IAP must be frozen before SI. If
3769         the generic parent of IAP is itself declared in a previous
3770         instantiation in the same scope, that instantiation must also
3771         be frozen before SI.
3772         (Install_Body): Prevent double insertion of freeze node for
3773         instance.
3775 2017-09-08  Hristian Kirtchev  <kirtchev@adacore.com>
3777         * sem_prag.adb (Resolve_State): Update the
3778         comment on documentation. Generate a reference to the state once
3779         resolution takes place.
3781 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3783         * sem_ch13.adb (Analyze_Aspect_Specifications, case
3784         Linker_Section): If the aspect applies to an object declaration
3785         with explicit initialization, do not delay the freezing of the
3786         object, to prevent access-before-elaboration in the generated
3787         initialization code.
3789 2017-09-08  Ed Schonberg  <schonberg@adacore.com>
3791         * a-wtdeio.adb (Put, all versions): Use Long_Long_Integer
3792         (Integer_Value (Item)) when the size of the fixed decimal type
3793         is larger than Integer.
3795 2017-09-07  Eric Botcazou  <ebotcazou@adacore.com>
3797         PR ada/82127
3798         * gcc-interface/decl.c (copy_and_substitute_in_layout): Put the fields
3799         in order of increasing position in more cases.
3801 2017-09-07  Yannick Moy  <moy@adacore.com>
3803         * a-exetim-mingw.ads: Add contract Global=>null
3804         on all operations that are modeled as having no read or write
3805         of global variables in SPARK.
3807 2017-09-07  Raphael Amiard  <amiard@adacore.com>
3809         * a-chtgop.adb, a-chtgop.ads (Generic_Iteration_With_Position): Added
3810         to Hmaps.Generic_Ops.
3811         * a-cohama.adb (Ada.Containers.Hmaps.Iterate): Pass proper position in
3812         cursors.
3813         * a-cihama.adb (Ada.Containers.Indefinite_Hmaps.Iterate): Pass pos in
3814         cursors.
3815         * a-cohase.adb (Ada.Containers.Hashed_Sets.Iterate): Pass proper
3816         position in cursors.
3818 2017-09-07  Javier Miranda  <miranda@adacore.com>
3820         * sem_elab.adb (Check_Task_Activation): Adding switch -gnatd.y to
3821         allow disabling the generation of implicit pragma Elaborate_All
3822         on task bodies.
3824 2017-09-07  Javier Miranda  <miranda@adacore.com>
3826         * exp_disp.adb (Make_Tags): Avoid suffix counter
3827         in the external name of the elaboration flag. Required to fix
3828         the regressions introduced by the initial version of this patch.
3830 2017-09-07  Bob Duff  <duff@adacore.com>
3832         * sem_ch6.adb (Analyze_Function_Return): Do not
3833         insert an explicit conversion to force the displacement of the
3834         "this" pointer to reference the secondary dispatch table in the
3835         case where the return statement is returning a raise expression,
3836         as in "return raise ...".
3838 2017-09-07  Arnaud Charlet  <charlet@adacore.com>
3840         * sem_disp.adb (Is_User_Defined_Equality): Removed procedure.
3841         * sem_util.ads, sem_util.adb (Is_User_Defined_Equality): Copied
3842         procedure from sem_disp.adb.
3843         * sem_ch12.ads (Get_Unit_Instantiation_Node): rename Package
3844         with Unit.
3845         * sem_ch12.adb (Get_Unit_Instantiation_Node): function extended to
3846         return the instantiation node for subprograms. Update references
3847         to Get_Unit_Instantiation_Node.
3848         * sem_ch7.adb (Install_Parent_Private_Declarations): update
3849         reference to Get_Unit_Instantiation_Node.
3850         * exp_dist.adb (Build_Package_Stubs): update reference to
3851         Get_Unit_Instantiation_Node.
3852         * sem_ch9.adb: minor typo in comment.
3853         * lib-xref-spark_specific.adb
3854         (Traverse_Declaration_Or_Statement): traverse into task type
3855         definition.
3857 2017-09-07  Ed Schonberg  <schonberg@adacore.com>
3859         * sem_dim.adb (Analyze_Dimension_Type_Conversion): New procedure
3860         to handle properly various cases of type conversions where the
3861         target type and/or the expression carry dimension information.
3862         (Dimension_System_Root); If a subtype carries dimension
3863         information, obtain the source parent type that carries the
3864         Dimension aspect.
3866 2017-09-07  Dmitriy Anisimkov  <anisimko@adacore.com>
3868         * g-socket.adb, g-socket.ads (GNAT.Sockets.To_Ada): New routine.
3870 2017-09-07  Ed Schonberg  <schonberg@adacore.com>
3872         * exp_attr.adb (Expand_N_Attribute_Reference, case 'Constrained):
3873         If the prefix is a reference to an object, rewrite it as an
3874         explicit dereference, as required by 3.7.2 (2) and as is done
3875         with most other attributes whose prefix is an access value.
3877 2017-09-07  Bob Duff  <duff@adacore.com>
3879         * par-ch13.adb: Set the Inside_Depends flag if we are inside a
3880         Refined_Depends aspect.
3881         * par-ch2.adb: Set the Inside_Depends flag if we are inside a
3882         Refined_Depends pragma.
3883         * scans.ads: Fix documentation of Inside_Depends flag.
3884         * styleg.adb, styleg.ads: Minor reformatting and comment fixes.
3886 2017-09-07  Hristian Kirtchev  <kirtchev@adacore.com>
3888         * exp_ch7.adb (Insert_Actions_In_Scope_Around):
3889         Account for the case where the are no lists to insert, but the
3890         secondary stack still requires management.
3891         * a-chtgop.adb, a-cihama.adb, a-cohama.adb, a-cohase.adb, a-tags.adb,
3892         comperr.adb, einfo.adb, exp_aggr.adb, exp_ch3.adb, exp_disp.adb,
3893         lib-xref.adb, lib-xref-spark_specific.adb, sem_ch12.adb, sem_ch13.adb,
3894         sem_ch6.adb, sem_dim.adb, sem_dim.ads, sem_elab.adb, sem_prag.adb:
3895         Minor reformatting.
3897 2017-09-07  Vincent Celier  <celier@adacore.com>
3899         * clean.adb: Do not get the target parameters before calling
3900         gprclean.
3902 2017-09-07  Nicolas Roche  <roche@adacore.com>
3904         * s-osinte-solaris-posix.ads: Removed.
3906 2017-09-07  Arnaud Charlet  <charlet@adacore.com>
3908         * sem_prag.adb (Collect_States_And_Objects): Detect also instances of
3909         single concurrent objects.
3911 2017-09-07  Javier Miranda  <miranda@adacore.com>
3913         * s-regexp.ads: Fix documentation of the globbing grammar.
3915 2017-09-07  Gary Dismukes  <dismukes@adacore.com>
3917         * a-tags.ads, einfo.ads, exp_disp.ads: Minor reformatting.
3919 2017-09-07  Arnaud Charlet  <charlet@adacore.com>
3921         * gnat1drv.adb (Gnat1drv): Enable pragma Ignore_Pragma (Global)
3922         in CodePeer mode, to support more legacy code automatically.
3924 2017-09-07  Ed Schonberg  <schonberg@adacore.com>
3926         * exp_disp.adb (Replace_Formals): If thr formal is classwide,
3927         and thus not a controlling argument, preserve its type after
3928         rewriting because it may appear in an nested call with a classwide
3929         parameter.
3931 2017-09-07  Arnaud Charlet  <charlet@adacore.com>
3933         * comperr.adb (Delete_SCIL_Files): Handle case of
3934         N_Package_Instantiation.
3936 2017-09-07  Ed Schonberg  <schonberg@adacore.com>
3938         * sem_ch10.adb (Remove_Private_With_Clause): If a private with
3939         clause for a unit U appears in a context that includes a regular
3940         with_clause on U, rewrite the redundant private clause into a null
3941         statement, rather than removing it altogether from the context,
3942         so that ASIS tools can reconstruct the original source.
3944 2017-09-07  Ed Schonberg  <schonberg@adacore.com>
3946         * sem_ch13.adb (Check_Aspect_At_Freeze_Point): The expression
3947         for aspect Small can be of any real type (not only a universal
3948         real literal) as long as it is a static constant.
3950 2017-09-07  Thomas Quinot  <quinot@adacore.com>
3952         * par_sco.adb: Minor reformatting.
3954 2017-09-07  Arnaud Charlet  <charlet@adacore.com>
3956         * s-parame-ae653.ads: Removed.
3958 2017-09-07  Nicolas Roche  <roche@adacore.com>
3960         * s-traces-default.adb, s-trafor-default.adb, s-trafor-default.ads,
3961         s-traces.adb, s-traces.ads, s-tratas-default.adb, s-tfsetr-default.adb,
3962         s-tfsetr-vxworks.adb, s-tratas.adb, s-tratas.ads, s-tasuti.adb,
3963         s-parame-hpux.ads, s-tassta.adb, s-taasde.adb, s-tasren.adb,
3964         s-taprob.adb, a-caldel.adb, s-parame.ads, Makefile.rtl, s-tpobop.adb,
3965         s-taenca.adb, s-parame-vxworks.ads: Remove support for System.Traces.
3967 2017-09-07  Yannick Moy  <moy@adacore.com>
3969         * a-ngelfu.ads Add preconditions to all functions
3970         listed in Ada RM A.5.1(19-33) as having constraints on inputs.
3972 2017-09-07  Arnaud Charlet  <charlet@adacore.com>
3974         * lib-xref.adb (Generate_Reference): ignore
3975         references to entities which are Part_Of single concurrent
3976         objects.
3978 2017-09-07  Eric Botcazou  <ebotcazou@adacore.com>
3980         * sem_ch7.adb (Hide_Public_Entities): Add paragraph to main
3981         comment.
3983 2017-09-07  Arnaud Charlet  <charlet@adacore.com>
3985         * a-taside.adb (Activation_Is_Complete): Raise Program_Error if
3986         Null_Task_Id is passed.
3988 2017-09-07  Javier Miranda  <miranda@adacore.com>
3990         * einfo.ads, einfo.adb (Access_Disp_Table_Elab_Flag): New
3991         attribute. Defined for record types and subtypes.
3992         * exp_ch3.ads (Init_Secondary_Tags): Adding new formal
3993         (Init_Tags_List) to facilitate generating separate code in the
3994         IP routine to initialize the object components and for completing
3995         the elaboration of dispatch tables.
3996         * exp_ch3.adb (Build_Init_Procedure): Improve the code
3997         generated in the IP routines by means of keeping separate
3998         the initialization of the object components from the
3999         initialization of its dispatch tables.  (Init_Secondary_Tags):
4000         Adding new formal (Init_Tags_List) and adjusting calls to
4001         Ada.Tags.Set_Dynamic_Offset_To_Top since it has a new formal;
4002         adjusting also calls to Ada.Tags.Register_Interface_Offset
4003         because the type of one of its formals has been changed.
4004         * a-tags.ads, a-tags.adb (Register_Interface_Offset): Profile
4005         modified. Instead of receiving a pointer to an object this
4006         routine receives now a primary tag.
4007         (Set_Dyanic_Offset_To_Top): Profile modified. This routine receives an
4008         additional formal: the tag of the primary dispatch table.
4009         * exp_disp.ads (Elab_Flag_Needed): New subprogram.
4010         * exp_disp.adb (Elab_Flag_Needed): New subprogram.
4011         (Make_Tags): Adding the declaration of the elaboration flag (if needed).
4012         * exp_aggr.adb (Build_Record_Aggr_Code): Adding actual of new
4013         formal in calls to Init_Secondary_Tags.
4015 2017-09-07  Javier Miranda  <miranda@adacore.com>
4017         * ghost.adb (Mark_And_Set_Ghost_Instantiation.Check_Ghost_Actuals): New
4018         subprogram.
4019         * sem_prag.adb (Pragma_Ghost): Add missing support for ghost
4020         applied to generic subprograms.
4022 2017-09-07  Arnaud Charlet  <charlet@adacore.com>
4024         * sem_util.adb (Check_Part_Of_Reference): rename Conc_Typ to Conc_Obj
4025         (because it refers to the anonymous concurrent object, not its type);
4026         fix condition for emitting error message about task/protected type,
4028 2017-09-07  Bob Duff  <duff@adacore.com>
4030         * binde.adb (Debug_Flag_Old): If both -do and -dp
4031         are specified, behave as if just -do was specified, rather than
4032         using a mixture.
4034 2017-09-07  Nicolas Roche  <roche@adacore.com>
4036         * system-vxworks-sparcv9.ads, s-vxwork-m68k.ads, s-vxwork-mips.ads,
4037         system-vxworks-m68k.ads, system-vxworks-mips.ads: Removed.
4039 2017-09-07  Arnaud Charlet  <charlet@adacore.com>
4041         * sem_prag.adb (Find_Role): The Global_Seen flag
4042         is now consulted not only for abstract states and variables,
4043         but for all kinds of items.
4044         (Collect_Subprogram_Inputs_Outputs): Do not process formal
4045         generic parameters, because unlike ordinary formal parameters,
4046         generic formals only act as input/ outputs if they are explicitly
4047         mentioned in a Global contract.
4049 2017-09-07  Yannick Moy  <moy@adacore.com>
4051         * ghost.adb (Check_Ghost_Context): Do not err on ghost code inside
4052         predicate procedure. Check predicate pragma/aspect with Ghost entity.
4053         * exp_ch6.adb, par-ch6.adb, sem_ch13.adb, sem_prag.adb; Minor
4054         reformatting.
4056 2017-09-07  Ed Schonberg  <schonberg@adacore.com>
4058         * sem_aggr.adb: Move New_Copy_Tree_And_Dimensions to sem_dim
4059         (code cleanup);
4060         * sem_ch3.adb (Build_Derived_Record_Type):i Call
4061         Copy_Dimensions_Of_Components after creating the copy of the
4062         record declaration.
4063         * sem_dim.ads, sem_dim.adb (Copy_Dimensions_Of_Components): For a
4064         derived recor type, copy the dikensions if any of each component
4065         of the parent record to the corresponding component declarations
4066         of the derived record. These expressions are used among other
4067         things as default values in aggregates with box associations.
4068         * a-dirval-mingw.adb, g-cgi.adb, gnatcmd.adb, lib-xref.adb,
4069         repinfo.adb, sem_attr.adb, sem_ch10.adb, sem_ch6.adb, sem_prag.adb:
4070         Minor reformatting.
4072 2017-09-07  Arnaud Charlet  <charlet@adacore.com>
4074         * sem_util.adb: Remove extra space after THEN.
4076 2017-09-07  Eric Botcazou  <ebotcazou@adacore.com>
4078         * sem_ch7.adb (Has_Referencer): For a subprogram renaming,
4079         also mark the renamed subprogram as referenced.
4081 2017-09-07  Ed Schonberg  <schonberg@adacore.com>
4083         * par-ch6.adb (P_Subprogram): Improve error message on null
4084         procedure with misplaced aspect specification, which the parser
4085         first attempts to interpret as a malformed expression function.
4087 2017-09-07  Gary Dismukes  <dismukes@adacore.com>
4089         * sem_attr.adb (Analyze_Attribute_Old_Result):
4090         Allow attributes Result and Old in the case of an expression
4091         function.
4093 2017-09-07  Justin Squirek  <squirek@adacore.com>
4095         * sem_prag.adb (Process_Atomic_Independent_Shared_Volatile): Propagate
4096         Volatile to subcomponents.
4098 2017-09-07  Bob Duff  <duff@adacore.com>
4100         * exp_ch7.adb (Find_Last_Init): Check for the
4101         case where a build-in-place function call has been replaced by a
4102         'Reference attribute reference.
4104 2017-09-07  Eric Botcazou  <ebotcazou@adacore.com>
4106         * sem_ch7.adb (Has_Referencer): Recurse on Actions of freeze
4107         nodes.
4109 2017-09-07  Bob Duff  <duff@adacore.com>
4111         * exp_ch6.adb (Make_Build_In_Place_Call_In_Object_Declaration,
4112         Make_Build_In_Place_Call_In_Anonymous_Context): Do not use the
4113         secondary stack for all functions that return limited tagged
4114         types -- just do it for dispatching calls.  Misc cleanup.
4115         * sem_util.ads, sem_util.adb (Unqual_Conv): New function to
4116         remove qualifications and type conversions. Fix various bugs
4117         where only a single level of qualification or conversion was
4118         removed, so e.g. "T1'(T2'(X))" would incorrectly return "T2'(X)"
4119         instead of "X".
4120         * checks.adb, exp_util.ads, exp_util.adb, sem_res.adb: Misc related
4121         cleanup.
4123 2017-09-07  Ed Schonberg  <schonberg@adacore.com>
4125         * sem_ch6.adb (setr_Actual_Subtypes): Within a predicate function
4126         do not create actual subtypes that may generate further predicate
4127         functions.
4128         * sem_ch13.adb (Build_Predicate_Functions): Indicate that entity
4129         of body is a predicate function as well.
4130         (Resolve_Aspect_Expressions, Resolve_Name): For a component
4131         association, only the expression needs resolution, not the name.
4132         (Resolve_Aspect_Expressions, case Predicates): Construct and
4133         analyze the predicate function declaration in the scope of the
4134         type, before making the type and its discriminants visible.
4136 2017-09-06  Eric Botcazou  <ebotcazou@adacore.com>
4138         * gcc-interface/decl.c (warn_on_field_placement): Issue the warning
4139         only if the record type itself comes from source.
4141 2017-09-06  Gary Dismukes  <dismukes@adacore.com>
4143         * sem_ch5.adb: Minor reformatting and a typo fix
4145 2017-09-06  Arnaud Charlet  <charlet@adacore.com>
4147         * sinput-l.ads: minor remove extra period at the end of comment
4149 2017-09-06  Arnaud Charlet  <charlet@adacore.com>
4151         * sem_prag.adb (Add_Item_To_Name_Buffer): remove support for
4152         E_Discriminant.
4153         (Find_Role): remove support for E_Discriminant.
4155 2017-09-06  Javier Miranda  <miranda@adacore.com>
4157         * exp_ch6.adb (Expand_Simple_Function_Return):
4158         Add missing implicit type conversion to force displacement of the
4159         "this" pointer.
4161 2017-09-06  Hristian Kirtchev  <kirtchev@adacore.com>
4163         * sem_ch3.adb, sem_aux.adb, sem_res.adb: Minor reformatting.
4165 2017-09-06  Yannick Moy  <moy@adacore.com>
4167         * sem_ch12.adb (Analyze_Instance_And_Renamings): Refactor to set
4168         global variable Ignore_SPARK_Mode_Pragmas_In_Instance only once.
4170 2017-09-06  Bob Duff  <duff@adacore.com>
4172         * sem_ch8.adb: Change Assert to be consistent with
4173         other similar ones.
4175 2017-09-06  Bob Duff  <duff@adacore.com>
4177         * binde.adb (Find_Elab_Order): Do not run Elab_Old unless
4178         requested. Previously, the -do switch meant "run Elab_New and
4179         Elab_Old and use the order chosen by Elab_Old, possibly with
4180         debugging printouts comparing the two orders."  Now it means
4181         "do not run Elab_New." This is of use if there are bugs that
4182         cause Elab_New to crash.
4183         (Elab_Position, Num_Chosen): Change type to Nat, to avoid various
4184         type conversions.
4185         * ali.ads (Elab_Position): Change type to Nat, to avoid various
4186         type conversions.
4188 2017-09-06  Arnaud Charlet  <charlet@adacore.com>
4190         * sem_prag.adb (Check_Mode_Restriction_In_Enclosing_Context): Fix
4191         reference to SPARK RM.
4193 2017-09-06  Eric Botcazou  <ebotcazou@adacore.com>
4195         * layout.adb: Use SSU short hand consistently throughout the file.
4197 2017-09-06  Eric Botcazou  <ebotcazou@adacore.com>
4199         * freeze.adb (Freeze_Record_Type)
4200         <Sized_Component_Total_Round_RM_Size>: New local variable to
4201         accumulate the rounded RM_Size of components.  Update it for
4202         every component whose RM_Size is statically known.  Add missing
4203         guard to check that bit packing is really required before issuing
4204         the error about packing.  Swap condition for clarity's sake.
4205         * sem_prag.adb (Usage_Error): Fix reference to SPARK RM in comment.
4207 2017-09-06  Fedor Rybin  <frybin@adacore.com>
4209         * makeutl.adb, makeutl.ads, mlib.adb, mlib.ads, mlib-fil.adb,
4210         mlib-fil.ads, mlib-prj.adb, mlib-prj.ads, mlib-tgt.adb, mlib-tgt.ads,
4211         mlib-tgt-specific.adb, mlib-tgt-specific.ads,
4212         mlib-tgt-specific-aix.adb, mlib-tgt-specific-darwin.adb,
4213         mlib-tgt-specific-hpux.adb, mlib-tgt-specific-linux.adb,
4214         mlib-tgt-specific-mingw.adb, mlib-tgt-specific-solaris.adb,
4215         mlib-tgt-specific-vxworks.adb, mlib-tgt-specific-xi.adb, mlib-utl.adb,
4216         mlib-utl.ads, prj.adb, prj.ads, prj-attr.adb, prj-attr.ads,
4217         prj-attr-pm.adb, prj-attr-pm.ads, prj-com.ads, prj-conf.adb,
4218         prj-conf.ads, prj-dect.adb, prj-dect.ads, prj-env.adb, prj-env.ads,
4219         prj-err.adb, prj-err.ads, prj-ext.adb, prj-ext.ads, prj-makr.adb,
4220         prj-makr.ads, prj-nmsc.adb, prj-nmsc.ads, prj-pars.adb, prj-pars.ads,
4221         prj-part.adb, prj-part.ads, prj-pp.adb, prj-pp.ads, prj-proc.adb,
4222         prj-proc.ads, prj-strt.adb, prj-strt.ads, prj-tree.adb, prj-tree.ads,
4223         prj-util.adb, prj-util.ads, sinput-p.adb, sinput-p.ads: Remove obsolete
4224         project manager sources.
4226 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4228         * sem_ch5.adb (Analyze_Assigment): If the left-hand side is an
4229         entity of a mutable type and the right-hand side is a conditional
4230         expression, resolve the alternatives of the conditional using
4231         the base type of the target entity, because the alternatives
4232         may have distinct subtypes. This is particularly relevant if
4233         the alternatives are aggregates.
4235 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4237         * checks.adb (Apply_Predicate_Check): If the expression is an
4238         aggregate that is the RHS of an assignment, apply the check to
4239         the LHS after the assignment, rather than to the aggregate. This
4240         is more efficient than creating a temporary for the aggregate,
4241         and prevents back-end crashes when the aggregate includes a
4242         dynamic "others' association.
4244 2017-09-06  Yannick Moy  <moy@adacore.com>
4246         * sem_ch12.adb (Analyze_Instance_And_Renamings):
4247         Set variable to ignore SPARK_Mode in instance before the analysis
4248         of the generated package declaration.
4250 2017-09-06  Yannick Moy  <moy@adacore.com>
4252         * sem_res.adb (Resolve_Call): Do not issue a
4253         message for calls inside expression function, unless body was
4254         seen and is candidate for inlining.
4256 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4258         * sem_aux.adb (Is_Generic_Formal): Handle properly formal packages.
4259         * sem_ch3.adb (Analyze_Declarations): In a generic subprogram
4260         body. do not freeze the formals of the generic unit.
4262 2017-09-06  Gary Dismukes  <dismukes@adacore.com>
4264         * errout.adb (Error_Msg): Separate the
4265         treatment for warning vs. style messages in inlinings and
4266         instantiations. Prevents blowups on calls to Warn_Insertion for
4267         style messages, which should not be called in that case because
4268         Warning_Msg_Char is not set.
4270 2017-09-06  Justin Squirek  <squirek@adacore.com>
4272         * sem_prag.adb (Check_VFA_Conflicts): Created
4273         to group all Volatile_Full_Access checks relating to other
4274         representation pragmas (Mark_Component_Or_Object): Created
4275         to centeralize the flagging of attributes for the record type
4276         component case, a pragma applied individually to a component, and
4277         the object case.
4278         (Process_Atomic_Independent_Shared_Volatile):
4279         Add propagation of certain pragmas to record components and move
4280         evaluation of VFA checks
4282 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4284         * sem_prag.adb (Check_Postcondition_Use_In_Inlined_Subprogram):
4285         Do not warn on conditions that are not obeyed for Inline_Always
4286         subprograms, when assertions are not enabled.
4288 2017-09-06  Arnaud Charlet  <charlet@adacore.com>
4290         * sem_util.adb (Unique_Entity): For abstract states return their
4291         non-limited view.
4293 2017-09-06  Bob Duff  <duff@adacore.com>
4295         * sem_ch12.adb (Copy_Generic_Node): When we copy a node
4296         that is a proper body corresponding to a stub, we defer the
4297         adjustment of the sloc until after the correct adjustment has
4298         been computed. Otherwise, Adjust_Instantiation_Sloc will ignore
4299         the adjustment, because it will be outside the range in (the old,
4300         incorrect) S_Adjustment.
4301         * inline.adb: Use named notation for readability and uniformity.
4302         * sinput-l.adb: Minor improvements to debugging output printed
4303         for Debug_Flag_L.
4304         * sinput-l.ads (Create_Instantiation_Source): Minor comment
4305         correction.
4307 2017-09-06  Vincent Celier  <celier@adacore.com>
4309         * make.adb: Do not invoke gprbuild for -bargs -P.
4311 2017-09-06  Sylvain Dailler  <dailler@adacore.com>
4313         * sem_eval.adb (Compile_Time_Known_Value_Or_Aggr): Adding a
4314         case when Op is of kind N_Qualified_Expression. In this case,
4315         the function is called recursively on the subexpression like in
4316         other cases.
4317         * make.adb: Minor reformatting
4319 2017-09-06  Justin Squirek  <squirek@adacore.com>
4321         * einfo.adb (Set_Linker_Section_Pragma): Modify
4322         Set_Linker_Section_Pragma to be consistant with the "getter"
4323         Linker_Section_Pragma.
4324         * exp_ch5.adb (Expand_Formal_Container_Loop): Add proper error
4325         checking for container loops so that the index cursor is not
4326         directly changable by the user with the use of E_Loop_Parameter.
4327         * sem_ch5.adb (Analyze_Block_Statement): Revert previous change.
4328         * sem_warn.adb (Check_References): Revert previous change.
4330 2017-09-06  Bob Duff  <duff@adacore.com>
4332         * exp_util.adb (Is_Displace_Call): Make sure it works for indirect
4333         calls and the like.
4335 2017-09-06  Yannick Moy  <moy@adacore.com>
4337         * sem_prag.adb (Analyze_Depends_Global): Reinforce test on object
4338         declarations to only consider valid uses of Global/Depends those on
4339         single concurrent objects.
4341 2017-09-06  Eric Botcazou  <ebotcazou@adacore.com>
4343         * sem_ch13.adb (Check_Record_Representation_Clause): Give an
4344         error as soon as one of the specified components overlaps the
4345         parent field.
4347 2017-09-06  Arnaud Charlet  <charlet@adacore.com>
4349         * sem_prag.ads: minor fix typo in comment.
4351 2017-09-06  Justin Squirek  <squirek@adacore.com>
4353         * sem_ch5.adb (Analyze_Block_Statement): Verify a block comes
4354         from source before checking source references.
4355         * sem_warn.adb (Check_References): Add check for internal block
4356         before recursing.
4358 2017-09-06  Vincent Celier  <celier@adacore.com>
4360         * make.adb, makeusg.adb, switch-m.adb, switch-m.ads, make_util.adb,
4361         make_util.ads, sinput.adb, sinput.ads, clean.adb, gnatls.adb,
4362         gnatname.adb: Remove the Project Manager from the GNAT tools.
4363         * gcc-interface/Makefile.in: ditto.
4365 2017-09-06  Bob Duff  <duff@adacore.com>
4367         * sem_util.ads: Minor comment fix.
4369 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4371         * sem_ch12.adb (Analyze_Associations, case of Formal_Package):
4372         Generate a freeze node for the actual of a formal package, if
4373         the actual is declared in the same unit and has a corresponding
4374         body, to prevent the current instance from being frozen before
4375         the actual is.
4377 2017-09-06  Eric Botcazou  <ebotcazou@adacore.com>
4379         * sem_ch7.adb (Entity_Table_Size): Change to nearest prime number.
4381 2017-09-06  Yannick Moy  <moy@adacore.com>
4383         * sem_warn.adb: Minor refactoring.
4385 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4387         * einfo.ads, einfo.adb (Get_Classwwide_Pragma): New utility,
4388         to retrieve the inherited classwide precondition/postcondition
4389         of a subprogram.
4390         * freeze.adb (Freeze_Entity): Use Get_Classwide_Pragma when
4391         freezing a subprogram, to complete the generation of the
4392         corresponding checking code.
4394 2017-09-06  Hristian Kirtchev  <kirtchev@adacore.com>
4396         * exp_util.adb (Is_Controlled_Indexing): New routine.
4397         (Is_Displace_Call): Use routine Strip to remove indirections.
4398         (Is_Displacement_Of_Object_Or_Function_Result): Code clean up. Add a
4399         missing case of controlled generalized indexing.
4400         (Is_Source_Object): Use routine Strip to remove indirections.
4401         (Strip): New routine.
4403 2017-09-06  Bob Duff  <duff@adacore.com>
4405         * sysdep.c (__gnat_has_cap_sys_nice): If HAVE_CAPABILITY is defined,
4406         we include the proper header. Otherwise, we just declare the necessary
4407         things from the capabilities library. This is so we can build on
4408         machines without that library, while still enabling that library.
4409         At run time, we're using weak symbols, so __gnat_has_cap_sys_nice will
4410         simply return 0 if the library is not present, or not included
4411         in the link.
4413 2017-09-06  Pierre-Marie de Rodat  <derodat@adacore.com>
4415         * exp_dbug.adb (Debug_Renaming_Declaration): Do not create an encoding
4416         for renamings that involve function calls in prefix form.
4418 2017-09-06  Bob Duff  <duff@adacore.com>
4420         * sem_ch3.adb (Analyze_Subtype_Declaration):
4421         Set Has_Delayed_Freeze on a subtype of an incomplete type.
4423 2017-09-06  Pierre-Marie de Rodat  <derodat@adacore.com>
4425         * par_sco.adb (Extend_Statement_Sequence): When the accept statement
4426         has no parameter specification and no entry index, use the entry name
4427         as the end of the generated SCO statement.
4429 2017-09-06  Steve Baird  <baird@adacore.com>
4431         * exp_util.adb (Side_Effect_Free): For CodePeer (only) treat
4432         uses of 'Image and related attributes as having side effects in
4433         order to avoid replicating such uses.
4434         * pprint.ads (Expression_Image) Add new generic formal flag
4435         Hide_Temp_Derefs.  The flag defaults to False; CodePeer will
4436         (eventually) override the default.
4437         * pprint.adb (Expression_Image) If the new flag is set, then
4438         suppress the ".all" suffix when displaying a dereference whose
4439         prefix is a use of a value-capturing compiler temp of the sort
4440         generated by Expr_Util.Remove_Side_Effects .
4441         * exp_attr.adb, g-catiio.adb, inline.adb, sem_attr.adb, sem_ch13.adb,
4442         sem_ch7.adb, sem_dim.adb, sem_util.adb, sem_util.ads, sem_warn.adb:
4443         Minor reformatting.
4444         * inline.adb: Minor wording change.
4446 2017-09-06  Eric Botcazou  <ebotcazou@adacore.com>
4448         * sem_ch7.adb: Update comment.
4450 2017-09-06  Yannick Moy  <moy@adacore.com>
4452         * einfo.adb, einfo.ads (Is_Subprogram_Or_Entry): New predicate.
4453         * inline.adb (Can_Be_Inlined_In_GNATprove_Mode): Use new function.
4454         * sem_util.adb, sem_util.ads (Within_Protected_Type): Renaming
4455         with slight modification from Is_Subp_Or_Entry_Inside_Protected,
4456         so that applies to any entity.
4458 2017-09-06  Yannick Moy  <moy@adacore.com>
4460         * sem_ch3.adb (Derived_Type_Declaration): Use
4461         Incomplete_Or_Partial_View rather than local Find_Partial_View.
4463 2017-09-06  Javier Miranda  <miranda@adacore.com>
4465         * g-catiio.ads, g-catiio.adb (Value): Extended to parse an UTC time
4466         following ISO-8861.
4468 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4470         * sem_dim.adb (Analyze_Dimension): In an instance, a type
4471         conversion takes its dimensions from the expression, not from
4472         the context type.
4473         (Dimensions_Of_Operand): Ditto.
4475 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4477         * exp_ch6.adb (Expand_Call_Helper): Do not optimize calls to
4478         null procedures when GNAT coverage is used, so that their (empty)
4479         bodies are properly covered.
4481 2017-09-06  Bob Duff  <duff@adacore.com>
4483         * sem_ch13.adb (Resolve_Aspect_Expressions): If
4484         the entity is a type with discriminants, make the discriminants
4485         directly visible in aspect clauses.
4487 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4489         * sem_res.adb (Resolve_Arithmentic_Op): If both operands are
4490         Universal_Real and the context is a floating-point type, resolve
4491         both operands to the target type.
4493 2017-09-06  Hristian Kirtchev  <kirtchev@adacore.com>
4495         * a-comlin.adb, exp_aggr.adb, exp_ch6.adb, frontend.adb, gnatbind.adb,
4496         sem_ch3.adb, sem_util.adb: Minor reformatting.
4498 2017-09-06  Yannick Moy  <moy@adacore.com>
4500         * freeze.adb (Check_Inherited_Conditions): Rewriting
4501         of inherited preconditions and postconditions should only occur
4502         in GNATprove mode, that is, when GNATprove_Mode is True, not to
4503         be confused with SPARK_Mode being On.
4505 2017-09-06  Yannick Moy  <moy@adacore.com>
4507         * sem_warn.adb (Check_References): Take into
4508         account possibility of attribute reference as original node.
4510 2017-09-06  Yannick Moy  <moy@adacore.com>
4512         * exp_attr.adb (Expand_N_Attribute_Reference): Protect against invalid
4513         use of attribute.
4515 2017-09-06  Eric Botcazou  <ebotcazou@adacore.com>
4517         * inline.adb (Split_Unconstrained_Function): Also set Is_Inlined
4518         on the procedure created to encapsulate the body.
4519         * sem_ch7.adb: Add with clause for GNAT.HTable.
4520         (Entity_Table_Size): New constant.
4521         (Entity_Hash): New function.
4522         (Subprogram_Table): New instantiation of GNAT.Htable.Simple_HTable.
4523         (Is_Subprogram_Ref): Rename into...
4524         (Scan_Subprogram_Ref): ...this. Record references to subprograms in
4525         the table instead of bailing out on them. Scan the value of constants
4526         if it is not known at compile time.
4527         (Contains_Subprograms_Refs): Rename into...
4528         (Scan_Subprogram_Refs): ...this.
4529         (Has_Referencer): Scan the body of all inlined subprograms. Reset the
4530         Is_Public flag on subprograms if they are not actually referenced.
4531         (Hide_Public_Entities): Beef up comment on the algorithm.
4532         Reset the table of subprograms on entry.
4534 2017-09-06  Yannick Moy  <moy@adacore.com>
4536         * inline.adb: Add comments to Can_Be_Inlined_In_GNATprove_Mode.
4538 2017-09-06  Javier Miranda  <miranda@adacore.com>
4540         * exp_aggr.adb (Component_Not_OK_For_Backend): The C backend
4541         cannot handle a type conversion of an array as an aggregate
4542         component.
4544 2017-09-06  Bob Duff  <duff@adacore.com>
4546         * g-comlin.adb (Try_Help): Remove ".exe" so we
4547         get the same results on windows and unix.
4549 2017-09-06  Justin Squirek  <squirek@adacore.com>
4551         * exp_imgv.adb (Expand_Image_Attribute),
4552         (Expand_Wide_Image_Attribute), (Expand_Wide_Wide_Image_Attribute):
4553         Added case to handle new-style 'Image expansion
4554         (Rewrite_Object_Image): Moved from exp_attr.adb
4555         * exp_attr.adb (Expand_N_Attribute_Reference): Modified Image
4556         attribute cases so that the relevant subprograms in exp_imgv.adb
4557         handle all expansion.
4558         (Rewrite_Object_Reference_Image): Moved to exp_imgv.adb
4559         * sem_attr.adb (Analyze_Attribute): Modified Image attribute
4560         cases to call common function Analyze_Image_Attribute.
4561         (Analyze_Image_Attribute): Created as a common path for all
4562         image attributes (Check_Object_Reference_Image): Removed
4563         * sem_util.ads, sem_util.adb (Is_Image_Applied_To_Object):
4564         Removed and refactored into Is_Object_Image (Is_Object_Image):
4565         Created as a replacement for Is_Image_Applied_To_Object
4567 2017-09-06  Yannick Moy  <moy@adacore.com>
4569         * sem_prag.adb (Analyze_Depends_In_Decl_Part): Add continuation
4570         message for missing input.
4572 2017-09-06  Yannick Moy  <moy@adacore.com>
4574         * inline.adb (Can_Be_Inlined_In_GNATprove_Mode): Prevent inlining
4575         of protected subprograms and entries.
4576         * sem_util.adb, sem_util.ads (Is_Subp_Or_Entry_Inside_Protected):
4577         New function to detect when a subprogram of entry is defined
4578         inside a protected object.
4580 2017-09-06  Bob Duff  <duff@adacore.com>
4582         * sysdep.c (__gnat_has_cap_sys_nice): New function to determine
4583         whether the current process has the CAP_SYS_NICE capability.
4584         * s-taprop-linux.adb (Get_Ceiling_Support): Update this to allow
4585         ceiling priorities if the current process has the CAP_SYS_NICE
4586         capability.
4588 2017-09-06  Bob Duff  <duff@adacore.com>
4590         * a-comlin.ads, a-comlin.adb (Argument): Move the constraint
4591         check back to the body, because SPARK is not yet ready for
4592         "or else raise Constraint_Error".
4594 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4596         * exp_ch6.adb (Expand_Call_Helper): Replace call to null
4597         procedure by a single null statement, after evaluating the
4598         actuals that require it.
4600 2017-09-06  Javier Miranda  <miranda@adacore.com>
4602         * exp_aggr.adb (Backend_Processing_Possible.Component_Check):
4603         Generating C code improve the code that checks the use of nested
4604         aggregates to initialize object declarations.
4606 2017-09-06  Yannick Moy  <moy@adacore.com>
4608         * sem_ch3.adb (Derived_Type_Declaration): Detect
4609         violations of new rule SPARK RM 3.4(1).  Also refactor existing
4610         check to use the new function Find_Partial_View.
4612 2017-09-06  Vincent Celier  <celier@adacore.com>
4614         * gnatcmd.adb: gnat ls -V -P... invokes gprls -V -P...  The code
4615         from the Prj hierarchy has been removed from the GNAT driver.
4617 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4619         * sem_type.adb (Interface_Present_In_Ancestor): Within an
4620         expression function, or within a spec expression (default value,
4621         etc) a reference to an incomplete type is legal: legality of
4622         the operation will be checked when some related entity (type,
4623         object or subprogram) is frozen.
4625 2017-09-06  Gary Dismukes  <dismukes@adacore.com>
4627         * exp_ch5.adb, s-diinio.ads, sem_ch4.adb, s-diflio.ads: Minor spelling
4628         adjustments and a typo fix.
4630 2017-09-06  Yannick Moy  <moy@adacore.com>
4632         * sem_res.adb (Resolve_Call): Do not issue info
4633         message about inlining of calls to functions in assertions,
4634         for functions whose body has not been seen yet.
4636 2017-09-06  Bob Duff  <duff@adacore.com>
4638         * a-comlin.ads, a-comlin.adb (Argument): Simplify the code, now that
4639         we can use modern Ada in this package.
4640         * s-resfil.ads, s-resfil.adb, a-clrefi.ads, a-clrefi.adb:
4641         Move Ada.Command_Line.Response_File to System.Response_File,
4642         and make Ada.Command_Line.Response_File into a rename of
4643         System.Response_File. This is to avoid having gnatbind depend
4644         Ada.Command_Line, which would damage the bootstrap process now
4645         that Ada.Command_Line contains modern Ada (the raise expression).
4646         * gnatbind.adb: Avoid dependence on
4647         Ada.Command_Line. Depend on System.Response_File instead
4648         of Ada.Command_Line.Response_File. Change one call to
4649         Ada.Command_Line.Command_Name to use Fill_Arg.  Change one call
4650         to Ada.Command_Line.Argument_Count to use Arg_Count.
4651         * gcc-interface/Make-lang.in, Makefile.rtl: Take note of the new files.
4653 2017-09-06  Bob Duff  <duff@adacore.com>
4655         * frontend.adb (Frontend): Skip -gnatec=gnat.adc
4656         switch, because we've already read gnat.adc by default.
4658 2017-09-06  Bob Duff  <duff@adacore.com>
4660         * exp_ch5.adb (Get_Default_Iterator): Replace
4661         "Assert(False)" with "return Iter", because if an iterable
4662         type is derived from a noniterable one, then we won't find an
4663         overriding or inherited default iterator.
4665 2017-09-06  Yannick Moy  <moy@adacore.com>
4667         * sem_warn.adb (Warn_On_Suspicious_Index): Improve warning when the
4668         literal index used to access a string is null or negative.
4670 2017-09-06  Hristian Kirtchev  <kirtchev@adacore.com>
4672         * einfo.adb (Status_Flag_Or_Transient_Decl): The attribute is now
4673         allowed on loop parameters.
4674         (Set_Status_Flag_Or_Transient_Decl): The attribute is now allowed
4675         on loop parameters.
4676         (Write_Field15_Name): Update the output for
4677         Status_Flag_Or_Transient_Decl.
4678         * einfo.ads: Attribute Status_Flag_Or_Transient_Decl now applies
4679         to loop parameters. Update the documentation of the attribute
4680         and the E_Loop_Parameter entity.
4681         * exp_ch7.adb (Process_Declarations): Remove the bogus guard
4682         which assumes that cursors can never be controlled.
4683         * exp_util.adb (Requires_Cleanup_Actions): Remove the bogus
4684         guard which assumes that cursors can never be controlled.
4686 2017-09-06  Hristian Kirtchev  <kirtchev@adacore.com>
4688         * exp_attr.adb, sem_util.adb, sem_attr.adb, sem_ch6.adb, sem_ch8.adb,
4689         sem_warn.adb: Minor reformatting.
4691 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4693         * sem_warn.adb (Warn_On_Overlapping_Actuals): Refine previous
4694         fix and preserve older GNAT warning on overlapping actuals that
4695         are not elementary types.
4697 2017-09-06  Justin Squirek  <squirek@adacore.com>
4699         * sem_attr.adb: Comment correction.
4701 2017-09-06  Gary Dismukes  <dismukes@adacore.com>
4703         * sem_util.adb: Minor reformatting.
4705 2017-09-06  Yannick Moy  <moy@adacore.com>
4707         * a-comlin.ads (Argument): Add precondition for analysis.
4709 2017-09-06  Yannick Moy  <moy@adacore.com>
4711         * sem_res.adb (Resolve): Update message for function call as statement.
4713 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4715         * sem_ch6.adb (Check_Returns): Clean up warnings coming from
4716         generated bodies for renamings that are completions, when renamed
4717         procedure is No_Return.
4718         * sem_ch8.adb (Analyze_Subprogram_Renaming): Implement legality
4719         rule in 6.5.1 (7/2): if a renaming is a completion of a subprogram
4720         with No_Return, the renamed entity must be No_Return as well.
4722 2017-09-06  Hristian Kirtchev  <kirtchev@adacore.com>
4724         * exp_ch5.adb, freeze.adb, exp_ch4.adb, exp_ch6.adb, lib-xref.adb:
4725         Minor reformatting.
4727 2017-09-06  Justin Squirek  <squirek@adacore.com>
4729         * exp_attr.adb (Expand_N_Attribute_Reference): Modified Image
4730         attribute cases (Rewrite_Object_Reference_Image): Created to
4731         aid the rewriting of new-style 'Image attributes.
4732         * sem_attr.adb (Analyze_Attribute): Modified Image attribute cases
4733         (Check_Object_Reference_Image): Created to handle verification of
4734         'Image with object-references as prefixes.
4735         * sem_util.ads, sem_util.adb (Is_Image_Applied_To_Object):
4736         Create predicate to identify cases where an 'Image attribute's
4737         prefix applies to an object reference.
4739 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4741         * freeze.adb (Freeze_Entity): Do not generate a freeze
4742         node for a generic unit, even if it includes delayed aspect
4743         specifications. Freeze nodes for generic entities must never
4744         appear in the tree that reaches the back-end of the compiler.
4746 2017-09-06  Yannick Moy  <moy@adacore.com>
4748         * treepr.adb (Print_Entity_Info): Do not print empty Elist.
4750 2017-09-06  Yannick Moy  <moy@adacore.com>
4752         * inline.adb (Can_Be_Inlined_In_GNATprove_Mode): Do not consider calls
4753         to subprograms in other units as possibly inlined.
4755 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4757         * freeze.adb (Freeze_Entity): For a derived type that has no
4758         explicit delayed aspects but may inherit delayed aspects from its
4759         parent type, analyze aspect at freeze point for proper capture
4760         of an inherited aspect.
4762 2017-09-06  Arnaud Charlet  <charlet@adacore.com>
4764         * lib-xref.adb (Get_Through_Renamings): Get through subprogram
4765         renamings; also, avoid repeated calls to Renamed_Object when getting
4766         through object renamings.
4768 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4770         * sem_ch3.adb (Array_Type_Declaration): Handle properly an
4771         array type declaration in a private part, when an index is a
4772         subtype indication of a discrete type with a private partial view.
4774 2017-09-06  Javier Miranda  <miranda@adacore.com>
4776         * exp_ch4.adb (Expand_Modular_Op): Force generating
4777         temporary to improve the generated code.
4779 2017-09-06  Tristan Gingold  <gingold@adacore.com>
4781         * s-fatgen.adb: Minor typo fix in comment.
4783 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4785         * exp_ch5.adb (Make_Field_Assign): If the type
4786         of the right-hand side has stored constraint, use its values
4787         (except for those that are renamings of parent discriminants)
4788         to produce additional assignments for the discriminants of the
4789         left-hand side, which are invisible in the righ-hand side and
4790         not retrievable as selected components.
4792 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4794         * sem_util.adb (Needs_One_Formal): The first formal of such a
4795         function must be a controlling formal, so that Obj.F (X, Y)
4796         can have the interpretation F(Obj)(X, Y).
4797         * sem_util.ads: Clarify documentation.
4799 2017-09-06  Eric Botcazou  <ebotcazou@adacore.com>
4801         * table.ads, table.adb: Restore original implementation.
4802         * namet.h (Names_Ptr): Adjust back.
4803         (Name_Chars_Ptr): Likewise.
4804         * uintp.h (Uints_Ptr): Likewise.
4805         (Udigits_Ptr): Likewise.
4806         * g-table.ads: Remove pragma Compiler_Unit_Warning.
4807         * par_sco.adb: Do not with GNAT.Table and use Table consistently.
4808         * scos.ads: Replace GNAT.Table with Table and adjust instantiations.
4809         * spark_xrefs.ads: Likewise.
4810         * scos.h: Undo latest changes.
4812 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4814         * sem_ch12.adb (Analyze_Subprogram_Instantiation): Propagate
4815         No_Return flag to instance if pragma applies to generic unit. This
4816         must be done explicitly because the pragma does not appear
4817         directly in the generic declaration (unlike the corresponding
4818         aspect specification).
4820 2017-09-06  Eric Botcazou  <ebotcazou@adacore.com>
4822         * sem_ch7.adb (Has_Referencer): Move up and expand comment
4823         explaining the test used to detect inlining.  Use same test
4824         in second occurrence.
4825         (Analyze_Package_Body_Helper): Minor formatting fixes.
4827 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4829         * exp_ch4.adb (Handle_Changed_Representation): For an untagged
4830         derived type with a mixture of renamed and constrained parent
4831         discriminants, the constraint for the target must obtain the
4832         discriminant values from both the operand and from the stored
4833         constraint for it, given that the constrained discriminants are
4834         not visible in the object.
4835         * exp_ch5.adb (Make_Field_Assign): The type of the right-hand
4836         side may be derived from that of the left-hand side (as in the
4837         case of an assignment with a change of representation) so the
4838         discriminant to be used in the retrieval of the value of the
4839         component must be the entity in the type of the right-hand side.
4841 2017-09-06  Hristian Kirtchev  <kirtchev@adacore.com>
4843         * sem_ch3.adb, sem_ch7.adb, sem_util.adb, g-debpoo.adb, sem_ch4.adb,
4844         sem_ch6.adb, sem_ch8.adb: Minor reformatting.
4845         * exp_util.adb (Is_Source_Object): Account for
4846         the cases where the source object may appear as a dereference
4847         or within a type conversion.
4848         * exp_ch6.adb: Fix missing space in error message.
4850 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4852         * sem_prag.adb: Update description of Eliminate.
4854 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4856         * sem_attr.adb (Analyze_Attribute, case 'Loop_Entry): Handle
4857         properly an attribute reference 'Loop_Entry that appears in the
4858         list of indices of an indexed expression, to prevent an infinite
4859         loop in the compiler.
4861 2017-09-06  Bob Duff  <duff@adacore.com>
4863         * s-fileio.adb (Name): Do not raise Use_Error for temp files.
4865 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4867         * sem_ch4.adb (Analyze_Set_Membership):  If an alternative
4868         in a set membership is an overloaded enumeration literal, and
4869         the type of the alternative is resolved from a previous one,
4870         replace the entity of the alternative as well as the type,
4871         to prevent inconsistencies between the entity and the type.
4873 2017-09-06  Eric Botcazou  <ebotcazou@adacore.com>
4875         * ali.ads (ALIs_Record): Add No_Component_Reordering component.
4876         (No_Component_Reordering_Specified): New switch.
4877         * ali.adb (Initialize_ALI): Set No_Component_Reordering_Specified.
4878         (Scan_ALI): Set No_Component_Reordering and deal with NC marker.
4879         * bcheck.adb (Check_Consistent_No_Component_Reordering):
4880         New check.
4881         (Check_Configuration_Consistency): Invoke it.
4882         * debug.adb (d.r): Toggle the effect of the switch.
4883         (d.v): Change to no-op.
4884         * einfo.ads (Has_Complex_Representation):
4885         Restrict to record types.
4886         (No_Reordering): New alias for Flag239.
4887         (OK_To_Reorder_Components): Delete.
4888         (No_Reordering): Declare.
4889         (Set_No_Reordering): Likewise.
4890         (OK_To_Reorder_Components): Delete.
4891         (Set_OK_To_Reorder_Components): Likewise.
4892         * einfo.adb (Has_Complex_Representation): Expect record types.
4893         (No_Reordering): New function.
4894         (OK_To_Reorder_Components): Delete.
4895         (Set_Has_Complex_Representation): Expect base record types.
4896         (Set_No_Reordering): New procedure.
4897         (Set_OK_To_Reorder_Components): Delete.
4898         (Write_Entity_Flags): Adjust to above change.
4899         * fe.h (Debug_Flag_Dot_R): New macro and declaration.
4900         * freeze.adb (Freeze_Record_Type): Remove conditional code setting
4901         OK_To_Reorder_Components on record types with convention Ada.
4902         * lib-writ.adb (Write_ALI): Deal with NC marker.
4903         * opt.ads (No_Component_Reordering): New flag.
4904         (No_Component_Reordering_Config): Likewise.
4905         (Config_Switches_Type): Add No_Component_Reordering component.
4906         * opt.adb (Register_Opt_Config_Switches): Copy
4907         No_Component_Reordering onto No_Component_Reordering_Config.
4908         (Restore_Opt_Config_Switches): Restore No_Component_Reordering.
4909         (Save_Opt_Config_Switches): Save No_Component_Reordering.
4910         (Set_Opt_Config_Switches): Set No_Component_Reordering.
4911         * par-prag.adb (Prag): Deal with Pragma_No_Component_Reordering.
4912         * sem_ch3.adb (Analyze_Private_Extension_Declaration): Also set the
4913         No_Reordering flag from the default.
4914         (Build_Derived_Private_Type): Likewise.
4915         (Build_Derived_Record_Type): Likewise.  Then inherit it
4916         for untagged types and clean up handling of similar flags.
4917         (Record_Type_Declaration): Likewise.
4918         * sem_ch13.adb (Same_Representation): Deal with No_Reordering and
4919         remove redundant test on Is_Tagged_Type.
4920         * sem_prag.adb (Analyze_Pragma): Handle No_Component_Reordering.
4921         (Sig_Flags): Likewise.
4922         * snames.ads-tmpl (Name_No_Component_Reordering): New name.
4923         (Pragma_Id): Add Pragma_No_Component_Reordering value.
4924         * warnsw.adb (Set_GNAT_Mode_Warnings): Enable -gnatw.q as well.
4925         * gcc-interface/decl.c (gnat_to_gnu_entity) <E_Record_Type>:
4926         Copy the layout of the parent type only if the No_Reordering
4927         settings match.
4928         (components_to_record): Reorder record types with
4929         convention Ada by default unless No_Reordering is set or -gnatd.r
4930         is specified and do not warn if No_Reordering is set in GNAT mode.
4932 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4934         * sem_util.ads, sem_util.adb (Check_Previous_Null_Procedure):
4935         new predicate to reject declarations that can be completions,
4936         when there is a visible prior homograph that is a null procedure.
4937         * sem_ch6.adb (Analyze_Null_Procedure): use it.
4938         * sem_ch8.adb (Analyze_Subprogram_Renaming): ditto.
4940 2017-09-06  Thomas Quinot  <quinot@adacore.com>
4942         * s-regpat.adb (Compile.Parse_Literal): Fix handling of literal
4943         run of 253 characters or more.
4945 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4947         * einfo.adb (Designated_Type): Use Is_Incomplete_Type to handle
4948         properly incomplete subtypes that may be created by explicit or
4949         implicit declarations.
4950         (Is_Base_Type): Take E_Incomplete_Subtype into account.
4951         (Subtype_Kind): Ditto.
4952         * sem_ch3.adb (Build_Discriminated_Subtype): Set properly the
4953         Ekind of a subtype of a discriminated incomplete type.
4954         (Fixup_Bad_Constraint): Use Subtype_Kind in all cases, including
4955         incomplete types, to preserve error reporting.
4956         (Process_Incomplete_Dependents): Do not create a subtype
4957         declaration for an incomplete subtype that is created internally.
4958         * sem_ch7.adb (Analyze_Package_Specification): Handle properly
4959         incomplete subtypes that do not require a completion, either
4960         because they are limited views, of they are generic actuals.
4962 2017-09-06  Hristian Kirtchev  <kirtchev@adacore.com>
4964         * checks.adb (Insert_Valid_Check): Remove the
4965         suspicious manipulation of the Do_Range_Check flag as ths is
4966         no linger needed. Suppress validity check when analysing the
4967         validation variable.
4969 2017-09-06  Philippe Gil  <gil@adacore.com>
4971         * g-debpoo.adb: adapt GNAT.Debug_Pools to allow safe thread
4972         GNATCOLL.Memory
4974 2017-09-06  Bob Duff  <duff@adacore.com>
4976         * sem_elim.adb: Minor comment fix.
4978 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
4980         * sem_util.adb (Is_Object_Reference): A function call is an
4981         object reference, and thus attribute references for attributes
4982         that are functions (such as Pred and Succ) as well as predefined
4983         operators are legal in contexts that require an object, such as
4984         the prefix of attribute Img and the Ada2020 version of 'Image.
4986 2017-09-06  Hristian Kirtchev  <kirtchev@adacore.com>
4988         * exp_util.adb, einfo.adb, sem_attr.adb, exp_ch4.adb, gnatls.adb,
4989         exp_ch3.adb, xoscons.adb: Minor reformatting.
4991 2017-09-06  Raphael Amiard  <amiard@adacore.com>
4993         * a-chtgop.ads, a-chtgop.adb: Add versions of First and Next with
4994         Position parameter. If supplied, use it to provide efficient iteration.
4995         * a-cohase.ads, a-cohase.adb, a-cihama.ads, a-cihama.adb,
4996         a-cohama.ads, a-cohama.adb: Add/Use Position to provide efficient
4997         iteration.
4999 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
5001         * exp_util.adb (Build_Allocate_Deallocate_Proc): If the
5002         designated type is class-wide and the expression is an unchecked
5003         conversion, preserve the conversion when checking the tag of the
5004         designated object, to prevent spurious semantic errors when the
5005         expression in the conversion has an untagged type (for example
5006         an address attribute).
5008 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
5010         * sem_res.adb (Resolve_Entry_Call): Check whether a protected
5011         operation is subject to a pragma Eliminate.
5013 2017-09-06  Ed Schonberg  <schonberg@adacore.com>
5015         * sem_elim.ads, exp_ch4.adb: Minor reformatting.
5017 2017-09-06  Eric Botcazou  <ebotcazou@adacore.com>
5019         * fe.h (Eliminate_Error_Msg): Remove.
5021 2017-09-05  Richard Sandiford  <richard.sandiford@linaro.org>
5023         * gcc-interface/utils.c (make_packable_type): Update call to
5024         mode_for_size_tree.
5026 2017-09-05  Richard Sandiford  <richard.sandiford@linaro.org>
5028         * gcc-interface/utils2.c (build_load_modify_store):
5029         Use int_mode_for_size.
5031 2017-09-05  Eric Botcazou  <ebotcazou@adacore.com>
5033         PR ada/62235
5034         * gcc-interface/decl.c (gnat_to_gnu_entity): Skip regular processing
5035         for Itypes that are E_Record_Subtype with a cloned subtype.
5036         <E_Record_Subtype>: Use the DECL of the cloned type directly, if any.
5038 2017-09-05  Eric Botcazou  <ebotcazou@adacore.com>
5040         * gcc-interface/trans.c (convert_with_check): Use a custom base type
5041         if the base type of the expression has a different machine mode.
5042         Rename a couple of parameters and local variable.
5044 2017-09-05  Eric Botcazou  <ebotcazou@adacore.com>
5046         * gcc-interface/trans.c (Attribute_to_gnu) <Attr_Address>: Do not strip
5047         conversions around prefixes that are not references.
5049 2017-09-05  Eric Botcazou  <ebotcazou@adacore.com>
5051         * gcc-interface/utils.c (unchecked_convert): When the result type is a
5052         non-biased integral type with size 0, set the result to 0 directly.
5054 2017-09-05  Eric Botcazou  <ebotcazou@adacore.com>
5056         * gcc-interface/gigi.h (renaming_from_generic_instantiation_p): Turn to
5057         (renaming_from_instantiation_p): ...this.
5058         * gcc-interface/decl.c (gnat_to_gnu_entity): Use inline predicate
5059         instead of explicit tests on kind of entities.  Adjust for renaming.
5060         (gnat_to_gnu_profile_type): Likewise.
5061         (gnat_to_gnu_subprog_type): Likewise.
5062         * gcc-interface/trans.c (Identifier_to_gnu): Likewise.
5063         (Case_Statement_to_gnu): Likewise.
5064         (gnat_to_gnu): Likewise.
5065         (process_freeze_entity): Likewise.
5066         (process_type): Likewise.
5067         (add_stmt_with_node): Adjust for renaming.
5068         * gcc-interface/utils.c (gnat_pushdecl): Adjust for renaming.
5069         (renaming_from_generic_instantiation_p): Rename to...
5070         (renaming_from_instantiation_p): ...this.  Use inline predicate.
5071         (pad_type_hasher::keep_cache_entry): Fold.
5073 2017-09-05  Eric Botcazou  <ebotcazou@adacore.com>
5075         * gcc-interface/trans.c (adjust_for_implicit_deref): New function.
5076         (gnat_to_gnu) <N_Explicit_Dereference>: Translate result type first.
5077         (N_Indexed_Component): Invoke adjust_for_implicit_deref on the prefix.
5078         (N_Slice): Likewise.
5079         (N_Selected_Component): Likewise.  Do not try again to translate it.
5080         (N_Free_Statement): Invoke adjust_for_implicit_deref on the expression.
5082 2017-09-05  Eric Botcazou  <ebotcazou@adacore.com>
5084         * repinfo.ads: Document new treatment of dynamic values.
5085         (TCode): Bump upper bound to 29.
5086         (Dynamic_Val): New constant set to 29.
5087         * repinfo.adb (Print_Expr) <Dynamic_Val>: New case.
5088         (Rep_Value)  <Dynamic_Val>: Likewise.
5089         * repinfo.h (Dynamic_Val): New macro.
5090         * gcc-interface/decl.c (annotate_value): Tidy up and cache result for
5091         DECL_P nodes too.
5092         <INTEGER_CST>: Set TCODE instead of recursing.
5093         <COMPONENT_REF>: Set TCODE instead of calling Create_Node manually.
5094         <VAR_DECL>: New case.
5095         <MULT_EXPR, PLUS_EXPR>: Fold conversions into inner operations.
5096         <BIT_AND_EXPR>: Adjust.
5097         <CALL_EXPR>: Do not fall through.
5099 2017-09-05  Eric Botcazou  <ebotcazou@adacore.com>
5101         * gcc-interface/trans.c (Call_to_gnu): If this is a function call and
5102         there is no target, do not create a temporary for the return value for
5103         an allocator either.
5105 2017-09-05  Eric Botcazou  <ebotcazou@adacore.com>
5107         * gcc-interface/trans.c (pos_to_constructor): Skip conversions to an
5108         unconstrained array type.
5110 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
5111             Alan Hayward  <alan.hayward@arm.com>
5112             David Sherwood  <david.sherwood@arm.com>
5114         * gcc-interface/decl.c (validate_size): Use NARROWEST_INT_MODE
5115         instead of GET_CLASS_NARROWEST_MODE (MODE_INT).
5117 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
5118             Alan Hayward  <alan.hayward@arm.com>
5119             David Sherwood  <david.sherwood@arm.com>
5121         * gcc-interface/decl.c (check_ok_for_atomic_type): Use
5122         is_a <scalar_int_mode>.
5123         * gcc-interface/trans.c (Pragma_to_gnu): Likewise.
5124         * gcc-interface/utils.c (gnat_type_for_mode): Likewise.
5126 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
5127             Alan Hayward  <alan.hayward@arm.com>
5128             David Sherwood  <david.sherwood@arm.com>
5130         * gcc-interface/decl.c (gnat_to_gnu_entity): Use int_mode_for_size
5131         instead of mode_for_size.
5132         (gnat_to_gnu_subprog_type): Likewise.
5133         * gcc-interface/utils.c (make_type_from_size): Likewise.
5135 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
5136             Alan Hayward  <alan.hayward@arm.com>
5137             David Sherwood  <david.sherwood@arm.com>
5139         * gcc-interface/misc.c (fp_prec_to_size): Use opt_scalar_float_mode.
5140         (fp_size_to_prec): Likewise.
5142 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
5143             Alan Hayward  <alan.hayward@arm.com>
5144             David Sherwood  <david.sherwood@arm.com>
5146         * gcc-interface/utils.c (gnat_type_for_mode): Use is_a
5147         <scalar_float_mode> instead of SCALAR_FLOAT_MODE_P.
5149 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
5150             Alan Hayward  <alan.hayward@arm.com>
5151             David Sherwood  <david.sherwood@arm.com>
5153         * gcc-interface/decl.c (validate_size): Update use of
5154         GET_MODE_WIDER_MODE, forcing a wider mode to exist.
5156 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
5157             Alan Hayward  <alan.hayward@arm.com>
5158             David Sherwood  <david.sherwood@arm.com>
5160         * gcc-interface/misc.c (fp_prec_to_size): Use new mode iterators.
5161         (fp_size_to_prec): Likewise.
5163 2017-08-29  Martin Liska  <mliska@suse.cz>
5165         PR other/39851
5166         * gcc-interface/trans.c (Pragma_to_gnu): Set argument to NULL.
5168 2017-08-08  Martin Liska  <mliska@suse.cz>
5170         * gcc-interface/trans.c: Include header files.
5172 2017-07-29  Jakub Jelinek  <jakub@redhat.com>
5174         * gcc-interface/utils.c (gnat_write_global_declarations): Pass false
5175         as new argument to the imported_module_or_decl debug hook.
5177 2017-07-25  Javier Miranda  <miranda@adacore.com>
5179         * checks.adb (Apply_Divide_Checks): Ensure that operands are not
5180         evaluated twice. 
5182 2017-07-19  Jakub Jelinek  <jakub@redhat.com>
5184         * gcc-interface/ada-tree.h (TYPE_OBJECT_RECORD_TYPE,
5185         TYPE_GCC_MIN_VALUE): Use TYPE_MIN_VALUE_RAW instead of TYPE_MINVAL.
5186         (TYPE_GCC_MAX_VALUE): Use TYPE_MAX_VALUE_RAW instead of TYPE_MAXVAL.
5188 2017-07-18  Mike Frysinger  <vapier@chromium.org>
5190         * gcc-interface/Makefile.in (../../gnatmake$(exeext)): Delete $(P).
5191         (../../gnatlink$(exeext)): Likewise.
5193 2017-07-15  John Paul Adrian Glaubitz  <glaubitz@physik.fu-berlin.de>
5195         PR ada/81446
5196         * system-linux-m68k.ads: Add pragma No_Elaboration_Code_All.
5197         (Backend_Overflow_Checks): Set to True.
5199 2017-06-23  Jakub Jelinek  <jakub@redhat.com>
5201         * gcc-interface/trans.c (gnat_to_gnu): Initialize sync to false.
5203 2017-06-21  Pierre-Marie de Rodat  <derodat@adacore.com>
5205         * gcc-interface/ada-tree.h (DECL_FUNCTION_IS_DEF): Update copyright
5206         notice.  New macro.
5207         * gcc-interface/trans.c (Subprogram_Body_to_gnu): Tag the subprogram
5208         as a definition.
5209         (Compilation_Unit_to_gnu): Tag the elaboration procedure as a
5210         definition.
5211         * gcc-interface/decl.c (gnat_to_gnu_entity): Tag declarations of
5212         imported subprograms for the current compilation unit as
5213         definitions.  Disable debug info for references to variables.
5214         * gcc-interface/gigi.h (create_subprog_decl): Update declaration.
5215         * gcc-interface/utils.c (gnat_pushdecl): Add external DECLs that are
5216         not built-in functions to their binding scope.
5217         (create_subprog_decl): Add a DEFINITION parameter.  If it is true, tag
5218         the function as a definition.  Update all callers.
5219         (gnat_write_global_declarations): Emit debug info for imported
5220         functions.  Filter out external variables for which debug info
5221         is disabled.
5223 2017-06-15  Nicolas Boulenguez  <nicolas.boulenguez@free.fr>
5225         PR ada/81105
5226         * gcc-interface/Makefile.in (x86 kfreebsd): Adjust system.ads setting.
5227         (i[3456]86-pc-gnu): Likewise.
5228         (x86_64 kfreebsd): Likewise.
5230 2017-06-12  Eric Botcazou  <ebotcazou@adacore.com>
5232         PR bootstrap/80897
5233         * exp_ch3.adb (Make_Predefined_Primitive_Specs): Use Positive index.
5235 2017-06-12  Eric Botcazou  <ebotcazou@adacore.com>
5237         PR ada/81070
5238         * s-interr-hwint.adb: Reinstate.
5239         * gcc-interface/Makefile.in (RTEMS): Use it again.
5241 2017-06-08  Olivier Hainque  <hainque@adacore.com>
5243         * vx_crtbegin_auto.c: Update year in copyright notice.
5244         * vx_crtbegin.c: Likewise.
5245         * vx_crtbegin.inc: Likewise. 
5246         * vx_crtend.c:  Likewise.
5248 2017-06-07  Sebastian Huber  <sebastian.huber@embedded-brains.de>
5250         * Makefile.in (rtems): Use TLS implementation for s-tpopsp.adb.
5251         * s-tpopsp-rtems.adb: Delete.
5253 2017-06-02  Olivier Hainque  <hainque@adacore.com>
5255         * vx_crtbegin_auto.c: New file.
5256         * vx_crtbegin.c: New file.
5257         * vx_crtbegin.inc: New file.
5258         * vx_crtend.c: New file.
5260 2017-05-25  Jonathan Wakely  <jwakely@redhat.com>
5262         * gcc-interface/utils2.c (compare_elmt_bitpos): Remove redundant
5263         const qualifiers that cause -Wignored-qualifiers warnings.
5265 2017-05-22  Eric Botcazou  <ebotcazou@adacore.com>
5267         * gcc-interface/decl.c (gnat_to_gnu_entity): Skip regular processing
5268         for Itypes that are E_Access_Subtype.
5269         <E_Access_Subtype>: Use the DECL of the base type directly.
5271 2017-05-22  Ed Schonberg  <schonberg@adacore.com>
5272             Eric Botcazou  <ebotcazou@adacore.com>
5274         * sem_ch4.adb (Analyze_Call): In Ada2012 an incomplete type from a
5275         limited view may appear in the profile of a function, and a call to
5276         that function in another unit in which the full view is available must
5277         use this full view to spurious type errors at the point of call.
5278         * inline.adb (Analyze_Inlined_Bodies): Remove restriction on loading
5279         of parent body with a with clause for the main unit.
5280         * gcc-interface/decl.c (defer_limited_with_list): Document new usage.
5281         (gnat_to_gnu_entity) <E_Access_Type>: Handle completed Taft Amendment
5282         types declared in external units like types from limited with clauses.
5283         Adjust final processing of defer_limited_with_list accordingly.
5284         * gcc-interface/trans.c (gnat_to_gnu) < N_Selected_Component>: Try
5285         again to translate the prefix after the field if it is incomplete.
5287 2017-05-22  Eric Botcazou  <ebotcazou@adacore.com>
5289         * gcc-interface/decl.c (gnat_to_gnu_field): Do not enforce strict
5290         alignment for simple volatile fields and remove associated errors.
5292 2017-05-15  Eric Botcazou  <ebotcazou@adacore.com>
5294         * gcc-interface/gigi.h (get_elaboration_procedure): Delete.
5295         * gcc-interface/trans.c (get_elaboration_procedure): Make static.
5297 2017-05-15  Pierre-Marie de Rodat  <derodat@adacore.com>
5299         * gcc-interface/utils.c (can_materialize_object_renaming_p):
5300         Synchronize with GNAT's Exp_Dbug.Debug_Renaming_Declaration:
5301         process Original_Node instead of expanded names.
5303 2017-05-15  Eric Botcazou  <ebotcazou@adacore.com>
5305         * gcc-interface/trans.c (return_value_ok_for_nrv_p): Only apply the
5306         addressability check in the constrained case.
5308 2017-05-15  Eric Botcazou  <ebotcazou@adacore.com>
5310         * gcc-interface/trans.c (Identifier_to_gnu): Also accept incomplete
5311         types not coming from a limited context.
5313 2017-05-15  Eric Botcazou  <ebotcazou@adacore.com>
5315         * gcc-interface/trans.c (Compilation_Unit_to_gnu): Skip subprograms on
5316         the inlined list that are not public.
5317         * gcc-interface/utils.c (create_subprog_decl): Clear TREE_PUBLIC if
5318         there is a pragma Inline_Always on the subprogram.
5320 2017-05-15  Eric Botcazou  <ebotcazou@adacore.com>
5322         * gcc-interface/trans.c (gnat_to_gnu) <N_Aggregate>: Fix formatting.
5323         <N_Allocator>: Use properly typed constants.
5324         (extract_values): Move around.
5325         (pos_to_constructor): Minor tweaks.
5326         (Sloc_to_locus): Fix formatting.
5327         * gcc-interface/utils.c (process_deferred_decl_context): Minor tweaks.
5328         * gcc-interface/gigi.h (MARK_VISITED): Remove blank line.
5329         (Gigi_Equivalent_Type): Adjust head comment.
5330         * gcc-interface/decl.c (Gigi_Equivalent_Type): Likewise.
5332 2017-05-15  Eric Botcazou  <ebotcazou@adacore.com>
5334         * gcc-interface/decl.c (gnat_to_gnu_entity) <E_Record_Type>: When there
5335         is a representation clause on an extension, propagate the alignment of
5336         the parent type only if the platform requires strict alignment.
5338 2017-05-12  Eric Botcazou  <ebotcazou@adacore.com>
5340         * system-linux-arm.ads (Memory_Size): Use Long_Integer'Size
5341         instead of Word_Size.
5343         Revert
5344         2017-03-28  Andreas Schwab  <schwab@suse.de>
5346         PR ada/80117
5347         * system-linux-aarch64-ilp32.ads: New file.
5348         * gcc-interface/Makefile.in (LIBGNAT_TARGET_PAIRS_COMMON): Rename
5349         from LIBGNAT_TARGET_PAIRS.
5350         (LIBGNAT_TARGET_PAIRS_32, LIBGNAT_TARGET_PAIRS_64): Define.
5351         (LIBGNAT_TARGET_PAIRS): Use LIBGNAT_TARGET_PAIRS_COMMON, and
5352         LIBGNAT_TARGET_PAIRS_64 or LIBGNAT_TARGET_PAIRS_32 for -mabi=lp64
5353         or -mabi=ilp32, resp.
5355 2017-05-10  H.J. Lu  <hongjiu.lu@intel.com>
5357         PR ada/80626
5358         * system-linux-x86.ads (Memory_Size): Use Long_Integer'Size
5359         instead of Word_Size.
5361 2017-05-10  Bernd Edlinger  <bernd.edlinger@hotmail.de>
5363         * raise-gcc.c (exception_class_eq): Make ec parameter const.
5365 2017-05-02  Richard Biener  <rguenther@suse.de>
5367         * gcc-interface/misc.c (gnat_post_options): Do not set
5368         -fstrict-overflow.
5370 2017-05-02  Eric Botcazou  <ebotcazou@adacore.com>
5372         * gcc-interface/trans.c (assoc_to_constructor): Make sure
5373         Corresponding_Discriminant is only called on discriminants.
5374         Skip the saving of the result only for them.
5375         (gnat_to_gnu) <N_Selected_Component>: Likewise.
5376         <N_Unchecked_Type_Conversion>: Translate the result type first.
5377         (gigi): Set TREE_NOTHROW on Begin_Handler.
5378         (stmt_list_cannot_raise_p): New predicate.
5379         (Exception_Handler_to_gnu_gcc): Emit a simple final call instead of
5380         a cleanup if the statements of the handler cannot raise.
5381         (process_freeze_entity): Use Is_Record_Type.
5382         (process_type): Likewise.
5384 2017-05-02  Eric Botcazou  <ebotcazou@adacore.com>
5386         * einfo.ads (Corresponding_Record_Component): New alias
5387         for Node21 used for E_Component and E_Discriminant.
5388         * einfo.adb (Corresponding_Record_Component): New function.
5389         (Set_Corresponding_Record_Component): New procedure.
5390         (Write_Field21_Name): Handle Corresponding_Record_Component.
5391         * sem_ch3.adb (Inherit_Component): Set
5392         Corresponding_Record_Component for every component in
5393         the untagged case.  Clear it afterwards for non-girder
5394         discriminants.
5395         * gcc-interface/decl.c (gnat_to_gnu_entity)
5396         <E_Record_Type>: For a derived untagged type with discriminants
5397         and constraints, apply the constraints to the layout of the
5398         parent type to deduce the layout.
5399         (field_is_aliased): Delete.
5400         (components_to_record): Test DECL_ALIASED_P directly.
5401         (annotate_rep): Check that fields are present except for
5402         an extension.
5403         (create_field_decl_from): Add DEBUG_INFO_P
5404         parameter and pass it in recursive and other calls.  Add guard
5405         for the manual CSE on the size.
5406         (is_stored_discriminant): New predicate.
5407         (copy_and_substitute_in_layout): Consider only
5408         stored discriminants and check that original fields are present
5409         in the old type.  Deal with derived types.  Adjust call to
5410         create_variant_part_from.
5412 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5414         * exp_ch6.adb (Expand_Call_Helper): When locating the
5415         accessibility entity created for an access parameter, handle
5416         properly a reference to a formal of an enclosing subprogram. if
5417         the reference appears in an inherited class-wide condition, it
5418         is the rewriting of the reference in the ancestor expression,
5419         but the accessibility entity must be that of the current formal.
5421 2017-05-02  Javier Miranda  <miranda@adacore.com>
5423         * exp_ch4.adb (Expand_Non_Binary_Modular_Op): New subprogram.
5424         (Expand_N_Op_Add, Expand_N_Op_Divide, Expand_N_Op_Minus,
5425         Expand_N_Op_Multiply, Expand_N_Op_Or, Expand_N_Op_Subtract):
5426         Call Expand_Non_Binary_Modular_Op.
5428 2017-05-02  Eric Botcazou  <ebotcazou@adacore.com>
5430         * sem_ch3.adb (Build_Derived_Private_Type): If the parent type
5431         has discriminants, do not override the Stored_Constraint list of
5432         the full view of the derived type with that of the derived type.
5434 2017-05-02  Bob Duff  <duff@adacore.com>
5436         * sem_attr.adb (Attribute_Enum_Rep): Disallow T'Enum_Rep.
5438 2017-05-02  Vasiliy Fofanov  <fofanov@adacore.com>
5440         * s-os_lib.ads: Minor typo fix.
5442 2017-05-02  Vasiliy Fofanov  <fofanov@adacore.com>
5444         * gnatls.adb: Merge and refactor code from Prj.Env and remove
5445         this deprecated dependency.
5447 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5449         * exp_util.ads: minor comment addition.
5451 2017-05-02  Eric Botcazou  <ebotcazou@adacore.com>
5453         * sem_ch3.adb (Build_Derived_Record_Type): Fix a few typos and
5454         pastos in part #3 of the head comment.
5456 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5458         * exp_ch3.adb (Freeze_Type): Do not generate an invariant
5459         procedure body for a local (sub)type declaration within a
5460         predicate function. Invariant checks do not apply to these, and
5461         the expansion of the procedure will happen in the wrong scope,
5462         leading to misplaced freeze nodes.
5464 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5466         * exp_util.adb (Insert_Library_Level_Action): Use proper scope
5467         to analyze generated actions.  If the main unit is a body,
5468         the required scope is that of the corresponding unit declaration.
5470 2017-05-02  Arnaud Charlet  <charlet@adacore.com>
5472         * einfo.adb (Declaration_Node): flip branches of
5473         an IF statement to avoid repeated negations in its condition;
5474         no change in semantics, only to improve readability.
5476 2017-05-02  Arnaud Charlet  <charlet@adacore.com>
5478         * sem_case.adb: Remove extra spaces in parameter declarations.
5480 2017-05-02  Justin Squirek  <squirek@adacore.com>
5482         * usage.adb: Replace space with hyphen ("run time" -> "run-time")
5483         in usage line for new -gnatwE switch.
5485 2017-05-02  Claire Dross  <dross@adacore.com>
5487         * a-cofuve.ads (Remove): Remove unnecessary
5488         conditions in precondition.
5490 2017-05-02  Vasiliy Fofanov  <fofanov@adacore.com>
5492         * a-stream.ads, exp_imgv.adb, sem_ch10.adb,
5493         sem_attr.adb, s-finmas.ads, osint.adb: Minor typo fix.
5495 2017-05-02  Justin Squirek  <squirek@adacore.com>
5497         * sem_ch4.adb (Analyze_Case_Expression): Add check for valid
5498         alternative expression.
5499         * sem_res.adb (Resolve_Case_Expression): Ditto.
5501 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5503         * exp_disp.adb (Set_All_DT_Position, In_Predef_Prim_DT):
5504         Refine predicate for the case where the primitive operation
5505         is a renaming of equality.  An overriding operation that is
5506         a user-defined renaming of predefined equality inherits its
5507         slot from the overridden operation. Otherwise it is treated
5508         as a predefined op and occupies the same predefined slot as
5509         equality. A call to it is transformed into a call to its alias,
5510         which is the predefined equality. A dispatching call thus uses
5511         the proper slot if operation is further inherited and called
5512         with class-wide arguments.
5514 2017-05-02  Justin Squirek  <squirek@adacore.com>
5516         * errout.adb (Set_Msg_Text): Add a case to switch the message
5517         type when the character '[' is detected signifying a warning
5518         about a run-time exception.
5519         * opt.ads Add a new Warning_Mode value for new switch
5520         * switch-b.adb (Scan_Binder_Switches): Add case for the binder
5521         to handle new warning mode
5522         * usage.adb (Usage): Add usage entry for -gnatwE
5523         * warnsw.adb (Set_Warning_Switch): Add case for the new switch
5525 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5527         * sem_prag.adb (Process_Conversion): Reject an intrinsic operator
5528         declaration that operates on some fixed point type.
5530 2017-05-02  Justin Squirek  <squirek@adacore.com>
5532         * a-crbtgo.adb, s-taasde.adb: Remove unused use-type clauses.
5534 2017-05-02  Hristian Kirtchev  <kirtchev@adacore.com>
5536         * sem_ch6.adb (Analyze_Null_Procedure): Revert previous change.
5538 2017-05-02  Justin Squirek  <squirek@adacore.com>
5540         * sem_ch4.adb (Analyze_Case_Expression): Add check for valid
5541         expression (Analyze_If_Expression): Add check for valid condition
5542         * sem_eval.adb (Eval_Case_Expression): Add check for error posted
5543         on case-expression
5544         * sem_res.adb (Resolve_If_Expression): Add check for valid
5545         condition and then-expression.
5547 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5549         * exp_ch3.adb (Build_Initialization_Call): Generate a null
5550         statement if the initialization call is a null procedure, as
5551         can happen with a controlled type with no explicit Initialize
5552         procedure, or an array of such.
5553         * exp_ch7.adb (Process_Object_Declaration): For a type with
5554         controlled components that has a trivial Initialize procedure,
5555         insert declaration for finalization counter after object
5556         declaration itself.
5557         (Make_Deep_Array_Body, Build_Initialize_statements): Do not create
5558         finalization block and attendant declarations if component has
5559         a trivial Initialize procedure.
5560         (Make_Init_Call): Do not generate a call if controlled type has
5561         a trivial Initialize procedure.
5563 2017-05-02  Eric Botcazou  <ebotcazou@adacore.com>
5565         * g-forstr.ads (Data): Move Format component last.
5566         * g-forstr.adb ("+"): Adjust for above change.
5567         * g-rewdat.ads (Buffer): Move Buffer, Current, Pattern and Value last.
5568         * g-sechas.ads (Context): Move Key last.
5569         * g-socket.ads (Service_Entry_Type): Move Aliases last.
5570         * s-fileio.adb (Temp_File_Record): Move Name last.
5571         * s-regexp.adb (Regexp_Value): Move Case_Sensitive last.
5572         * xr_tabls.ads (Project_File): Move Src_Dir and Obj_Dir last.
5574 2017-05-02  Jerome Lambourg  <lambourg@adacore.com>
5576         * bindusg.adb, bindgen.adb, gnatbind.adb, opt.ads: Remove the -nognarl
5577         switch introduced recently. finally not needed.
5579 2017-05-02  Hristian Kirtchev  <kirtchev@adacore.com>
5581         * sem_ch6.adb (Analyze_Null_Procedure): Set the
5582         Corresponding_Body link for a null procedure declaration.
5584 2017-05-02  Eric Botcazou  <ebotcazou@adacore.com>
5586         * atree.h (Flag290): Add missing terminating parenthesis.
5587         * einfo.adb (Is_Class_Wide_Clone): Use Flag290.
5588         (Set_Is_Class_Wide_Clone): Likewise.
5589         * einfo.ads (Is_Class_Wide_Clone): Likewise.
5591 2017-05-02  Gary Dismukes  <dismukes@adacore.com>
5593         * checks.ads (Null_Exclusion_Static_Checks): Add Boolean
5594         parameter Array_Comp to indicate the case of an array object
5595         with null-excluding components.
5596         * checks.adb (Null_Exclusion_Static_Checks):
5597         Call Compile_Time_Constraint_Error instead of
5598         Apply_Compile_Time_Constraint_Error in the component case. Also
5599         call that when Array_Comp is True, with an appropriate warning for
5600         the array component case. Only create an explicit initialization
5601         by null in the case of an object of a null-excluding access type
5602         (and no longer do that in the component case).
5603         * sem_ch3.adb (Check_Component): Add a Boolean parameter
5604         Array_Comp defaulted to False.  Pass Empty for the Comp
5605         actual when calling Null_Exclusion_Static_Checks in the case
5606         where Comp_Decl matches Object_Decl, because we don't have a
5607         component in that case. In the case of an object or component
5608         of an array type, pass True for Array_Comp on the recursive call
5609         to Check_Component.
5611 2017-05-02  Bob Duff  <duff@adacore.com>
5613         * s-taprop-linux.adb (Prio_To_Linux_Prio): New function to correctly
5614         compute the linux priority from the Ada priority. Call this everywhere
5615         required. In particular, the previous version was not doing this
5616         computation when setting the ceiling priority in various places. It
5617         was just converting to C.int, which results in a ceiling that is off
5618         by 1.
5620 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5622         * sem_ch3.adb: Comment predicate inheritance.
5624 2017-05-02  Tristan Gingold  <gingold@adacore.com>
5626         * s-trasym.ads: Add comment.
5628 2017-05-02  Bob Duff  <duff@adacore.com>
5630         * sem_elab.adb, sem_elab.ads: Minor comment fixes.
5631         * sem_ch4.adb: Minor reformatting.
5632         * s-taprop-linux.adb, s-taspri-posix.ads: Code refactoring.
5633         * s-taspri-posix-noaltstack.ads: Minor refactoring.
5634         * sinput.ads: Minor typo fix.
5636 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5638         * exp_ch9.adb (Discriminated_Size): Moved to sem_util.
5639         * sem_util.ads, sem_util.adb (Discriminated_Size): Predicate moved
5640         here from exp_ch9, to recognize objects whose creation requires
5641         dynamic allocation, so that the proper warning can be emitted
5642         when restriction No_Implicit_Heap_Allocation is in effect.
5643         * sem_ch3.adb (Analyze_Object_Declaration): Use Discriminated_Size
5644         to emit proper warning when an object that requires dynamic
5645         allocation is declared.
5647 2017-05-02  Tristan Gingold  <gingold@adacore.com>
5649         * s-trasym.ads, s-trasym.adb (Enable_Cache): New.
5651 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5653         * sem_ch4.adb (Find_Equality_Types, Try_One_Interp): The same relaxed
5654         visibility rules for equality operators that apply within an
5655         instantiation apply within an inlined body.
5656         * sem_type.adb (Add_One_Interp): ditto.
5658 2017-05-02  Hristian Kirtchev  <kirtchev@adacore.com>
5660         * sem_prag.adb (Analyze_Pragma): Forbid pragma Contract_Cases on null
5661         procedures.
5663 2017-05-02  Eric Botcazou  <ebotcazou@adacore.com>
5665         * snames.ads-tmpl
5666         (Name_Assume, Name_Attribute_Definition, Name_Loop_Optimize,
5667         Name_No_Tagged_Streams): Move to regular pragmas.  Add
5668         placeholders for Default_Scalar_Storage_Order, Dispatching_Domain,
5669         and Secondary_Stack_Size.
5670         (Pragma_Id): Move Pragma_Assume,
5671         Pragma_Attribute_Definition, Pragma_Loop_Optimize and
5672         Pragma_No_Tagged_Streams to second part.
5674 2017-05-02  Hristian Kirtchev  <kirtchev@adacore.com>
5676         * exp_attr.adb: Minor reformatting.
5678 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5680         * sem_ch4.adb (Analyze_Selected_Component): Improve error
5681         detection for illegal references to private components or
5682         operations of a protected type in the body of the type.
5684 2017-05-02  Eric Botcazou  <ebotcazou@adacore.com>
5686         * opt.ads: Add missing GNAT markers in comments.
5687         * opt.adb (Set_Opt_Config_Switches): Do not override earlier
5688         settings of Optimize_Alignment at the end.
5690 2017-05-02  Hristian Kirtchev  <kirtchev@adacore.com>
5692         * checks.adb (Apply_Constraint_Check): Do not apply
5693         a discriminant check when the associated type is a constrained
5694         subtype created for an unconstrained nominal type.
5695         * exp_attr.adb: Minor reformatting.
5697 2017-05-02  Bob Duff  <duff@adacore.com>
5699         * sem_ch3.adb (OK_For_Limited_Init_In_05): Handle correctly
5700         the N_Raise_Expression case.
5701         * sem_ch6.adb (Check_Limited_Return): Minor: clarify comment,
5702         and add assertions.
5704 2017-05-02  Yannick Moy  <moy@adacore.com>
5706         * exp_ch4.adb (Expand_N_Op_Ne): Do not bump parenthese level and
5707         optimize length comparison in GNATprove mode.
5708         * exp_spark.adb (Expand_SPARK_Op_Ne): New function to rewrite
5709         operator /= into negation of operator = when needed.
5710         (Expand_SPARK): Call new
5711         function to expand operator /=.
5713 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5715         * exp_fixd.adb (Expand_Divide_Fixed_By_Fixed_Giving_Fixed):
5716         Simplify the expression for a fixed-fixed division to remove
5717         divisions by constants whenever possible, as an optimization
5718         for restricted targets.
5720 2017-05-02  Hristian Kirtchev  <kirtchev@adacore.com>
5722         * checks.adb, sem_ch3.adb, sem_ch6.adb: Minor reformatting.
5724 2017-05-02  Bob Duff  <duff@adacore.com>
5726         * exp_attr.adb (Callable, Identity, Terminated): Use Find_Prim_Op
5727         to find primitive ops, instead of using an Identifier that will
5728         later be looked up. This is necessary because these ops are not
5729         necessarily visible at all places where we need to call them.
5730         * exp_util.ads: Minor comment fix.
5732 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5734         * sem_ch6.adb (Fully_Conformant_Expressions): Two entity
5735         references are fully conformant if they are both expansions
5736         of the discriminant of a protected type, within one of the
5737         protected operations. One occurrence may be expanded into a
5738         constant declaration while the other is an input parameter to
5739         the corresponding generated subprogram.
5741 2017-05-02  Justin Squirek  <squirek@adacore.com>
5743         * sem_ch3.adb (Check_For_Null_Excluding_Components): Created for
5744         recursivly searching composite-types for null-excluding access
5745         types and verifying them.
5746         (Analyze_Object_Declaration): Add a
5747         call to Check_Null_Excluding_Components for static verification
5748         of non-initialized objects.
5749         * checks.adb, checks.ads (Null_Exclusion_Static_Checks): Added
5750         a parameter for a composite-type's component and an extra case
5751         for printing component information.
5753 2017-05-02  Yannick Moy  <moy@adacore.com>
5755         * sem_ch10.adb (Analyze_Subunit): Take
5756         configuration pragma into account when restoring appropriate
5757         pragma for analysis of subunit.
5759 2017-05-02  Justin Squirek  <squirek@adacore.com>
5761         * s-tasren.adb, s-tasini.adb, s-taprop-linux.adb,
5762         s-mudido-affinity.adb,, a-exetim-posix.adb, a-direio.adb,
5763         g-socket.adb, s-taenca.adb, s-fileio.adb: Remove unused use-type
5764         clauses from the runtime.
5766 2017-05-02  Eric Botcazou  <ebotcazou@adacore.com>
5768         * freeze.adb (Check_Component_Storage_Order): Do not treat bit-packed
5769         array components specially.
5771 2017-05-02  Ed Schonberg  <schonberg@adacore.com>
5773         * sem_ch8.adb (Premature_Usage): If the premature usage of
5774         an entity is as the expression in its own object decaration,
5775         rewrite the reference as Any_Id to prevent cascaded errors or
5776         compiler loops when such an entity is used in an address clause.
5778 2017-05-01  Eric Botcazou  <ebotcazou@adacore.com>
5780         * gcc-interface/decl.c (components_to_record): Add missing guard.
5782 2017-05-01  Eric Botcazou  <ebotcazou@adacore.com>
5784         * gcc-interface/decl.c (components_to_record): Add more comments.
5785         Put back pending fields onto the regular list if the misalignment
5786         happens to cancel itself.
5788 2017-04-28  Ed Schonberg  <schonberg@adacore.com>
5790         * sem_ch4.adb (Complete_Object_Operation): When rewriting the
5791         controlling actual in a prefixed call, preserve the original node
5792         information if the prefix itself has been rewritten, for ASIS use.
5794 2017-04-28  Hristian Kirtchev  <kirtchev@adacore.com>
5796         * exp_ch6.adb (Insert_Post_Call_Actions):
5797         Code clean up. Insert the post-call actions after an enclosing
5798         procedure call when N denotes a function call and appears as an
5799         actual parameter in the procedure call.
5801 2017-04-28  Eric Botcazou  <ebotcazou@adacore.com>
5803         * freeze.adb (Check_Component_Storage_Order): If there is a clause
5804         for the component, also reject the attribute if the component
5805         doesn't end on a byte boundary and its scalar storage order is
5806         different from that of the enclosing record type.
5808 2017-04-28  Javier Miranda  <miranda@adacore.com>
5810         * atree.ads (Info_Messages): Removed.
5811         (Warning_Info_Messages): New counter.
5812         (Report_Info_Messages): New counter.
5813         * err_vars.ads Update documentation.
5814         * errout.adb (Delete_Warning_And_Continuations): Update
5815         Info_Message occurrences.
5816         (Error_Msg_Internal): Update Info_Message occurrences.
5817         (Delete_Warning): Update Info_Message occurrences.
5818         (Write_Error_Summary): Update Info_Message occurrences.
5819         (Output_Messages): Update Info_Message occurrences.
5820         (To_Be_Removed): Update Info_Message occurrences.
5821         (Reset_Warnings): Update Info_Message occurrences.
5822         * errutil.adb (Error_Msg): Update Info_Message occurrences.
5823         (Finalize): Update Info_Message occurrences.
5824         (Initialize): Update Info_Message occurrences.
5825         * erroutc.adb (Delete_Msg): Update Info_Message occurrences.
5826         (Compilation_Errors): Update Info_Message_Occurences.
5828 2017-04-28  Eric Botcazou  <ebotcazou@adacore.com>
5830         * exp_ch3.adb (Build_Init_Statements): Likewise on Nam.
5831         * freeze.adb (Check_Component_Storage_Order): And on Comp_Byte_Aligned.
5832         * sem_aggr.adb (Resolve_Record_Aggregate): Initialize Box_Node.
5833         * sem_attr.adb (Loop_Entry): Initialize Encl_Loop.
5834         * sem_ch12.adb (Build_Operator_Wrapper): Add pragma Warnings on Expr.
5835         * sem_ch13.adb (Validate_Address_Clauses): Initialize Y_Alignment and
5836         Y_Size.
5837         * sem_eval.adb (Why_Not_Static): Initialize Typ.
5838         * sem_prag.adb (Analyze_Pragma): Add pragma Warnings on Str.
5840 2017-04-28  Bob Duff  <duff@adacore.com>
5842         * sem_util.ads, sem_util.adb (Might_Raise): New function
5843         that replaces Is_Exception_Safe, but has the opposite
5844         sense. Is_Exception_Safe was missing various cases -- calls inside
5845         a pragma Debug, calls inside an 'if' or assignment statement,
5846         etc. Might_Raise now walks the entire subtree looking for things
5847         that can raise.
5848         * exp_ch9.adb (Is_Exception_Safe): Remove.
5849         (Build_Protected_Subprogram_Body): Replace call to
5850         Is_Exception_Safe with "not Might_Raise". Misc cleanup (use
5851         constants where possible).
5852         * exp_ch7.adb: Rename Is_Protected_Body -->
5853         Is_Protected_Subp_Body. A protected_body is something different
5854         in the grammar.
5856 2017-04-28  Eric Botcazou  <ebotcazou@adacore.com>
5858         * inline.adb (Expand_Inlined_Call): Initialize Targ1 variable.
5859         * par-ch3.adb (P_Component_Items): Initialize Decl_Node variable.
5860         (P_Discrete_Choice_List): Initialize Expr_Node variable.
5861         * par-ch9.adb (P_Task): Initialize Aspect_Sloc variable.
5862         (P_Protected): Likewise.
5863         * sem_case.adb (Check_Duplicates):
5864         Add pragma Warnings on variable.
5865         * sem_ch12.adb (Preanalyze_Actuals): Initialize Vis variable.
5866         * sem_ch4.adb (List_Operand_Interps):  Add pragma Warnings on variable.
5867         * sem_ch5.adb (Analyze_Assignment): Initialize Save_Full_Analysis.
5868         (Analyze_Exit_Statement): Initialize Scope_Id variable.
5869         (Analyze_Iterator_Specification): Initialize Bas variable.
5870         * sem_ch9.adb (Allows_Lock_Free_Implementation): Initialize
5871         Error_Count (Satisfies_Lock_Free_Requirements): Likewise.
5872         (Analyze_Accept_Statement): Initialize Task_Nam.
5874 2017-04-28  Hristian Kirtchev  <kirtchev@adacore.com>
5876         * checks.adb (Install_Primitive_Elaboration_Check):
5877         Do not generate an elaboration check if all checks have been
5878         suppressed.
5880 2017-04-28  Ed Schonberg  <schonberg@adacore.com>
5882         * sem_ch13.adb (Analyze_Aspect_Specifications, case
5883         Interrupt_Handler and Attach_Handler): Generate reference
5884         to protected operation to prevent spurious warnings about
5885         unreferenced entities. Previous scheme failed with style checks
5886         enabled.
5888 2017-04-28  Ed Schonberg  <schonberg@adacore.com>
5890         * sem_prag.adb (Relocate_Pragmas_To_Body): A pragma Warnings
5891         that follows an expression function must not be relocated to
5892         the generated body, because it applies to the code that follows.
5894 2017-04-28  Gary Dismukes  <dismukes@adacore.com>
5896         * sem_util.adb (Is_Dependent_Component_Of_Mutable_Object): Test
5897         Relaxed_RM_Semantics to avoid having CodePeer issue errors on
5898         code that might violate the more stringent checking for 'Access
5899         introduced in Ada 2005.
5901 2017-04-28  Arnaud Charlet  <charlet@adacore.com>
5903         * a-cforse.adb: minor style fix in comment.
5905 2017-04-28  Eric Botcazou  <ebotcazou@adacore.com>
5907         * exp_ch9.adb (Build_Lock_Free_Unprotected_Subprogram_Body): Also
5908         initialize Block_Decls variable.
5909         (Expand_Entry_Barrier): Add pragma Warnings on Func_Body variable.
5910         (Build_Dispatching_Requeue): Add pragma Warnings on Op variable.
5911         * exp_disp.adb (Expand_Interface_Actuals): Initialize
5912         Formal_DDT and Actual_DDT variables.
5913         (Expand_Interface_Thunk): Initialize Iface_Formal.
5914         (Make_DT): Initialize Size_Comp.
5915         (Make_Select_Specific_Data_Table): Initialize Decls.
5916         * exp_dist.adb (Add_RACW_Primitive_Declarations_And_Bodies):
5917         Also initialize more RPC_Receiver_* variables.
5918         (Build_To_Any_Function): Initialize Cstr_Formal.
5919         * exp_prag.adb (Expand_Pragma_Contract_Cases): Initialize Msg_Str.
5921 2017-04-28  Ed Schonberg  <schonberg@adacore.com>
5923         * sem_ch6.adb (Freeze_Type_Refs): For an interface conversion
5924         node between access types, freeze the designated type as well,
5925         so that dispatch table pointers are created in the proper scope,
5926         and not in the constructed body of the expression function.
5928 2017-04-28  Bob Duff  <duff@adacore.com>
5930         * alloc.ads (Nodes_Initial): Go back to previous value. The large
5931         value makes large compilations faster, but small compilations slower.
5933 2017-04-28  Arnaud Charlet  <charlet@adacore.com>
5935         * sem_util.adb: minor typos in Is_Child_Or_Sibling.
5937 2017-04-28  Hristian Kirtchev  <kirtchev@adacore.com>
5939         * erroutc.adb (Compilation_Errors): Do not consider info messages
5940         as suitable warnings when warnings must be treated as errors.
5941         * sem_ch7.adb (Analyze_Package_Specification): Do not consider
5942         internally-generated packages when outputting completion
5943         information.
5944         * errout.adb (Output_Messages): Do not consider info messages as
5945         suitable warnings when warnings must be treated as errors.
5946         * errutil.adb (Finalize): Do not consider info messages as
5947         suitable warnings when warnings must be treated as errors.
5949 2017-04-28  Eric Botcazou  <ebotcazou@adacore.com>
5951         * warnsw.ads: Minor fix for incorrect wording in comment.
5953 2017-04-28  Ed Schonberg  <schonberg@adacore.com>
5955         * sem_res.adb (In_Instance_Code): New predicate in
5956         Valid_Conversion, to determine whether a type conversion appears
5957         as (or within) an actual for a formal object.  Type conversions
5958         in instances are not rechecked in Valid_Conversion because
5959         visibility changes between generic location andi instance may
5960         lead to spurious errors, but conversions within an actual must be
5961         fully checked, and they are not fully resolved when pre-analyzing
5962         the actuals.
5964 2017-04-28  Hristian Kirtchev  <kirtchev@adacore.com>
5966         * exp_ch6.adb (Expand_N_Extended_Return_Statement): Use
5967         New_Copy_Tree instead of Relocate_Node as any subsequent copies
5968         of the relocated node will have mangled Parent pointers.
5969         * sem_util.adb (Build_NCT_Hash_Tables): Reset both hash
5970         tables used in conjunction with entity and itype replication.
5971         (Visit_Entity): Rewrite the restriction on which entities
5972         require duplication.  The restriction now includes all types.
5974 2017-04-28  Hristian Kirtchev  <kirtchev@adacore.com>
5976         * a-cofuse.ads, a-cfdlli.ads, a-cfhase.adb, a-cfhase.ads, a-cfinve.adb,
5977         a-cfinve.ads, a-cforma.adb, a-cforma.ads, a-cofuma.adb, a-cofuma.ads,
5978         a-cfhama.adb, a-cfhama.ads, a-cforse.adb: Minor reformatting and code
5979         cleanups.
5981 2017-04-28  Hristian Kirtchev  <kirtchev@adacore.com>
5983         * exp_util.adb, g-dyntab.adb, par-ch4.adb, sem_util.adb, sem_attr.adb,
5984         gnat1drv.adb, exp_disp.adb, namet.adb, alloc.ads: Minor reformatting.
5986 2017-04-28  Gary Dismukes  <dismukes@adacore.com>
5988         * exp_util.adb: Minor reformatting.
5990 2017-04-28  Ed Schonberg  <schonberg@adacore.com>
5992         * sem_ch4.adb: Fix copy/pasto.
5994 2017-04-27  Tristan Gingold  <gingold@adacore.com>
5996         * gcc-interface/Make-lang.in: Define EH_MECHANISM while building
5997         raise-gcc.c. Fix include search path for raise-gcc.c
5999 2017-04-27  Eric Botcazou  <ebotcazou@adacore.com>
6001         * fe.h (Warn_On_Questionable_Layout): Declare.
6002         * warnsw.ads (Warn_On_Record_Holes): Move down.
6003         (Warn_On_Questionable_Layout): New boolean variable.
6004         (Warning_Record): Add Warn_On_Questionable_Layout field.
6005         * warnsw.adb (All_Warnings): Set Warn_On_Questionable_Layout.
6006         (Restore_Warnings): Likewise.
6007         (Save_Warnings): Likewise.
6008         (Set_Dot_Warning_Switch): Handle 'q' and 'Q' letters.
6009         * gcc-interface/decl.c (gnat_to_gnu_entity): Adjust call to
6010         components_to_record.
6011         (gnu_field_to_gnat): New function.
6012         (warn_on_field_placement): Likewise.
6013         (components_to_record): Add GNAT_RECORD_TYPE and remove REORDER
6014         parameters.  Rename local variables and adjust recursive call.
6015         Rework final scan of the field list and implement warnings on the
6016         problematic placement of specific sorts of fields.
6018 2017-04-27  Bob Duff  <duff@adacore.com>
6020         * errout.adb, exp_aggr.adb, exp_attr.adb, exp_code.adb, fname.adb,
6021         * fname.ads, freeze.adb, inline.adb, lib.adb, lib.ads, lib-list.adb,
6022         * lib-load.adb, lib-writ.adb, par.adb, restrict.adb, rtsfind.adb,
6023         * sem.adb, sem_cat.adb, sem_ch10.adb, sem_ch12.adb, sem_ch3.adb,
6024         * sem_ch4.adb, sem_ch6.adb, sem_ch8.adb, sem_ch9.adb, sem_elab.adb,
6025         * sem_intr.adb, sem_res.adb, sem_util.adb, sem_warn.adb, sprint.adb:
6026         For efficiency, cache results of Is_Internal_File_Name and
6027         Is_Predefined_File_Name in the Units table. This avoids a lot
6028         of repeated text processing.
6030 2017-04-27  Emmanuel Briot  <briot@adacore.com>
6032         * g-comlin.adb (Sort_Sections): remove useless test.
6034 2017-04-27  Claire Dross  <dross@adacore.com>
6036         * a-cfhase.adb, a-cfhase.ads (=): Generic parameter removed to
6037         allow the use of regular equality over elements in contracts.
6038         (Formal_Model): Ghost package containing model functions that are
6039         used in subprogram contracts.
6040         (Current_To_Last): Removed, model functions should be used instead.
6041         (First_To_Previous): Removed, model functions should be used instead.
6042         (Strict_Equal): Removed, model functions should be used instead.
6043         (No_Overlap): Removed, model functions should be used instead.
6044         (Equivalent_Keys): Functions over cursors are removed. They were
6045         awkward with explicit container parameters.
6046         * a-cforse.adb, a-cforse.ads (=): Generic parameter removed to
6047         allow the use of regular equality over elements in contracts.
6048         (Formal_Model): Ghost package containing model functions that
6049         are used in subprogram contracts.
6050         (Current_To_Last): Removed, model functions should be used instead.
6051         (First_To_Previous): Removed, model functions should be used instead.
6052         (Strict_Equal): Removed, model functions should be used instead.
6053         (No_Overlap): Removed, model functions should be used instead.
6055 2017-04-27  Yannick Moy  <moy@adacore.com>
6057         * gnat1drv.adb: Code cleanup.
6059 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6061         * exp_util.adb (Replace_Entity): The prefix of a 'Result
6062         attribute reference in a post- condition is the subprogram to
6063         which the condition applies. If the condition is inherited
6064         by a type extension, the prefix becomes a reference to the
6065         inherited operation, but there is no need to create a wrapper
6066         for this operation, because 'Result is expanded independently
6067         when elaborating the postconditions.
6069 2017-04-27  Bob Duff  <duff@adacore.com>
6071         * sinput.adb: Minor code cleanup.
6072         * namet.adb (Append): Create faster versions of
6073         Append(String) and Append(Name_Id) by using slice assignment
6074         instead of loops.
6075         * sem_util.adb (In_Instance): Speed this up by removing
6076         unnecessary tests; Is_Generic_Instance is defined for all
6077         entities.
6078         * sem_util.ads, sem_util.adb (In_Parameter_Specification):
6079         Remove unused function.
6080         * alloc.ads (Nodes_Initial): Use a much larger value, because
6081         the compiler was spending a lot of time copying the nodes table
6082         when it grows. This number was chosen in 1996, so is rather out
6083         of date with current memory sizes. Anyway, it's virtual memory.
6084         Get rid of Orig_Nodes_...; use Node_... instead.
6085         * atree.adb (Lock): Do not release the Nodes tables; it's a
6086         waste of time.
6087         Orig_Nodes_ ==> Nodes_
6088         * nlists.adb: Orig_Nodes_ ==> Nodes_
6089         * g-table.adb: Remove unused "with" clause.
6090         * g-table.ads, table.ads: Remove Big_Table_Type, which should
6091         not be used by clients.
6092         * g-dyntab.adb (Last_Allocated): New function
6093         to encapsulate T.P.Last_Allocated, which I'm thinking of changing.
6095 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6097         * sem_eval.adb (Subtypes_Statically_Compatible): Remove duplicated
6098         check.
6099         (Subtypes_Statically_Match): Remove duplicate check.
6100         * sem_prag.adb (Check_Arg_Is_External_Name): Remove duplicate check.
6102 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6104         * exp_aggr.adb (Replace_Type): Remove the special processing
6105         for selected components.
6106         * exp_attr.adb (Expand_N_Attribute_Reference): Merge the
6107         processing for attributes Fixed_Value and Integer_Value.
6108         * exp_util.adb (Side_Effect_Free): Merge the processing for
6109         qualified expressions, type conversions, and unchecked type
6110         conversions.
6111         * g-comlin.adb (Is_In_Config): Merge the processing for No_Space
6112         and Optional.
6113         * par-ch3.adb (P_Declarative_Items): Merge the processing for
6114         tokens function, not, overriding, and procedure.
6115         * sem_ch6.adb (Fully_Conformant_Expressions): Merge the processing
6116         for qualified expressions, type conversions, and unchecked
6117         type conversions.
6118         * sem_util.adb (Compile_Time_Constraint_Error): Merge the
6119         processing for Ada 83 and instances.
6120         (Object_Access_Level): Merge the processing for indexed components
6121         and selected components.
6122         * uname.adb (Add_Node_Name): Merge the processing for stubs.
6124 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6126         * checks.adb (Install_Primitive_Elaboration_Check):
6127         Do not generate the check when restriction No_Elaboration_Code
6128         is in effect.
6130 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6132         * exp_disp.adb (Build_Class_Wide_Check): New subsidiary
6133         of Expand_Dispatching_Call. If the denoted subprogram has a
6134         class-wide precondition, this is the only precondition that
6135         applies to the call, rather that the class-wide preconditions
6136         that may apply to the body that is executed. (This is specified
6137         in AI12-0195).
6139 2017-04-27  Yannick Moy  <moy@adacore.com>
6141         * gnat1drv.adb (Adjust_Global_Switches): Issue
6142         a warning in GNATprove mode if the runtime library does not
6143         support IEEE-754 floats.
6145 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6147         * sem_prag.adb (Inherit_Class_Wide_Pre): If the parent operation
6148         is itself inherited it does not carry any contract information,
6149         so examine its parent operation which is its Alias.
6151 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6153         * sem_attr.adb (Analyze_Attribute, case 'Image): In Ada2012 the
6154         prefix can be an object reference in which case Obj'Image (X)
6155         can only be interpreted as an indexing of the parameterless
6156         version of the attribute.
6157         * par-ch4.adb (P_Name): An attribute reference can be the prefix of
6158         an indexing or a slice operation if the attribute does not require
6159         parameters. In Ada2012 'Image also belongs in this category,
6160         and A'Image (lo .. hi) is legal and must be parsed as a slice.
6162 2017-04-27  Yannick Moy  <moy@adacore.com>
6164         * exp_ch4.adb: Minor reformatting.
6165         * gnat1drv.adb (Adjust_Global_Switches): When in GNATprove mode,
6166         disable the CodePeer and C generation modes. Similar to the
6167         opposite actions done in CodePeer mode.
6169 2017-04-27  Yannick Moy  <moy@adacore.com>
6171         * sem_res.adb: Remove duplicate code.
6172         * sem_attr.adb: Delete duplicate code.
6174 2017-04-27  Bob Duff  <duff@adacore.com>
6176         * g-dyntab.adb: Reduce the amount of copying in
6177         Release. No need to copy items past Last.
6179 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6181         * checks.adb Add with and use clauses for Sem_Disp.
6182         (Install_Primitive_Elaboration_Check): New routine.
6183         * checks.ads (Install_Primitive_Elaboration_Check): New routine.
6184         * exp_attr.adb (Expand_N_Attribute_Reference): Clean up the
6185         processing of 'Elaborated.
6186         * exp_ch6.adb (Expand_N_Subprogram_Body): Install a primitive
6187         elaboration check.
6189 2017-04-27  Bob Duff  <duff@adacore.com>
6191         * g-dyntab.ads, g-dyntab.adb, g-table.ads: Remove incorrect assertion.
6192         If the table grows and then shrinks back to empty, we won't necessarily
6193         point back to the empty array. Code cleanups.
6194         * sinput.ads: Add 'Base to Size clause to match the declared
6195         component subtypes.
6197 2017-04-27  Claire Dross  <dross@adacore.com>
6199         * a-cforma.adb, a-cforma.ads (=): Generic parameter removed to
6200         allow the use of regular equality over elements in contracts.
6201         (Formal_Model): Ghost package containing model functions that
6202         are used in subprogram contracts.
6203         (Current_To_Last): Removed, model functions should be used instead.
6204         (First_To_Previous): Removed, model functions should be used instead.
6205         (Strict_Equal): Removed, model functions should be used instead.
6206         (No_Overlap): Removed, model functions should be used instead.
6207         * a-cofuma.adb, a-cofuma.ads (Enable_Handling_Of_Equivalence)
6208         Boolean generic parameter to disable contracts for equivalence
6209         between keys.
6210         (Witness): Create a witness of a key that is used for handling of
6211         equivalence between keys.
6212         (Has_Witness): Check whether a witness is contained in a map.
6213         (W_Get): Get the element associated to a witness.
6214         (Lift_Equivalent_Keys): Removed, equivalence between keys is handled
6215         directly.
6216         * a-cofuse.adb, a-cofuse.ads (Enable_Handling_Of_Equivalence)
6217         Boolean generic parameter to disable contracts for equivalence
6218         between keys.
6219         * a-cfhama.adb, a-cfhama.ads (Formal_Model.P) Disable handling
6220         of equivalence on functional maps.
6221         * a-cfdlli.adb, a-cfdlli.ads (Formal_Model.P) Disable handling
6222         of equivalence on functional maps.
6224 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6226         * exp_ch9.adb (Expand_Entry_Barrier): Code
6227         cleanup. Do not perform the optimization which removes the
6228         declarations of the discriminant and component renamings when
6229         validity checks on operands and attributes are in effect.
6231 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6233         * exp_spark.adb, exp_util.adb, sem_ch7.adb, g-dyntab.adb, g-dyntab.ads,
6234         freeze.adb, a-cfinve.ads, a-cofuma.adb, a-cofuma.ads, a-cfhama.adb,
6235         a-cfhama.ads, a-cofove.ads: Minor reformatting.
6237 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6239         * g-debpoo.adb (Dump_Gnatmem): Protect against a possible null
6240         pointer dereference.
6241         * g-spipat.adb (Dump): Code clean up. Protect against a possible
6242         null pointer dereference.
6244 2017-04-27  Bob Duff  <duff@adacore.com>
6246         * g-dyntab.ads, g-dyntab.adb: Default for Table_Low_Bound.
6247         Rename Empty --> Empty_Table_Ptr, and don't duplicate code for it.
6248         Free renames Init, since they do the same thing.
6249         * g-table.ads: Default for Table_Low_Bound.
6250         * table.ads: Default for Table_Low_Bound, Table_Initial, and
6251         Table_Increment.
6253 2017-04-27  Bob Duff  <duff@adacore.com>
6255         * g-dyntab.ads, g-dyntab.adb: Add assertions to subprograms that
6256         can reallocate.
6257         * atree.adb, elists.adb, fname-uf.adb, ghost.adb, inline.adb,
6258         * lib.adb, namet.adb, nlists.adb, sem.adb, sinput.adb, stringt.adb:
6259         Reorder code so that above assertions do not fail.
6260         * table.ads: Remove obsolete comment on Locked.
6262 2017-04-27  Claire Dross  <dross@adacore.com>
6264         * a-cfdlli.ads: Code cleanup.
6266 2017-04-27  Yannick Moy  <moy@adacore.com>
6268         * exp_spark.adb (Expand_SPARK_Freeze_Type): Build a DIC procedure
6269         when needed for proof.  (Expand_SPARK): Call the new procedure.
6270         * exp_util.ads Fix typo.
6272 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
6274         * a-cofuma.ads, a-cfhama.ads: Minor reformatting, grammar, and typo
6275         fixes.
6277 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6279         * sem_elab.adb Add new type Visited_Element
6280         and update the contents of table Elab_Visited.  Various code clean up.
6281         (Check_Elab_Call): Determine whether a prior call to
6282         the same subprogram was already examined within the same context.
6283         (Check_Internal_Call_Continue): Register the subprogram being
6284         called as examined within a particular context. Do not suppress
6285         elaboration warnings.
6287 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
6289         * xoscons.adb, osint.ads: Minor reformatting.
6291 2017-04-27  Bob Duff  <duff@adacore.com>
6293         * g-dyntab.ads, g-dyntab.adb: Misc cleanup. Rename
6294         Table_Count_Type --> Table_Last_Type, because the name
6295         was confusing (a "count" usually starts at zero).  Add
6296         functionality supported or needed by other tables packages
6297         (Move, Release_Threshold).
6298         * g-table.ads, g-table.adb: This is now just a thin wrapper
6299         around g-dyntab.ads/g-dyntab.adb.  Add functionality supported
6300         or needed by other tables packages (Save, Restore).
6301         * table.ads, table.adb: This is now just a thin wrapper around
6302         * g-table.ads/g-table.adb.
6303         * namet.h, scos.h, uintp.h: These files are reaching into the
6304         private data of some instances of g-table, whose names changed,
6305         so the above change requires some adjustment here. It now uses
6306         public interfaces.
6308 2017-04-27  Bob Duff  <duff@adacore.com>
6310         * namet.adb, namet.ads: Minor: remove unused procedures.
6312 2017-04-27  Eric Botcazou  <ebotcazou@adacore.com>
6314         * checks.adb (Apply_Scalar_Range_Check): Initialize Ok variable too.
6315         (Minimize_Eliminate_Overflows): Initialize Llo and Lhi.
6316         Add pragma Warnings on Rtype variable in nested block.  *
6317         * exp_ch3.adb (Build_Init_Statements): Initialize VAR_LOC.
6318         * exp_ch4.adb (Expand_Concatenate): Initialize 3 variables.
6319         (Size_In_Storage_Elements): Add pragma Warnings on Res variable.
6320         * exp_ch7.adb (Build_Adjust_Statements): Initialize Bod_Stmts.
6321         (Process_Component_List_For_Finalize): Initialize Counter_Id.
6322         (Build_Finalize_Statements): Initialize Bod_Stmts.
6323         * exp_disp.adb (Expand_Dispatching_Call): Initialize SCIL_Node.
6325 2017-04-27  Claire Dross  <dross@adacore.com>
6327         * a-cfhama.adb, a-cfhamai.ads (=): Generic parameter removed to
6328         allow the use of regular equality over elements in contracts.
6329         (Formal_Model): Ghost package containing model functions that are
6330         used in subprogram contracts.
6331         (Current_To_Last): Removed, model
6332         functions should be used instead.
6333         (First_To_Previous): Removed, model functions should be used instead.
6334         (Strict_Equal): Removed, model functions should be used instead.
6335         (No_Overlap): Removed, model functions should be used instead.
6336         (Equivalent_Keys): Functions over cursors are removed. They were
6337         awkward with explicit container parameters.
6338         * a-cofuma.adb, a-cofuma.ads (Lift_Equivalent_Keys): New lemma
6339         (proof only) procedure to help GNATprove when equivalence over
6340         keys is not equality.
6342 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6344         * exp_util.adb, a-cfdlli.adb, a-cfdlli.ads, exp_ch9.adb, g-dyntab.adb,
6345         sem_dim.adb, a-cfinve.adb, a-cfinve.ads, a-cofove.adb, a-cofove.ads:
6346         Minor reformatting and code cleanups.
6348 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6350         * freeze.adb (Build_Inherited_Condition_Pragmas): New procedure,
6351         subsidiary of Check_Inherited_Conditions, to build pragmas for an
6352         operation whose ancestor has classwide pre/postconditions. This
6353         is used both to check the legality of the inheritance in Ada
6354         and in SPARK, and to determine whether a wrapper is needed for
6355         an inherited operation.
6356         * exp_util.adb (Build_Class_Wide_Expression, Replace_Entity):
6357         Improve placement of error message for inherited classwide
6358         conditions that become illegal on type derivation.
6360 2017-04-27  Yannick Moy  <moy@adacore.com>
6362         * sem_ch12.adb (Analyze_Generic_Package_Declaration): Set
6363         SPARK_Mode from context on generic package.
6364         * sem_ch7.adb (Analyze_Package_Declaration): Simplify code to remove
6365         useless test.
6367 2017-04-27  Claire Dross  <dross@adacore.com>
6369         * a-cofuve.ads (Range_Shifted): Rewrite precondition to avoid
6370         overflows in computations.
6371         * a-cofove.ads (Capacity_Range): Rewrite last bound to avoid
6372         overflows in computations.
6373         (Insert): Rewrite precondition to avoid overflows in computations.
6374         * a-cfinve.ads (Capacity_Range): Rewrite last bound to avoid
6375         overflows in computations.
6376         (Insert): Rewrite precondition to avoid overflows in computations.
6378 2017-04-27  Steve Baird  <baird@adacore.com>
6380         * exp_ch9.adb (Expand_N_Asynchronous_Select): Initialize the Cancel
6381         flag when it is declared in order to avoid confusing CodePeer about
6382         the possibility of an uninitialized variable read.
6384 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6386         * sem_dim.adb (Analyze_Dimension_Object_Declaration): There is
6387         no dimensionality error if the subtype of the expression is
6388         identical to the nominal subtype in the declaration, even though
6389         the expression itself may have been constant-folded and lack a
6390         dimension vector.
6391         * sem_dim.ads: Add comments on setting of dimension vectors and
6392         its interaction with node rewritings and side-effect removal.
6394 2017-04-27  Bob Duff  <duff@adacore.com>
6396         * debug.adb: Minor comment correction.
6397         * sem_dim.ads: Minor reformatting and typo fixes.
6399 2017-04-27  Bob Duff  <duff@adacore.com>
6401         * g-table.adb, g-table.adsa, scos.h: From the C side, access First and
6402         Last of the tables via function calls, rather than relying on layout
6403         of data structures.
6405 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6407         * exp_util.adb: No wrapper in GNATprove mode.
6409 2017-04-27  Yannick Moy  <moy@adacore.com>
6411         * sem_res.adb (Resolve_Comparison_Op): Always
6412         evaluate comparisons between values of universal types.
6414 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6416         * sem_elab.adb (Check_Internal_Call_Continue): Do not generate
6417         an elaboration counter nor a check when in GNATprove mode.
6418         * sem_util.adb (Build_Elaboration_Entity): Do not create an
6419         elaboration counter when in GNATprove mode.
6421 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6423         * freeze.adb: copy-paste typo.
6425 2017-04-27  Yannick Moy  <moy@adacore.com>
6427         * sem_prag.adb (Analyze_Pre_Post_In_Decl_Part):
6428         Use correct test to detect call in GNATprove mode instead of
6429         compilation.
6431 2017-04-27  Claire Dross  <dross@adacore.com>
6433         * a-cfdlli.adb, a-cfdlli.ads (Formal_Model.M_Elements_In_Union):
6434         New property function expressing that the element of a
6435         sequence are contained in the union of two sequences.
6436         (Formal_Model.M_Elements_Included): New property function
6437         expressing that the element of a sequence are another sequence.
6438         (Generic_Sorting): Use new property functions to state that
6439         elements are preserved by Sort and Merge.
6440         * a-cofove.adb, a-cofove.ads (=): Generic parameter removed to
6441         allow the use of regular equality over elements in contracts.
6442         (Formal_Model): Ghost package containing model functions
6443         that are used in subprogram contracts.  (Capacity):
6444         On unbounded containers, return the maximal capacity.
6445         (Current_To_Last): Removed, model functions should be used instead.
6446         (First_To_Previous): Removed, model functions should be used instead.
6447         (Append): Default parameter value replaced
6448         by new wrapper to allow more precise contracts.
6449         (Insert): Subprogram restored, it seems it was useful to users even if
6450         it is inefficient.
6451         (Delete): Subprogram restored, it seems it was useful to users even if
6452         it is inefficient.
6453         (Prepend): Subprogram restored, it seems it was useful to users even
6454         if it is inefficient.
6455         (Delete_First): Subprogram restored, it seems it
6456         was useful to users even if it is inefficient.  (Delete_Last):
6457         Default parameter value replaced by new wrapper to allow more
6458         precise contracts.
6459         (Generic_Sorting.Merge): Subprogram restored.
6460         * a-cfinve.adb, a-cfinve.ads (=): Generic parameter removed to
6461         allow the use of regular equality over elements in contracts.
6462         (Formal_Model): Ghost package containing model functions
6463         that are used in subprogram contracts.  (Capacity):
6464         On unbounded containers, return the maximal capacity.
6465         (Current_To_Last): Removed, model functions should be used
6466         instead.
6467         (First_To_Previous): Removed, model functions should be used instead.
6468         (Append): Default parameter value replaced
6469         by new wrapper to allow more precise contracts.
6470         (Insert): Subprogram restored, it seems it was useful to users even if
6471         it is inefficient.
6472         (Delete): Subprogram restored, it seems it was useful to users even if
6473         it is inefficient.
6474         (Prepend): Subprogram restored, it seems it was useful to users even
6475         if it is inefficient.
6476         (Delete_First): Subprogram restored, it seems it
6477         was useful to users even if it is inefficient.  (Delete_Last):
6478         Default parameter value replaced by new wrapper to allow more
6479         precise contracts.
6480         (Generic_Sorting.Merge): Subprogram restored.
6481         (Vector): Do not reuse formal vectors, as it is no longer possible
6482         to supply them with an equality function over elements.
6484 2017-04-27  Bob Duff  <duff@adacore.com>
6486         * g-dyntab.adb (Release): When allocating the new
6487         table, use the correct slice of the old table to initialize it.
6489 2017-04-27  Eric Botcazou  <ebotcazou@adacore.com>
6491         * einfo.ads: Minor fixes in comments.
6493 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6495         * sem_prag.adb: disable clones in SPARK_Mode.
6497 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
6499         * sem_util.ads, contracts.adb: Minor reformatting.
6501 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6503         * sem_util.adb, sem_util.ads (Build_Class_Wide_Clone_Body):
6504         Build body of subprogram that has a class-wide condition that
6505         contains calls to other primitives.
6506         (Build_Class_Wide_Clone_Call); Build a call to the common
6507         class-wide clone of a subprogram with classwide conditions. The
6508         body of the subprogram becomes a wrapper for a call to the
6509         clone. The inherited operation becomes a similar wrapper to which
6510         modified conditions apply, and the call to the clone includes
6511         the proper conversion in a call the parent operation.
6512         (Build_Class_Wide_Clone_Decl (Spec_Id : Entity_Id): For a
6513         subprogram that has a classwide condition that contains calls to
6514         other primitives, build an internal subprogram that is invoked
6515         through a type-specific wrapper for all inherited subprograms
6516         that may have a modified condition.
6517         * sem_prag.adb (Check_References): If subprogram has a classwide
6518         condition, create entity for corresponding clone, to be invoked
6519         through wrapper subprograns.
6520         (Analyze_Pre_Post_Condition_In_Decl_Part): Do not emit error
6521         message about placement if pragma isi internally generated.
6522         * sem_ch6.adb (Analyze_Subprogram_Body_Helper): If subprogram has
6523         a classwide clone, build body of clone as copy of original body,
6524         and rewrite original body as a wrapper as a wrapper for a call to
6525         the clone, so that it incorporates the original pre/postconditions
6526         of the subprogram.
6527         * freeze.adb (Check_Inherited_Conditions): For an inherited
6528         subprogram that inherits a classwide condition, build spec and
6529         body of corresponding wrapper so that call to inherited operation
6530         gets the modified conditions.
6531         * contracts.adb (Analyze_Contracts): If analysis of classwide
6532         condition has created a clone for a primitive operation, analyze
6533         declaration of clone.
6535 2017-04-27  Steve Baird  <baird@adacore.com>
6537         * exp_util.adb (Build_Allocate_Deallocate_Proc):
6538         Add "Suppress => All_Checks" to avoid generating unnecessary
6539         checks.
6541 2017-04-27  Yannick Moy  <moy@adacore.com>
6543         * debug.adb: Reserve debug flag 'm' for no inlining in GNATprove.
6544         * sem_ch6.adb (Anayze_Subprogram_Body_Helper): Skip creation of
6545         inlining body in GNATprove mode when switch -gnatdm used.
6546         * sem_res.adb (Resolve_Call): Skip detection of lack of inlining
6547         in GNATprove mode when switch -gnatdm used.
6549 2017-04-27  Arnaud Charlet  <charlet@adacore.com>
6551         * sem_ch13.adb (Analyze_Attribute_Definition_Clause
6552         [Attribute_Address]): Call Set_Address_Taken when ignoring rep
6553         clauses, so that we keep an indication of the address clause
6554         before removing it from the tree.
6556 2017-04-27  Yannick Moy  <moy@adacore.com>
6558         * exp_util.ads, exp_util.adb (Evaluate_Name): Force evaluation
6559         of expression being qualified, when not an object name, or else
6560         evaluate the underlying name.
6562 2017-04-27  Jerome Lambourg  <lambourg@adacore.com>
6564         * bindusg.adb, bindgen.adb, gnatbind.adb, opt.ads: add -nognarl switch.
6566 2017-04-27  Justin Squirek  <squirek@adacore.com>
6568         * exp_ch7.adb (Build_Finalize_Statements): Move Num_Comps to
6569         Process_Component_List_For_Finalization as a local variable.
6570         (Process_Component_For_Finalize): Add an extra parameter to avoid
6571         global references.
6572         (Process_Component_List_For_Finalization): Correct calls to
6573         Process_Component_For_Finalize to take Num_Comps as a parameter.
6575 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6577         * sem_ch8.adb (Find_Direct_Name): Account for the case where
6578         a use-visible entity is defined within a nested scope of an
6579         instance when giving priority to entities which were visible in
6580         the original generic.
6581         * sem_util.ads, sem_util.adb (Nearest_Enclosing_Instance): New routine.
6583 2017-04-27  Tristan Gingold  <gingold@adacore.com>
6585         * raise-gcc.c: Don't use unwind.h while compiling
6586         for the frontend, but mimic host behavior.
6588 2017-04-27  Javier Miranda  <miranda@adacore.com>
6590         * sem_ch3.adb (Build_Discriminated_Subtype):
6591         Propagate Has_Pragma_Unreferenced_Objects to the built subtype.
6593 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6595         * sem_prag.adb (Analyze_Global_Item):
6596         Do not consider discriminants because they are not "entire
6597         objects". Remove the discriminant-related checks because they are
6598         obsolete.
6599         (Analyze_Input_Output): Do not consider discriminants
6600         because they are not "entire objects".
6602 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6604         * sem_ch13.adb (Check_Aspect_At_End_Of_Declarations): Do not
6605         perform check if the current scope does not come from source,
6606         as is the case for a rewritten task body, because check has
6607         been performed already, and may not be doable because of changed
6608         visibility.
6610 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6612         * a-cofuse.adb, a-cfdlli.adb, a-cofuse.ads, a-cfdlli.ads, a-cofuve.adb,
6613         a-cofuve.ads, a-cofuma.adb, a-cofuma.ads, sem_eval.adb, a-cofuba.adb:
6614         Minor reformatting.
6616 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6618         * sem_ch4.adb (Analyze_Call): If the return type of a function
6619         is incomplete in an context in which the full view is available,
6620         replace the type of the call by the full view, to prevent spurious
6621         type errors.
6622         * exp_disp.adb (Check_Premature_Freezing): Disable check on an
6623         abstract subprogram so that compiler does not reject a parameter
6624         of a primitive operation of a tagged type being frozen, when
6625         the untagged type of that parameter cannot be frozen.
6627 2017-04-27  Bob Duff  <duff@adacore.com>
6629         * sem_attr.adb (Compute_Type_Key): Don't walk
6630         representation items for irrelevant types, which could be in a
6631         different source file.
6633 2017-04-27  Steve Baird  <baird@adacore.com>
6635         * exp_attr.adb (Expand_N_Attribute_Reference):
6636         Don't expand Image, Wide_Image, Wide_Wide_Image attributes
6637         for CodePeer.
6639 2017-04-27  Yannick Moy  <moy@adacore.com>
6641         * exp_unst.ads: Fix typos in comments.
6643 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6645         * sem_eval.adb (Choice_Matches): Handle properly a real literal
6646         whose type has a defined static predicate.
6648 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6650         * exp_ch4.adb (Insert_Dereference_Action):
6651         Do not adjust the address of a controlled object when the
6652         associated access type is subject to pragma No_Heap_Finalization.
6653         Code reformatting.
6655 2017-04-27  Pierre-Marie de Rodat  <derodat@adacore.com>
6657         * gcc-interface/utils.c (gnat_type_for_size): Set
6658         TYPE_ARTIFICIAL on created types.
6660 2017-04-27  Claire Dross  <dross@adacore.com>
6662         * a-cfdlli.adb, a-cfdlli.ads (Formal_Model): Adapt to
6663         modifications in functional containers.
6664         * a-cofuba.ads, a-cofuma.ads, a-cofuse.ads, a-cofuve.ads Reformat
6665         to improve readablity. Subprograms are separated between basic
6666         operations, constructors and properties. Universally quantified
6667         formulas in contracts are factorized in independant functions
6668         with a name and a comment.  Names of parameters are improved.
6670 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
6672         * exp_spark.adb, sem_elab.adb: Minor reformatting and typo fix.
6674 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6676         * sem_res.adb (Resolve_Type_Conversion): Do not
6677         install a predicate check here since this is already done during
6678         the expansion phase. Verify whether the operand satisfies the
6679         static predicate (if any) of the target type.
6680         * sem_ch3.adb (Analyze_Object_Declaration): Do
6681         not install a predicate check if the object is initialized by
6682         means of a type conversion because the conversion is subjected
6683         to the same check.
6685 2017-04-27  Tristan Gingold  <gingold@adacore.com>
6687         * raise.c (__gnat_builtin_longjmp): Remove.
6688         (__gnat_bracktrace):
6689         Add a dummy definition for the compiler (__gnat_eh_personality,
6690         __gnat_rcheck_04, __gnat_rcheck_10) (__gnat_rcheck_19,
6691         __gnat_rcheck_20, __gnat_rcheck_21) (__gnat_rcheck_30,
6692         __gnat_rcheck_31, __gnat_rcheck_32): Likewise.
6693         * a-exexpr.adb: Renamed from a-exexpr-gcc.adb
6694         * a-except.ads, a-except.adb: Renamed from a-except-2005.ads
6695         and a-except-2005.adb.
6696         * raise-gcc.c: Allow build in compiler, compiled as a C++
6697         file.
6698         (__gnat_Unwind_ForcedUnwind): Adjust prototype.
6699         (db): Constify msg_format.
6700         (get_call_site_action_for): Don't use void arithmetic.
6701         * system.ads (Frontend_Exceptions): Set to False.
6702         (ZCX_By_Default): Set to True.
6703         (GCC_ZC_Support): Set to True.
6704         * gcc-interface/Makefile.in: No more variants for a-exexpr.adb and
6705         a-except.ad[sb].
6706         * gcc-interface/Make-lang.in: Add support for backend zcx exceptions
6707         in gnat1 and gnatbind.
6708         * gnat1, gnatbind: link with raise-gcc.o, a-exctra.o, s-addima.o,
6709         s-excmac.o, s-imgint.o, s-traceb.o, s-trasym.o, s-wchstw.o
6710         * s-excmac.ads, s-excmac.adb: Copy of variants.
6711         * a-except.o: Adjust preequisites.
6712         Add handling of s-excmac-arm.adb and s-excmac-gcc.adb.
6714 2017-04-27  Claire Dross  <dross@adacore.com>
6716         * a-cfdlli.adb, a-cfdlli.ads (Formal_Model): Adapt to
6717         modifications in functional containers.
6718         * a-cofuba.ads, a-cofuma.ads, a-cofuse.ads, a-cofuve.ads Reformat
6719         to improve readablity. Subprograms are separated between basic
6720         operations, constructors and properties. Universally quantified
6721         formulas in contracts are factorized in independant functions
6722         with a name and a comment.  Names of parameters are improved.
6724 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
6726         * exp_spark.adb, sem_elab.adb: Minor reformatting and typo fix.
6728 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6730         * sem_res.adb (Resolve_Type_Conversion): Do not
6731         install a predicate check here since this is already done during
6732         the expansion phase. Verify whether the operand satisfies the
6733         static predicate (if any) of the target type.
6734         * sem_ch3.adb (Analyze_Object_Declaration): Do
6735         not install a predicate check if the object is initialized by
6736         means of a type conversion because the conversion is subjected
6737         to the same check.
6739 2017-04-27  Tristan Gingold  <gingold@adacore.com>
6741         * a-except.ads, a-except.adb, a-exexpr.adb: Removed (will be
6742         replaced by their variants).
6744 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6746         * exp_prag.adb, a-cofuse.adb, a-cofuse.ads, einfo.adb, sem_prag.adb,
6747         cstand.adb, par-prag.adb, a-cofuve.adb, a-cofuve.ads, a-cofuma.adb,
6748         a-cofuma.ads, a-cofuba.adb, a-cofuba.ads: Minor reformatting.
6750 2017-04-27  Tristan Gingold  <gingold@adacore.com>
6752         * s-excmac-gcc.ads, s-excmac-gcc.adb,
6753         s-excmac-arm.ads, s-excmac-arm.adb (New_Occurrence): Rewrite it in
6754         Ada95.
6756 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6758         * exp_ch7.adb (Establish_Transient_Scope): Rewrite
6759         the loop which detects potential enclosing transient scopes. The
6760         loop now terminates much earlier as transient scopes are bounded
6761         by packages and subprograms.
6763 2017-04-27  Claire Dross  <dross@adacore.com>
6765         * a-cfdlli.adb, a-cfdlli.ads (=): Generic parameter removed to
6766         allow the use of regular equality over elements in contracts.
6767         (Cursor): Type is now public so that it can be used in
6768         model functions.
6769         (Formal_Model): Ghost package containing
6770         model functions that are used in subprogram contracts.
6771         (Current_To_Last): Removed, model functions should be used
6772         instead.
6773         (First_To_Previous): Removed, model functions should
6774         be used instead.
6775         (Strict_Equal): Removed, model functions
6776         should be used instead.
6777         (Append): Default parameter value
6778         replaced by new wrapper to allow more precise contracts.
6779         (Insert): Default parameter value replaced by new wrapper to
6780         allow more precise contracts.
6781         (Delete): Default parameter
6782         value replaced by new wrapper to allow more precise contracts.
6783         (Prepend): Default parameter value replaced by new wrapper to
6784         allow more precise contracts.
6785         (Delete_First): Default parameter
6786         value replaced by new wrapper to allow more precise contracts.
6787         (Delete_Last): Default parameter value replaced by new wrapper
6788         to allow more precise contracts.
6790 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6792         * exp_spark.adb (Expand_SPARK): Perform specialized expansion
6793         for object declarations.
6794         (Expand_SPARK_N_Object_Declaration): New routine.
6795         * sem_elab.adb (Check_A_Call): Include calls to the
6796         Default_Initial_Condition procedure of a type under the SPARK
6797         elaboration checks umbrella.
6799 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6801         * sem.adb (Analyze): Diagnose an illegal iterated component
6802         association.
6803         * sem_util.ads, sem_util.adb
6804         (Diagnose_Iterated_Component_Association): New routine.
6806 2017-04-27  Bob Duff  <duff@adacore.com>
6808         * adaint.c (__gnat_get_current_dir): Return 0 in length if
6809         getcwd fails.
6810         * a-direct.adb, g-dirope.adb, osint.adb, s-os_lib.adb: Raise
6811         exception if getcwd failed.
6813 2017-04-27  Yannick Moy  <moy@adacore.com>
6815         * exp_dbug.adb, exp_dbug.ads (Get_External_Name): Prefix ghost
6816         entities with special prefix.
6818 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6820         * debug.adb Change the documentation of switch -gnatd.s.
6821         * exp_ch7.adb (Make_Transient_Block): Transient blocks do not need
6822         to manage the secondary stack when an enclosing scope already
6823         performs this functionality (aka relaxed management). Switch
6824         -gnatd.s may be used to force strict management in which case
6825         the block will manage the secondary stack unconditionally. Add
6826         a guard to stop the traversal when encountering a package or a
6827         subprogram scope.
6829 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6831         * sem_res.adb (Resolve_Call): Refine further the handling of
6832         limited views of return types in function calls. If the function
6833         that returns a limited view appears in the current unit,
6834         we do not replace its type by the non-limited view because
6835         this transformation is performed int the back-end. However,
6836         the type of the call itself must be the non-limited view, to
6837         prevent spurious resolution errors.
6839 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6841         * einfo,ads, einfo.adb (Class_Wide_Preconds, Class_Wide_Postconds):
6842         Removed, proposed implementation using generics for class-wide
6843         preconditions proved impractical.
6844         (Class_Wide_Clone): New attribute of subprogram. Designates
6845         subprogram created for primitive operations with class-wide
6846         pre/postconditions that contain calls to other primitives. The
6847         clone holds the body of the original primitive, but the
6848         pre/postonditions do not apply to it. The original body is
6849         rewritten as a wrapper for a call to the clone.
6850         (Is_Class_Wide_Clone): New flag to identify a Class_Wide_Clone. If
6851         the flag is set, no code for the corresponding pre/postconditions
6852         is inserted into its body.
6854 2017-04-27  Bob Duff  <duff@adacore.com>
6856         * exp_prag.adb, par-prag.adb, sem_ch13.adb: Ignore
6857         Scalar_Storage_Order if -gnatI is given.
6858         * sem_prag.adb (Analyze_Pragma): Ignore
6859         Default_Scalar_Storage_Order if -gnatI is given.
6861 2017-04-27  Claire Dross  <dross@adacore.com>
6863         * a-cofuba.ads (Add): Take as an additional input parameter
6864         the position where the element should be inserted.
6865         (Remove): New function that removes an element from the container.
6866         * a-cofuma.ads (Add): Adapt to the new API of Base.Add.
6867         * a-cofuse.ads (Add): Adapt to the new API of Base.Add.
6868         (Remove): New function that removes an element from a set.
6869         * a-cofuve.ads (Add): Adapt to the new API of Base.Add.
6870         (Remove): New function that removes an element from a sequence.
6871         (Insert): New function that adds anywhere in a sequence.
6873 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6875         * checks.adb (Generate_Range_Check): Revert previous change.
6877 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
6879         * sem_util.adb: Minor reformatting/rewording.
6881 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6883         * lib-xref.adb (Generate_Reference): The use
6884         of attribute 'Result is not considered a violation of pragma
6885         Unreferenced.
6887 2017-04-27  Justin Squirek  <squirek@adacore.com>
6889         * cstand.adb (Create_Standard): Correctly set
6890         Directly_Designated_Type for Any_Access.
6891         * sem_type.adb (Covers): Minor grammar fixes.
6893 2017-04-27  Bob Duff  <duff@adacore.com>
6895         * sem_attr.adb: Minor cleanup.
6897 2017-04-27  Claire Dross  <dross@adacore.com>
6899         * a-cofuba.ads, a-cofuba.adb (Ada.Containers.Functional_Base): New
6900         private child of Ada.Containers used to implement all functional
6901         containers.
6902         * a-cofuma.ads, a-cofuma.adb (Ada.Containers.Functional_Maps): New
6903         child of Ada.Containers. It provides functional indefinite unbounded
6904         maps which can be used as high level models for specification
6905         of data structures.
6906         * a-cofuse.ads, a-cofuse.adb (Ada.Containers.Functional_Sets): New
6907         child of Ada.Containers. It provides functional indefinite unbounded
6908         sets which can be used as high level models for specification
6909         of data structures.
6910         * a-cofuve.ads, a-cofuve.adb (Ada.Containers.Functional_Vectors): New
6911         child of Ada.Containers.  It provides functional indefinite unbounded
6912         vectors which can be used as high level models for specification
6913         of data structures.
6914         * Makefile.rtl: Add new packages.
6915         * impunit.adb: Add new packages.
6917 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
6919         * sem_ch4.adb: Minor reformatting.
6921 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6923         * sem_ch12.adb (Analyze_Associations): minor reformatting.
6924         (Check_Fixed_Point_Actual): Do not emit a warning on a fixed
6925         point type actual that has user-defined arithmetic primitives,
6926         when there is a previous actual for a formal package that defines
6927         a fixed-point type with the parent user-defined operator.
6929 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6931         * checks.adb (Generate_Range_Check): Reinstate part of previous change.
6932         * sem_attr.adb (Resolve_Attribute): Generate a range check when
6933         the component type allows range checks.
6935 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6937         * sem_aux.adb (Is_Generic_Formal): Use original node to locate
6938         corresponding declaration, because formal derived types are
6939         rewritten as private extensions.
6941 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
6943         * sem_dim.adb (Analyze_Dimension_Binary_Op): Do not check
6944         dimensions of operands if node has been analyzed already, because
6945         previous analysis and dimension checking will have removed the
6946         dimension information from the operands.
6948 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6950         * debug.adb: Document the use of switch -gnatd.s.
6951         * einfo.ads Update the documentation on attribute
6952         Sec_Stack_Needed_For_Return and attribute Uses_Sec_Stack. Remove
6953         the uses of these attributes from certain entities.
6954         * exp_ch7.adb (Make_Transient_Block): Reimplement the circuitry
6955         which determines whether the block should continue to manage
6956         the secondary stack.
6957         (Manages_Sec_Stack): New routine.
6959 2017-04-27  Bob Duff  <duff@adacore.com>
6961         * atree.ads: Minor edit.
6963 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
6965         * sinfo.ads: Update the section on Ghost mode. Add
6966         a section on SPARK mode. Update the placement of section on
6967         expression functions.
6969 2017-04-27  Bob Duff  <duff@adacore.com>
6971         * sinput.adb (Get_Source_File_Index): Don't
6972         assert that S is in the right range in the case where this is
6973         a .dg file under construction.
6975 2017-04-27  Yannick Moy  <moy@adacore.com>
6977         * sem_util.adb (Check_Result_And_Post_State):
6978         Handle more precisely each conjunct in expressions formed by
6979         and'ing sub-expressions.
6981 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
6983         * exp_ch4.adb, sem_ch4.adb: Minor typo fix and reformatting.
6985 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
6987         * gnat_rm.texi, gnat_ugn.texi,
6988         doc/gnat_ugn/building_executable_programs_with_gnat.rst,
6989         doc/gnat_ugn/platform_specific_information.rst,
6990         doc/gnat_ugn/gnat_and_program_execution.rst,
6991         doc/gnat_ugn/gnat_utility_programs.rst,
6992         doc/gnat_ugn/the_gnat_compilation_model.rst,
6993         doc/gnat_rm/implementation_defined_attributes.rst,
6994         doc/gnat_rm/the_gnat_library.rst,
6995         doc/gnat_rm/implementation_defined_pragmas.rst,
6996         doc/gnat_rm/representation_clauses_and_pragmas.rst,
6997         doc/gnat_rm/implementation_of_specific_ada_features.rst,
6998         doc/gnat_rm/implementation_defined_aspects.rst,
6999         doc/gnat_rm/implementation_defined_characteristics.rst: Update
7000         documentation.
7002 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
7004         * exp_ch4.adb (Expand_N_Case_Expression): Emit error message when
7005         generating C code on complex case expressions.
7007 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
7009         * sem_prag.adb (Analyze_Pragma): Generate a warning instead
7010         of silently ignoring pragma Ada_xxx in Latest_Ada_Only mode.
7011         * directio.ads, ioexcept.ads, sequenio.ads, text_io.ads: Use
7012         Ada_2012 instead of Ada_2005 to be compatible with the above
7013         change.
7014         * bindgen.adb: Silence new warning on pragma Ada_95.
7016 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7018         * checks.adb (Generate_Range_Check): Revert part of previous change.
7020 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7022         * sem_ch4.adb (Try_Container_Indexing): Handle properly a
7023         container indexing operation that appears as a an actual in a
7024         parameter association in a procedure call.
7026 2017-04-25  Olivier Ramonat  <ramonat@adacore.com>
7028         * prj-proc.adb, sem_util.adb, s-stposu.adb, sem_attr.adb, prj-conf.ads:
7029         Fix spelling mistakes.
7031 2017-04-25  Bob Duff  <duff@adacore.com>
7033         * types.ads, osint.adb, sinput-c.adb, sinput-d.adb, sinput-l.adb,
7034         * sinput-p.adb: Use regular fat pointers, with bounds checking,
7035         for source buffers.  Fix misc obscure bugs.
7036         * sinput.ads, sinput.adb: Use regular fat pointers, with bounds
7037         checking, for source buffers.  Modify representation clause for
7038         Source_File_Record as appropriate.  Move Source_File_Index_Table
7039         from spec to body, because it is not used outside the body.
7040         Move Set_Source_File_Index_Table into the private part, because
7041         it is used only in the body and in children.  Use trickery to
7042         modify the dope in the generic instantiation case.  It's ugly,
7043         but not as ugly as the previous method.  Fix documentation.
7044         Remove obsolete code.
7045         * fname-sf.adb, targparm.adb: Fix misc out-of-bounds
7046         indexing in source buffers.
7047         * fmap.adb: Avoid conversions from one string type to another.
7048         Remove a use of global name buffer.
7049         * osint.ads, sfn_scan.ads, sfn_scan.adb, sinput-c.ads: Comment
7050         fixes.
7052 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
7054         * exp_util.adb, exp_ch4.adb: Minor reformatting.
7056 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7058         * checks.adb: Code clean up in various routines.
7059         (Generate_Range_Check): Do not generate a range check when the
7060         expander is not active or when index/range checks are suppressed
7061         on the target type.
7062         (Insert_List_After_And_Analyze, Insert_List_Before_And_Analyze):
7063         Remove variants that include a Supress parameter. These routines
7064         are never used, and were introduced before the current scope-based
7065         check suppression method.
7067 2017-04-25  Vasiliy Fofanov  <fofanov@adacore.com>
7069         * prj-part.adb, cstreams.c, osint.adb, osint.ads: Remove VMS specific
7070         code and some subprogram calls that are now noop.
7072 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
7074         * exp_ch4.adb (Expand_N_Case_Expression): Take
7075         Minimize_Expression_With_Actions into account when possible.
7077 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7079         * exp_util.adb (Known_Non_Null): Moved to Sem_Util.
7080         (Known_Null): Moved to Sem_Util.
7081         * exp_util.ads (Known_Non_Null): Moved to Sem_Util.
7082         (Known_Null): Moved to Sem_Util.
7083         * sem_util.adb Add new enumeration type Null_Status_Kind.
7084         (Known_Non_Null): Moved from Exp_Util. Most of the logic in
7085         this routine is now carried out by Null_Status.
7086         (Known_Null): Moved from Exp_Util. Most of the logic in this routine
7087         is now carried out by Null_Status.
7088         (Null_Status): New routine.
7089         * sem_util.ads (Known_Non_Null): Moved from Exp_Util.
7090         (Known_Null): Moved from Exp_Util.
7092 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7094         * sem_ch6.adb (Analyze_Expression_Function): Do not report an
7095         error on the return type of an expression function that is a
7096         completion, if the type is derived from a generic formal type.
7098 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7100         * sem_dim.adb (Dimensions_Of_Operand): The dimensions of a type
7101         conversion are those of the target type.
7103 2017-04-25  Bob Duff  <duff@adacore.com>
7105         * a-clrefi.adb: Minor cleanup.
7107 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
7109         * exp_util.adb, exp_util.ads, types.ads: Minor reformatting.
7111 2017-04-25  Bob Duff  <duff@adacore.com>
7113         * err_vars.ads, fmap.adb, fmap.ads, comperr.adb, fname-sf.adb,
7114         types.adb, types.ads, types.h, sinput-l.adb, targparm.adb,
7115         errout.adb, sinput.adb, sinput.ads, cstand.adb, scn.adb,
7116         scn.ads, gnatls.adb: Eliminate the vestigial Internal_Source_File and
7117         the Internal_Source buffer. This removes the incorrect call to "="
7118         the customer noticed.
7119         Wrap remaining calls to "=" in Null_Source_Buffer_Ptr. We
7120         eventually need to eliminate them altogether. Or else get rid
7121         of zero-origin addressing.
7123 2017-04-25  Claire Dross  <dross@adacore.com>
7125         * exp_util.ads (Expression_Contains_Primitives_Calls_Of): New
7126         function used in GNATprove to know if an expression contains
7127         non-dispatching calls on primitives of a tagged type.
7129 2017-04-25  Bob Duff  <duff@adacore.com>
7131         * rtsfind.adb (Initialize): Initialize
7132         First_Implicit_With. Building the compiler with Normalize_Scalars
7133         and validity checking finds this being used as an uninitialized
7134         variable.
7136 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7138         * contracts.adb (Analyze_Entry_Or_Subprogram_Body_Contract):
7139         Add a warning about SPARK mode management. The routine now
7140         saves and restores both the mode and associated pragma.
7141         (Analyze_Entry_Or_Subprogram_Contract): Add a warning about
7142         SPARK mode management. The routine now saves and restores both
7143         the mode and associated pragma.
7144         (Analyze_Object_Contract):
7145         Add a warning about SPARK mode management. The routine
7146         now saves and restores both the mode and associated pragma.
7147         (Analyze_Package_Body_Contract): Add a warning about SPARK mode
7148         management.  The routine now saves and restores both the mode
7149         and associated pragma.  (Analyze_Package_Contract): Add a warning
7150         about SPARK mode management. The routine now saves and restores
7151         both the mode and associated pragma.
7152         (Analyze_Task_Contract):
7153         Add a warning about SPARK mode management. The routine now saves
7154         and restores both the mode and associated pragma.
7155         * expander.adb (Expand): Change the way the Ghost mode is saved
7156         and restored.
7157         * exp_ch3.adb (Freeze_Type): Change the way the Ghost mode is
7158         saved and restored.
7159         * exp_disp.adb (Make_DT): Change the way the Ghost mode is saved
7160         and restored.
7161         * exp_util.adb (Build_DIC_Procedure_Body):
7162         Change the way the Ghost mode is saved and restored.
7163         (Build_DIC_Procedure_Declaration): Change the way the Ghost
7164         mode is saved and restored.
7165         (Build_Invariant_Procedure_Body):
7166         Change the way the Ghost mode is saved and restored.
7167         (Build_Invariant_Procedure_Declaration): Change the way the Ghost
7168         mode is saved and restored.
7169         (Make_Predicate_Call): Change the
7170         way the Ghost mode is saved and restored.
7171         * freeze.adb (Freeze_Entity): Change the way the Ghost mode is
7172         saved and restored.
7173         * ghost.adb (Mark_And_Set_Ghost_Assignment): Remove parameter Mode
7174         and its assignment.
7175         (Mark_And_Set_Ghost_Body): Remove parameter
7176         Mode and its assignment.
7177         (Mark_And_Set_Ghost_Completion):
7178         Remove parameter Mode and its assignment.
7179         (Mark_And_Set_Ghost_Declaration): Remove parameter Mode and its
7180         assignment.
7181         (Mark_And_Set_Ghost_Instantiation): Remove parameter
7182         Mode and its assignment.
7183         (Mark_And_Set_Ghost_Procedure_Call):
7184         Remove parameter Mode and its assignment.
7185         (Set_Ghost_Mode):
7186         Remove parameter Mode and its assignment.
7187         * ghost.ads (Mark_And_Set_Ghost_Assignment): Remove parameter Mode
7188         and update the comment on usage.
7189         (Mark_And_Set_Ghost_Body):
7190         Remove parameter Mode and update the comment on usage.
7191         (Mark_And_Set_Ghost_Completion): Remove parameter Mode and
7192         update the comment on usage.
7193         (Mark_And_Set_Ghost_Declaration):
7194         Remove parameter Mode and update the comment on usage.
7195         (Mark_And_Set_Ghost_Instantiation): Remove parameter Mode and
7196         update the comment on usage.
7197         (Mark_And_Set_Ghost_Procedure_Call):
7198         Remove parameter Mode and update the comment on usage.
7199         (Set_Ghost_Mode): Remove parameter Mode and update the comment
7200         on usage.
7201         * lib.ads Remove obsolete fields SPARK_Mode_Pragma from various
7202         types.
7203         * lib-load.adb (Create_Dummy_Package_Unit): Remove the assignment
7204         of obsolete field SPARK_Mode_Pragma.
7205         (Load_Main_Source): Remove
7206         the assignment of obsolete field SPARK_Mode_Pragma.
7207         (Load_Unit): Remove the assignment of obsolete field SPARK_Mode_Pragma.
7208         * lib-writ.adb (Add_Preprocessing_Dependency): Remove
7209         the assignment of obsolete field SPARK_Mode_Pragma.
7210         (Ensure_System_Dependency): Remove the assignment of obsolete
7211         field SPARK_Mode_Pragma.
7212         * rtsfind.adb (Load_RTU): Add a warning about Ghost and SPARK
7213         mode management. Change the way Ghost and SPARK modes are saved
7214         and restored.
7215         * sem.adb (Analyze): Change the way the Ghost mode is saved
7216         and restored.
7217         * sem_ch3.adb (Analyze_Object_Declaration): Change the way the
7218         Ghost mode is saved and restored.
7219         (Process_Full_View): Change
7220         the way the Ghost mode is saved and restored.
7221         * sem_ch5.adb (Analyze_Assignment): Change the way the Ghost
7222         mode is saved and restored.
7223         * sem_ch6.adb (Analyze_Procedure_Call): Change the way the Ghost
7224         mode is saved and restored.
7225         (Analyze_Subprogram_Body_Helper):
7226         Change the way the Ghost mode is saved and restored.
7227         * sem_ch7.adb (Analyze_Package_Body_Helper): Change the way the
7228         Ghost mode is saved and restored.
7229         * sem_ch10.adb (Analyze_Subunit): Add a warning about SPARK mode
7230         management. Save the SPARK mode-related data prior to any changes
7231         to the scope stack and contexts. The mode is then reinstalled
7232         before the subunit is analyzed in order to restore the original
7233         view of the subunit.
7234         * sem_ch12.adb (Analyze_Package_Instantiation): Update the
7235         warning on region management.  Change the way the Ghost and
7236         SPARK modes are saved and restored.
7237         (Inline_Instance_Body):
7238         Add a warning about SPARK mode management. Code clean up.
7239         (Analyze_Subprogram_Instantiation): Update the warning on region
7240         management.  Change the way the Ghost and SPARK modes are saved
7241         and restored.
7242         (Instantiate_Package_Body): Update the warning
7243         on region management. Change the way the Ghost and SPARK modes
7244         are saved and restored.
7245         (Instantiate_Subprogram_Body): Update
7246         the warning on region management. Change the way the Ghost and
7247         SPARK modes are saved and restored.
7248         (Set_Instance_Env): Add a
7249         warning about SPARK mode management. Change the way SPARK mode
7250         is saved and restored.
7251         * sem_ch13.adb (Build_Predicate_Functions):
7252         Change the way the Ghost mode is saved and restored.
7253         (Build_Predicate_Function_Declaration): Change the way the Ghost
7254         mode is saved and restored.
7255         * sem_elab.adb (Check_Elab_Calls): Add a warning about SPARK
7256         mode management. Change the way SPARK mode is saved and restored.
7257         * sem_prag.adb (Analyze_Contract_Cases_In_Decl_Part):
7258         Change the way the Ghost mode is saved and restored.
7259         (Analyze_Initial_Condition_In_Decl_Part): Change the way
7260         the Ghost mode is saved and restored.
7261         (Analyze_Pragma):
7262         Change the way the Ghost mode is saved and restored.
7263         (Analyze_Pre_Post_Condition_In_Decl_Part): Change the way the
7264         Ghost mode is saved and restored.
7265         * sem_util.adb (Install_SPARK_Mode): New routine.
7266         (Restore_SPARK_Mode): New routine.
7267         (Save_SPARK_Mode_And_Set): Removed.
7268         (Set_SPARK_Mode): New routine.
7269         * sem_util.ads (Install_SPARK_Mode): New routine.
7270         (Restore_SPARK_Mode): New routine.
7271         (Save_SPARK_Mode_And_Set): Removed.
7272         (Set_SPARK_Mode): New routine.
7274 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7276         * sem_util.adb, sem_util.ads (From_Nested_Package): New predicate
7277         to determine whether a type is declared in a local package that
7278         has not yet been frozen.
7279         * freeze.adb (Freeze_Before): Use new predicate to determine
7280         whether a local package must be installed on the scope stack
7281         in order to evaluate in the proper scope actions generated by
7282         aspect specifications, such as Predicate
7283         * sem_ch13.adb: Simplify code in Analyze_Aspects_At_Freeze_Point
7284         using new predicate.
7286 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7288         * sem_warn.adb (Warn_On_Constant_Valid_Condition): Do not consider
7289         comparisons between non- scalar expressions expressions because
7290         their values cannot be invalidated.
7291         * sem_warn.ads (Warn_On_Constant_Valid_Condition): Update the
7292         comment on usage.
7294 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7296         * par_sco.adb: Minor reformatting.
7298 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7300         * sem_ch13.adb (Analyze_Aspects_At_Freeze_Point): If entity
7301         is a type from an unfrozen local package, install package to
7302         complete the analysis of delayed aspects of the type.
7304 2017-04-25  Tristan Gingold  <gingold@adacore.com>
7306         * bingen.adb (System_Version_Control_Used): New variable.
7307         (Resolve_Binder_Options): Set the above variable.
7308         (Gen_Output_File_Ada): Conditionally call Gen_Versions.
7309         (Gen_Elab_Order): Emit blank line before.
7311 2017-04-25  Justin Squirek  <squirek@adacore.com>
7313         * sem_cat.adb (Validate_RT_RAT_Component): Added
7314         an extra check to ignore incomplete types.
7316 2017-04-25  Thomas Quinot  <quinot@adacore.com>
7318         * sem_prag.adb (Analyze_Pragma, case Pragma_Check): Remove
7319         bogus circuitry for the case where Name is Predicate.
7321 2017-04-25  Thomas Quinot  <quinot@adacore.com>
7323         * par_sco.adb(Traverse_Declarations_Or_Statements.Traverse_Aspects):
7324         Create SCOs for Predicate aspects in disabled
7325         state initially, to be enabled later on by...
7326         * sem_ch13.adb (Build_Predicate_Functions.Add_Predicates): Mark
7327         SCO for predicate as enabled.
7329 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7331         * comperr.adb (Compiler_Abort): Remove now obsolete pair of
7332         pragmas Warnings Off / On.
7333         * namet.adb (Finalize): Remove now obsolete pair of pragmas
7334         Warnings Off / On.
7335         * output.adb: Remove now obsolete pair of pragmas Warnings Off / On.
7336         * sem_warn.adb (Warn_On_Constant_Valid_Condition): Do not
7337         consider comparisons between static expressions because their
7338         values cannot be invalidated.
7339         * urealp.adb (Tree_Read): Remove now obsolete pair of pragmas
7340         Warnings Off / On.
7341         (Tree_Write): Remove now obsolete pair of pragmas Warnings Off / On.
7342         * usage.adb Remove now obsolete pair of pragmas Warnings Off / On.
7344 2017-04-25  Bob Duff  <duff@adacore.com>
7346         * sem_elab.adb (In_Task_Activation): Trace internal calls in
7347         task bodies.
7349 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
7351         * sem_prag.adb, sem_warn.adb, sem_eval.adb: Minor reformatting and
7352         typo fixes.
7354 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7356         * comperr.adb (Compiler_Abort): Add a pair of pragma Warnings
7357         On/Off to defend against a spurious warning in conditional
7358         compilation.
7359         * exp_ch4.adb (Rewrite_Comparison): Reimplemented.
7360         * namet.adb (Finalize): Add a pair of pragma Warnings On/Off to
7361         defend against a spurious warning in conditional compilation.
7362         * output.adb Add a pair of pragma Warnings On/Off to defend
7363         against a spurious warning in conditional compilation.
7364         * sem_eval.adb (Eval_Relational_Op): Major code clean up.
7365         (Fold_General_Op): New routine.
7366         (Fold_Static_Real_Op): New routine.
7367         (Test_Comparison): New routine.
7368         * sem_eval.ads (Test_Comparison): New routine.
7369         * sem_warn.adb (Is_Attribute_Constant_Comparison): New routine.
7370         (Warn_On_Constant_Valid_Condition): New routine.
7371         (Warn_On_Known_Condition): Use Is_Attribute_Constant_Comparison
7372         to detect a specific case.
7373         * sem_warn.adb (Warn_On_Constant_Valid_Condition): New routine.
7374         * urealp.adb (Tree_Read): Add a pair of pragma Warnings On/Off
7375         to defend against a spurious warning in conditional compilation.
7376         (Tree_Write): Add a pair of pragma Warnings On/Off to defend
7377         against a spurious warning in conditional compilation.
7378         * usage.adb Add a pair of pragma Warnings On/Off to defend
7379         against a spurious warning in conditional compilation.
7381 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
7383         * sinfo.ads, sem_ch13.adb: Update comment.
7385 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7387         * sem_util.adb (Is_Post_State): A reference to a
7388         generic in out parameter is considered a change in the post-state
7389         of a subprogram.
7391 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7393         * sem_ch12.adb (Load_Parent_Of_Generic); When retrieving the
7394         declaration of a subprogram instance within its wrapper package,
7395         skip over null statements that may result from the rewriting of
7396         ignored pragmas.
7398 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7400         * exp_attr.adb (Expand_Attribute_Reference, case 'Read):
7401         If the type is an unchecked_union, replace the attribute with
7402         a Raise_Program_Error (rather than inserting such before the
7403         attribute reference) to handle properly the case where we are
7404         processing a component of a larger record, and we need to prevent
7405         further expansion for the unchecked union.
7406         (Expand_Attribute_Reference, case 'Write): If the type is
7407         an unchecked_union, check whether enclosing scope is a Write
7408         subprogram. Replace attribute with a Raise_Program_Error if the
7409         discriminants of the unchecked_union type have not default values
7410         because such a use is erroneous..
7412 2017-04-25  Tristan Gingold  <gingold@adacore.com>
7414         * exp_ch9.adb (Expand_N_Task_Type_Declaration):
7415         Add relative_deadline to task record on edf profile.
7416         (Make_Initialize_Protection): Pass deadline_floor value on edf profile.
7417         (Make_Task_Create_Call): Pass relative_deadline value.
7418         * par-prag.adb (Prag): Handle Pragma_Deadline_Floor.
7419         * s-rident.ads (Profile_Name): Add GNAT_Ravenscar_EDF.
7420         (Profile_Info): Add info for GNAT_Ravenscar_EDF.
7421         * sem_prag.adb (Set_Ravenscar_Profile): Handle
7422         GNAT_Ravenscar_EDF (set scheduling policy).
7423         (Analyze_Pragma): Handle GNAT_Ravenscar_EDF profile and Deadline_Floor
7424         pragma.
7425         (Sig_Flags): Add choice for Pragma_Deadline_Floor.
7426         * snames.ads-tmpl (Name_Deadline_Floor, Name_Gnat_Ravenscar_EDF):
7427         New names.
7428         (Pragma_Deadline_Floor): New pragma.
7429         * targparm.adb (Get_Target_Parameters): Recognize
7430         GNAT_Ravenscar_EDF profile.
7432 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
7434         * gnatvsn.ads (Library_Version): Bump to 8. Update comment.
7436 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7438         * sem_aux.adb (Nearest_Ancestor): Use original node of type
7439         declaration to locate nearest ancestor, because derived
7440         type declarations for record types are rewritten as record
7441         declarations.
7442         * sem_ch13.adb (Add_Call): Use an unchecked conversion to handle
7443         properly derivations that are completions of private types.
7444         (Add_Predicates): If type is private, examine rep. items of full
7445         view, which may include inherited predicates.
7446         (Build_Predicate_Functions): Ditto.
7448 2017-04-25  Javier Miranda  <miranda@adacore.com>
7450         * sem_util.adb (New_Copy_Tree.Visit_Entity): Extend previous change
7451         to generate new entities for subtype declarations located in
7452         Expression_With_Action nodes.
7454 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7456         * sem_elab.adb (Check_A_Call): Remove
7457         local variables Is_DIC_Proc and Issue_In_SPARK. Verify the
7458         need for Elaborate_All when SPARK elaboration checks are
7459         required. Update the checks for instances, variables, and calls
7460         to Default_Initial_Condition procedures.
7462 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7464         * aspects.ads, aspects.adb: Make the GNAT-specific pragma No_Inline
7465         into a boolean aspect, in analogy with the Ada aspect No_Return.
7467 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7469         * exp_ch6.adb, sem_ch13.adb, sem_ch6.adb: Minor reformatting.
7471 2017-04-25  Bob Duff  <duff@adacore.com>
7473         * sem_res.adb (Resolve_Actuals): Under -gnatd.q, reset
7474         Is_True_Constant for an array variable that is passed to a
7475         foreign function as an 'in' parameter.
7476         * debug.adb: Document -gnatd.q.
7478 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7480         * sem_ch6.adb (Analyze_Expression_Function): If expression function
7481         is completion and return type is an access type do not freeze
7482         designated type: this will be done in the process of freezing
7483         the expression if needed.
7484         (Freeze_Expr_Types): Check whether type is complete before
7485         creating freeze node, to provide a better error message if
7486         reference is premature.
7487         * sem_ch13.adb (Check_Indexing_Functions): Ignore inherited
7488         functions created by type derivations.
7490 2017-04-25  Pascal Obry  <obry@adacore.com>
7492         * g-sercom.ads: Add simple usage of GNAT.Serial_Communication.
7494 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7496         * sem_res.adb (Resolve_Type_Conversion):
7497         When resolving against any fixed type, set the type of the
7498         operand as universal real when the operand is a multiplication
7499         or a division where both operands are of any fixed type.
7500         (Unique_Fixed_Point_Type): Add local variable ErrN. Improve the
7501         placement of an error message by pointing to the operand of a
7502         type conversion rather than the conversion itself.
7504 2017-04-25  Thomas Quinot  <quinot@adacore.com>
7506         * sem_ch13.adb (Build_Predicate_Function_Declaration): Set
7507         Needs_Debug_Info when producing SCOs.
7509 2017-04-25  Thomas Quinot  <quinot@adacore.com>
7511         * exp_ch6.adb (Add_Finalization_Master_Actual_To_Build_In_Place_Call):
7512         Always pass a null finalization master for a library level named access
7513         type to which a pragme No_Heap_Finalization applies.
7515 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
7517         PR ada/78845
7519         * a-ngcoar.adb, a-ngrear.adb (Inverse): call Unit_Matrix with First_1
7520         set to A'First(2) and vice versa.
7522 2017-04-25  Yannick Moy  <moy@adacore.com>
7524         * freeze.adb (Freeze_Record_Type): Remove obsolete
7525         rule on volatile tagged record restriction on SPARK code.
7527 2017-04-25  Yannick Moy  <moy@adacore.com>
7529         * sem_prag.adb (minor) Fix SPARK RM reference.
7531 2017-04-25  Yannick Moy  <moy@adacore.com>
7533         * sem_util.adb, sem_util.ads (Unique_Defining_Entity): Update
7534         comment to reflect which entity is chosen as unique entity.
7535         (Unique_Entity): Return full view instead of private spec for
7536         protected type or task type. Fix possible incorrect access when
7537         called on entry.
7539 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
7541         * sem_res.adb (Set_Slice_Subtype): Treat specially bit-packed
7542         array types only instead of all packed array types.
7544 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7546         * sem_ch6.adb (Conforming_Types): If type of formal as a specified
7547         dimension system, verify that dimensions of both match.
7548         (Check_Conformance): Add error message in case of dimension
7549         mismatch.
7550         * sem_dim.ads, sem_dim.adb (Dimensions_Match): New utility
7551         predicate.
7553 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
7555         * gnatxref.adb, gnatfind.adb: Avoid using the term project file,
7556         confusing.
7558 2017-04-25  Yannick Moy  <moy@adacore.com>
7560         * sem_util.adb: Minor refactoring.
7561         * freeze.adb (Freeze_Record_Type): Fix checking of SPARK RM 7.1.3(5).
7563 2017-04-25  Claire Dross  <dross@adacore.com>
7565         * sem_prag.adb (Collect_Inherited_Class_Wide_Conditions): Go to
7566         ultimate alias when accessing overridden operation. Indeed, if the
7567         overridden operation is itself inherited, it won't have any explicit
7568         contract.
7570 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7572         * sem_warn.adb (Warn_On_Overlapping_Actuals): There can be no
7573         overlap if the two formals have different types, because formally
7574         the corresponding actuals cannot designate the same objects.
7576 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7578         * sem_dim.adb (Dimensions_Of_Operand): minot cleanups: a) If
7579         dimensions are present from context, use them.  b) If operand is
7580         a static constant rewritten as a literal, obtain the dimensions
7581         from the original declaration, otherwise use dimensions of type
7582         established from context.
7584 2017-04-25  Yannick Moy  <moy@adacore.com>
7586         * sem_util.adb (Is_Effectively_Volatile): Protect against base type
7587         of array that is private.
7589 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
7591         * sem_ch3.adb, exp_util.adb, sem_prag.adb, exp_ch4.adb: Minor
7592         reformatting.
7594 2017-04-25  Yannick Moy  <moy@adacore.com>
7596         * a-ngelfu.adb, a-ngelfu.ads: Add SPARK_Mode On on spec, Off
7597         on body.
7599 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7601         * sem_disp.adb (Check_Dispatching_Context): Add guard to refine
7602         the check that recognizes a call to a private overridding and
7603         replaces the called subprogram with its alias.
7605 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7607         * exp_util.adb: Minor reformatting.
7609 2017-04-25  Justin Squirek  <squirek@adacore.com>
7611         * exp_ch3.adb (Freeze_Type): Add condition to always treat
7612         interface types as a partial view of a private type for the
7613         generation of invariant procedure bodies.
7614         * exp_util.adb, exp_util.ads (Add_Inherited_Invariants):
7615         Add a condition to get the Corresponding_Record_Type for
7616         concurrent types, add condition to return in the absence of a
7617         class in the pragma, remove call to Replace_Type_References,
7618         and add call to Replace_References.
7619         (Add_Interface_Invariatns),
7620         (Add_Parent_Invariants): Modify call to Add_Inherited_Invariants
7621         to including the working type T.
7622         (Add_Own_Invariants): Remove
7623         legacy condition for separate units, remove dispatching for ASIS
7624         and save a copy of the expression in the pragma expression.
7625         (Build_Invariant_Procedure_Body): Default initalize vars,
7626         remove return condition on interfaces, always use the
7627         private type for interfaces, and move the processing of types
7628         until after the processing of invariants for the full view.
7629         (Build_Invariant_Procedure_Declaration): Remove condition
7630         to return if an interface type is encountered and add
7631         condition to convert the formal parameter to its class-wide
7632         counterpart if Work_Typ is abstract.
7633         (Replace_Type): Add call to Remove_Controlling_Arguments.
7634         (Replace_Type_Ref): Remove class-wide dispatching for the current
7635         instance of the type.
7636         (Replace_Type_References): Remove parameter "Derived"
7637         (Remove_Controlling_Arguments): Created in order to removing
7638         the controlliong argument from calls to primitives in the case
7639         of the formal parameter being an class-wide abstract type.
7640         * sem_ch3.adb (Build_Assertion_Bodies_For_Type): Almost identical
7641         to the change made to Freeze_Type in exp_ch3. Add a condition
7642         to treat interface types as a partial view.
7643         * sem_prag.adb (Analyze_Pragma): Modify parameters in the call
7644         to Build_Invariant_Procedure_Declaration to properly generate a
7645         "partial" invariant procedure when Typ is an interface.
7647 2017-04-25  Bob Duff  <duff@adacore.com>
7649         * a-numeri.ads: Go back to using brackets encoding for the Greek
7650         letter pi.
7652 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7654         * sem_ch3.adb (Derive_Subprogram): Implement rule in RM 6.1.1
7655         (10-15): if derived type T with progenitors is abstract,
7656         and primitive P of this type inherits non-trivial classwide
7657         preconditions from both a parent operation and from an interface
7658         operation, then the inherited operation is abstract if the parent
7659         operation is not null.
7660         * sem_disp.ads, sem_disp.adb: replace function Covers_Some_Interface
7661         with Covered_Interface_Op to yield the actual interface operation
7662         that is implemented by a given inherited operation.
7664 2017-04-25  Javier Miranda  <miranda@adacore.com>
7666         * exp_ch4.adb (Expand_N_Op_Expon): Relocate left
7667         and right operands after performing the validity checks. Required
7668         because validity checks may remove side effects from the operands.
7670 2017-04-25  Javier Miranda  <miranda@adacore.com>
7672         * exp_attr.adb (Attribute_Unrestricted_Access):
7673         Do not disable implicit type conversion.  Required to generate
7674         code that displaces the pointer to reference the secondary
7675         dispatch table.
7677 2017-04-25  Pascal Obry  <obry@adacore.com>
7679         * prj-attr.adb, snames.ads-tmpl: Add package Install's
7680         Required_Artifacts attribute.
7682 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7684         * sem_util.adb (Same_Value): String literals are compile-time
7685         values, and comparing them must use Expr_Value_S.
7687 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7689         * sem_ch4.adb (Complete_Object_Interpretation): If an explicit
7690         dereference is introduced for the object, and the object is
7691         overloaded, do not check whether it is aliased, because it may
7692         include an implicit dereference.
7693         * sem_type.adb (Disambiguate): If two interpretations are access
7694         attribute types with the same designated type keep either of
7695         them and do not report an ambiguity.  A true ambiguity will be
7696         reported elsewhere.
7698 2017-04-25  Bob Duff  <duff@adacore.com>
7700         * a-numeri.ads: Change the encoding of Greek letter Pi from
7701         brackets encoding to UTF-8.  Use pragma Wide_Character_Encoding
7702         to indicate the encoding. We considered using a byte order mark
7703         (BOM), but that causes various trouble (misc software eats the
7704         BOM, if you have a patch with a BOM, then it's not at the start
7705         of the patch, so it's not a BOM, the BOM affects with-ing files,
7706         etc.).
7707         * scng.adb, s-wchcnv.adb: Minor.
7709 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7711         * sem_ch3.adb, sem_ch8.adb, sem_disp.adb: Minor reformatting.
7712 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7714         * sem_ch3.adb (Add_Internal_Interface_Entities): Move
7715         Has_Non_Trivial_Precondition to sem_util. for use elsewhere.
7716         Improve error message on operations that inherit non-conforming
7717         classwide preconditions from ancestor and progenitor.
7718         * sem_util.ads, sem_util.adb (Has_Non_Trivial_Precondition):
7719         moved here from sem_ch3.
7720         * sem_ch8.adb (Analyze_Subprogram_Renaming): Implement legality
7721         check given in RM 6.1.1 (17) concerning renamings of overriding
7722         operations that inherits class-wide preconditions from ancestor
7723         or progenitor.
7725 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7727         * exp_ch7.adb (Build_Adjust_Or_Finalize_Statements): Code cleanup.
7728         (Build_Adjust_Statements): Code cleanup.
7729         (Build_Finalizer): Update the initialization of
7730         Exceptions_OK.
7731         (Build_Finalize_Statements): Code cleanup.
7732         (Build_Initialize_Statements): Code cleanup.
7733         (Make_Deep_Array_Body): Update the initialization of
7734         Exceptions_OK.
7735         (Make_Deep_Record_Body): Update the initialization of Exceptions_OK.
7736         (Process_Object_Declaration): Generate a null exception handler only
7737         when exceptions are allowed.
7738         (Process_Transients_In_Scope): Update the initialization of
7739         Exceptions_OK.
7740         * exp_util.ads, exp_util.adb (Exceptions_In_Finalization_OK): New
7741         routine.
7742         * sem_ch11.adb (Analyze_Exception_Handlers): Do not check any
7743         restrictions when the handler is internally generated and the
7744         mode is warnings.
7746 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7748         * sem_ch3.adb (Has_Non_Trivial_Precondition): New predicate to
7749         enforce legality rule on classwide preconditions inherited from
7750         both an ancestor and a progenitor (RM 6.1.1 (10-13).
7751         * sem_disp.adb (Check_Dispatching_Context): A call to an abstract
7752         subprogram need not be dispatching if it appears in a precondition
7753         for an abstract or null subprogram.
7755 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
7757         * sem_ch10.adb: Minor typo fix.
7759 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
7761         * gcc-interface/Makefile.in: Cleanup VxWorks targets.
7763 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
7765         * fname.adb (Is_Internal_File_Name): Arrange for the slices to
7766         have a length which is a power of 2.
7767         (Is_Predefined_File_Name): Likewise. Adjust comment.
7769 2017-04-25  Bob Duff  <duff@adacore.com>
7771         * exp_aggr.adb (Component_Count): Protect the
7772         arithmetic from attempting to convert a value >= 2**31 to Int,
7773         which would otherwise raise Constraint_Error.
7775 2017-04-25  Bob Duff  <duff@adacore.com>
7777         * opt.ads (Locking_Policy): Fix incorrect documentation. The
7778         first character of the policy name is not unique.
7780 2017-04-25  Bob Duff  <duff@adacore.com>
7782         * s-fileio.adb (Name): Raise Use_Error if the file is a temp file.
7783         * s-ficobl.ads (Is_Temporary_File): Remove incorrect comment
7784         about this flag not being used. It was already used, and it is
7785         now used more.
7787 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7789         * einfo.adb Flag301 is now known as Ignore_SPARK_Mode_Pragmas.
7790         (Ignore_SPARK_Mode_Pragmas): New routine.
7791         (Set_Ignore_SPARK_Mode_Pragmas): New routine.
7792         (Write_Entity_Flags): Add an entry for Ignore_SPARK_Mode_Pragmas.
7793         * einfo.ads Add new attribute Ignore_SPARK_Mode_Pragmas and update
7794         related entities.
7795         (Ignore_SPARK_Mode_Pragmas): New routine
7796         along with pragma Inline.
7797         (Set_Ignore_SPARK_Mode_Pragmas): New routine along with pragma Inline.
7798         * opt.ads Rename flag Ignore_Pragma_SPARK_Mode to
7799         Ignore_SPARK_Mode_Pragmas_In_Instance.
7800         * sem_ch6.adb (Analyze_Subprogram_Body_Helper):
7801         Save and restore the value of global flag
7802         Ignore_SPARK_Mode_Pragmas_In_Instance. Set or reinstate the value
7803         of global flag Ignore_SPARK_Mode_Pragmas_In_Instance when either
7804         the corresponding spec or the body must ignore all SPARK_Mode
7805         pragmas found within.
7806         (Analyze_Subprogram_Declaration): Mark
7807         the spec when it needs to ignore all SPARK_Mode pragmas found
7808         within to allow the body to infer this property in case it is
7809         instantiated or inlined later.
7810         * sem_ch7.adb (Analyze_Package_Body_Helper): Save and restore the
7811         value of global flag Ignore_SPARK_Mode_Pragmas_In_Instance. Set
7812         the value of global flag Ignore_SPARK_Mode_Pragmas_In_Instance
7813         when the corresponding spec also ignored all SPARK_Mode pragmas
7814         found within.
7815         (Analyze_Package_Declaration): Mark the spec when
7816         it needs to ignore all SPARK_Mode pragmas found within to allow
7817         the body to infer this property in case it is instantiated or
7818         inlined later.
7819         * sem_ch12.adb (Analyze_Formal_Package_Declaration):
7820         Save and restore the value of flag
7821         Ignore_SPARK_Mode_Pragmas_In_Instance. Mark the
7822         formal spec when it needs to ignore all SPARK_Mode
7823         pragmas found within to allow the body to infer this
7824         property in case it is instantiated or inlined later.
7825         (Analyze_Package_Instantiation): Save and restore the value
7826         of global flag Ignore_SPARK_Mode_Pragmas_In_Instance. Mark
7827         the instance spec when it needs to ignore all SPARK_Mode
7828         pragmas found within to allow the body to infer this
7829         property in case it is instantiated or inlined later.
7830         (Analyze_Subprogram_Instantiation): Save and restore the value
7831         of global flag Ignore_SPARK_Mode_Pragmas_In_Instance. Mark the
7832         instance spec and anonymous package when they need to ignore
7833         all SPARK_Mode pragmas found within to allow the body to infer
7834         this property in case it is instantiated or inlined later.
7835         (Instantiate_Package_Body): Save and restore the value of global
7836         flag Ignore_SPARK_Mode_Pragmas_In_Instance. Set the value of
7837         global flag Ignore_SPARK_Mode_Pragmas_In_Instance when the
7838         corresponding instance spec also ignored all SPARK_Mode pragmas
7839         found within.
7840         (Instantiate_Subprogram_Body): Save and restore the
7841         value of global flag Ignore_SPARK_Mode_Pragmas_In_Instance. Set
7842         the value of global flag Ignore_SPARK_Mode_Pragmas_In_Instance
7843         when the corresponding instance spec also ignored all SPARK_Mode
7844         pragmas found within.
7845         * sem_prag.adb (Analyze_Pragma): Update the reference to
7846         Ignore_Pragma_SPARK_Mode.
7847         * sem_util.adb (SPARK_Mode_Is_Off): A construct which ignored
7848         all SPARK_Mode pragmas defined within yields mode "off".
7850 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7852         * bindgen.adb, exp_dbug.adb, errout.adb, fname.adb: Minor reformatting.
7854 2017-04-25  Bob Duff  <duff@adacore.com>
7856         * exp_atag.adb (Build_CW_Membership): Add "Suppress =>
7857         All_Checks" to avoid generating unnecessary checks.
7858         * exp_ch4.adb (Expand_N_In, Make_Tag_Check): Add "Suppress =>
7859         All_Checks".
7860         * sem.ads: Fix comment.
7861         * expander.ads: Fix comment.
7862         * exp_atag.ads: Fix comment: "Index = 0" should be
7863         "Index >= 0".
7865 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
7867         * s-taprop-linux.adb: Minor editorial fixes.
7869 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
7871         * sem_util.adb (New_Copy_Tree): Put back the declarations of the
7872         hash tables at library level.  Reinstate the NCT_Hash_Tables_Used
7873         variable and set it to True whenever the main hash table is
7874         populated.  Short- circuit the Assoc function if it is false
7875         and add associated guards.
7877 2017-04-25  Olivier Hainque  <hainque@adacore.com>
7879         * bindgen.adb (Gen_Elab_Calls): Also update counter of lone
7880         specs without elaboration code that have an elaboration counter
7881         nevertheless, e.g.  when compiled with -fpreserve-control-flow.
7882         * sem_ch10.adb (Analyze_Compilation_Unit):
7883         Set_Elaboration_Entity_Required when requested to preserve
7884         control flow, to ensure the unit elaboration is materialized at
7885         bind time, resulting in the inclusion of the unit object file
7886         in the executable closure at link time.
7888 2017-04-25  Pierre-Marie de Rodat  <derodat@adacore.com>
7890         * exp_dbug.adb: In Debug_Renaming_Declaration,
7891         when dealing with indexed component, accept to produce a renaming
7892         symbol when the index is an IN parameter or when it is a name
7893         defined in an outer scope.
7895 2017-04-25  Yannick Moy  <moy@adacore.com>
7897         * errout.adb (Error_Msg): Adapt continuation
7898         message in instantiations and inlined bodies for info messages.
7900 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
7902         * fname.adb (Has_Internal_Extension): Add pragma Inline.
7903         Use direct 4-character slice comparisons.
7904         (Has_Prefix): Add
7905         pragma Inline.  (Has_Suffix): Delete.
7906         (Is_Internal_File_Name):
7907         Test Is_Predefined_File_Name first.
7908         (Is_Predefined_File_Name):
7909         Use direct slice comparisons as much as possible and limit all
7910         comparisons to at most 8 characters.
7912 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7914         * checks.adb (Insert_Valid_Check): Code cleanup.
7915         * exp_ch6.adb (Add_Validation_Call_By_Copy_Code): New routine.
7916         (Expand_Actuals): Generate proper copy-back for a validation
7917         variable when it acts as the argument of a type conversion.
7918         * sem_util.adb (Is_Validation_Variable_Reference): Augment the
7919         predicate to operate on type qualifications.
7921 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7923         * sem_prag.adb, exp_ch6.adb, binde.adb, sem_disp.adb, s-fileio.adb:
7924         Minor reformatting.
7926 2017-04-25  Bob Duff  <duff@adacore.com>
7928         * sem_prag.adb (No_Return): Give an error if the pragma applies
7929         to a body. Specialize the error for the specless body case,
7930         as is done for (e.g.) pragma Convention.
7931         * debug.adb: Add switch -gnatd.J to disable the above legality
7932         checks. This is mainly for use in our test suite, to avoid
7933         rewriting a lot of illegal (but working) code.  It might also
7934         be useful to customers. Under this switch, if a pragma No_Return
7935         applies to a body, and the procedure raises an exception (as it
7936         should), the pragma has no effect. If the procedure does return,
7937         execution is erroneous.
7939 2017-04-25  Bob Duff  <duff@adacore.com>
7941         * exp_ch6.adb (Expand_Actuals): This is the
7942         root of the problem. It took N as an 'in out' parameter, and in
7943         some cases, rewrote N, but then set N to Original_Node(N). So
7944         the node returned in N had no Parent. The caller continued
7945         processing of this orphaned node. In some cases that caused a
7946         crash (e.g. Remove_Side_Effects climbs up Parents in a loop,
7947         and trips over the Empty Parent). The solution is to make N an
7948         'in' parameter.  Instead of rewriting it, return the list of
7949         post-call actions, so the caller can do the rewriting later,
7950         after N has been fully processed.
7951         (Expand_Call_Helper): Move most of Expand_Call here. It has
7952         too many premature 'return' statements, and we want to do the
7953         rewriting on return.
7954         (Insert_Post_Call_Actions): New procedure to insert the post-call
7955         actions in the appropriate place. In the problematic case,
7956         that involves rewriting N as an Expression_With_Actions.
7957         (Expand_Call): Call the new procedures Expand_Call_Helper and
7958         Insert_Post_Call_Actions.
7960 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7962         * sem_prag.adb (Inherits_Class_Wide_Pre): Cleanup code, handle
7963         properly type derived from generic formal types, to handle
7964         properly modified version of ACATS 4.1B B611017.
7966 2017-04-25  Javier Miranda  <miranda@adacore.com>
7968         * exp_unst.adb (Subp_Index): Adding missing
7969         support for renamings and functions that return a constrained
7970         array type (i.e. functions for which the frontend built a
7971         procedure with an extra out parameter).
7973 2017-04-25  Pascal Obry  <obry@adacore.com>
7975         * s-string.adb: Minor code clean-up.
7977 2017-04-25  Bob Duff  <duff@adacore.com>
7979         * s-os_lib.ads, s-os_lib.adb (Non_Blocking_Wait_Process): New
7980         procedure.
7981         * adaint.h, adaint.c (__gnat_portable_no_block_wait): C support
7982         function for Non_Blocking_Wait_Process.
7984 2017-04-25  Bob Duff  <duff@adacore.com>
7986         * prep.adb (Preprocess): Remove incorrect
7987         Assert. Current character can be ASCII.CR.
7989 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
7991         * sem_prag.adb (Set_Convention_From_Pragma): Cleanup code for
7992         convention Stdcall, which has a number of exceptions. Convention
7993         is legal on a component declaration whose type is an anonymous
7994         access to subprogram.
7996 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
7998         * sem_ch4.adb: sem_ch4.adb Various reformattings.
7999         (Try_One_Prefix_Interpretation): Use the base type when dealing
8000         with a subtype created for purposes of constraining a private
8001         type with discriminants.
8003 2017-04-25  Javier Miranda  <miranda@adacore.com>
8005         * einfo.ads, einfo.adb (Has_Private_Extension): new attribute.
8006         * warnsw.ads, warnsw.adb (All_Warnings): Set warning on late
8007         dispatching primitives (Restore_Warnings): Restore warning on
8008         late dispatching primitives (Save_Warnings): Save warning on late
8009         dispatching primitives (Do_Warning_Switch): Use -gnatw.j/-gnatw.J
8010         to enable/disable this warning.
8011         (WA_Warnings): Set warning on late dispatching primitives.
8012         * sem_ch3.adb (Analyze_Private_Extension_Declaration): Remember
8013         that its parent type has a private extension.
8014         * sem_disp.adb (Warn_On_Late_Primitive_After_Private_Extension):
8015         New subprogram.
8016         * usage.adb: Document -gnatw.j and -gnatw.J.
8018 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8020         * exp_ch7.adb, checks.adb, sem_prag.adb, eval_fat.adb: Minor
8021         reformatting.
8023 2017-04-25  Bob Duff  <duff@adacore.com>
8025         * binde.adb (Validate): Do not pass dynamic strings
8026         to pragma Assert, because older compilers do not support that.
8028 2017-04-25  Bob Duff  <duff@adacore.com>
8030         * s-fileio.adb (Close): When a temp file is
8031         closed, delete it and clean up its Temp_File_Record immediately,
8032         rather than waiting until later.
8033         (Temp_File_Record): Add File
8034         component, so Close can know which Temp_File_Record corresponds
8035         to the file being closed.
8036         (Delete): Don't delete temp files,
8037         because they are deleted by Close.
8038         (Open): Set the File component
8039         of Temp_File_Record. This requires moving the creation of the
8040         Temp_File_Record to the end, after the AFCB has been created.
8042 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8044         * checks.adb (Insert_Valid_Check): Do not generate
8045         a validity check when inside a generic.
8047 2017-04-25  Yannick Moy  <moy@adacore.com>
8049         * sem_res.adb (Resolve_Type_Conversion): Fix bad logic.
8051 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
8053         * snames.ads-tmpl (Snames): More names for detecting predefined
8054         potentially blocking subprograms.
8056 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8058         * sem_prag.adb (Analyze_Pre_Post_Condition): The rules
8059         concerning inheritance of class-wide preconditions do not apply
8060         to postconditions.
8062 2017-04-25  Bob Duff  <duff@adacore.com>
8064         * s-ficobl.ads: Minor comment fix.
8066 2017-04-25  Yannick Moy  <moy@adacore.com>
8068         * checks.adb (Apply_Scalar_Range_Check): Analyze precisely
8069         conversions from float to integer in GNATprove mode.
8070         (Apply_Type_Conversion_Checks): Make sure in GNATprove mode
8071         to call Apply_Type_Conversion_Checks, so that range checks
8072         are properly positioned when needed on conversions, including
8073         when converting from float to integer.  (Determine_Range): In
8074         GNATprove mode, take into account the possibility of conversion
8075         from float to integer.
8076         * sem_res.adb (Resolve_Type_Conversion): Only enforce range
8077         check on conversions from fixed-point to integer, not anymore
8078         on conversions from floating-point to integer, when in GNATprove
8079         mode.
8081 2017-04-25  Yannick Moy  <moy@adacore.com>
8083         * checks.adb (Determine_Range_R): Special case type conversions
8084         from integer to float in order to get bounds in that case too.
8085         * eval_fat.adb (Machine): Avoid issuing warnings in GNATprove
8086         mode, for computations involved in interval checking.
8088 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8090         * checks.adb (Insert_Valid_Check): Partially reimplement validity
8091         checks.
8092         * einfo.adb Node36 is now used as Validated_Object.
8093         (Validated_Object): New routine.
8094         (Set_Validated_Object): New routine.
8095         (Write_Field36_Name): Add an entry for Validated_Object.
8096         * einfo.ads Add new attribute Validated_Object along with
8097         usage in entities.
8098         (Validated_Object): New routine along with pragma Inline.
8099         (Set_Validated_Object): New routine along with pragma Inline.
8100         * exp_attr.adb (Make_Range_Test): Add processing for validation
8101         variables to avoid extra reads and copies of the prefix.
8102         * exp_ch6.adb (Expand_Actuals): Add copy-back for validation
8103         variables in order to reflect any changes done in the variable
8104         back into the original object.
8105         * sem_util.adb (Is_Validation_Variable_Reference): New routine.
8106         * sem_util.ads (Is_Validation_Variable_Reference): New routine.
8108 2017-04-25  Steve Baird  <baird@adacore.com>
8110         * exp_ch7.adb (Build_Array_Deep_Procs,
8111         Build_Record_Deep_Procs, Make_Finalize_Address_Body): Don't
8112         generate Finalize_Address routines for CodePeer.
8114 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8116         * sem_prag.adb (Inherits_Class_Wide_Pre): subsidiary of
8117         Analyze_Pre_Post_Condition, to implement the legality checks
8118         mandated by AI12-0131: Pre'Class shall not be specified for an
8119         overriding primitive subprogram of a tagged type T unless the
8120         Pre'Class aspect is specified for the corresponding primitive
8121         subprogram of some ancestor of T.
8123 2017-04-25  Bob Duff  <duff@adacore.com>
8125         * sem_ch8.adb (Use_One_Type): If a use_type_clause
8126         is redundant, set its Used_Operations to empty. This is only
8127         necessary for use clauses that appear in the parent of a generic
8128         child unit, because those use clauses get reanalyzed when we
8129         instantiate the generic, and we don't want the Used_Operations
8130         carried over from the original context (where it was probably
8131         not redundant).
8133 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8135         * exp_ch6.adb: Minor reformatting.
8137 2017-04-25  Bob Duff  <duff@adacore.com>
8139         * sem_prag.adb (Process_Restrictions_Or_Restriction_Warnings):
8140         Use Source_Index (Current_Sem_Unit) to find the correct casing.
8141         * exp_prag.adb (Expand_Pragma_Check): Use Source_Index
8142         (Current_Sem_Unit) to find the correct casing.
8143         * par.adb (Par): Null out Current_Source_File, to ensure that
8144         the above bugs won't rear their ugly heads again.
8146 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8148         * sem_ch8.adb (Find_Type): For an attribute reference
8149         'Class, if prefix type is synchronized and previous errors
8150         have suppressed the creation of the corresponding record type,
8151         create a spurious class-wide for the synchonized type itself,
8152         to catch other misuses of the attribute
8154 2017-04-25  Steve Baird  <baird@adacore.com>
8156         * exp_ch6.adb (Expand_Simple_Function_Return): if CodePeer_Mode
8157         is True, then don't generate the accessibility check for the
8158         tag of a tagged result.
8159         * exp_intr.adb (Expand_Dispatching_Constructor_Call):
8160         if CodePeer_Mode is True, then don't generate the
8161         tag checks for the result of call to an instance of
8162         Ada.Tags.Generic_Dispatching_Constructor (i.e., both the "is a
8163         descendant of" check and the accessibility check).
8165 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8167         * sem_ch13.adb: Code cleanups.
8168         * a-strbou.ads: minor whitespace fix in Trim for bounded strings.
8169         * sem_ch8.ads: Minor comment fix.
8171 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
8173         * exp_ch4.adb (Library_Level_Target): New function.
8174         (Expand_Concatenate): When optimization is enabled, also expand
8175         the operation out-of-line if the concatenation is present within
8176         the expression of the declaration of a library-level object and
8177         not only if it is the expression of the declaration.
8179 2017-04-25  Bob Duff  <duff@adacore.com>
8181         * freeze.adb (Freeze_Object_Declaration): Do
8182         not Remove_Side_Effects if there is a pragma Linker_Section,
8183         because in that case we want static initialization in the
8184         appropriate section.
8186 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
8188         * exp_dbug.adb: Minor rewording and reformatting.
8190 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8192         * sem_attr.adb (Statically_Denotes_Object): New predicate, to
8193         handle the proposed changes to rules concerning potentially
8194         unevaluated expressions, to include selected components that
8195         do not depend on discriminants, and indexed components with
8196         static indices.
8197         * sem_util.adb (Is_Potentially_Unevaluated): Add check for
8198         predicate in quantified expression, and fix bugs in the handling
8199         of case expressions and membership test.
8200         (Analyze_Attribute_Old_Result): use new predicate.
8201         (Analyze_Attribute, case Loop_Entry): ditto.
8203 2017-04-25  Bob Duff  <duff@adacore.com>
8205         * s-secsta.adb (SS_Info): Add a comment
8206         explaining why we don't need to walk all the chunks in order to
8207         compute the total size.
8209 2017-04-25  Bob Duff  <duff@adacore.com>
8211         * namet.ads, namet.adb (Global_Name_Buffer): Increase the length
8212         of the global name buffer to 4*Max_Line_Length.
8214 2017-04-25  Javier Miranda  <miranda@adacore.com>
8216         * exp_ch8.adb (Expand_N_Object_Renaming_Declaration): When creating a
8217         renaming entity for debug information, mark the entity as needing debug
8218         info if it comes from sources.
8220 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8222         * sem_ch13.adb (Analyze_Attribute_Definition_Clause): Remove the
8223         restriction converning the use of 'Address where the prefix is
8224         of a controlled type.
8226 2017-04-25  Pierre-Marie de Rodat  <derodat@adacore.com>
8228         * exp_dbug.adb: In Debug_Renaming_Declaration,
8229         skip slices that are made redundant by an indexed component
8230         access.
8231         * atree.h: New definition for Original_Node.
8233 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8235         * sem_prag.adb, sem_prag.ads: Minor reformatting.
8237 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8239         * sem_ch3.adb (Check_Entry_Contract): Call
8240         Preanalyze_Spec_Expression so that resolution takes place as well.
8241         * sem_util.adb (Check_Internal_Protected_Use): Reject properly
8242         internal calls that appear in preconditions of protected
8243         operations, in default values for same, and in contract guards
8244         for contract cases in SPARK.
8246 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
8248         * a-numaux.ads: Fix description of a-numaux-darwin
8249         and a-numaux-x86.
8250         (Double): Define to Long_Float.
8251         * a-numaux-vxworks.ads (Double): Likewise.
8252         * a-numaux-darwin.ads
8253         (Double): Likewise.
8254         * a-numaux-libc-x86.ads (Double): Define to Long_Long_Float.
8255         * a-numaux-x86.ads: Fix package description.
8256         * a-numaux-x86.adb (Is_Nan): Minor tweak.
8257         (Reduce): Adjust and complete description. Call Is_Nan instead of
8258         testing manually. Use an integer temporary to hold rounded value.
8259         * a-numaux-darwin.adb (Reduce): Likewise.
8260         (Is_Nan): New function.
8262 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8264         * sem_ch4.adb (Analyze_Selected_Component): Additional refinement
8265         on analysis of prefix whose type is a current instance of a
8266         synchronized type, but where the prefix itself is an entity that
8267         is an object.
8269 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8271         * exp_ch5.adb (Replace_Target): When rewriting the RHS, preserve
8272         the identity of callable entities therein, because they have been
8273         properly resolved, and prefixed calls may have been rewritten
8274         as normal calls.
8276 2017-04-25  Patrick Bernardi  <bernardi@adacore.com>
8278         * exp_ch3.adb (Build_Init_Statements): Convert
8279         the expression of the pragma/aspect Secondary_Stack_Size to
8280         internal type System.Parameters.Size_Type before assigning
8281         it to the Secondary_Stack_Size component of the task type's
8282         corresponding record.
8284 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
8286         * sem_eval.adb (Compile_Time_Compare): Reinstate the expr+literal
8287         (etc) optimizations when the type is modular and the offsets
8288         are equal.
8290 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
8292         * s-osinte-freebsd.ads: Minor comment tweaks
8294 2017-04-25  Javier Miranda  <miranda@adacore.com>
8296         * urealp.adb (UR_Write): Reverse previous patch
8297         adding documentation on why we generate multiplications instead
8298         of divisions (needed to avoid expressions whose computation with
8299         large numbers may cause division by 0).
8301 2017-04-25  Bob Duff  <duff@adacore.com>
8303         * erroutc.adb (Set_Specific_Warning_Off,
8304         Set_Warnings_Mode_Off): Use the correct source file for
8305         Stop. Was using Current_Source_File, which is only valid during
8306         parsing. Current_Source_File will have a leftover value from
8307         whatever file happened to be parsed last, because of a with_clause
8308         or something.
8310 2017-04-25  Bob Duff  <duff@adacore.com>
8312         * lib.ads, lib.adb (In_Internal_Unit): New functions similar
8313         to In_Predefined_Unit, but including GNAT units.
8314         * sem_util.ads, sem_util.adb (Should_Ignore_Pragma): Replace
8315         with Should_Ignore_Pragma_Par and Should_Ignore_Pragma_Sem,
8316         because Should_Ignore_Pragma was not working reliably outside
8317         the parser, because Current_Source_File is not valid.
8318         * sem_prag.adb, exp_prag.adb: Call Should_Ignore_Pragma_Sem.
8319         * par-prag.adb: Call Should_Ignore_Pragma_Par.
8321 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
8323         * gnat1drv.adb (Gnat1Drv): Disable Generate_Processed_File in
8324         codepeer mode.
8326 2017-04-25  Javier Miranda  <miranda@adacore.com>
8328         * urealp.adb (UR_Write): Fix output of constants with a base other
8329         that 10.
8331 2017-04-25  Justin Squirek  <squirek@adacore.com>
8333         * sem_ch13.adb (Get_Interfacing_Aspects): Moved to sem_util.adb.
8334         * sem_prag.adb (Analyze_Pragma, Process_Import_Or_Interface):
8335         Add extra parameter for Process_Interface_Name.
8336         (Process_Interface_Name): Add parameter for pragma to analyze
8337         corresponding aspect.
8338         * sem_util.ads, sem_util.adb (Get_Interfacing_Aspects): Added
8339         from sem_ch13.adb
8341 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
8343         * exp_ch7.adb, einfo.ads, sem_prag.adb: Minor reformatting and typo
8344         correction.
8346 2017-04-25  Yannick Moy  <moy@adacore.com>
8348         * sem_res.adb (Resolve_Comparison_Op): Do not
8349         attempt evaluation of relational operations inside assertions.
8351 2017-04-25  Justin Squirek  <squirek@adacore.com>
8353         * exp_util.adb (Add_Interface_Invariants):
8354         Restored, code moved back from Build_Invariant_Procedure_Body.
8355         (Add_Parent_Invariants): Restored, code moved back from
8356         Build_Invariant_Procedure_Body.
8357         (Build_Invariant_Procedure_Body):
8358         Remove refactored calls and integrated code from
8359         Add_Parent_Invariants and Add_Interface_Invariants.
8361 2017-04-25  Johannes Kanig  <kanig@adacore.com>
8363         * errout.adb (Output_Messages): Adjust computation of total
8364         errors
8365         * erroutc.adb (Error_Msg): In statistics counts, deal
8366         correctly with informational messages that are not warnings.
8367         * errutil.adb (Finalize): adjust computation of total errors.
8369 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
8371         * terminals.c (__gnat_terminate_pid): New.
8372         * g-exptty.ads (Terminate_Process): New. Update comments.
8374 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
8376         * a-cfinve.ads, a-cofove.ads (Empty_Vector): add Global contract.
8378 2017-04-25  Justin Squirek  <squirek@adacore.com>
8380         * sem_ch3.adb (Analyze_Declarations): Minor
8381         correction to comments, move out large conditional and scope
8382         traversal into a predicate.
8383         (Uses_Unseen_Lib_Unit_Priv): Predicate function made from extracted
8384         logic.
8386 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8388         * sem_ch4.adb (Analyze_Selected_Component): Refine analysis
8389         of prefix whose type is a current instance of a synchronized
8390         type. If the prefix is an object this is an external call (or
8391         requeue) that can only access public operations of the object. The
8392         previous predicate was too restrictive, and did not allow public
8393         protected operations, only task entries.
8395 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8397         * sem_ch5.adb, fname.adb: Minor reformatting.
8399 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8401         * einfo.adb (Is_Anonymous_Access_Type): New routine.
8402         * einfo.ads Update the placement of
8403         E_Anonymous_Access_Subprogram_Type along with all subtypes that
8404         mention the ekind.
8405         (Is_Anonymous_Access_Type): New routine.
8406         * exp_ch7.adb (Allows_Finalization_Master): Do not generate a
8407         master for an access type subject to pragma No_Heap_Finalization.
8408         * exp_util.adb (Build_Allocate_Deallocate_Proc): An object being
8409         allocated or deallocated does not finalization actions if the
8410         associated access type is subject to pragma No_Heap_Finalization.
8411         * opt.ads Add new global variable No_Heap_Finalization_Pragma.
8412         * par-prag.adb Pragma No_Heap_Finalization does not need special
8413         processing from the parser.
8414         * sem_ch6.adb (Check_Return_Subtype_Indication): Remove ancient
8415         ??? comments. Use the new predicate Is_Anonymous_Access_Type.
8416         * sem_prag.adb Add an entry in table Sig_Flags for pragma
8417         No_Heap_Finalization.
8418         (Analyze_Pragma): Add processing for
8419         pragma No_Heap_Finalization. Update various error messages to
8420         use Duplication_Error.
8421         * sem_util.ads, sem_util.adb (No_Heap_Finalization): New routine.
8422         * snames.ads-tmpl: Add new predefined name No_Heap_Finalization
8423         and corresponding pragma id.
8425 2017-04-25  Bob Duff  <duff@adacore.com>
8427         * freeze.adb (Freeze_Record_Type): Use the
8428         underlying type of the component type to determine whether it's
8429         elementary. For representation clause purposes, a private type
8430         should behave the same as its full type.
8431         * fname.ads, fname.adb (Is_Predefined_File_Name):
8432         Make sure things like "system.ali" are recognized as predefined.
8434 2017-04-25  Javier Miranda  <miranda@adacore.com>
8436         * debug.adb: Update documentation of -gnatd.6.
8438 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8440         * sem_ch5.adb (Preanalyze_Range): Handle properly an Ada2012
8441         element iterator when the name is an overloaded function call,
8442         one of whose interpretations yields an array.
8444 2017-04-25  Bob Duff  <duff@adacore.com>
8446         * uname.ads, uname.adb (Is_Predefined_Unit_Name,
8447         Is_Internal_Unit_Name): New functions for operating on unit
8448         names, as opposed to file names. There's some duplicated code
8449         with fname.adb, which is unfortunate, but it seems like we don't
8450         want to add dependencies here.
8451         * fname-uf.adb (Get_File_Name): Change Is_Predefined_File_Name
8452         to Is_Predefined_Unit_Name; the former was wrong, because Uname
8453         is not a file name at all.
8454         * fname.ads, fname.adb: Document the fact that
8455         Is_Predefined_File_Name and Is_Internal_File_Name can be called
8456         for ALI files, and fix the code so it works properly for ALI
8457         files. E.g. these should return True for "system.ali".
8459 2017-04-25  Justin Squirek  <squirek@adacore.com>
8461         * exp_util.adb (Add_Invariant): Removed,
8462         code moved to Add_Invariant_Check, Add_Inherited_Invariant,
8463         and Add_Own_Invariant.  (Add_Invariant_Check): Used
8464         for adding runtime checks from any kind of invariant.
8465         (Add_Inherited_Invariant): Generates invariant checks for
8466         class-wide invariants (Add_Interface_Invariants): Removed, code
8467         moved to Build_Invariant_Procedure_Body (Add_Own_Invariant):
8468         Create a types own invariant procedure (Add_Parent_Invariants):
8469         Removed, code moved to Build_Invariant_Procedure_Body
8470         (Build_Invariant_Procedure_Body): Add refactored calls
8471         and integrated code from Add_Parent_Invariants and
8472         Add_Interface_Invariants.
8473         (Process_Type): Removed, the
8474         relavant code was inlined into both Add_Own_Invariant and
8475         Add_Inherited_Invariant.
8477 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8479         * make.adb, par-ch2.adb, sem_util.adb, scans.ads, sem_ch8.adb,
8480         scn.adb, osint.adb, fname.adb: Minor reformatting.
8482 2017-04-25  Pascal Obry  <obry@adacore.com>
8484         * s-taprop-mingw.adb: Do not check for CloseHandle in
8485         Finalize_TCB.
8487 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8489         * sem_util.adb (Check_Part_Of_Reference):
8490         Continue to examine the context if the reference appears within
8491         an expression function.
8493 2017-04-25  Justin Squirek  <squirek@adacore.com>
8495         * exp_ch7.adb, exp_ch7.ads Remove Build_Invariant_Procedure_Body
8496         and Build_Invariant_Procedure_Declaration.
8497         * exp_util.ads, exp_util.adb Add Build_Invariant_Procedure_Body
8498         and Build_Invariant_Procedure_Declaration from exp_ch7
8499         and break-out Is_Untagged_Private_Derivation from
8500         Build_Invariant_Procedure_Body.
8501         (Replace_Type_References):
8502         Append an extra parameter to allow for dispatching replacements
8503         and add the corrasponding logic.
8504         (Type_Invariant): Remove
8505         Replace_Typ_Refs and replace its references with calls to
8506         Replace_Type_References.
8507         * sem_ch3.adb, sem_prag.adb: Remove with and use of exp_ch7.
8509 2017-04-25  Bob Duff  <duff@adacore.com>
8511         * sem_util.ads, sem_util.adb (Should_Ignore_Pragma): New function
8512         that returns True when appropriate.
8513         * par-prag.adb, exp_prag.adb, sem_prag.adb: Do not ignore pragmas
8514         when compiling predefined files.
8515         * fname.ads, fname.adb (Is_Predefined_File_Name): Fix bug:
8516         "gnat.adc" should not be considered a predefined file name.
8517         That required (or at least encouraged) a lot of cleanup of global
8518         variable usage. We shouldn't be communicating information via
8519         the global name buffer.
8520         * bindgen.adb, errout.adb, fname-uf.adb, lib-load.adb, make.adb,
8521         * restrict.adb, sem_ch10.adb, sem_ch6.adb, sem_ch8.adb: Changes
8522         required by the above-mentioned cleanup.
8524 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8526         * osint.adb (Find_File): Handle properly a request for a
8527         configuration file whose name is a directory.
8529 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8531         * sem_attr.adb, sem_ch5.adb: Minor reformatting.
8533 2017-04-25  Bob Duff  <duff@adacore.com>
8535         * types.ads: Minor: Fix '???' comment.
8536         * sem_ch8.adb: Minor comment fix.
8538 2017-04-25  Bob Duff  <duff@adacore.com>
8540         * sem_prag.adb: Remove suspicious uses of Name_Buf.
8541         * stringt.ads, stringt.adb, exp_dbug.adb, sem_dim.adb: Remove
8542         Add_String_To_Name_Buffer, to avoid using the global Name_Buf.
8543         Add String_To_Name with no side effects.
8545 2017-04-25  Justin Squirek  <squirek@adacore.com>
8547         * sem_ch3.adb (Analyze_Declarations): Add
8548         additional condition for edge case.
8550 2017-04-25  Bob Duff  <duff@adacore.com>
8552         * par-ch2.adb, scans.ads, scn.adb: Do not give an error for
8553         reserved words inside pragmas. This is necessary to allow the
8554         pragma name Interface to be used in pragma Ignore_Pragma.
8555         * par.adb: Minor comment fix.
8557 2017-04-25  Javier Miranda  <miranda@adacore.com>
8559         * a-tags.ads, a-tags.adb (Type_Is_Abstract): Renamed as Is_Abstract.
8560         * rtsfind.ads (RE_Type_Is_Abstract): Renamed as Is_Abstract.
8561         * exp_disp.adb (Make_DT): Update occurrences of RE_Type_Is_Abstract.
8562         * exp_intr.adb (Expand_Dispatching_Constructor_Call): Update
8563         occurrences of RE_Type_Is_Abstract
8565 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8567         * exp_util.adb (Build_Chain): Account for ancestor
8568         subtypes while traversing the derivation chain.
8570 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8572         * sem_attr.adb: minor reformatting.
8574 2017-04-25  Doug Rupp  <rupp@adacore.com>
8576         * sigtramp-vxworks-target.inc [PPC64]: Add a .localentry pseudo-op.
8578 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8580         * sem_ch5.adb (Analyze_Assignment): Reset Full_Analysis flag on
8581         the first pass over an assignment statement with target names,
8582         to prevent the generation of subtypes (such as discriminated
8583         record components)that may carry the target name outside of the
8584         tree for the assignment. The subtypes will be generated when
8585         the assignment is reanalyzed in full.
8586         (Analyze_Target_Name): Handle properly class-wide types.
8588 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8590         * elists.ads, elists.adb (Prepend_Unique_Elmt): New routine.
8591         * exp_ch3.adb (Freeze_Type): Signal the DIC body is created for
8592         the purposes of freezing.
8593         * exp_util.adb Update the documentation and structure of the
8594         type map used in class-wide semantics of assertion expressions.
8595         (Add_Inherited_Tagged_DIC): There is really no need to preanalyze
8596         and resolve the triaged expression because all substitutions
8597         refer to the proper entities.  Update the replacement of
8598         references.
8599         (Build_DIC_Procedure_Body): Add formal parameter
8600         For_Freeze. Add local variable Build_Body. Inherited DIC pragmas
8601         are now only processed when freezing occurs.  Build a body only
8602         when one is needed.
8603         (Entity_Hash): Removed.
8604         (Map_Types): New routine.
8605         (Replace_Object_And_Primitive_References): Removed.
8606         (Replace_References): New routine.
8607         (Replace_Type_References): Moved to the library level of Exp_Util.
8608         (Type_Map_Hash): New routine.
8609         (Update_Primitives_Mapping): Update the mapping call.
8610         (Update_Primitives_Mapping_Of_Types): Removed.
8611         * exp_util.ads (Build_DIC_Procedure_Body): Add formal
8612         parameter For_Freeze and update the comment on usage.
8613         (Map_Types): New routine.
8614         (Replace_References): New routine.
8615         (Replace_Type_References): Moved to the library level of Exp_Util.
8616         (Update_Primitives_Mapping_Of_Types): Removed.
8617         * sem_ch7.adb (Preserve_Full_Attributes): Propagate the DIC
8618         properties of the private type to the full view in case the full
8619         view derives from a parent type and inherits a DIC pragma.
8620         * sem_prag.adb (Analyze_Pragma): Guard against a case where a
8621         DIC pragma is placed at the top of a declarative region.
8623 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
8625         * a-tasatt.adb: Complete previous change and use an unsigned
8626         int to avoid overflow checks.
8628 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8630         * sem_attr.adb (Analyze_Attribute, case 'Access): Specialize
8631         the error message when the attribute reference is an actual in
8632         a call to a subprogram inherited from a generic formal type with
8633         unknown discriminants, which makes the subprogram and its formal
8634         parameters intrinsic (see RM 6.3.1 (8) and (13)).
8636 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8638         * sem_aggr.adb, inline.adb, einfo.adb, einfo.ads, scng.adb,
8639         sem_prag.adb: Minor reformatting.
8641 2017-04-25  Bob Duff  <duff@adacore.com>
8643         * sem_attr.adb (Type_Key): Add code in the
8644         recursive Compute_Type_Key to protect against fetching the source
8645         code for Standard, in case a component of the type is declared
8646         in Standard. There was already code to do this for the original
8647         type, but not for its components.
8649 2017-04-25  Javier Miranda  <miranda@adacore.com>
8651         * exp_ch3.adb (Build_Initialization_Call): Handle
8652         subtypes of private types when searching for the underlying full
8653         view of a private type.
8655 2017-04-25  Javier Miranda  <miranda@adacore.com>
8657         * sem_res.adb (Set_Mixed_Mode_Operand): A universal
8658         real conditional expression can appear in a fixed-type context
8659         and must be resolved with that context to facilitate the code
8660         generation to the backend.
8662 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8664         * einfo.adb, einfo.ads (Body_Needed_For_Inlining): New flag,
8665         to indicate whether during inline processing, when some unit U1
8666         appears in the context of a unit U2 compiled for instantiation
8667         or inlining purposes, the body of U1 needs to be compiled as well.
8668         * sem_prag.adb (Process_Inline): Set Body_Needed_For_Inlining if
8669         context is a package declaration.
8670         * sem_ch12.adb (Analyze_Generic_Subprogram_Declaration,
8671         Analyze_Generic_Package_Declaration): ditto.
8672         * inline.adb (Analyze_Inlined_Bodies): Check
8673         Body_Needed_For_Inlining.
8675 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8677         * par.adb (Current_Assign_Node): Global variable use to record
8678         the presence of a target_name in the right hand side of the
8679         assignment being parsed.
8680         * par-ch4.adb (P_Name): If the name is a target_name, mark the
8681         enclosing assignment node accordingly.
8682         * par-ch5.adb (P_Assignment_Statement): Set Current_Assign_Node
8683         appropriately.
8684         * sem_ch5.adb (Analyze_Assignment): Disable expansion before
8685         analyzing RHS if the statement has target_names.
8686         * sem_aggr.adb (Resolve_Iterated_Component_Association): Handle
8687         properly choices that are subtype marks.
8688         * exp_ch5.adb: Code cleanup.
8690 2017-04-25  Bob Duff  <duff@adacore.com>
8692         * s-memory.adb: Add a comment regarding efficiency.
8693         * atree.adb: Fix the assertion, and combine 2 assertions into one,
8694         "the source has an extension if and only if the destination does."
8695         * sem_ch3.adb, sem_ch13.adb: Address ??? comments.
8697 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
8699         * a-tasatt.adb (Set_Value): Fix handling of 32bits -> 64bits
8700         conversion.
8702 2017-04-25  Doug Rupp  <rupp@adacore.com>
8704         * init.c (__gnat_error_handler) [vxworks]: Turn on sigtramp
8705         handling for ppc64-vx7.
8706         * sigtramp-vxworks-target.inc
8707         [SIGTRAMP_BODY]: Add section for ppc64-vx7.
8709 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
8711         * ada_get_targ.adb: New file.
8713 2017-04-25  Bob Duff  <duff@adacore.com>
8715         * uintp.adb (Most_Sig_2_Digits): In case Direct (Right), fetch
8716         Direct_Val (Right), instead of the incorrect Direct_Val (Left).
8717         (UI_GCD): Remove ??? comment involving possible efficiency
8718         improvements. This just isn't important after all these years.
8719         Also minor cleanup.
8720         * uintp.ads: Minor cleanup.
8722 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8724         * exp_util.adb, exp_util.ads, sem_ch7.adb, sem_prag.adb, exp_ch3.adb:
8725         Revert previous changes.
8726         * scng.adb: Minor reformatting.
8727         * s-stratt.ads: Fix unbalanced parens in comment.
8729 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8731         * sem_ch3.adb, exp_util.adb, sem_prag.adb, freeze.adb, sem_util.adb:
8732         Minor reformatting.
8734 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8736         * scng.adb (Scan): Handle '@' appropriately.
8737         * sem_ch5.adb: Code cleanup.
8739 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8741         * freeze.adb (Check_Expression_Function): Do not check for the
8742         use of deferred constants if the freezing of the expression
8743         function is triggered by its generated body, rather than a
8744         premature use.
8746 2017-04-25  Javier Miranda  <miranda@adacore.com>
8748         * exp_attr.adb (Rewrite_Stream_Proc_Call): Handle
8749         subtypes of private types when performing the view conversion.
8751 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8753         * exp_ch3.adb (Freeze_Type): Signal the DIC body is created for
8754         the purposes of freezing.
8755         * exp_util.adb Update the documentation and structure of the
8756         type map used in class-wide semantics of assertion expressions.
8757         (Add_Inherited_Tagged_DIC): There is really no need to preanalyze
8758         and resolve the triaged expression because all substitutions
8759         refer to the proper entities.  Update the replacement of
8760         references.
8761         (Build_DIC_Procedure_Body): Add formal parameter
8762         For_Freeze. Add local variable Build_Body. Inherited DIC pragmas
8763         are now only processed when freezing occurs.  Build a body only
8764         when one is needed.
8765         (Entity_Hash): Removed.
8766         (Map_Types): New routine.
8767         (Replace_Object_And_Primitive_References): Removed.
8768         (Replace_References): New routine.
8769         (Replace_Type_References): Moved to the library level of Exp_Util.
8770         (Type_Map_Hash): New routine.
8771         (Update_Primitives_Mapping): Update the mapping call.
8772         (Update_Primitives_Mapping_Of_Types): Removed.
8773         * exp_util.ads (Build_DIC_Procedure_Body): Add formal
8774         parameter For_Freeze and update the comment on usage.
8775         (Map_Types): New routine.
8776         (Replace_References): New routine.
8777         (Replace_Type_References): Moved to the library level of Exp_Util.
8778         (Update_Primitives_Mapping_Of_Types): Removed.
8779         * sem_ch7.adb (Preserve_Full_Attributes): Propagate the DIC
8780         properties of the private type to the full view in case the full
8781         view derives from a parent type and inherits a DIC pragma.
8782         * sem_prag.adb (Analyze_Pragma): Guard against a case where a
8783         DIC pragma is placed at the top of a declarative region.
8785 2017-04-25  Tristan Gingold  <gingold@adacore.com>
8787         * s-mmap.ads (Data): Add pragma Inline.
8789 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
8791         * checks.adb (Insert_Valid_Check): Do not use
8792         a renaming to alias a volatile name because this will lead to
8793         multiple evaluations of the volatile name. Use a constant to
8794         capture the value instead.
8796 2017-04-25  Doug Rupp  <rupp@adacore.com>
8798         * init.c [VxWorks Section]: Disable sigtramp for ppc64-vx7.
8800 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8802         * exp_util.adb, exp_util.ads (Build_Class_Wide_Expression):
8803         Add out parameter to indicate to caller that a wrapper must
8804         be constructed for an inherited primitive whose inherited
8805         pre/postcondition has called to overridden primitives.
8806         * freeze.adb (Check_Inherited_Conditions): Build wrapper body
8807         for inherited primitive that requires it.
8808         * sem_disp.adb (Check_Dispatching_Operation): Such wrappers are
8809         legal primitive operations and belong to the list of bodies
8810         generated after the freeze point of a type.
8811         * sem_prag.adb (Build_Pragma_Check_Equivalent): Use new signature
8812         of Build_Class_Wide_Expression.
8813         * sem_util.adb, sem_util.ads (Build_Overriding_Spec): New procedure
8814         to construct the specification of the wrapper subprogram created
8815         for an inherited operation.
8817 2017-04-25  Bob Duff  <duff@adacore.com>
8819         * s-osinte-linux.ads (pthread_mutexattr_setprotocol,
8820         pthread_mutexattr_setprioceiling): Add new interfaces for these
8821         pthread operations.
8822         * s-taprop-linux.adb (Initialize_Lock, Initialize_TCB): Set
8823         protocols as appropriate for Locking_Policy 'C' and 'I'.
8824         * s-taprop-posix.adb: Minor reformatting to make it more similar
8825         to s-taprop-linux.adb.
8827 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
8829         * sem_ch3.adb (Get_Discriminant_Value, Search_Derivation_Levels):
8830         Handle properly a multi- level derivation involving both renamed
8831         and constrained parent discriminants, when the type to be
8832         constrained has fewer discriminants that the ultimate ancestor.
8834 2017-04-25  Bob Duff  <duff@adacore.com>
8836         * sem_util.adb (Is_Object_Reference): In the
8837         case of N_Explicit_Dereference, return False if it came from a
8838         conditional expression.
8840 2017-04-25  Bob Duff  <duff@adacore.com>
8842         * par-ch4.adb (P_Case_Expression): If a semicolon
8843         is followed by "when", assume that ";" was meant to be ",".
8845 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
8847         * sem_ch9.adb, sem_ch10.adb, sem_util.adb: Minor reformatting and typo
8848         fixes.
8850 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
8852         * rtsfind.ads (SPARK_Implicit_Load): New procedure for forced
8853         loading of an entity.
8854         * rtsfind.adb (SPARK_Implicit_Load): Body with a pattern
8855         previously repeated in the analysis.
8856         * sem_ch9.adb (Analyze_Protected_Type_Declaration): use new
8857         procedure SPARK_Implicit_Load.  (Analyze_Task_Type_Declaration):
8858         use new procedure SPARK_Implicit_Load.
8859         * sem_ch10.adb (Analyze_Compilation_Unit): Use new procedure
8860         SPARK_Implicit_Load.
8862 2017-04-25  Javier Miranda  <miranda@adacore.com>
8864         * sem_util.adb (New_Copy_Tree): By default
8865         copying of defining identifiers is prohibited because
8866         this would introduce an entirely new entity into the
8867         tree. This patch introduces an exception to this general
8868         rule: the declaration of constants and variables located in
8869         Expression_With_Action nodes.
8870         (Copy_Itype_With_Replacement): Renamed as Copy_Entity_With_Replacement.
8871         (In_Map): New subprogram.
8872         (Visit_Entity): New subprogram.
8873         (Visit_Node): Handle EWA_Level,
8874         EWA_Inner_Scope_Level, and take care of defining entities defined
8875         in Expression_With_Action nodes.
8877 2017-04-25  Thomas Quinot  <quinot@adacore.com>
8879         * exp_ch6.adb: minor comment edit.
8880         * sinfo.ads, sinfo.adb: New Null_Statement attribute for null
8881         procedure specifications that come from source.
8882         * par-ch6.adb (P_Subprogram, case of a null procedure): Set new
8883         Null_Statement attribute.
8884         * par_sco.adb (Traverse_Declarations_Or_Statements): For a null
8885         procedure, generate statement SCO for the generated NULL statement.
8886         * sem_ch6.adb (Analyze_Null_Procedure): Use null statement from
8887         parser, if available.
8889 2017-04-04  Andreas Krebbel  <krebbel@linux.vnet.ibm.com>
8891         * system-linux-s390.ads: Use Long_Integer'Size to define
8892         Memory_Size.
8894 2017-04-04  Eric Botcazou  <ebotcazou@adacore.com>
8896         * sem_ch3.adb (Build_Derived_Record_Type): Fix long line.
8898 2017-04-03  Jonathan Wakely  <jwakely@redhat.com>
8900         * doc/gnat_ugn/gnat_and_program_execution.rst: Fix typo.
8901         * g-socket.adb (To_Host_Entry): Fix typo in comment.
8902         * gnat_ugn.texi: Fix typo.
8903         * raise.c (_gnat_builtin_longjmp): Fix capitalization in comment.
8904         * s-stposu.adb (Allocate_Any_Controlled): Fix typo in comment.
8905         * sem_ch3.adb (Build_Derived_Record_Type): Likewise.
8906         * sem_util.adb (Mark_Coextensions): Likewise.
8907         * sem_util.ads (Available_Full_View_Of_Component): Likewise.
8909 2017-03-28  Andreas Schwab  <schwab@suse.de>
8911         PR ada/80117
8912         * system-linux-aarch64-ilp32.ads: New file.
8913         * gcc-interface/Makefile.in (LIBGNAT_TARGET_PAIRS_COMMON): Rename
8914         from LIBGNAT_TARGET_PAIRS.
8915         (LIBGNAT_TARGET_PAIRS_32, LIBGNAT_TARGET_PAIRS_64): Define.
8916         (LIBGNAT_TARGET_PAIRS): Use LIBGNAT_TARGET_PAIRS_COMMON, and
8917         LIBGNAT_TARGET_PAIRS_64 or LIBGNAT_TARGET_PAIRS_32 for -mabi=lp64
8918         or -mabi=ilp32, resp.
8920 2017-03-14  James Cowgill  <James.Cowgill@imgtec.com>
8922         * s-osinte-linux.ads (struct_sigaction): Use correct type for sa_flags.
8924 2017-03-08  Thanassis Tsiodras  <ttsiodras@gmail.com>
8926         PR ada/79903
8927         * socket.c (__gnat_gethostbyaddr): Add missing test for __rtems__.
8929 2017-03-08  Eric Botcazou  <ebotcazou@adacore.com>
8931         PR ada/79945
8932         * system-linux-ppc.ads (Default_Bit_Order): Use Standard's setting.
8934         * system-linux-arm.ads (Default_Bit_Order): Likewise.
8935         * system-linux-mips.ads (Default_Bit_Order): Likewise.
8936         * system-linux-armeb.ads: Delete.
8937         * system-linux-mipsel.ads: Likewise.
8938         * gcc-interface/Makefile.in (MIPS/Linux): Adjust.
8939         (ARM/Linux): Likewise.
8941 2017-02-24  Jakub Jelinek  <jakub@redhat.com>
8943         PR c/79677
8944         * gcc-interface/misc.c (gnat_handle_option): Pass true to
8945         handle_generated_option GENERATED_P.
8947 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
8949         * gcc-interface/decl.c (gnat_to_gnu_field): Do not remove the wrapper
8950         around a justified modular type if it doesn't have the same scalar
8951         storage order as the enclosing record type.
8953 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
8955         * gcc-interface/trans.c (gnat_to_gnu): Do not apply special handling
8956         of boolean rvalues to function calls.
8958 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
8960         * gcc-interface/utils.c (fold_bit_position): New function.
8961         (rest_of_record_type_compilation): Call it instead of bit_position to
8962         compute the field position and remove the call to remove_conversions.
8963         (compute_related_constant): Factor out the multiplication in both
8964         operands, if any, and streamline the final test.
8966 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
8968         * gcc-interface/trans.c (return_value_ok_for_nrv_p): Add sanity check.
8970 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
8972         * gcc-interface/decl.c: Include demangle.h.
8973         (is_cplusplus_method): Return again true for a primitive operation
8974         only if it is dispatching.  For a subprogram with an interface name,
8975         call the demangler to get the number of C++ parameters and compare it
8976         with the number of Ada parameters.
8978 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
8980         * gcc-interface/trans.c (Handled_Sequence_Of_Statements_to_gnu): If
8981         there is no end label, put the location of the At_End procedure on
8982         the call to the procedure.
8984 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
8986         * gcc-interface/misc.c (gnat_type_max_size): Try to return a meaningful
8987         value for array types with TYPE_INDEX_TYPE set on their domain type.
8988         * gcc-interface/utils.c (max_size): For operations and expressions, do
8989         not build a new node if the operands have not changed or are missing.
8991 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
8993         * gcc-interface/utils.c (max_size) <tcc_expression>: Flip the second
8994         argument when recursing on TRUTH_NOT_EXPR.
8996 2017-02-12  John Marino  <gnugcc@marino.st>
8998         * system-freebsd-x86.ads: Rename into...
8999         * system-freebsd.ads: ...this.
9000         (Default_Bit_Order): Define using Standard'Default_Bit_Order.
9001         * gcc-interface/Makefile.in: Support aarch64-freebsd.
9002         (x86-64/FreeBSD): Adjust to above renaming.
9003         (i386/FreeBSD): Likewise.
9005 2017-02-09  Gerald Pfeifer  <gerald@pfeifer.com>
9007         * comperr.adb: Update FSF bug reporting URL.
9009 2017-02-01  Eric Botcazou  <ebotcazou@adacore.com>
9010             Jakub Jelinek  <jakub@redhat.com>
9012         PR ada/79309
9013         * adaint.c (__gnat_killprocesstree): Fix broken string handling.
9015 2017-01-25  Maxim Ostapenko  <m.ostapenko@samsung.com>
9017         PR lto/79061
9018         * gcc-interface/utils.c (get_global_context): Pass main_input_filename
9019         to build_translation_unit_decl.
9021 2017-01-23  Javier Miranda  <miranda@adacore.com>
9023         * sem_util.adb (New_Copy_Tree): Code cleanup:
9024         removal of the internal map (ie. variable Actual_Map, its
9025         associated local variables, and all the code handling it).
9026         * sem_ch9.adb (Analyze_Task_Type_Declaration): in GNATprove mode
9027         force loading of the System package when processing a task type.
9028         (Analyze_Protected_Type_Declaration): in GNATprove mode force
9029         loading of the System package when processing a protected type.
9030         * sem_ch10.adb (Analyze_Compilation_Unit): in GNATprove mode
9031         force loading of the System package when processing compilation
9032         unit with a main-like subprogram.
9033         * frontend.adb (Frontend): remove forced loading of the System
9034         package.
9036 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
9038         * sem_prag.adb (Default_Initial_Condition): If the desired type
9039         declaration is a derived type declaration with discriminants,
9040         it is rewritten as a private type declaration.
9041         * sem_ch13.adb (Replace_Type_References_Generic,
9042         Visible_Component): A discriminated private type with descriminnts
9043         has components that must be rewritten as selected components
9044         if they appear as identifiers in an aspect expression such as
9045         a Default_Initial_Condition.
9046         * sem_util.adb (Defining_Entity): support N_Iterator_Specification
9047         nodes.
9049 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9051         * ghost.ads, ghost.adb (Is_Ignored_Ghost_Unit): New routine.
9052         * gnat1drv.adb Generate an empty object file for an ignored
9053         Ghost compilation unit.
9054         * inline.adb, sem_util.adb, sem_ch4.adb: Minor reformatting.
9056 2017-01-23  Yannick Moy  <moy@adacore.com>
9058         * sem_ch4.adb (Analyze_Indexed_Component_Form):
9059         Adapt to inlined prefix with string literal subtype.
9060         * inline.adb (Expand_Inlined_Call): Keep unchecked
9061         conversion inside inlined call when formal type is constrained.
9063 2017-01-23  Javier Miranda  <miranda@adacore.com>
9065         * sem_util.adb (New_Copy_Tree): Code cleanup:
9066         removal of global variables. All the global variables, global
9067         functions and tables of this subprogram are now declared locally.
9069 2017-01-23  Gary Dismukes  <dismukes@adacore.com>
9071         * exp_strm.ads: Minor reformatting and typo fixes.
9073 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9075         * sem_aggr.adb, par_sco.adb, exp_util.adb, sem.adb, sem_ch4.adb,
9076         exp_aggr.adb: Minor reformatting.
9077         * g-diopit.adb: minor grammar/punctuation fix in comment.
9078         * g-byorma.ads: minor fix of unbalanced parens in comment.
9080 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9082         * par.adb: Update the documentation of component Labl.
9083         * par-ch6.adb (P_Return_Statement): Set the expected label of
9084         an extended return statement to Error.
9086 2017-01-23  Tristan Gingold  <gingold@adacore.com>
9088         * s-boustr.ads, s-boustr.adb (Is_Full): New function.
9090 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
9092         * expander.adb: Handle N_Delta_Aggregate.
9094 2017-01-23  Javier Miranda  <miranda@adacore.com>
9096         * exp_ch6.adb (Expand_Call): Improve the code that
9097         checks if some formal of the called subprogram is a class-wide
9098         interface, to handle subtypes of class-wide interfaces.
9100 2017-01-23  Javier Miranda  <miranda@adacore.com>
9102         * checks.adb (Apply_Parameter_Aliasing_Checks):
9103         Remove side effects of the actuals before generating the overlap
9104         check.
9106 2017-01-23  Justin Squirek  <squirek@adacore.com>
9108         * exp_strm.ads, exp_strm.ads
9109         (Build_Record_Or_Elementary_Input_Function): Add an extra parameter so
9110         as to avoid getting the underlying type by default.
9111         * exp_attr.adb (Expand_N_Attribute_Reference): Remove use of
9112         underlying type in the Iiput and output attribute cases when
9113         building their respective functions.
9115 2017-01-23  Gary Dismukes  <dismukes@adacore.com>
9117         * scng.adb: Minor reformatting of error message.
9119 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
9121         * sem_ch6.adb (Analyze_Expression_Function): Do not attempt
9122         to freeze the return type of an expression funxtion that is a
9123         completion, if the type is a limited view and the non-limited
9124         view is available.
9126 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
9128         * par-ch4.adb (P_Aggregate_Or_Parent_Expr): Recognize delta
9129         aggregate construct.
9130         (P_Record_Or_Array_Component_Association): An array aggregate
9131         can start with an Iterated_Component_Association.
9132         * scng.adb: Modify error message on improper use of @ in earlier
9133         versions of the language.
9134         * sinfo.ads: New node kind N_Delta_Aggregate.
9135         * sinfo.adb: An N_Delta_Aggregate has component associations and
9136         an expression.
9137         * sem_res.adb (Resolve): Call Resolve_Delta_Aggregate.
9138         * sem_aggr.ads, sem_aggr.adb (Resolve_Iterated_Component_Association):
9139         Create a new index for each one of the choices in the association,
9140         to prevent spurious homonyms in the scope.
9141         (Resolve_Delta_Aggregate): New.
9142         * sem.adb: An N_Delta_Aggregate is analyzed like an aggregate.
9143         * exp_util.adb (Insert_Actions): Take into account
9144         N_Delta_Aggregate.
9145         * exp_aggr.ads: New procedure Expand_N_Delta_Aggregate.
9146         * exp_aggr.adb: New procedure Expand_N_Delta_Aggregate,
9147         and local procedures Expand_Delta_Array_Aggregate and
9148         expand_Delta_Record_Aggregate.
9149         * sprint.adb: Handle N_Delta_Aggregate.
9151 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9153         * exp_ch11.adb (Expand_N_Exception_Declaration): Generate an
9154         empty name when the exception declaration is subject to pragma
9155         Discard_Names.
9156         (Null_String): New routine.
9158 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9160         * par-ch9.adb (P_Protected_Definition): Parse
9161         any optional and potentially illegal pragmas which appear in
9162         a protected operation declaration list.
9163         (P_Task_Items): Parse
9164         any optional and potentially illegal pragmas which appear in a
9165         task item list.
9167 2017-01-23  Pascal Obry  <obry@adacore.com>
9169         * s-taprop-mingw.adb (Enter_Task): Initialize the Thread handle which
9170         is needed when a foreign thread call a Win32 API using a thread handle
9171         like GetThreadTimes() for example.
9173 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9175         * sem_ch13.adb (Analyze_Attribute_Definition_Clause): Do not
9176         allow an 'Address clause to be specified on a prefix of a
9177         class-wide type.
9179 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9181         * checks.adb (Insert_Valid_Check): Ensure that the prefix of
9182         attribute 'Valid is a renaming of the original expression when
9183         the expression denotes a name. For all other kinds of expression,
9184         use a constant to capture the value.
9185         * exp_util.adb (Is_Name_Reference): Moved to Sem_Util.
9186         * sem_util.ads, sem_util.adb (Is_Name_Reference): Moved from Exp_Util.
9188 2017-01-23  Justin Squirek  <squirek@adacore.com>
9190         * sem_eval.adb (Eval_Integer_Literal): Add special
9191         case to avoid optimizing out check if the literal appears in
9192         an if-expression.
9194 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9196         * sem_ch13.adb (Analyze_Attribute_Definition_Clause): Do not
9197         allow an 'Address clause to be specified on a prefix of a
9198         class-wide type.
9200 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9202         * checks.adb (Insert_Valid_Check): Ensure that the prefix of
9203         attribute 'Valid is a renaming of the original expression when
9204         the expression denotes a name. For all other kinds of expression,
9205         use a constant to capture the value.
9206         * exp_util.adb (Is_Name_Reference): Moved to Sem_Util.
9207         * sem_util.ads, sem_util.adb (Is_Name_Reference): Moved from Exp_Util.
9209 2017-01-23  Justin Squirek  <squirek@adacore.com>
9211         * sem_eval.adb (Eval_Integer_Literal): Add special
9212         case to avoid optimizing out check if the literal appears in
9213         an if-expression.
9215 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
9217         * sem_ch4.adb (Try_Primitive_Operations,
9218         Is_Valid_First_Argument_Of): argument is valid if it is a derived
9219         type with unknown discriminants that matches its underlying
9220         record view.
9221         * exp_util.adb (Expand_Subtype_From_Expr): Do not expand
9222         expression if its type is derived from a limited type with
9223         unknown discriminants, because the expansion (which is a call)
9224         must be expanded in the enclosing context to add the proper build-
9225         in-place parameters to the call.
9226         * lib.ads, exp_ch9.adb: Minor fixes in comments.
9228 2017-01-23  Yannick Moy  <moy@adacore.com>
9230         * frontend.adb (Frontend): Do not load runtime
9231         unit for GNATprove when parsing failed.
9232         * exp_ch9.adb: minor removal of extra whitespace
9233         * exp_ch6.adb: minor typo in comment
9234         * sem_util.adb: Code cleanup.
9235         * exp_ch9.ads, par-ch2.adb: minor style fixes in whitespace and comment
9236         * a-ngcefu.adb: minor style fix in whitespace
9238 2017-01-23  Thomas Quinot  <quinot@adacore.com>
9240         * scos.ads: Document usage of 'd' as default SCO kind for
9241         declarations.
9242         * par_sco.adb (Traverse_Declarations_Or_Statements.
9243         Traverse_Degenerate_Subprogram): New supporting routine for expression
9244         functions and null procedures.
9245         (Traverse_Declarations_Or_Statements.Traverse_One): Add
9246         N_Expression_Function to the subprogram case; add required
9247         support for null procedures and expression functions.
9249 2017-01-23  Bob Duff  <duff@adacore.com>
9251         * namet.ads (Bounded_String): Decrease the size of type
9252         Bounded_String to avoid running out of stack space.
9253         * namet.ads (Append): Don't ignore buffer overflow; raise
9254         Program_Error instead.
9256 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9258         * exp_ch5.adb, freeze.adb, par-ch4.adb, scng.adb, sem_ch13.adb,
9259         sem_ch3.adb, sem_ch5.adb, sem_ch5.ads, sem_util.adb, sinfo.ads: Minor
9260         reformatting.
9261         * exp_ch9.adb: minor style fix in comment.
9263 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
9265         * sem_ch4.adb (Analyze_Allocator): Handle properly a type derived
9266         for a limited record extension with unknown discriminants whose
9267         full view has no discriminants.
9269 2017-01-23  Yannick Moy  <moy@adacore.com>
9271         * exp_spark.adb: Alphabetize with clauses.
9273 2017-01-23  Yannick Moy  <moy@adacore.com>
9275         * sem_util.adb (Has_Enabled_Property): Treat
9276         protected objects and variables differently from other variables.
9278 2017-01-23  Thomas Quinot  <quinot@adacore.com>
9280         * sem_ch13.adb (Adjust_Record_For_Reverse_Bit_Order):
9281         Split original Ada 95 part off into new subprogram
9282         below. Call that subprogram (instead of proceeding with
9283         AI95-0133 behaviour) if debug switch -gnatd.p is in use.
9284         (Adjust_Record_For_Reverse_Bit_Order_Ada_95): ... new subprogram
9285         * debug.adb Document new switch -gnatd.p
9286         * freeze.adb (Freeze_Entity.Freeze_Record_Type): Do not adjust
9287         record for reverse bit order if an error has already been posted
9288         on the record type.  This avoids generating extraneous "info:"
9289         messages for illegal code.
9291 2017-01-23  Justin Squirek  <squirek@adacore.com>
9293         * sem_ch3.adb (Analyze_Declarations): Correct comments
9294         * freeze.adb (Find_Constant): Add detection of deferred constants
9295         so they are not incorrectly flagged as premature.
9297 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
9299         * scans.ads: New token At_Sign. Remove '@' from list of illegal
9300         characters for future version of the language. '@' is legal name.
9301         * scng.ads, scng.adb (Scan):  Handle '@' appropriately.
9302         * scn.adb (Scan_Reserved_Identifier): An occurrence of '@'
9303         denotes a Target_Name.
9304         * par-ch4.adb (P_Name, P_Primary): Handle Target_Name.
9305         * sinfo.ads, sinfo.adb (N_Target_Name): New non-terminal node.
9306         (Has_Target_Names): New flag on N_Assignment_Statement, to
9307         indicate that RHS has occurrences of N_Target_Name.
9308         * sem.adb: Call Analyze_Target_Name.
9309         * sem_ch5.ads, sem_ch5.adb (Analyze_Target_Name): New subpogram.
9310         (urrent_LHS): Global variable that denotes LHS of assignment,
9311         used in the analysis of Target_Name nodes.
9312         * sem_res.adb (Resolve_Target_Name): New procedure.
9313         * exp_ch5.adb (Expand_Assign_With_Target_Names): (AI12-0125):
9314         N is an assignment statement whose RHS contains occurences of @
9315         that designate the value of the LHS of the assignment. If the
9316         LHS is side-effect free the target names can be replaced with
9317         a copy of the LHS; otherwise the semantics of the assignment
9318         is described in terms of a procedure with an in-out parameter,
9319         and expanded as such.
9320         (Expand_N_Assignment_Statement): Call
9321         Expand_Assign_With_Target_Names when needed.
9322         * exp_util.adb (Insert_Actions): Take into account N_Target_Name.
9323         * sprint.adb: Handle N_Target_Name.
9325 2017-01-23  Eric Botcazou  <ebotcazou@adacore.com>
9327         * checks.adb: Minor fix in comment.
9329 2017-01-23  Philippe Gil  <gil@adacore.com>
9331         * g-debpoo.adb (Do_Report) remove freed chunks from chunks
9332         count in Sort = Memory_Usage or Allocations_Count
9334 2017-01-23  Justin Squirek  <squirek@adacore.com>
9336         * sem_ch3.adb: Code cleanup.
9338 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9340         * sem_prag.adb (Analyze_Refined_Depends_In_Decl_Part): Move all global
9341         variables to the local variable section. Update the profile
9342         of various nested routine that previously had visibility
9343         of those globals. One the matching phase has completed,
9344         remove certain classes of clauses which are considered noise.
9345         (Check_Dependency_Clause): Properly detect a match between two
9346         'Result attributes. Update the various post-match cases to use
9347         Is_Already_Matched as this routine now automatically recognizes
9348         a previously matched 'Result attribute.
9349         (Is_Already_Matched): New routine.
9350         (Remove_Extra_Clauses): New routine.
9351         (Report_Extra_Clauses): Remove the detection of ... => null
9352         clauses as this is now done in Remove_Extra_Clauses.
9354 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
9356         * sem_aggr.adb (Resolve_Array_Aggregate): In ASIS mode do not
9357         report on spurious overlaps between values involving a subtype
9358         with a static predicate, because the expansion of such a subtype
9359         into individual ranges in inhibited in ASIS mode.
9361 2017-01-23  Justin Squirek  <squirek@adacore.com>
9363         * sem_ch3.adb (Analyze_Declarations): Add detection
9364         of an edge case and delay freezing if it is present.
9366 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9368         * sem_ch3.adb, exp_spark.adb, exp_attr.adb, sem_ch9.adb, sem_prag.adb,
9369         sem_util.adb, sem_warn.adb, exp_ch3.adb: Minor reformatting.
9371 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9373         * freeze.adb (Freeze_Subprogram): Ensure that all anonymous
9374         access-to-subprogram types inherit the convention of the
9375         associated subprogram.  (Set_Profile_Convention): New routine.
9376         * sem_ch6.adb (Check_Conformance): Do not compare the conventions
9377         of the two entities directly, use Conventions_Match to account
9378         for anonymous access-to-subprogram and subprogram types.
9379         (Conventions_Match): New routine.
9381 2017-01-23  Claire Dross  <dross@adacore.com>
9383         * exp_spark.adb (Expand_SPARK_Attribute_Reference): For attributes
9384         which return Universal_Integer, force the overflow check flag for
9385         Length and Range_Length for types as big as Long_Long_Integer.
9387 2017-01-23  Claire Dross  <dross@adacore.com>
9389         * exp_spark.adb (Expand_SPARK_Attribute_Reference):  For
9390         attributes which return Universal_Integer, introduce a conversion
9391         to the expected type with the appropriate check flags set.
9392         * sem_res.adb (Resolve_Range): The higher bound can be in Typ's
9393         base type if the range is null. It may still be invalid if it
9394         is higher than the lower bound. This is checked later in the
9395         context in which the range appears.
9397 2017-01-23  Pierre-Marie de Rodat  <derodat@adacore.com>
9399         * scos.ads: Introduce a constant to represent ignored
9400         dependencies in SCO_Unit_Table_Entry.
9402 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
9404         * exp_ch9.adb (Expand_N_Protected_Type_Declaration): Remove extra
9405         spaces from error messages.
9407 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
9409         * exp_ch3.adb (Check_Large_Modular_Array): New procedure,
9410         subsidiary to Expand_N_Object_ Declaration, to compute a guard on
9411         an object declaration for an array type with a modular index type
9412         with the size of Long_Long_Integer. Special processing is needed
9413         in this case to compute reliably the size of the object, and
9414         eventually  to raise Storage_Error, when wrap-around arithmetic
9415         might compute a meangingless size for the object.
9417 2017-01-23  Justin Squirek  <squirek@adacore.com>
9419         * a-wtenau.adb, par-endh.adb, sem_prag.adb,
9420         sem_type.adb: Code cleanups.
9422 2017-01-23  Bob Duff  <duff@adacore.com>
9424         * sem_res.adb (Resolve_Call): In the part of the code where
9425         it is deciding whether to turn the call into an indexed
9426         component, avoid doing so if the call is to an instance of
9427         Unchecked_Conversion. Otherwise, the compiler turns it into an
9428         indexed component, and resolution of that turns it back into a
9429         function call, and so on, resulting in infinite recursion.
9430         * sem_util.adb (Needs_One_Actual): If the first formal has a
9431         default, then return False.
9433 2017-01-21  Eric Botcazou  <ebotcazou@adacore.com>
9435         * sem_eval.adb (Compile_Time_Compare): Reinstate the expr+literal (etc)
9436         optimizations when the type is modular and the offsets are equal.
9438 2017-01-20  Thomas Quinot  <quinot@adacore.com>
9440         * sem_warn.adb (Warn_On_Useless_Assignment): Adjust wording of warning
9441         message.
9443 2017-01-20  Nicolas Roche  <roche@adacore.com>
9445         * terminals.c: Ignore failures on setpgid and tcsetpgrp commands.
9447 2017-01-20  Bob Duff  <duff@adacore.com>
9449         * sem_eval.adb (Compile_Time_Compare): Disable the expr+literal
9450         (etc) optimizations when the type is modular.
9452 2017-01-20  Yannick Moy  <moy@adacore.com>
9454         * sem_ch6.adb (Move_Pragmas): move some pragmas,
9455         but copy the SPARK_Mode pragma instead of moving it.
9456         (Build_Subprogram_Declaration): Ensure that the generated spec
9457         and original body share the same SPARK_Pragma aspect/pragma.
9458         * sem_util.adb, sem_util.ads (Copy_SPARK_Mode_Aspect): New
9459         procedure to copy SPARK_Mode aspect.
9461 2017-01-20  Bob Duff  <duff@adacore.com>
9463         * sem_ch3.adb (Analyze_Declarations): Disable Resolve_Aspects
9464         even in ASIS mode.
9465         * sem_ch13.adb (Resolve_Name): Enable setting the entity to
9466         Empty even in ASIS mode.
9468 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
9470         * exp_ch9.adb: minor style fixes in comments.
9471         * sem_ch9.adb (Analyze_Delay_Relative): in GNATprove mode a delay
9472         relative statement introduces an implicit dependency on
9473         Ada.Real_Time.Clock_Time.
9474         * sem_util.adb: Minor reformatting.
9476 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
9478         * sem_ch13.adb (Analyze_Aspect_Specifications): Aspect Alignment
9479         must be treated as delayed aspect even if the expression is
9480         a literal, because the aspect affects the freezing and the
9481         elaboration of the object to which it applies.
9483 2017-01-20  Tristan Gingold  <gingold@adacore.com>
9485         * s-osinte-vxworks.ads (Interrup_Range): New subtype.
9487 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
9489         * lib-xref.adb (Generate_Reference): Do not warn about the
9490         presence of a pragma Unreferenced if the entity appears as the
9491         actual in a procedure call that does not come from source.
9493 2017-01-20  Pascal Obry  <obry@adacore.com>
9495         * expect.c, terminals.c: Fix some warnings about unused variables.
9496         * gsocket.h, adaint.c, adaint.h: Fix some more warnings in the C part
9497         of the runtime.
9499 2017-01-20  Bob Duff  <duff@adacore.com>
9501         * exp_attr.adb (Constrained): Apply an access check (check that
9502         the prefix is not null) when the prefix denotes an object of an
9503         access type; that is, when there is an implicit dereference.
9505 2017-01-20  Gary Dismukes  <dismukes@adacore.com>
9507         * s-rident.ads (constant Profile_Info): Remove
9508         No_Calendar from GNAT_Extended_Ravenscar restrictions.
9510 2017-01-20  Tristan Gingold  <gingold@adacore.com>
9512         *  s-maccod.ads: Add pragma No_Elaboration_Code_All
9514 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
9516         * ghost.adb (Mark_Ghost_Clause): New routine.
9517         (Prune_Node): Do not prune compilation unit nodes.
9518         (Remove_Ignored_Ghost_Code): Prune the compilation unit node directly.
9519         This does not touch the node itself, but does prune all its fields.
9520         * ghost.ads (Mark_Ghost_Clause): New routine.
9521         * sem_ch8.adb (Analyze_Use_Package): Emit an error when a use
9522         package clause mentions Ghost and non-Ghost packages. Mark a
9523         use package clause as Ghost when it mentions a Ghost package.
9524         (Analyze_Use_Type): Emit an error when a use type clause mentions
9525         Ghost and non-Ghost types. Mark a use type clause as Ghost when
9526         it mentions a Ghost type.
9527         * sem_ch10.adb (Analyze_With_Clause): Mark a with clause as
9528         Ghost when it withs a Ghost unit.
9530 2017-01-20  Javier Miranda  <miranda@adacore.com>
9532         * sem_res.adb (Resolve_Call): If a function call
9533         returns a limited view of a type and at the point of the call the
9534         function is not declared in the extended main unit then replace
9535         it with the non-limited view, which must be available. If the
9536         called function is in the extended main unit then no action is
9537         needed since the back-end handles this case.
9539 2017-01-20  Eric Botcazou  <ebotcazou@adacore.com>
9541         * sem_ch7.adb (Contains_Subp_Or_Const_Refs): Rename into...
9542         (Contains_Subprograms_Refs): ...this.  Adjust comment
9543         for constants.  (Is_Subp_Or_Const_Ref): Rename into...
9544         (Is_Subprogram_Ref): ...this.
9545         (Has_Referencer): Rename Has_Non_Subp_Const_Referencer variable into
9546         Has_Non_Subprograms_Referencer and adjust comment.  Remove
9547         incorrect shortcut for package declarations and bodies.
9549 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
9551         * sem_ch3.adb (Complete_Private_Subtype): If the scope of the
9552         base type differs from that of the completion and the private
9553         subtype is an itype (created for a constraint on an access
9554         type e.g.), set Delayed_Freeze on both to prevent out-of-scope
9555         anomalies in gigi.
9557 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
9559         * sem_ch6.adb (Analyze_Subprogram_Body_Helper):
9560         When inheriting the SPARK_Mode of a prior expression function,
9561         look at the properly resolved entity rather than the initial
9562         candidate which may denote a homonym.
9564 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
9566         * sem_prag.adb (Rewrite_Assertion_Kind): If the name is
9567         Precondition or Postcondition, and the context is pragma
9568         Check_Policy, indicate that this Pre-Ada2012 usage is deprecated
9569         and suggest the standard names Assertion_Policy /Pre /Post
9570         instead.
9572 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
9574         * sem_ch10.adb, sem_cat.adb: Minor reformatting.
9576 2017-01-20  Javier Miranda  <miranda@adacore.com>
9578         * sem_ch3.adb (Access_Type_Declaration): Protect access to the
9579         Entity attribute.
9580         * sem_ch10.adb (Install_Siblings): Skip processing malformed trees.
9581         * sem_cat.adb (Validate_Categoriztion_Dependency): Skip processing
9582         malformed trees.
9584 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
9586         * sem_ch13.adb (Analyze_Aspect_Specification, case
9587         Dynamic_Predicate): If the entity E is a subtype that inherits
9588         a static predicate for its parent P,, the inherited and the
9589         new predicate combine in the generated predicate function,
9590         and E only has a dynamic predicate.
9592 2017-01-20  Tristan Gingold  <gingold@adacore.com>
9594         * s-boustr.ads, s-boustr.adb: New package.
9595         * Makefile.rtl: Add s-boustr.
9597 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
9599         * inline.adb (Process_Formals): Qualify the
9600         expression of a return statement when it yields a universal type.
9602 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
9604         * freeze.adb (Freeze_All): Freeze the default
9605         expressions of all eligible formal parameters that appear in
9606         entries, entry families, and protected subprograms.
9608 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
9610         * sem_ch3.adb (Check_Nonoverridable_Aspects); Refine check
9611         for illegal inherited Implicit_Dereference aspects with renamed
9612         discriminants.
9614 2017-01-20  Javier Miranda  <miranda@adacore.com>
9616         * debug.adb (switch d.6): do not avoid declaring unreferenced itypes.
9617         * nlists.ads (Lock_Lists, Unlock_Lists): New subprograms.
9618         * nlists.adb (Lock_Lists, Unlock_Lists): New subprograms.
9619         (Set_First, Set_Last, Set_List_Link, Set_Next, Set_Parent,
9620         Set_Prev, Tree_Read): Adding assertion.
9621         * atree.ads (Lock_Nodes, Unlock_Nodes): New subprograms.
9622         * atree.adb (Lock_Nodes, Unlock_Nodes): New subprograms.
9623         (Set_Analyzed, Set_Check_Actuals, Set_Comes_From_Source,
9624         Set_Ekind, Set_Error_Posted, Set_Has_Aspects,
9625         Set_Is_Ignored_Ghost_Node, Set_Original_Node, Set_Paren_Count,
9626         Set_Parent, Set_Sloc, Set_Nkind, Set_FieldNN, Set_NodeNN,
9627         Set_ListNN, Set_ElistNN, Set_NameN, Set_StrN, Set_UintNN,
9628         Set_UrealNN, Set_FlagNNN, Set_NodeN_With_Parent,
9629         Set_ListN_With_Parent): Adding assertion.
9631 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
9633         * sem_prag.adb (Process_Convention): Diagnose properly a pragma
9634         import that applies to several homograph subprograms. when one
9635         of them is declared by a subprogram body.
9637 2017-01-20  Justin Squirek  <squirek@adacore.com>
9639         * exp_ch6.adb (Expand_Call): Remove optimization
9640         that nulls out calls to null procedures.
9642 2017-01-20  Yannick Moy  <moy@adacore.com>
9644         * inline.adb (Expand_Inlined_Call): Keep more
9645         precise type of actual for inlining whenever possible. In
9646         particular, do not switch to the formal type in GNATprove mode in
9647         some case where the GNAT backend might require it for visibility.
9649 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
9651         * sem_ch3.adb (Check_Non_Overridable_Aspects): An inherited
9652         aspect Implicit_Dereference can be inherited by a full view if
9653         the partial view has no discriminants, because there is no way
9654         to apply the aspect to the partial view.
9655         (Build_Derived_Record_Type): If derived type renames discriminants
9656         of the parent, the new discriminant inherits the aspect from
9657         the old one.
9658         * sem_ch4.adb (Analyze_Call): Handle properly a parameterless
9659         call through an access discriminant designating a subprogram.
9660         * sem_ch5.adb (Analyze_Assignment): (Analyze_Call): Handle
9661         properly a parameterless call through an access discriminant on
9662         the left-hand side of an assignment.
9663         * sem_res.adb (resolve): If an interpreation involves a
9664         discriminant with an implicit dereference and the expression is an
9665         entity, resolution takes place later in the appropriate routine.
9666         * sem_ch13.adb (Analyze_Aspect_Implicit_Dereference): Recognize
9667         access discriminants that designate a subprogram type.
9669 2017-01-20  Pascal Obry  <obry@adacore.com>
9671         * a-locale.adb, a-locale.ads: Update Ada.Locales for RM 2012 COR:1:2016
9673 2017-01-20  Yannick Moy  <moy@adacore.com>
9675         * sem_ch10.adb (Check_No_Elab_Code_All): Do not issue an error
9676         on implicitly with'ed units in GNATprove mode.
9677         * sinfo.ads (Implicit_With): Document use of flag for implicitly
9678         with'ed units in GNATprove mode.
9680 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
9682         * sem_cat.adb (Validate_Static_Object_Name): In a preelaborated
9683         unit Do not report an error on a non-static entity that appears
9684         in the context of a spec expression, such as an aspect expression.
9686 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
9688         * einfo.adb: Flag298 now denotes Is_Underlying_Full_View.
9689         (Is_Underlying_Full_View): New routine.
9690         (Set_Is_Underlying_Full_View): New routine.
9691         (Write_Entity_Flags): Add an entry for Is_Underlying_Full_View.
9692         * einfo.ads Add new attribute Is_Underlying_Full_View.
9693         (Is_Underlying_Full_View): New routine along with pragma Inline.
9694         (Set_Is_Underlying_Full_View): New routine along with pragma Inline.
9695         * exp_util.adb (Build_DIC_Procedure_Body): Do not consider
9696         class-wide types and underlying full views. The first subtype
9697         is used as the working type for all Itypes, not just array base types.
9698         (Build_DIC_Procedure_Declaration): Do not consider
9699         class-wide types and underlying full views. The first subtype
9700         is used as the working type for all Itypes, not just array
9701         base types.
9702         * freeze.adb (Freeze_Entity): Inherit the freeze node of a full
9703         view or an underlying full view without clobbering the attributes
9704         of a previous freeze node.
9705         (Inherit_Freeze_Node): New routine.
9706         * sem_ch3.adb (Build_Derived_Private_Type): Mark an underlying
9707         full view as such.
9708         (Build_Underlying_Full_View): Mark an underlying full view as such.
9709         * sem_ch7.adb (Install_Private_Declarations): Mark an underlying
9710         full view as such.
9712 2017-01-20  Yannick Moy  <moy@adacore.com>
9714         * sinfo.ads: Document lack of Do_Division_Check flag
9715         on float exponentiation.
9717 2017-01-19  Javier Miranda  <miranda@adacore.com>
9719         * ghost.adb (Propagate_Ignored_Ghost_Code): Protect access to the
9720         identifier attribute of a block-statement node. Required to avoid
9721         assertion failure when building the new containers library.
9723 2017-01-19  Bob Duff  <duff@adacore.com>
9725         * exp_ch3.adb: Update comment.
9727 2017-01-19  Vincent Celier  <celier@adacore.com>
9729         * gprep.adb (Gnatprep): Parse the definition file without
9730         "replace in comments" even when switch -C is used.
9732 2017-01-19  Justin Squirek  <squirek@adacore.com>
9734         * exp_ch9.adb (Is_Pure_Barrier): Create function
9735         Is_Count_Attribute to identify an expansion of the 'Count
9736         attribute.
9738 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
9740         * sem_ch5.adb (Analyze_Loop_Statement): In GNATprove mode the
9741         statements within an element iterator loop are only analyzed
9742         agter the loop is rewritten. Within a generic the analysis must
9743         be performed in any case to complete name capture.
9745 2017-01-19  Bob Duff  <duff@adacore.com>
9747         * sem_prag.adb (Analyze_Pragma): Check for ignored pragmas first,
9748         before checking for unrecognized pragmas.
9749         Initialize Pname on its declarations; that's always good style.
9751 2017-01-19  Claire Dross  <dross@adacore.com>
9753         * exp_ch7.adb (Build_Invariant_Procedure_Body): Semi-insert the
9754         body into the tree for GNATprove by setting its Parent field. The
9755         components invariants of composite types are not checked by
9756         the composite type's invariant procedure in GNATprove mode.
9757         (Build_Invariant_Procedure_Declaration): Semi-insert the
9758         declaration into the tree for GNATprove by setting its Parent
9759         field.
9760         * freeze.adb (Freeze_Arry_Type):In GNATprove mode, do not add
9761         the component invariants to the array type  invariant procedure
9762         so that the procedure can be used to  check the array type
9763         invariants if any.
9764         (Freeze_Record_Type): In GNATprove mode, do
9765         not add the component invariants to the record type  invariant
9766         procedure so that the procedure can be used to  check the record
9767         type invariants if any.
9769 2017-01-19  Hristian Kirtchev  <kirtchev@adacore.com>
9771         * lib-xref-spark_specific.adb: Minor reformatting.
9772         * exp_ch7.adb (Add_Parent_Invariants): Do not process array types.
9774 2017-01-19  Javier Miranda  <miranda@adacore.com>
9776         * exp_aggr.adb (Pass_Aggregate_To_Back_End): Renamed as
9777         Build_Back_End_Aggregate.
9778         (Generate_Aggregate_For_Derived_Type): Code cleanup.
9779         (Prepend_Stored_Values): Code cleanup.
9781 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
9783         * sem_ch6.adb (Analyze_Expression_Function): Check for an
9784         incomplete return type after attempting to freeze it, so that
9785         other freeze actiona are generated in the proper order.
9787 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
9789         * sem_aggr.adb (Resolve_Aggregate): If the type is a string
9790         type, ie. a type whose component is a character type, and the
9791         aggregate is positional, do not convert into a string literal
9792         if the index type is not an integer type, because the original
9793         type may be required in an enclosing operation.
9795 2017-01-19  Bob Duff  <duff@adacore.com>
9797         * binde.adb, debug.adb: Enable new elaboration order algorithm
9798         by default. -dp switch reverts to the old algorithm.
9800 2017-01-19  Hristian Kirtchev  <kirtchev@adacore.com>
9802         * sem_ch3.adb Add with and use clauses for Exp_Ch7.
9803         (Analyze_Declarations): Create the DIC and Invariant
9804         procedure bodies s after all freezing has taken place.
9805         (Build_Assertion_Bodies): New routine.
9806         * sem_ch7.adb Remove the with and use clauses for Exp_Ch7
9807         and Exp_Util.
9808         (Analyze_Package_Specification): Remove the
9809         generation of the DIC and Invariant procedure bodies. This is
9810         now done by Analyze_Declarations.
9811         * sem_disp.adb (Check_Dispatching_Operation): DIC and Invariant
9812         procedures are never treated as primitives.
9814 2017-01-19  Yannick Moy  <moy@adacore.com>
9816         * frontend.adb: Analyze inlined bodies and check elaboration
9817         rules in GNATprove mode too.
9818         * sem_elab.adb (Delay_Element): Add Boolean component to save
9819         indication that call is in SPARK code.  (Check_Elab_Calls):
9820         Check elaboration rules in GNATprove mode, and correctly set
9821         the current value of SPARK_Mode.
9822         * lib-xref-spark_specific.adb
9823         (Add_SPARK_Xrefs): Simplify iteration over dereferences.
9825 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
9827         * exp_ch4.adb (Expand_Concatenate): Do no enable overflow
9828         checks on the expression for the high bound of concatenation
9829         when checks are disabled, to suppress warnings about potential
9830         constraint errors in restricted runtimes.
9832 2017-01-19  Hristian Kirtchev  <kirtchev@adacore.com>
9834         * exp_ch3.adb (Expand_Freeze_Enumeration_Type): Mark the
9835         representation-to-position function as inlined.
9836         * sem_cat.adb (Set_Categorization_From_Scope): Do not modify
9837         the purity of an internally generated entity if it has been
9838         explicitly marked as pure for optimization purposes.
9839         * exp_aggr.adb: Minor reformatting.
9841 2017-01-19  Javier Miranda  <miranda@adacore.com>
9843         * exp_ch6.adb (Expand_Call): Remove side effects on
9844         actuals that are allocators with qualified expression since the
9845         initialization of the object is performed by means of individual
9846         statements (and hence it must be done before the call).
9848 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
9850         * sem_ch3.adb (Analyze_Declarations): Minor reformatting.
9851         (Build_Derived_Enumeration_Type): If the derived type inherits a
9852         dynamic predicate from its parent, the bounds of the type must
9853         freeze because an explicit constraint is constructed for the
9854         type and the corresponding range is elaborated now.
9856 2017-01-19  Arnaud Charlet  <charlet@adacore.com>
9858         * sem_attr.ads: minor fix of inconsistent casing in comment
9859         * lib-writ.ads: minor align comments in columns
9860         * sem_ch3.adb: Minor reformatting.
9861         * spark_xrefs.ads: minor fix typo in SPARK-related comment
9862         * table.ads: minor style fix in comment
9863         * lib-xref-spark_specific.adb
9864         (Add_SPARK_Xrefs): simplify processing of SPARK cross-references.
9865         * sem_ch12.adb: minor whitespace fix
9866         * freeze.adb: Add comment.
9867         * sem_util.adb (Unique_Name): for instances of
9868         generic subprograms ignore the name of the wrapper package.
9870 2017-01-19  Javier Miranda  <miranda@adacore.com>
9872         * exp_aggr.adb (Resolve_Record_Aggregate):
9873         Factorize code needed for aggregates of limited and unlimited
9874         types in a new routine.
9875         (Pass_Aggregate_To_Back_End): New subprogram.
9877 2017-01-19  Yannick Moy  <moy@adacore.com>
9879         * sinfo.adb (Pragma_Name): Only access up to Last_Pair of Pragma_Map.
9881 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
9883         * sem_ch4.ads, sem_ch4.adb (Try_Object_Operation): Make subprogram
9884         public, for use elsewhere.
9885         * sem_ch6.adb (Analyze_Procedure_Call): In SPARK_Mode and within
9886         an Inlined_body, recognize a call that uses object notation
9887         and has not been rewritten as a regular call because regular
9888         expansion has not taken place.
9890 2017-01-19  Bob Duff  <duff@adacore.com>
9892         * checks.adb (Apply_Type_Conversion_Checks): Disable small optimization
9893         in case of generic formal discrete types, because it causes crashes in
9894         the compiler when built with assertions on.
9896 2017-01-19  Hristian Kirtchev  <kirtchev@adacore.com>
9898         * lib-xref-spark_specific.adb, sem_util.adb, sem_util.ads,
9899         sem_ch4.adb, sem_ch8.adb, lib-xref.ads: Minor reformatting.
9901 2017-01-19  Bob Duff  <duff@adacore.com>
9903         * bcheck.adb (Check_Consistent_Dynamic_Elaboration_Checking):
9904         Increment Warnings_Detected.  It was decrementing, which is
9905         wrong since we just issued a warning message.
9906         * binderr.ads (Errors_Detected, Warnings_Detected): Declare
9907         these variables to be of subtype Nat instead of Int, because
9908         they should never be negative.
9910 2017-01-19  Javier Miranda  <miranda@adacore.com>
9912         * contracts.adb (Build_Postconditions_Procedure): Replace
9913         Generate_C_Code by Modify_Tree_For_C.
9914         * exp_aggr.adb (Build_Record_Aggr_Code, Expand_Array_Aggregate):
9915         Replace Generate_C_Code by Modify_Tree_For_C.
9916         * exp_attr.adb (Float_Valid, Is_GCC_Target): Replace Generate_C_Code by
9917         Modify_Tree_For_C.
9918         * exp_ch11.adb (Expand_N_Exception_Declaration): Replace
9919         Generate_C_Code by Modify_Tree_For_C.
9920         * exp_ch4.adb (Expand_Allocator_Expression): Replace
9921         Generate_C_Code by Modify_Tree_For_C.
9922         * exp_dbug.adb (Qualify_Entity_Name): Replace Generate_C_Code
9923         by Modify_Tree_For_C.
9924         * exp_util.adb (Remove_Side_Effects, Side_Effect_Free): Replace
9925         Generate_C_Code by Modify_Tree_For_C.
9926         * sem_res.adb (Resolve_Type_Conversion): Replace Generate_C_Code
9927         by Modify_Tree_For_C.
9928         * sinfo.ads (Modify_Tree_For_C): Adding documentation.
9930 2017-01-19  Javier Miranda  <miranda@adacore.com>
9932         * sem_util.ads, sem_util.adb (Expression_Of_Expression_Function): New
9933         subprogram.
9934         (Is_Inlinable_Expression_Function): New subprogram.
9935         * exp_ch6.ads, exp_ch6.adb (Expression_Of_Expression_Function): Moved
9936         to Sem_Util.
9937         (Is_Inlinable_Expression_Function): Moved to Sem_Util.
9939 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
9941         * sem_ch4.adb (Diagnose_Call): Improve error message when a
9942         selected component has a prefix that might be interpreted
9943         as a parameterless function call, but none of the candidate
9944         interpretations is parameterless, and there is a hidden homonym
9945         of the prefix that is a package.
9946         * sem_ch8.adb (Find_Selected_Component): If the prefix might be
9947         interpreted as a parameterless function call and its analysis
9948         fails, do not call Analyze_Selected_Component.
9950 2017-01-19  Steve Baird  <baird@adacore.com>
9952         * sem_util.ads: Add new Use_Full_View Boolean parameter to
9953         Get_Index_Bounds.
9954         * sem_util.adb (Get_Index_Bounds): replace calls to Scalar_Range with
9955         calls to a newly-defined Scalar_Range_Of_Right_View function.
9957 2017-01-19  Arnaud Charlet  <charlet@adacore.com>
9959         * gnat1drv.adb: minor fix of unbalanced parens in comment
9960         * lib-xref.ads (Traverse_Compilation_Unit): declaration moved
9961         to visible part of the package to allow re-use in GNATprove.
9962         * lib-xref-spark_specific.adb (Traverse_Stub): routine refactored
9963         from repeated code of Traverse_Compilation_Unit.
9964         (Traverse_Declaration_Or_Statement): fixed detection of
9965         generic subprograms and packages; also, iteration over case
9966         statement alternatives rewritten to avoid testing if the first
9967         alternative is present (since it must be present due to Ada
9968         syntax restrictions).
9970 2017-01-19  Hristian Kirtchev  <kirtchev@adacore.com>
9972         * exp_ch6.adb (Expand_N_Subprogram_Body): Mark the spec as
9973         returning by reference not just for subprogram body stubs,
9974         but for all subprogram cases.
9975         * sem_util.adb: Code reformatting.
9976         (Requires_Transient_Scope): Update the call to Results_Differ.
9977         (Results_Differ): Update the parameter profile and the associated
9978         comment on usage.
9980 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
9982         * sem_dim.adb (Analyze_Dimension): Analyze object declaration and
9983         identifier nodes that do not come from source, to handle properly
9984         dimensionality check within an inlined body which inclddes both
9985         original operands and rewritten operands. This removes spurious
9986         dimensionality errors in the presence of front-end inlining,
9987         as well as in SPARK mode.
9989 2017-01-16  Jakub Jelinek  <jakub@redhat.com>
9991         PR driver/49726
9992         * gcc-interface/lang.opt (gant, gnatO, gnat): Add Driver flag.
9994 2017-01-13  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
9996         * gcc-interface/Makefile.in (SPARC/Solaris): Fix typo.
9998 2017-01-13  Arnaud Charlet  <charlet@adacore.com>
10000         * doc/gnat_ugn/getting_started_with_gnat.rst,
10001         doc/gnat_ugn/inline_assembler.rst,
10002         doc/gnat_ugn/building_executable_programs_with_gnat.rst,
10003         doc/gnat_ugn/elaboration_order_handling_in_gnat.rst,
10004         doc/gnat_ugn/about_this_guide.rst,
10005         doc/gnat_ugn/platform_specific_information.rst,
10006         doc/gnat_ugn/example_of_binder_output.rst,
10007         doc/gnat_ugn/gnat_and_program_execution.rst,
10008         doc/gnat_ugn/gnat_utility_programs.rst,
10009         doc/gnat_ugn/the_gnat_compilation_model.rst,
10010         doc/gnat_rm/implementation_defined_attributes.rst,
10011         doc/gnat_rm/compatibility_and_porting_guide.rst,
10012         doc/gnat_rm/standard_library_routines.rst,
10013         doc/gnat_rm/standard_and_implementation_defined_restrictions.rst,
10014         doc/gnat_rm/implementation_defined_pragmas.rst,
10015         doc/gnat_rm/the_gnat_library.rst,
10016         doc/gnat_rm/obsolescent_features.rst,
10017         doc/gnat_rm/about_this_guide.rst,
10018         doc/gnat_rm/the_implementation_of_standard_i_o.rst,
10019         doc/gnat_rm/implementation_of_ada_2012_features.rst,
10020         doc/gnat_rm/interfacing_to_other_languages.rst,
10021         doc/gnat_rm/implementation_defined_aspects.rst,
10022         doc/gnat_rm.rst: Update documentation.
10023         * gnat_rm.texi, gnat_ugn.texi: Regenerated.
10025 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
10027         * einfo.ads: minor grammar fixes in comment of Normalized_Position_Max.
10028         * scil_ll.adb: Minor style fix in comment.
10029         * sem_ch8.adb (Analyze_Expanded_Name): Perform dimension analysis
10030         even if entity is already set, because the node may be renalyzed
10031         after inlining transformations.
10033 2017-01-13  Javier Miranda  <miranda@adacore.com>
10035         * sem_res.adb (Resolve_Call): Do not establish a transient scope
10036         for a call to inlinable expression function (since the call will
10037         be replaced by its returned object).
10038         * exp_ch6.ads (Is_Inlinable_Expression_Function): New subprogram.
10039         * exp_ch6.adb (Expression_Of_Expression_Function): New subprogram.
10040         (Expand_Call): For inlinable expression function call replace the
10041         call by its returned object.
10042         (Is_Inlinable_Expression_Function): New subprogram.
10044 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
10046         * checks.adb: Minor typo fix and reformatting.
10048 2017-01-13  Javier Miranda  <miranda@adacore.com>
10050         * contracts.adb (Contract_Only_Subprograms): Remove formal.
10051         (Copy_Original_Specification): Removed.
10052         (Skip_Contract_Only_Subprogram): Move here checks previously
10053         located in the caller of this routine (to leave the code more clean).
10054         (Build_Contract_Only_Subprogram): Code cleanup.
10055         * scil_ll.ads, scil_ll.adb (Get_Contract_Only_Body_Name): Removed.
10056         (Get_Contract_Only_Missing_Body_Name): Removed.
10058 2017-01-13  Javier Miranda  <miranda@adacore.com>
10060         * sem_ch6.adb (Cloned_Expression): New subprogram.
10061         (Freeze_Expr_Types): Complete previous patch since the expression
10062         of an expression-function may have iterators and loops with
10063         defining identifiers which, as part of the preanalysis of the
10064         expression, may be left decorated with itypes that will not be
10065         available in the tree passed to the backend.
10067 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
10069         * checks.adb (Apply_Type_Conversion_Checks): Optimize a type
10070         conversion to Integer of an expression that is an attribute
10071         reference 'Pos on an enumeration type.
10073 2017-01-13  Bob Duff  <duff@adacore.com>
10075         * atree.ads: Minor comment fix.
10077 2017-01-13  Justin Squirek  <squirek@adacore.com>
10079         * sem_ch6.adb (Check_Aggregate_Accessibility): Ignore function
10080         calls in accessibility check on return statement.
10082 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
10084         * sem_ch6.adb (Analyze_Subprogram_Body_Helper):
10085         Ensure that the input body is a subprogram body before trying to
10086         determine whether it denoted an expression function.  Note that
10087         subprogram body stubs cannot denote expression functions.
10089 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
10091         * bindgen.adb, sem_ch6.adb, binde.adb, exp_ch3.adb: Minor reformatting
10092         and typo fixes.
10094 2017-01-13  Javier Miranda  <miranda@adacore.com>
10096         * einfo.ads (Component_Bit_Offset): Fix documentation.
10097         * sem_ch13.adb (Check_Record_Representation_Clause): Skip check
10098         on record holes for components with unknown compile-time offsets.
10100 2017-01-13  Bob Duff  <duff@adacore.com>
10102         * ali.ads, ali.adb (Static_Elaboration_Model_Used): Remove unused flag.
10103         * g-locfil.ads: Minor comment fix.
10105 2017-01-13  Bob Duff  <duff@adacore.com>
10107         * binde.adb (Elab_New): New elaboration order algorithm
10108         that is expected to cause fewer ABE issues. This is a work in
10109         progress. The new algorithm is currently disabled, and can be
10110         enable by the -dp switch, or by modifying the Do_Old and Do_New
10111         etc. flags and rebuilding. Experimental code is included to
10112         compare the results of the old and new algorithms.
10113         * binde.ads: Use GNAT.Dynamic_Tables instead of Table, so we
10114         can have multiple of these tables, so the old and new algorithms
10115         can coexist.
10116         * bindgen.ads (Gen_Output_File): Pass Elab_Order as an 'in'
10117         parameter of type array. This avoids the global variable, and
10118         allows bounds checking (which is normally defeated by the tables
10119         packages). It also ensures that the Elab_Order is read-only
10120         to Bindgen.
10121         * bindgen.adb: Pass Elab_Order as an 'in' parameter to all
10122         subprograms that need it, as above.
10123         * debug.adb: Document new -dp switch. Modify doc of old -do
10124         switch.
10125         * gnatbind.adb (Gnatbind): Make use of new interfaces to Binde
10126         and Bindgen.  Move writing of closure (-R and -Ra switches)
10127         to Binde; that's more convenient.
10129 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
10131         * sem_ch6.adb (Analyze_Expression_Function): If the expression
10132         function is a completion, all entities referenced in the
10133         expression are frozen. As a consequence, a reference to an
10134         uncompleted private type from an enclosing scope is illegal.
10136 2017-01-13  Javier Miranda  <miranda@adacore.com>
10138         * sem_ch6.adb (Freeze_Expr_Types): New subprogram.
10139         (Analyze_Subprogram_Body_Helper): At the occurrence of an
10140         expression function declaration that is a completion, its
10141         expression causes freezing (AI12-0103).
10143 2017-01-13  Vadim Godunko  <godunko@adacore.com>
10145         * a-coinho-shared.adb: Fix memory leaks in Constant_Reference and
10146         Reference functions of Ada.Containers.Indefinite_Holders.
10148 2017-01-13  Bob Duff  <duff@adacore.com>
10150         * s-os_lib.ads: Minor comment fixes.
10152 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
10154         * exp_ch3.adb (Default_Initialize_Object): Do not default
10155         initialize an object when it is of a task type and restriction
10156         No_Tasking is in effect because the initialization is obsolete.
10157         * exp_ch9.adb (Build_Master_Entity): Do not generate a master when
10158         restriction No_Tasking is in effect.
10159         (Build_Master_Renaming): Do not rename a master when restriction
10160         No_Tasking is in effect.
10162 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
10164         * sem_aggr.adb (Resolve_Array_Aggregate): The code that verifies
10165         the legality of An others clause applies as well to a choice in
10166         an Iterated_component_ association.
10167         (Resolve_Iterated_Component_Association): An others choice
10168         is legal.
10169         * exp_aggr.adb (Aggr_Assignment_OK_For_Backend): An
10170         Iterated_Component_Association is not static.
10172 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
10174         * exp_ch3.adb (Freeze_Type): Mark the Ghost mode as set in case
10175         control is passed to the expresion handler before the new mode
10176         is set.
10177         * sem_ch12.adb (Analyze_Package_Instantiation,
10178         Analyze_Subprogram_Instantiation): Mark the Ghost mode as set
10179         in case control is passed to the expresion handler before the
10180         new mode is set.
10182 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
10184         * sem_aggr.adb, sem_ch3.adb, inline.adb, sem_util.adb, exp_ch4.adb,
10185         exp_aggr.adb: Minor reformatting.
10187 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
10189         * inline.adb: Minor reformatting and typo fix.
10191 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
10193         * sem_util.ads, sem_util.adb (Choice_List): Move function here
10194         from sem_aggr.adb, for use elsewhere.
10195         * sem_ch3.adb (Analyze_Object_Declaration): Use Choice_List.
10196         * sem_aggr.adb (Resolve_Array_Aggregate): Remove
10197         Iterated_Component_Present.
10198         * exp_aggr.adb: Use Choice_List throughout, to handle
10199         Iterated_Component_Associations.
10200         (Gen_Loop): Generate proper loop for an
10201         Iterated_Component_Association: loop variable has the identifier
10202         of the original association. Generate a loop even for a single
10203         component choice, in order to make loop parameter visible in
10204         expression.
10205         (Flatten): An Iterated_Component_Association is not static.
10207 2017-01-13  Yannick Moy  <moy@adacore.com>
10209         * exp_ch4.adb (Expand_N_Op_Expon): Ensure that the value of
10210         float exponentiation for statically known small negative values
10211         is the reciprocal of the exponentiation for the opposite value
10212         of the exponent.
10213         * s-exnllf.adb (Exn_Float, Exn_Long_Float, Exn_Long_Long_Float):
10214         Ensure that the value of float exponentiation for negative values
10215         is the reciprocal of the exponentiation for the opposite value
10216         of the exponent.
10217         * inline.adb (Expand_Inlined_Call): Fix the count
10218         for the number of generated gotos.
10220 2017-01-13  Yannick Moy  <moy@adacore.com>
10222         * inline.adb: Code cleanup.
10223         * sem_util.adb (Is_OK_Volatile_Context): Add
10224         expression in delay statement as OK for volatile context.
10226 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
10228         * sem_aggr.adb (Resolve_Array_Aggregate): In normal compilation
10229         mode a choice that is a subtype with a static predicate is
10230         replaced by the values it covers. This transformation must not
10231         be performed in ASIS mode, to preserve the source for analysis.
10233 2017-01-13  Justin Squirek  <squirek@adacore.com>
10235         * nlists.ads: Correct minor typo.
10237 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
10239         * sem_ch13.adb: Minor reformatting and typo fix.
10241 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
10243         * par-ch4.adb (P_Aggregate_Or_Parent_Expr): An
10244         Iterated_Component_Association is a named association in an
10245         array aggregate.
10246         * sem_aggr.adb (Resolve_Iterated_Component_Association): New
10247         procedure, subsidiary of Resolve_Array_Aggregate, to analyze
10248         and resolve the discrete choices and the expression of the
10249         new construct.
10250         * sinfo.adb, sinfo.ads: In analogy with N_Component_Association,
10251         Loop_Actions and Box_Present are attributes of
10252         N_Iterated_Component_Association nodes. Box_Present is always
10253         False in this case.
10254         * sprint.adb (Sprint_Node): An Iterated_Component_Association
10255         has a Discrete_Choices list, as specified in the RM. A
10256         Component_Association for aggregate uses instead a Choices list.
10257         We have to live with this small inconsistency because the new
10258         construct also has a defining identifier, and there is no way
10259         to merge the two node structures.
10261 2017-01-13  Yannick Moy  <moy@adacore.com>
10263         * inline.adb (Remove_Aspects_And_Pragmas): Add Unused to the
10264         list of pragmas to remove.  Remove pragmas from the list of
10265         statements in the body to inline.
10266         * namet.adb, namet.ads (Nam_In): New version with 12 parameters.
10268 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
10270         * sem_ch3.adb (Resolve_Aspects): New procedure, subsidiary of
10271         Analyze_Declarations, to analyze and resolve the expressions of
10272         aspect specifications in the current declarative list, so that
10273         the expressions have proper entity and type info.  This is needed
10274         for ASIS when there is no subsequent expansion to generate this
10275         semantic information.
10276         * sem_ch13.adb (Check_Aspect_At_End_Of_Declarations): Use Etype of
10277         original expression, to suppress cascaded errors when expression
10278         has been constant-folded.
10279         (Resolve_Aspect_Expressions, Resolve_Name): Preserve entities in
10280         ASIS mode, because there is no subsequent expansion to decorate
10281         the tree.
10283 2017-01-13  Yannick Moy  <moy@adacore.com>
10285         * inline.adb, inline.ads (Call_Can_Be_Inlined_In_GNATprove_Mode):
10286         New function to detect when a call may be inlined or not in
10287         GNATprove mode.
10288         (Expand_Inlined_Call): Ensure that a temporary
10289         is always created in the cases where a type conversion may be
10290         needed on an input parameter in GNATprove mode, so that GNATprove
10291         sees the check to perform.
10292         * sem_res.adb (Resolve_Call): In GNATprove mode, skip inlining
10293         when not applicable due to actual requiring type conversion
10294         with possible check but no temporary value can be copied for
10295         GNATprove to see the check.
10297 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
10299         * sem_aggr.adb, par_sco.adb, s-osprim-mingw.adb, exp_ch5.adb,
10300         exp_prag.adb, sem_ch3.adb, xr_tabls.adb, lib-xref-spark_specific.adb,
10301         layout.adb, sem_dist.adb, exp_spark.adb, exp_ch7.adb, gnatcmd.adb,
10302         exp_util.adb, prj-proc.adb, sem_aux.adb, comperr.adb, g-memdum.adb,
10303         exp_attr.adb, s-intman-solaris.adb, exp_ch9.adb, make.adb, live.adb,
10304         g-sercom-linux.adb, sem_dim.adb, mlib-prj.adb, s-intman-posix.adb,
10305         sem_ch9.adb, sem_ch10.adb, prep.adb, einfo.adb, scng.adb, checks.adb,
10306         prj-strt.adb, sem_prag.adb, eval_fat.adb, sem_ch12.adb, sem.adb,
10307         a-numaux-x86.adb, a-stwifi.adb, i-cobol.adb, prj.adb,
10308         get_spark_xrefs.adb, s-tasini.adb, rtsfind.adb, freeze.adb,
10309         g-arrspl.adb, par-ch4.adb, sem_util.adb, sem_res.adb, expander.adb,
10310         sem_attr.adb, exp_dbug.adb, prj-pp.adb, a-stzfix.adb, s-interr.adb,
10311         s-wchcnv.adb, switch-m.adb, gnat1drv.adb, sinput-l.adb, stylesw.adb,
10312         contracts.adb, s-intman-android.adb, g-expect.adb, exp_ch4.adb,
10313         g-comlin.adb, errout.adb, sinput.adb, s-exctra.adb, repinfo.adb,
10314         g-spipat.adb, g-debpoo.adb, exp_ch6.adb, sem_ch4.adb, exp_ch13.adb,
10315         a-wtedit.adb, validsw.adb, pprint.adb, widechar.adb, makeutl.adb,
10316         ali.adb, set_targ.adb, sem_mech.adb, sem_ch6.adb, gnatdll.adb,
10317         get_scos.adb, g-pehage.adb, s-tratas-default.adb, gnatbind.adb,
10318         prj-dect.adb, g-socthi-mingw.adb, par-prag.adb, prj-nmsc.adb,
10319         exp_disp.adb, par-ch12.adb, binde.adb, sem_ch8.adb,
10320         s-tfsetr-default.adb, s-regexp.adb, gprep.adb, s-tpobop.adb,
10321         a-teioed.adb, sem_warn.adb, sem_eval.adb, g-awk.adb, s-io.adb,
10322         a-ztedit.adb, xoscons.adb, exp_intr.adb, sem_cat.adb, sprint.adb,
10323         g-socket.adb, exp_dist.adb, sem_ch13.adb, s-tfsetr-vxworks.adb,
10324         par-ch3.adb, treepr.adb, g-forstr.adb, g-catiio.adb, par-ch5.adb,
10325         uname.adb, osint.adb, exp_ch3.adb, prj-env.adb, a-strfix.adb,
10326         a-stzsup.adb, prj-tree.adb, s-fileio.adb: Update all eligible case
10327         statements to reflect the new style for case alternatives. Various
10328         code clean up and reformatting.
10330 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
10332         * exp_util.adb: Minor reformatting.
10334 2017-01-13  Yannick Moy  <moy@adacore.com>
10336         * exp_spark.adb: Code cleanup.
10337         * sem_ch9.adb (Analyze_Delay_Until): Resolve
10338         expression so that calls are identified as such inside delay
10339         until.
10341 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
10343         * exp_util.adb (Insert_Actions): Handle Iterated_Component_Association.
10344         * par-ch3.adb (P_Discrete_Choice_List): An
10345         Iterated_Component_Association is an array aggregate component.
10346         * par-ch4.adb (P_Iterated_Component_Association): New procedure.
10347         (Is_Quantified_Expression): New function that performs a lookahead
10348         to distinguish quantified expressions from iterated component
10349         associations.
10350         (P_Aggregate_Or_Paren_Expr): Recognize iterated component
10351         associations.
10352         (P_Unparen_Cond_Case_Quant_Expression, P_Primary): Ditto.
10353         * sem.adb (Analyze): Handle Iterated_Component_Association.
10354         * sem_aggr.adb (Resolve_Array_Aggregate): Dummy handling of iterated
10355         component associations.
10356         * sinfo.ads, sinfo.adb: Entries for for
10357         N_Iterated_Component_Association and its fields.
10358         * sprint.adb (Sprint_Node_Actual): Handle
10359         N_Iterated_Component_Association.
10361 2017-01-13  Justin Squirek  <squirek@adacore.com>
10363         * sem_ch12.adb (Analyze_Package_Instantiation): Move disabiling
10364         of the style check until after preanalysis of acutals.
10366 2017-01-13  Yannick Moy  <moy@adacore.com>
10368         * sem_ch13.adb: Minor reformatting.
10369         * par-ch11.adb: minor style fix in whitespace
10370         * gnatbind.adb (Gnatbind): Scope of Std_Lib_File
10371         reduced to Add_Artificial_ALI_File; style fix in declaration of
10372         Text; grammar fix in comment.
10373         * osint-c.adb (Read_Library_Info): strip trailing NUL from result.
10374         * freeze.adb: Cleanup to pass pragma instead of
10375         expression to call.
10376         * exp_spark.adb (Expand_SPARK_Attribute_Reference): New procedure to
10377         replace System'To_Address by equivalent call.
10379 2017-01-13  Arnaud Charlet  <charlet@adacore.com>
10381         * bindusg.adb: Improve usage output for -f switch.
10383 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
10385         * frontend.adb, freeze.adb, sem_res.adb, sem_attr.adb, sem_ch8.adb:
10386         Minor reformatting.
10388 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
10390         * sem_ch13.adb (Is_Predicate_Static): Following the intent of the RM,
10391         treat comparisons on strings as legal in a Static_Predicate.
10392         (Is_Predicate_Static, Is_Type_Ref): Predicate also returns true on
10393         a function call that is the expansion of a string comparison.The
10394         function call is built when compiling the corresponding predicate
10395         function, but the expression has been found legal as a static
10396         predicate during earlier analysis.
10397         * sem_eval.adb (Real_Or_String_Static_Predicate_Matches): Handle
10398         properly a function call that is the expansion of a string
10399         comparison operation, in order to recover the Static_Predicate
10400         expression and apply it to a static argument when needed.
10402 2017-01-13  Tristan Gingold  <gingold@adacore.com>
10404         * s-mmap.adb, s-mmap.ads (Open_Read_No_Exception): New function.
10405         (Open_Read): Re-implement using Open_Read_No_Exception.
10406         (Open_Write): Raise exception in case of error.
10407         * s-mmosin-mingw.adb (Open_Common): Do not raise exception.
10408         * s-mmosin-unix.adb (Open_Read, Open_Write): Do not
10409         reaise exception.
10410         * s-mmosin-mingw.ads, s-mmosin-unix.ads (Open_Read): Adjust comment.
10412 2017-01-13  Yannick Moy  <moy@adacore.com>
10414         * checks.adb: Code cleanup.
10416 2017-01-13  Yannick Moy  <moy@adacore.com>
10418         * freeze.adb (Check_Inherited_Conditions): Use analyzed pragma
10419         expression instead of unanalyzed aspect expression for checking
10420         the validity of inheriting an operation. Also copy the expression
10421         being passing it to Build_Class_Wide_Expression, as this call
10422         modifies its argument.
10423         * sem_util.ads Fix comment to reference correct function name
10424         New_Copy_Tree.
10426 2017-01-13  Javier Miranda  <miranda@adacore.com>
10428         * sem_res.adb (Resolve_Generalized_Indexing): Compiling in ASIS mode,
10429         when we propagate information about the indexes back to the original
10430         indexing mode and the prefix of the index is a function call, do not
10431         remove any parameter from such call.
10433 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
10435         * exp_ch6.ads (Needs_BIP_Finalization_Master): Update comment.
10436         * exp_ch6.adb (Needs_BIP_Finalization_Master): Return True for
10437         a build-in-place function whose result type is tagged.
10439 2017-01-13  Yannick Moy  <moy@adacore.com>
10441         * sem_ch8.adb (Analyze_Subprogram_Renaming.Build_Class_Wide_Wrapper):
10442         Do not generate a wrapper when the only candidate is a class-wide
10443         subprogram.
10444         (Analyze_Subprogram_Renaming): Do not freeze the renaming or renamed
10445         inside a generic context.
10447 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
10449         * exp_util.adb (Add_Inherited_Tagged_DIC):
10450         Pass the object parameters of both the parent and the derived
10451         type DIC procedure to the reference replacement circuitry.
10452         (Find_DIC_Type): Modify the circuitry to present the partial
10453         view of a private type in case the private type defines its own
10454         DIC pragma.
10455         (Replace_Object_And_Primitive_References): Add two
10456         optional formal parameters.  Update the comment on usage. Update
10457         the replacement of references to object parameters.
10459 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
10461         * einfo.adb, sem_ch6.adb, atree.adb: Minor reformatting and typo fix.
10463 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
10465         * sem_res.adb (Resolve_Actuals): Apply Scalar_Range_Check to
10466         an out parameter that is a type conversion, independently of th
10467         range check that may apply to the expression of the conversion,
10468         for use in GNATProve.
10470 2017-01-13  Yannick Moy  <moy@adacore.com>
10472         * gnat1drv.adb (Gnat1drv): Move the implicit with for System in
10473         GNATprove_Mode here to Frontend.
10474         * frontend.adb (Frontend): Move the implicit with for System
10475         in GNATprove_Mode here as it ismore correct this way; the old
10476         place only worked by chance, since there were no overloaded names.
10477         * rtsfind.ads (RE_Id, RE_Unit_Table): Add RE_Tasking_State.
10478         * sem_attr.adb (Analyze_Attribute): In GNATprove_Mode, for the
10479         four attributes identified in SRM 9(18), add an implicit with
10480         to Ada.Task_Identification.
10481         * sem_ch8.adb (Analyze_Subprogram_Renaming.Build_Class_Wide_Wrapper):
10482         Deal specially with the wrapper introduced for AI05-0071 in GNATprove
10483         mode.
10484         * checks.adb (Apply_Discriminant_Check,
10485         Apply_Selected_Length_Checks, Apply_Selected_Range_Checks):
10486         In GNATprove mode, we do not apply the checks, but we still
10487         analyze the expression to possibly issue errors on SPARK
10488         code when a run-time error can be detected at compile time.
10489         (Selected_Length_Checks, Selected_Range_Checks): Perform analysis
10490         in GNATprove mode.
10492 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
10494         * expander.adb (Expand): Add a warning about using return
10495         statements in Ghost management code.
10496         * exp_ch3.adb (Freeze_Type): Add a warning about using return
10497         statements in Ghost management code.
10498         * exp_ch7.adb (Build_Invariant_Procedure_Body,
10499         Build_Invariant_Procedure_Declaration): Add a warning about
10500         using return statements in Ghost management code.
10501         * exp_disp.adb (Make_DT): Add a warning about using return
10502         statements in Ghost management code.
10503         * exp_util.adb (Build_DIC_Procedure_Body,
10504         Build_DIC_Procedure_Declaration, Make_Predicated_Call): Add a
10505         warning about using return statements in Ghost management code.
10506         * freeze.adb (Freeze_Entity): Add a warning about using return
10507         statements in Ghost management code.
10508         * sem.adb (Analyze, Do_Analyze): Add a warning about using return
10509         statements in Ghost management code.
10510         * sem_ch3.adb (Analyze_Object_Declaration, Process_Full_View): Add
10511         a warning about using return statements in Ghost management code.
10512         * sem_ch5.adb (Analyze_Assignment): Add a warning about using
10513         return statements in Ghost management code.
10514         * sem_ch6.adb (Analyze_Procedure_Call,
10515         Analyze_Subprogram_Body_Helper): Add a warning about using return
10516         statements in Ghost management code.
10517         * sem_ch7.adb (Analyze_Package_Body_Helper): Add a warning about
10518         using return statements in Ghost management code.
10519         * sem_ch12.adb (Analyze_Package_Instantiation,
10520         Analyze_Subprogram_Instantiation, Instantiate_Package_Body,
10521         Instantiate_Subprogram_Body): Add a warning about using return
10522         statements in Ghost management code.
10523         * sem_ch13.adb (Build_Predicate_Functions,
10524         Build_Predicate_Function_Declarations): Add a warning about
10525         using return statements in Ghost management code.
10526         * sem_prag.adb (Analyze_Contract_Cases_In_Decl_Part,
10527         Analyze_Initial_Condition_In_Decl_Part, Analyze_Pragma,
10528         Analyze_Pre_Post_Condition_In_Decl_Part):  Add a warning about
10529         using return statements in Ghost management code.
10531 2017-01-13  Tristan Gingold  <gingold@adacore.com>
10533         * s-mmosin-mingw.adb: Fix pragma import.
10535 2017-01-13  Arnaud Charlet  <charlet@adacore.com>
10537         * gnat1drv.adb (Adjust_Global_Switches): Ignore -gnateE in
10538         codepeer mode.
10540 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
10542         * atree.adb (Allocate_Initialize_Node): A newly created node is
10543         no longer marked as Ghost at this level.
10544         (Mark_New_Ghost_Node): New routine.
10545         (New_Copy): Mark the copy as Ghost.
10546         (New_Entity): Mark the entity as Ghost.
10547         (New_Node): Mark the node as Ghost.
10548         * einfo.adb (Is_Checked_Ghost_Entity): This attribute can now
10549         apply to unanalyzed entities.
10550         (Is_Ignored_Ghost_Entity): This attribute can now apply to unanalyzed
10551         entities.
10552         (Set_Is_Checked_Ghost_Entity): This attribute now
10553         applies to all entities as well as unanalyzed entities.
10554         (Set_Is_Ignored_Ghost_Entity): This attribute now applies to
10555         all entities as well as unanalyzed entities.
10556         * expander.adb Add with and use clauses for Ghost.
10557         (Expand): Install and revert the Ghost region associated with the node
10558         being expanded.
10559         * exp_ch3.adb (Expand_Freeze_Array_Type): Remove all Ghost-related code.
10560         (Expand_Freeze_Class_Wide_Type): Remoe all Ghost-related code.
10561         (Expand_Freeze_Enumeration_Type): Remove all Ghost-related code.
10562         (Expand_Freeze_Record_Type): Remove all Ghost-related code.
10563         (Freeze_Type): Install and revert the Ghost region associated
10564         with the type being frozen.
10565         * exp_ch5.adb Remove with and use clauses for Ghost.
10566         (Expand_N_Assignment_Statement): Remove all Ghost-related code.
10567         * exp_ch6.adb Remove with and use clauses for Ghost.
10568         (Expand_N_Procedure_Call_Statement): Remove all Ghost-relatd code.
10569         (Expand_N_Subprogram_Body): Remove all Ghost-related code.
10570         * exp_ch7.adb (Build_Invariant_Procedure_Body): Install and revert the
10571         Ghost region of the working type.
10572         (Build_Invariant_Procedure_Declaration): Install and revert
10573         the Ghost region of the working type.
10574         (Expand_N_Package_Body): Remove all Ghost-related code.
10575         * exp_ch8.adb Remove with and use clauses for Ghost.
10576         (Expand_N_Exception_Renaming_Declaration): Remove all Ghost-related
10577         code.
10578         (Expand_N_Object_Renaming_Declaration): Remove all Ghost-related code.
10579         (Expand_N_Package_Renaming_Declaration): Remove all Ghost-related code.
10580         (Expand_N_Subprogram_Renaming_Declaration): Remove all Ghost-related
10581         code.
10582         * exp_ch13.adb Remove with and use clauses for Ghost.
10583         (Expand_N_Freeze_Entity): Remove all Ghost-related code.
10584         * exp_disp.adb (Make_DT): Install and revert the Ghost region of
10585         the tagged type. Move the generation of various entities within
10586         the Ghost region of the type.
10587         * exp_prag.adb Remove with and use clauses for Ghost.
10588         (Expand_Pragma_Check): Remove all Ghost-related code.
10589         (Expand_Pragma_Contract_Cases): Remove all Ghost-related code.
10590         (Expand_Pragma_Initial_Condition): Remove all Ghost-related code.
10591         (Expand_Pragma_Loop_Variant): Remove all Ghost-related code.
10592         * exp_util.adb (Build_DIC_Procedure_Body): Install
10593         and revert the Ghost region of the working types.
10594         (Build_DIC_Procedure_Declaration): Install and revert the
10595         Ghost region of the working type.
10596         (Make_Invariant_Call): Install and revert the Ghost region of the
10597         associated type.
10598         (Make_Predicate_Call): Reimplemented. Install and revert the
10599         Ghost region of the associated type.
10600         * freeze.adb (Freeze_Entity): Install and revert the Ghost region
10601         of the entity being frozen.
10602         (New_Freeze_Node): Removed.
10603         * ghost.adb Remove with and use clauses for Opt.
10604         (Check_Ghost_Completion): Update the parameter profile
10605         and all references to formal parameters.
10606         (Ghost_Entity): Update the comment on usage.
10607         (Install_Ghost_Mode): New routines.
10608         (Is_Ghost_Assignment): New routine.
10609         (Is_Ghost_Declaration): New routine.
10610         (Is_Ghost_Pragma): New routine.
10611         (Is_Ghost_Procedure_Call): New routine.
10612         (Is_Ghost_Renaming): Removed.
10613         (Is_OK_Declaration): Reimplemented.
10614         (Is_OK_Pragma): Reimplemented.
10615         (Is_OK_Statement): Reimplemented.
10616         (Is_Subject_To_Ghost): Update the comment on usage.
10617         (Mark_And_Set_Ghost_Assignment): New routine.
10618         (Mark_And_Set_Ghost_Body): New routine.
10619         (Mark_And_Set_Ghost_Completion): New routine.
10620         (Mark_And_Set_Ghost_Declaration): New routine.
10621         (Mark_And_Set_Ghost_Instantiation): New routine.
10622         (Mark_And_Set_Ghost_Procedure_Call): New routine.
10623         (Mark_Full_View_As_Ghost): Removed.
10624         (Mark_Ghost_Declaration_Or_Body): New routine.
10625         (Mark_Ghost_Pragma): New routine.
10626         (Mark_Ghost_Renaming): New routine.
10627         (Mark_Pragma_As_Ghost): Removed.
10628         (Mark_Renaming_As_Ghost): Removed.
10629         (Propagate_Ignored_Ghost_Code): Update the comment on usage.
10630         (Prune_Node): Freeze nodes no longer need special pruning, they
10631         are processed by the general ignored Ghost code mechanism.
10632         (Restore_Ghost_Mode): New routine.
10633         (Set_Ghost_Mode): Reimplemented.
10634         (Set_Ghost_Mode_From_Entity): Removed.
10635         * ghost.ads Add with and use clauses for Ghost.
10636         (Check_Ghost_Completion): Update the parameter profile
10637         along with the comment on usage.
10638         (Install_Ghost_Mode): New routine.
10639         (Is_Ghost_Assignment): New routine.
10640         (Is_Ghost_Declaration): New routine.
10641         (Is_Ghost_Pragma): New routine.
10642         (Is_Ghost_Procedure_Call): New routine.
10643         (Mark_And_Set_Ghost_Assignment): New routine.
10644         (Mark_And_Set_Ghost_Body): New routine.
10645         (Mark_And_Set_Ghost_Completion): New routine.
10646         (Mark_And_Set_Ghost_Declaration): New routine.
10647         (Mark_And_Set_Ghost_Instantiation): New routine.
10648         (Mark_And_Set_Ghost_Procedure_Call): New routine.
10649         (Mark_Full_View_As_Ghost): Removed.
10650         (Mark_Ghost_Pragma): New routine.
10651         (Mark_Ghost_Renaming): New routine.
10652         (Mark_Pragma_As_Ghost): Removed.
10653         (Mark_Renaming_As_Ghost): Removed.
10654         (Restore_Ghost_Mode): New routine.
10655         (Set_Ghost_Mode): Redefined.
10656         (Set_Ghost_Mode_From_Entity): Removed.
10657         * sem.adb (Analyze): Install and revert the Ghost region of the
10658         node being analyzed.
10659         (Do_Analyze): Change the way a clean Ghost
10660         region is installed and reverted.
10661         * sem_ch3.adb (Analyze_Full_Type_Declaration): Remove
10662         all Ghost-related code.
10663         (Analyze_Incomplete_Type_Decl): Remove all Ghost-related code.
10664         (Analyze_Number_Declaration): Remove all Ghost-related code.
10665         (Analyze_Object_Declaration): Install and revert the Ghost region of
10666         a deferred object declaration's completion.
10667         (Array_Type_Declaration): Remove all Ghost-related code.
10668         (Build_Derived_Type): Update the comment on
10669         the propagation of Ghost attributes from a parent to a derived type.
10670         (Derive_Subprogram): Remove all Ghost-related code.
10671         (Make_Class_Wide_Type): Remove all Ghost-related code.
10672         (Make_Implicit_Base): Remove all Ghost-related code.
10673         (Process_Full_View): Install and revert the Ghost region of
10674         the partial view.  There is no longer need to check the Ghost
10675         completion here.
10676         * sem_ch5.adb (Analyze_Assignment): Install and revert the Ghost
10677         region of the left hand side.
10678         * sem_ch6.adb (Analyze_Abstract_Subprogram_Declaration): Remove
10679         all Ghost-related code.
10680         (Analyze_Expression_Function): Remove all Ghost-related code.
10681         (Analyze_Generic_Subprogram_Body): Remove all Ghost-related code.
10682         (Analyze_Procedure_Call): Install and revert the Ghost region of
10683         the procedure being called.
10684         (Analyze_Subprogram_Body_Helper): Install and revert the Ghost
10685         region of the spec or body.
10686         (Analyze_Subprogram_Declaration): Remove all Ghost-related code.
10687         (Build_Subprogram_Declaration): Remove all Ghost-related code.
10688         (Find_Corresponding_Spec): Remove all Ghost-related code.
10689         (Process_Formals): Remove all Ghost-related code.
10690         * sem_ch7.adb (Analyze_Package_Body_Helper): Install and revert
10691         the Ghost region of the spec.
10692         (Analyze_Package_Declaration): Remove all Ghost-related code.
10693         * sem_ch8.adb (Analyze_Exception_Renaming): Mark a renaming as
10694         Ghost when it aliases a Ghost entity.
10695         (Analyze_Generic_Renaming): Mark a renaming as Ghost when it aliases
10696         a Ghost entity.
10697         (Analyze_Object_Renaming): Mark a renaming as Ghost when
10698         it aliases a Ghost entity.
10699         (Analyze_Package_Renaming): Mark a renaming as Ghost when it aliases
10700         a Ghost entity.
10701         (Analyze_Subprogram_Renaming): Mark a renaming as Ghost when it
10702         aliases a Ghost entity.
10703         * sem_ch11.adb Remove with and use clauses for Ghost.
10704         (Analyze_Exception_Declaration): Remove all Ghost-related code.
10705         * sem_ch12.adb (Analyze_Generic_Package_Declaration): Remove all
10706         Ghost-related code.
10707         (Analyze_Generic_Subprogram_Declaration): Remove all Ghost-related
10708         code.
10709         (Analyze_Package_Instantiation): Install and revert the Ghost region
10710         of the package instantiation.
10711         (Analyze_Subprogram_Instantiation): Install
10712         and revert the Ghost region of the subprogram instantiation.
10713         (Instantiate_Package_Body): Code clean up. Install and revert the
10714         Ghost region of the package body.
10715         (Instantiate_Subprogram_Body): Code clean up. Install and revert the
10716         Ghost region of the subprogram body.
10717         * sem_ch13.adb (Build_Predicate_Functions): Install
10718         and revert the Ghost region of the related type.
10719         (Build_Predicate_Function_Declaration): Code clean up. Install
10720         and rever the Ghost region of the related type.
10721         * sem_prag.adb (Analyze_Contract_Cases_In_Decl_Part):
10722         Install and revert the Ghost region of the pragma.
10723         (Analyze_Initial_Condition_In_Decl_Part): Install and revert the
10724         Ghost region of the pragma.
10725         (Analyze_Pragma): Install and revert the Ghost region of various
10726         pragmas.  Mark a pragma as Ghost when it is related to a Ghost entity
10727         or encloses a Ghost entity.
10728         (Analyze_Pre_Post_Condition): Install and revert the Ghost
10729         region of the pragma.
10730         (Analyze_Pre_Post_Condition_In_Decl_Part): Install and revert the
10731         Ghost region of the pragma.
10732         * sem_res.adb (Resolve): Remove all Ghost-related code.
10733         * sem_util.adb (Is_Declaration): Reimplemented.
10734         (Is_Declaration_Other_Than_Renaming): New routine.
10735         * sem_util.ads (Is_Declaration_Other_Than_Renaming): New routine.
10736         * sinfo.adb (Is_Checked_Ghost_Pragma): New routine.
10737         (Is_Ghost_Pragma): Removed.
10738         (Is_Ignored_Ghost_Pragma): New routine.
10739         (Set_Is_Checked_Ghost_Pragma): New routine.
10740         (Set_Is_Ghost_Pragma): Removed.
10741         (Set_Is_Ignored_Ghost_Pragma): New routine.
10742         * sinfo.ads: Update the documentation on Ghost mode and
10743         Ghost regions.  New attributes Is_Checked_Ghost_Pragma
10744         and Is_Ignored_Ghost_Pragma along with usages in nodes.
10745         Remove attribute Is_Ghost_Pragma along with usages in nodes.
10746         (Is_Checked_Ghost_Pragma): New routine along with pragma Inline.
10747         (Is_Ghost_Pragma): Removed along with pragma Inline.
10748         (Is_Ignored_Ghost_Pragma): New routine along with pragma Inline.
10749         (Set_Is_Checked_Ghost_Pragma): New routine along with pragma Inline.
10750         (Set_Is_Ghost_Pragma): Removed along with pragma Inline.
10751         (Set_Is_Ignored_Ghost_Pragma): New routine along with pragma Inline.
10753 2017-01-12  Tristan Gingold  <gingold@adacore.com>
10755         * s-mmap.ads, s-mmap.adb, s-mmosin-unix.ads, s-mmosin-unix.adb,
10756         s-mmauni-long.ads, s-mmosin-mingw.ads, s-mmosin-mingw.adb: New files.
10758 2017-01-12  Yannick Moy  <moy@adacore.com>
10760         * errout.adb, errout.ads (Initialize): Factor common treatment
10761         in Reset_Warnings.
10762         (Reset_Warnings): New procedure to reset counts related to warnings.
10763         (Record_Compilation_Errors): New variable to store the presence of an
10764         error, used in gnat2why to allow changing the Warning_Mode.
10765         (Compilation_Errors): Use new variable Record_Compilation_Errors to
10766         store the presence of an error.
10768 2017-01-12  Javier Miranda  <miranda@adacore.com>
10770         * sem_ch13.adb (Analyze_Aspect_Specifications):
10771         For Interrupt_Handler and Attach_ Handler aspects, decorate the
10772         internally built reference to the protected procedure as coming
10773         from sources and force its analysis.
10775 2017-01-12  Ed Schonberg  <schonberg@adacore.com>
10777         * sem_ch3.adb (Build_Derived_Type): For a scalar derived type,
10778         inherit predicates if any from the first_subtype of the parent,
10779         not from the anonymous parent type.
10780         * sem_eval.adb (Is_Static_Subtype): A type that inherits a dynamic
10781         predicate is not a static subtype.
10783 2017-01-12  Gary Dismukes  <dismukes@adacore.com>
10785         * freeze.adb (Check_Suspicious_Convention): New procedure
10786         performing a warning check on discriminated record types with
10787         convention C or C++. Factored out of procedure Freeze_Record_Type,
10788         and changed to only apply to base types (to avoid spurious
10789         warnings on subtypes). Minor improvement of warning messages
10790         to refer to discriminated rather than variant record types.
10791         (Freeze_Record_Type): Remove code for performing a suspicious
10792         convention check.
10793         (Freeze_Entity): Only call Freeze_Record_Type
10794         on types that aren't declared within any enclosing generic units
10795         (rather than just excluding the type when the innermost scope
10796         is generic). Call Check_Suspicious_Convention whether or not
10797         the type is declared within a generic unit.
10798         * sem_ch8.adb (In_Generic_Scope): Move this function to Sem_Util.
10799         * sem_util.ads, sem_util.adb (In_Generic_Scope): New function (moved
10800         from Sem_Ch8).
10802 2017-01-12  Tristan Gingold  <gingold@adacore.com>
10804         * sysdep.c, adaint.c, rtinit.c, ming32.h:
10805         (__gnat_current_codepage): Renamed from CurrentCodePage
10806         (__gnat_current_ccs_encoding): Renamed from CurrentCCSEncoding
10808 2017-01-12  Ed Schonberg  <schonberg@adacore.com>
10810         * sem_ch6.adb (Fully_Conformant_Expressions): Handle properly
10811         quantified expressions, following AI12-050: the loop parameters
10812         of two quantified expressions are conformant if they have the
10813         same identifier.
10815 2017-01-12  Arnaud Charlet  <charlet@adacore.com>
10817         * gcc-interface/Makefile.in: Clean up VxWorks targets.
10819 2017-01-12  Ed Schonberg  <schonberg@adacore.com>
10821         * sem_attr.adb (Analyze_Attribute_Reference, case Loop_Entry):
10822         Hnadle properly the attribute reference when it appears as part
10823         of an expression in another loop aspect.
10825 2017-01-12  Ed Schonberg  <schonberg@adacore.com>
10827         * exp_ch3.adb (Check_Predicated_Discriminant): New procedure,
10828         subsidiary of Build_Initialization_Call, to complete generation
10829         of predicate checks on discriminants whose (sub)types have
10830         predicates, and to add checks on variants that do not have an
10831         others clause.
10832         * sem_util.adb (Gather_Components): A missing Others alternative is
10833         not an error when the type of the discriminant is a static predicate
10834         (and coverage has been checked when analyzing the case statement). A
10835         runtime check is generated to verify that a given discriminant
10836         satisfies the predicate (RM 3.8.1. (21.1/2)).
10838 2017-01-12  Yannick Moy  <moy@adacore.com>
10840         * gnat1drv.adb (Adjust_Global_Switches): Only
10841         perform checking of exception mechanism when generating code.
10843 2017-01-12  Justin Squirek  <squirek@adacore.com>
10845         * exp_ch7.adb (Add_Type_Invariants, Process_Array_Component):
10846         Remove handling of access component with invariant.
10847         (Build_Invariant_Procedure_Declaration): Remove return on class
10848         wide type.
10849         * freeze.adb (Freeze_Array_Type, Freeze_Record_Type): Remove
10850         conditional exception for component or array so Has_Own_Invariants
10851         flag is not falsly set.
10852         * sem_ch3.adb (Make_Class_Wide_Type): Initialize copy of class
10853         wide type to have no invariant flags.
10855 2017-01-12  Hristian Kirtchev  <kirtchev@adacore.com>
10857         * exp_ch9.adb, sem_prag.adb, s-tassta.adb, sem_util.adb, s-tarest.adb,
10858         sem_ch13.adb: Minor reformatting.
10860 2017-01-12  Hristian Kirtchev  <kirtchev@adacore.com>
10862         * exp_aggr.adb (Build_Record_Aggr_Code): Guard against a missing
10863         adjustment primitive when the ancestor type was not properly frozen.
10864         (Gen_Assign): Guard against a missing initialization
10865         primitive when the component type was not properly frozen.
10866         (Initialize_Array_Component): Guard against a missing adjustment
10867         primitive when the component type was not properly frozen.
10868         (Initialize_Record_Component): Guard against a missing adjustment
10869         primitive when the component type was not properly frozen.
10870         (Process_Transient_Component_Completion): The transient object may
10871         not be finalized when its associated type was not properly frozen.
10872         * exp_ch3.adb (Build_Assignment): Guard against a missing
10873         adjustment primitive when the component type was not properly frozen.
10874         (Build_Initialization_Call): Guard against a missing
10875         initialization primitive when the associated type was not properly
10876         frozen.
10877         (Expand_N_Object_Declaration): Guard against a missing
10878         adjustment primitive when the base type was not properly frozen.
10879         (Predefined_Primitive_Bodies): Create an empty Deep_Adjust
10880         body when there is no adjustment primitive available. Create an
10881         empty Deep_Finalize body when there is no finalization primitive
10882         available.
10883         * exp_ch4.adb (Apply_Accessibility_Check): Guard against a
10884         missing finalization primitive when the designated type was
10885         not properly frozen.
10886         (Expand_N_Allocator): Guard against a missing initialization primitive
10887         when the designated type was not properly frozen.
10888         * exp_ch5.adb (Make_Tag_Ctrl_Assignment): Add the adjustment call
10889         only when the corresponding adjustment primitive is available.
10890         * exp_ch7.adb (Build_Adjust_Or_Finalize_Statements): Generate the
10891         adjustment/finalization statements only when there is an available
10892         primitive to carry out the action.
10893         (Build_Initialize_Statements): Generate the initialization/finalization
10894         statements only when there is an available primitive to carry out the
10895         action.
10896         (Make_Adjust_Call): Do not generate a call when the underlying
10897         type is not present due to a possible missing full view.
10898         (Make_Final_Call): Do not generate a call when the underlying
10899         type is not present due to a possible missing full view.
10900         (Make_Finalize_Address_Stmts): Generate an empty body when the
10901         designated type lacks a finalization primitive.
10902         (Make_Init_Call): Do not generate a call when the underlying type is
10903         not present due to a possible missing full view.
10904         (Process_Component_For_Adjust): Add the adjustment call only when the
10905         corresponding adjustment primitive is available.
10906         (Process_Component_For_Finalize): Add the finalization call only when
10907         the corresponding finalization primitive is available.
10908         (Process_Object_Declaration): Use a null statement to emulate a
10909         missing call to the finalization primitive of the object type.
10910         * exp_ch7.ads (Make_Adjust_Call): Update the comment on usage.
10911         (Make_Final_Call): Update the comment on usage.
10912         (Make_Init_Call): Update the comment on usage.
10913         * exp_util.adb (Build_Transient_Object_Statements): Code reformatting.
10915 2017-01-12  Arnaud Charlet  <charlet@adacore.com>
10917         * einfo.ads: Update documentation of Address_Taken.
10918         * sem_attr.adb (Analyze_Access_Attribute, Resolve_Attribute
10919         [Access_Attribute]): Only consider 'Access/'Unchecked_Access
10920         for subprograms when setting Address_Taken flag.
10922 2017-01-12  Patrick Bernardi  <bernardi@adacore.com>
10924         * sem_ch10.adb (Analyze_With_Clause): Removed code that turned
10925         Configurable_Run_Time_Mode off when analysing with'ed predefined
10926         libraries.
10928 2017-01-12  Gary Dismukes  <dismukes@adacore.com>
10930         * sem_prag.adb: Minor reformatting.
10931         * sem_util.adb (Unique_Entity): fix result for
10932         bodies of entry families.
10934 2017-01-12  Justin Squirek  <squirek@adacore.com>
10936         * sem_prag.adb (Analyze_Pragma): Add appropriate calls to
10937         Resolve_Suppressible in the pragma Assertion_Policy case.
10938         (Resolve_Suppressible): Created this function to factor out
10939         common code used to resolve Suppress to either Ignore or Check
10940         * snames.ads-tmpl: Add name for Suppressible.
10942 2017-01-12  Gary Dismukes  <dismukes@adacore.com>
10944         * exp_ch9.adb, s-secsta.adb, snames.ads-tmpl, exp_ch3.adb: Minor
10945         reformatting.
10946         * debug.adb: Minor comment fixes.
10948 2017-01-12  Arnaud Charlet  <charlet@adacore.com>
10950         * sem_util.adb (Unique_Entity): For concurrent
10951         bodies that are defined with stubs and complete a declaration
10952         of a single concurrent object return the entity of an implicit
10953         concurrent type, not the entity of the anonymous concurrent
10954         object.
10955         * debug.adb: -gnatd.J is no longer used.
10956         * make.adb (Globalize): Removed, no longer used.
10957         * sem_ch9.adb: minor typo in comment for entry index
10959 2017-01-12  Patrick Bernardi  <bernardi@adacore.com>
10961         * aspect.adb, aspect.ads: Added new aspect Secondary_Stack_Size.
10962         * exp_ch3.adb (Build_Init_Statements): As part of initialising
10963         the value record of a task, set its _Secondary_Stack_Size field
10964         if present.
10965         * exp_ch9.adb (Expand_N_Task_Type_Declaration): Create
10966         a _Secondary_Stack_Size field in the value record of
10967         the task if a Secondary_Stack_Size rep item is present.
10968         (Make_Task_Create_Call): Include secondary stack size
10969         parameter. If No_Secondary_Stack restriction is in place, passes
10970         stack size of 0.
10971         * par-prag.adb, sem_prag.adb, sem_prag.ads: Added new pragma
10972         Secondary_Stack_Size.
10973         * s-secsta.adb, s-secsta.ads (Minimum_Secondary_Stack_Size): New
10974         function to define the overhead of the secondary stack.
10975         * s-tarest.adb (Create_Restricted_Task,
10976         Create_Restricted_Task_Sequential): Functions now include
10977         Secondary_Stack_Size parameter to pass to Initialize_ATCB.
10978         * s-tarest.adb (Create_Restricted_Task,
10979         Create_Restricted_Task_Sequential): Calls to Initialize_ATCB now
10980         include Secondary_Stack_Size parameter.
10981         (Task_Wrapper): Secondary stack now allocated to the size specified by
10982         the Secondary_Stack_Size parameter in the task's ATCB.
10983         * s-taskin.adb, s-taskin.adb (Common_ATCB, Initialize_ATCB): New
10984         Secondary_Stack_Size component.
10985         * s-tassta.adb, s-tassta.ads (Create_Restricted_Task,
10986         Create_Restricted_Task_Sequential): Function now include
10987         Secondary_Stack_Size parameter.
10988         (Task_Wrapper): Secondary stack now allocated to the size
10989         specified by the Secondary_Stack_Size parameter in the task's
10990         ATCB.
10991         * s-tproft.adb (Register_Foreign_Thread): Amended Initialize_ATCB call
10992         to include Secondary_Stack_Size parameter.
10993         * sem_ch13.adb (Analyze_Aspect_Specification): Add support for
10994         Secondary_Stack_Size aspect, turning the aspect into its corresponding
10995         internal attribute.
10996         (Analyze_Attribute_Definition): Process Secondary_Stack_Size attribute.
10997         * snames.adb-tmpl, snames.ads-tmpl: Added names
10998         Name_Secondary_Stack_Size, Name_uSecondary_Stack_Size,
10999         Attribute_Secondary_Stack_Size and Pragma_Secondary_Stack_Size.
11001 2017-01-12  Yannick Moy  <moy@adacore.com>
11003         * exp_spark.adb (Expand_SPARK_Potential_Renaming): Fix sloc of copied
11004         subtree.
11006 2017-01-12  Justin Squirek  <squirek@adacore.com>
11008         * exp_attr.adb (Expand_N_Attribute_Reference):
11009         Fix Finalization_Size case by properly resolving the type after
11010         rewritting the node.
11012 2017-01-12  Hristian Kirtchev  <kirtchev@adacore.com>
11014         * exp_util.adb (Build_DIC_Procedure_Body): Semi-insert the body into
11015         the tree.
11016         (Build_DIC_Procedure_Declaration): Semi-insert the body into the tree.
11017         * binde.adb, exp_ch5.adb, sem_type.adb, sem.ads, sem_res.adb,
11018         exp_sel.ads: Minor reformatting.
11020 2017-01-12  Justin Squirek  <squirek@adacore.com>
11022         * exp_ch6.adb (Expand_Call): Add guard to prevent
11023         invariant checks from being created for internally generated
11024         subprograms.
11026 2017-01-12  Bob Duff  <duff@adacore.com>
11028         * lib-writ.ads: Remove incorrect comment.
11030 2017-01-12  Javier Miranda  <miranda@adacore.com>
11032         * debug.adb (-gnatd.K): Enable generation of contract-only
11033         procedures in CodePeer mode.
11034         * contracts.adb (Build_And_Analyze_Contract_Only_Subprograms):
11035         New subprogram.
11036         (Analyze_Contracts): Generate contract-only procedures if -gnatdK is
11037         set.
11038         * scil_ll.ads, scil_ll.adb (Get_Contract_Only_Body_Name): New
11039         subprogram.
11040         (Get_Contract_Only_Missing_Body_Name): New subprogram.
11041         (Get_Contract_Only_Body): New subprogram.
11042         (Set_Contract_Only_Body): New subprogram.
11043         (Is_Contract_Only_Body): New subprogram.
11044         (Set_Is_Contract_Only_Body): New subprogram.
11045         (SCIL_Nodes): Replace table by hash-table.
11047 2017-01-12  Hristian Kirtchev  <kirtchev@adacore.com>
11049         * exp_ch6.adb: Minor reformatting.
11050         * spark_xrefs.ads: minor cleanup of comments for SPARK xrefs
11052 2017-01-12  Bob Duff  <duff@adacore.com>
11054         * binde.adb (Forced): New reason for a dependence.
11055         (Force_Elab_Order): Implementation of the new switch.
11056         * binde.ads: Minor comment fixes.
11057         * bindusg.adb: Add -f switch. Apparently, there was an -f switch
11058         long ago that is no longer supported; removed comment about that.
11059         * opt.ads (Force_Elab_Order_File): Name of file specified for
11060         -f switch.
11061         * switch-b.adb: Parse -f switch.
11063 2017-01-12  Justin Squirek  <squirek@adacore.com>
11065         * exp_ch6.adb (Check_View_Conversion): Created this function
11066         to properly chain calls to check type invariants that may be
11067         present in a subprogram call after the subprogram.
11068         (Expand_Call): Add a conditional to identify when a view conversion
11069         needs to be checked.
11070         * nlists.adb, nlists.ads (Prepend_New): New routine.
11071         (Prepend_New_To): New routine.
11073 2017-01-12  Hristian Kirtchev  <kirtchev@adacore.com>
11075         * sinfo.ads: Minor reformatting.
11077 2017-01-12  Gary Dismukes  <dismukes@adacore.com>
11079         * exp_util.adb, exp_util.ads, einfo.ads: Minor typo fixes and
11080         reformatting.
11082 2017-01-12  Hristian Kirtchev  <kirtchev@adacore.com>
11084         * exp_ch6.adb (Make_Build_In_Place_Call_In_Anonymous_Context): Add new
11085         variable Definite. Create a local object and pass its 'Access to the
11086         BIP function when the result type is either definite or it does not
11087         require any finalization or secondary stack management.
11089 2017-01-12  Bob Duff  <duff@adacore.com>
11091         * contracts.adb, einfo.adb, errout.adb, exp_attr.adb,
11092         exp_ch3.adb, exp_ch7.adb, exp_ch9.adb, exp_prag.adb, freeze.adb,
11093         frontend.adb, ghost.adb, inline.adb, lib-writ.adb, lib-xref.adb,
11094         par.adb, par-ch10.adb, par-ch2.adb, par-prag.adb, par_sco.adb,
11095         sem_attr.adb, sem_aux.adb, sem_ch10.adb, sem_ch12.adb,
11096         sem_ch13.adb, sem_ch6.adb, sem_ch8.adb, sem_ch9.adb, sem_elab.adb,
11097         sem_prag.adb, sem_res.adb, sem_util.adb, sem_util.ads,
11098         sem_warn.adb, sinfo.adb, sinfo.ads, sprint.adb (Pragma_Name):
11099         Change name to Pragma_Name_Unmapped.
11100         (Pragma_Name_Mapped): Change name to Pragma_Name.
11101         This is because the "mapped" version should be the usual case.
11103 2017-01-09  Hristian Kirtchev  <kirtchev@adacore.com>
11105         * einfo.ads, einfo.adb: Remove uses of flags Has_Default_Init_Cond,
11106         Is_Default_Init_Cond_Procedure, and
11107         Has_Inherited_Default_Init_Cond.  Add uses of flags
11108         Has_Own_DIC, Is_DIC_Procedure, and Has_Inherited_DIC.
11109         (Default_Init_Cond_Procedure): Removed.
11110         (DIC_Procedure): New routine.
11111         (Has_Default_Init_Cond): Removed.
11112         (Has_DIC): New routine.
11113         (Has_Inheritable_Invariants): The attribute applies to the base type.
11114         (Has_Inherited_Default_Init_Cond): Removed.
11115         (Has_Inherited_DIC): New routine.
11116         (Has_Inherited_Invariants): The attribute applies to the base type.
11117         (Has_Own_DIC): New routine.
11118         (Has_Own_Invariants): The attribute applies to the base type.
11119         (Is_Default_Init_Cond_Procedure): Removed.
11120         (Is_DIC_Procedure): New routine.
11121         (Set_Default_Init_Cond_Procedure): Removed.
11122         (Set_DIC_Procedure): New routine.
11123         (Set_Has_Default_Init_Cond): Removed.
11124         (Set_Has_Inheritable_Invariants): The attribute applies
11125         to the base type.
11126         (Set_Has_Inherited_Default_Init_Cond): Removed.
11127         (Set_Has_Inherited_DIC): New routine.
11128         (Set_Has_Inherited_Invariants): The attribute applies to the base type.
11129         (Set_Has_Own_DIC): New routine.
11130         (Set_Has_Own_Invariants): The attribute applies to the base type.
11131         (Set_Is_Default_Init_Cond_Procedure): Removed.
11132         (Set_Is_DIC_Procedure): New routine.
11133         (Write_Entity_Flags): Update the output of all flags related to
11134         default initial condition.
11135         * exp_ch3.adb (Expand_N_Object_Declaration): Update the generation
11136         of the call to the DIC procedure.
11137         (Freeze_Type): Generate the body of the DIC procedure.
11138         * exp_ch7.adb (Build_Invariant_Procedure_Body): Replace
11139         all occurrences of Create_Append with Append_New_To. Do
11140         not generate an invariant procedure for a class-wide type.
11141         The generated body acts as a freeze action of the working type.
11142         (Build_Invariant_Procedure_Declaration): Do not generate an
11143         invariant procedure for a class-wide type.
11144         (Create_Append): Removed.
11145         * exp_util.adb: Add with and use clauses for Sem_Ch3, sem_ch6,
11146         sem_Ch12, Sem_Disp, and GNAT.HTable. Move the handling of
11147         class-wide pre/postcondition description and data structures from
11148         Sem_Prag.
11149         (Build_Class_Wide_Expression): Moved from Sem_Prag.
11150         (Build_DIC_Call): New routine.
11151         (Build_DIC_Procedure_Body): New routine.
11152         (Build_DIC_Procedure_Declaration): New routine.
11153         (Entity_Hash): Moved from Sem_Prag.
11154         (Find_DIC_Type): New routine.
11155         (Update_Primitives_Mapping): Reimplemented.
11156         (Update_Primitives_Mapping_Of_Types): New routine.
11157         * exp_util.ads (Build_Class_Wide_Expression): Moved from Sem_Prag.
11158         (Build_DIC_Call): New routine.
11159         (Build_DIC_Procedure_Body): New routine.
11160         (Build_DIC_Procedure_Declaration): New routine.
11161         (Update_Primitives_Mapping): Moved from Sem_Prag.
11162         (Update_Primitives_Mapping_Of_Types): New routine.
11163         * nlists.adb (Append_New): New routine.
11164         (Append_New_To): New routine.
11165         * nlists.ads (Append_New): New routine.
11166         (Append_New_To): New routine.
11167         * sem_ch3.adb (Analyze_Declarations): Do not generate the bodies
11168         of DIC procedures here. This is now done at the end of the
11169         visible declarations, private declarations, and at the freeze
11170         point of a type.
11171         (Analyze_Private_Extension_Declaration):
11172         A private extension inherits the DIC pragma of a parent type.
11173         (Analyze_Subtype_Declaration): No need to propagate invariant
11174         attributes to a subtype as those apply to the base type.
11175         (Build_Derived_Record_Type): No need to inherit invariants here
11176         as this is now done in Build_Derived_Type.
11177         (Build_Derived_Type): Inherit both the DIC pragma and invariants from
11178         a parent type.
11179         (Process_Full_View): Update the propagation of DIC attributes.
11180         (Propagate_Default_Init_Cond_Attributes): Removed.
11181         * sem_ch7.adb Add with and use clauses for Exp_Util.
11182         (Analyze_Package_Specification): Create the body of the DIC
11183         procedure at the end of the visible and private declarations.
11184         (Preserve_Full_Attributes): Propagate DIC attributes.
11185         * sem_ch9.adb (Analyze_Protected_Type_Declaration): Propagate
11186         DIC attributes.
11187         (Analyze_Task_Type_Declaration): Propagate DIC attributes.
11188         * sem_elab.adb (Check_A_Call): Update the call to
11189         Is_Nontrivial_Default_Init_Cond_Procedure.
11190         * sem_prag.adb Remove the with and use clauses for
11191         GNAT.HTable. Move the handling of class- wide pre/postcondition
11192         description and data structures to Exp_Util.
11193         (Analyze_Pragma): Create the declaration of the DIC procedure. There
11194         is no need to propagate invariant-related attributes at this point
11195         as this is done in Build_Invariant_Procedure_Declaration.
11196         (Build_Class_Wide_Expression): Moved to Exp_Util.
11197         (Entity_Hash): Moved to Exp_Util.
11198         (Update_Primitives_Mapping): Moved to Exp_Util.
11199         * sem_prag.ads (Build_Class_Wide_Expression): Moved to Exp_Util.
11200         (Update_Primitives_Mapping): Moved to Exp_Util.
11201         * sem_util.adb: Remove with and use clauses for Ghost
11202         and Sem_Ch13.
11203         (Build_Default_Init_Cond_Call): Removed.
11204         (Build_Default_Init_Cond_Procedure_Bodies): Removed.
11205         (Build_Default_Init_Cond_Procedure_Declaration): Removed.
11206         (Get_Views): Reimplemented.
11207         (Has_Full_Default_Initialization): Reimplement the section on DIC.
11208         (Inherit_Default_Init_Cond_Procedure): Removed.
11209         (Is_Nontrivial_Default_Init_Cond_Procedure): Removed.
11210         (Is_Nontrivial_DIC_Procedure): New routine.
11211         (Is_Verifiable_DIC_Pragma): New routine.
11212         (Propagate_DIC_Attributes): New routine.
11213         * sem_util.ads (Build_Default_Init_Cond_Call): Removed.
11214         (Build_Default_Init_Cond_Procedure_Bodies): Removed.
11215         (Build_Default_Init_Cond_Procedure_Declaration): Removed.
11216         (Inherit_Default_Init_Cond_Procedure): Removed.
11217         (Is_Nontrivial_Default_Init_Cond_Procedure): Removed.
11218         (Is_Nontrivial_DIC_Procedure): New routine.
11219         (Is_Verifiable_DIC_Pragma): New routine.
11220         (Propagate_DIC_Attributes): New routine.
11221         * sem_warn.adb (Is_OK_Fully_Initialized): Reimplement the section
11222         on DIC.
11223         * sinfo.ads, sinfo.adb: Add new attribute Expression_Copy along with
11224         usage in nodes.
11225         (Expression_Copy): New routine along with pragma Inline.
11226         (Set_Expression_Copy): New routine along with pragma Inline.
11228 2017-01-06  Bob Duff  <duff@adacore.com>
11230         * bindgen.adb (Gen_Adainit, Gen_Adafinal): Change
11231         "Bind_Main_Program" to "not Bind_For_Library", because otherwise
11232         we won't generate the call to s_stalib_adafinal when the main
11233         is not written in Ada.
11235 2017-01-06  Bob Duff  <duff@adacore.com>
11237         * sem_prag.adb: Minor: remove pragma Warnings.
11239 2017-01-06  Tristan Gingold  <gingold@adacore.com>
11241         * Makefile.rtl: Do not compile s-stchop by default.
11243 2017-01-06  Patrick Bernardi  <bernardi@adacore.com>
11245         * aspects.adb, aspects.ads, exp_ch3.adb, exp_ch9.adb, par-prag.adb,
11246         sem_ch13.adb, sem_prag.adb, sem_prag.ads, snames.adb-tmpl,
11247         snames.ads-tmpl, s-secsta.adb, s-secsta.ads, s-tarest.adb,
11248         s-tarest.ads, s-taskin.adb, s-taskin.ads, s-tassta.adb, s-tassta.ads:
11249         Reverted previous change for now.
11251 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
11253         * exp_ch3.adb (Build_Initialization_Call): Apply predicate
11254         check to default discriminant value if checks are enabled.
11255         (Build_Assignment): If type of component has static predicate,
11256         apply check to its default value, if any.
11258 2017-01-06  Patrick Bernardi  <bernardi@adacore.com>
11260         * aspect.adb, aspect.ads: Added new aspect Secondary_Stack_Size.
11261         * exp_ch3.adb (Build_Init_Statements): As part of initialising
11262         the value record of a task, set its _Secondary_Stack_Size field
11263         if present.
11264         * exp_ch9.adb (Expand_N_Task_Type_Declaration): Create
11265         a _Secondary_Stack_Size field in the value record of
11266         the task if a Secondary_Stack_Size rep item is present.
11267         (Make_Task_Create_Call): Include secondary stack size
11268         parameter. If No_Secondary_Stack restriction is in place, passes
11269         stack size of 0.
11270         * par-prag.adb, sem_prag.adb, sem_prag.ads: Added new pragma
11271         Secondary_Stack_Size.
11272         * s-secsta.adb, s-secsta.ads (Minimum_Secondary_Stack_Size): New
11273         function to define the overhead of the secondary stack.
11274         * s-tarest.adb (Create_Restricted_Task,
11275         Create_Restricted_Task_Sequential): Functions now include
11276         Secondary_Stack_Size parameter to pass to Initialize_ATCB.
11277         * s-tarest.adb (Create_Restricted_Task,
11278         Create_Restricted_Task_Sequential): Calls to Initialize_ATCB
11279         now include Secondary_Stack_Size parameter.
11280         (Task_Wrapper):
11281         Secondary stack now allocated to the size specified by the
11282         Secondary_Stack_Size parameter in the task's ATCB.
11283         * s-taskin.adb, s-taskin.adb (Common_ATCB, Initialise_ATCB): New
11284         Secondary_Stack_Size component.
11285         * s-tassta.adb, s-tassta.ads (Create_Restricted_Task,
11286         Create_Restricted_Task_Sequential): Function now include
11287         Secondary_Stack_Size parameter.
11288         (Task_Wrapper): Secondary stack
11289         now allocated to the size specified by the Secondary_Stack_Size
11290         parameter in the task's ATCB.
11291         * sem_ch13.adb (Analyze_Aspect_Specification): Add support
11292         for Secondary_Stack_Size aspect, turning the aspect into its
11293         corresponding internal attribute.
11294         (Analyze_Attribute_Definition):
11295         Process Secondary_Stack_Size attribute.
11296         * snames.adb-tmpl, snames.ads-tmpl: Added names
11297         Name_Secondary_Stack_Size, Name_uSecondary_Stack_Size,
11298         Attribute_Secondary_Stack_Size and Pragma_Secondary_Stack_Size.
11300 2017-01-06  Pascal Obry  <obry@adacore.com>
11302         * a-direio.adb, a-direio.ads, a-sequio.adb, a-sequio.ads: Add Flush to
11303         Sequential_IO and Direct_IO.
11305 2017-01-06  Bob Duff  <duff@adacore.com>
11307         * snames.ads-tmpl (Renamed): New name for the pragma argument.
11308         * par-ch2.adb: Allow the new pragma (with analysis deferred
11309         to Sem_Prag).
11310         * sinfo.ads, sinfo.adb (Map_Pragma_Name, Pragma_Name_Mapped):
11311         Keep a mapping from new pragma names to old names.
11312         * sem_prag.adb: Check legality of pragma Rename_Pragma, and
11313         implement it by calling Map_Pragma_Name.
11314         * checks.adb, contracts.adb, einfo.adb, errout.adb,
11315         * exp_attr.adb, exp_ch3.adb, exp_ch6.adb, exp_ch7.adb, exp_ch9.adb,
11316         * exp_prag.adb, exp_util.adb, freeze.adb, frontend.adb, ghost.adb,
11317         * inline.adb, lib-writ.adb, scans.adb, scans.ads, sem_attr.adb,
11318         * sem_aux.adb, sem_ch10.adb, sem_ch13.adb, sem_ch6.adb, sem_ch9.adb,
11319         * sem_elab.adb, sem_res.adb, sem_util.adb, sem_util.ads,
11320         * sem_warn.adb: Call Pragma_Name_Mapped instead of Pragma_Name
11321         as appropriate.
11323 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
11325         * exp_ch9.adb: Minor reformatting.
11327 2017-01-06  Tristan Gingold  <gingold@adacore.com>
11329         * exp_ch9.ads, exp_ch9.adb (Build_Entry_Names): Remove (unused).
11330         * rtsfind.ads (RE_Task_Entry_Names_Array, RO_ST_Set_Entry_Names)
11331         (RE_Protected_Entry_Names_Array, RO_PE_Set_Entry_Names): Remove
11332         (unused).
11333         * s-taskin.ads, s-taskin.adb (Set_Entry_Names,
11334         Task_Entry_Names_Array, Task_Entry_Names_Access): Remove.
11335         * s-tpoben.ads, s-tpoben.adb (Set_Entry_Names,
11336         Protected_Entry_Names_Array, Protected_Entry_Names_Access): Remove.
11338 2017-01-06  Bob Duff  <duff@adacore.com>
11340         * sinfo.ads, sinfo.adb (Map_Pragma_Name): Preparation work,
11341         dummy implementation of Map_Pragma_Name.
11343 2017-01-06  Tristan Gingold  <gingold@adacore.com>
11345         * exp_ch9.adb (Expand_N_Protected_Type_Declaration): Make the
11346         entry_body variable constant.
11347         * s-taprob.ads (Entry_Body_Access): Move to s-tposen.
11348         * s-tpoben.ads (Protected_Entry_Body_Access): Now access
11349         to constant.
11350         * s-tposen.ads (Entry_Body_Access): Moved from s-taprob,
11351         now access to constant.
11353 2017-01-06  Gary Dismukes  <dismukes@adacore.com>
11355         * einfo.ads, sem_res.adb, sem_attr.adb, sem_ch6.adb: Minor
11356         reformatting and typo fixes.
11358 2017-01-06  Bob Duff  <duff@adacore.com>
11360         * snames.ads-tmpl: New names for pragma renaming.
11361         * snames.adb-tmpl (Is_Configuration_Pragma_Name): Minor cleanup.
11362         * par-prag.adb: Add new pragma name to case statement.
11363         * sem_prag.adb (Rename_Pragma): Initial cut at semantic analysis
11364         of the pragma.
11365         * sinfo.ads, sinfo.adb (Pragma_Name_Mapped): Preparation work,
11366         Dummy implementation of Pragma_Name_Mapped.
11368 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
11370         * exp_ch6.adb (Expand_Protected_Subprogram_Call): Add guard to
11371         better detect call within an entry_wrapper.
11372         * sem_res.adb (Resolve_Call): A protected call within an
11373         entity_wrapper is analyzed in the context of the protected
11374         object but corresponds to a pre-analysis and is not an access
11375         before elaboration.
11376         * sem_attr.adb: Minor reformatting.
11378 2017-01-06  Justin Squirek  <squirek@adacore.com>
11380         * sem_attr.adb (Analyze_Attribute): Modify semantic checks for
11381         Finalization_Size to allow a prefix of any non-class-wide type.
11382         * sem_attr.ads Modify comment for Finalization_Size to include
11383         definite type use case.
11385 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
11387         * einfo.ads, einfo.adb (Is_Entry_Wrapper): New flag, defined
11388         on procedures that are wrappers created for entries that have
11389         preconditions.
11390         * sem_ch6.adb (Analyze_Subrogram_Body_Helper): If the subprogram
11391         body is an entry_wrapper, compile it in the context of the
11392         synchronized type, because a precondition may refer to funtions
11393         of the type.
11394         * exp_ch9.adb (Build_Contract_Wrapper): Set Is_Entry_Wrapper on
11395         body entity.
11396         * exp_ch6.adb (Expand_Protected_Subprogram_Call): if the call is
11397         within an Entry_Wrapper this is an external call whose target
11398         is the synchronized object that is the actual in the call to
11399         the wrapper.
11401 2017-01-06  Yannick Moy  <moy@adacore.com>
11403         * sem_attr.adb (Analyze_Attribute/Attribute_Loop_Entry): Analyze node
11404         in tree, which means not analyzing the previous prefix if the node has
11405         been rewritten into its prefix.
11407 2017-01-06  Gary Dismukes  <dismukes@adacore.com>
11409         * s-tpobop.adb: Minor reformatting.
11411 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
11413         * checks.adb (Ensure_Valid): Do not generate a validity check
11414         within a generated predicate function, validity checks will have
11415         been applied earlier when required.
11417 2017-01-06  Tristan Gingold  <gingold@adacore.com>
11419         * s-tpoben.ads (Protection_Entries): Add comment and reorder
11420         components for performances.
11421         * s-tpobop.adb (PO_Do_Or_Queue): Implement Max_Queue_Length runtime
11422         semantic.
11424 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
11426         * sem_eval.adb (Check_Expression_Against_Static_Predicate):
11427         If expression is compile-time known and obeys a static predicate
11428         it must be labelled as static, to prevent spurious warnings and
11429         run-time errors, e.g. in case statements. This is relevant when
11430         the expression is the result of constant-folding a type conversion
11431         whose expression is a variable with a known static value.
11433 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
11435         * exp_attr.adb, sem_attr.ads: Minor reformatting.
11437 2017-01-06  Justin Squirek  <squirek@adacore.com>
11439         * exp_attr.adb (Expand_N_Attribute_Reference): Add entry for
11440         expansion of Finalization_Size attribute.
11441         * sem_attr.adb (Analyze_Attribute): Add entry to check the
11442         semantics of Finalization_Size.
11443         (Eval_Attribute): Add null entry for Finalization_Size.
11444         * sem_attr.ads: Add Finalization_Size to the implementation
11445         dependent attribute list.
11446         * snames.ads-tmpl: Add name entry for Finalization_Size attribute.
11448 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
11450         * sem_ch5.adb (Analyze_Loop_Statement): If the loop includes an
11451         iterator specification with a serious syntactic error, transform
11452         construct into an infinite loop in order to continue analysis
11453         and prevent a compiler abort.
11455 2017-01-06  Tristan Gingold  <gingold@adacore.com>
11457         * exp_ch9.adb (Expand_N_Protected_Type_Declaration): Do not generate
11458         max_queue_lengths_array if unused.
11460 2017-01-06  Bob Duff  <duff@adacore.com>
11462         * errout.adb (Set_Msg_Text): Protect against out-of-bounds
11463         array access, in case "\" is at the end of Text.
11464         * stylesw.adb (Set_Style_Check_Options): Don't include input
11465         characters in the error message template, because they could
11466         be control characters such as "\", which Errout will try to
11467         interpret.
11469 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
11471         * sem_ch4.adb (Find_Indexing_Operations, Inspect_Declarations):
11472         For a private type examine the visible declarations that follow
11473         the partial view, not just the private declarations that follow
11474         the full view.
11476 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
11478         * exp_ch5.adb, sem_ch3.adb, checks.adb: Minor reformatting and
11479         code cleanup.
11481 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
11483         * exp_ch5.adb (Get_Default_Iterator): For a derived type, the
11484         alias of the inherited op is the parent iterator, no need to
11485         examine dispatch table positions which might not be established
11486         yet if type is not frozen.
11487         * sem_disp.adb (Check_Controlling_Formals): The formal of a
11488         predicate function may be a subtype of a tagged type.
11489         * sem_ch3.adb (Complete_Private_Subtype): Adjust inheritance
11490         of representation items for the completion of a type extension
11491         where a predicate applies to the partial view.
11492         * checks.ads, checks.adb (Apply_Predicate_Check): Add optional
11493         parameter that designates function whose actual receives a
11494         predicate check, to improve warning message when the check will
11495         lead to infinite recursion.
11496         * sem_res.adb (Resolve_Actuals): Pass additional parameter to
11497         Apply_Predicate_Check.
11499 2017-01-06  Tristan Gingold  <gingold@adacore.com>
11501         * s-rident.ads (Profile_Info): Remove No_Entry_Queue from
11502         Gnat_Extended_Ravenscar.
11503         * exp_ch9.adb, s-tpoben.adb, s-tpoben.ads: Fix spelling.
11505 2017-01-06  Gary Dismukes  <dismukes@adacore.com>
11507         * sem_util.ads: Minor typo fix and reformatting.
11509 2017-01-06  Yannick Moy  <moy@adacore.com>
11511         * ghost.adb Minor fixing of references to SPARK RM.
11512         (Check_Ghost_Context): Check whether reference is to a lvalue
11513         before issuing an error about violation of SPARK RM 6.9(13)
11514         when declaration has Ghost policy Check and reference has Ghost
11515         policy Ignore.
11516         * sem_util.adb Minor indentation.
11517         * sem_ch10.adb (Analyze_Package_Body_Stub, Analyze_Protected_Body_Stub,
11518         Analyze_Task_Body_Stub): Set Ekind of the defining identifier.
11519         * sem_util.ads (Unique_Defining_Entity): Document the result
11520         for package body stubs.
11522 2017-01-06  Tristan Gingold  <gingold@adacore.com>
11524         * raise-gcc.c (abort): Macro to call Abort_Propagation.
11525         * s-tpoben.ads (Protected_Entry_Queue_Max_Access): Make it access
11526         constant.
11527         * exp_ch9.adb (Expand_N_Protected_Type_Declaration):
11528         Do not generate the Entry_Max_Queue_Lengths_Array if all default
11529         values.
11530         * exp_util.adb (Corresponding_Runtime_Package): Consider
11531         Max_Queue_Length pragma.
11533 2017-01-06  Justin Squirek  <squirek@adacore.com>
11535         * exp_ch9.adb (Expand_N_Protected_Type_Declaration):
11536         Remove declaration generation in the case of
11537         System_Tasking_Protected_Objects_Single_Entry being used,
11538         and add a warning message when this is detected to occur.
11539         (Make_Initialize_Protection): Remove reference pass in the case
11540         of System_Tasking_Protected_Objects_Single_Entry.
11541         * rtsfind.ads: Remove RE_Protected_Entry_Queue_Max
11542         * s-tposen.adb (Initialize_Protection_Entry): Remove
11543         Entry_Queue_Max parameter.
11544         * s-tposen.ads: Remove the types use to store the entry queue
11545         maximum.
11546         * sem_prag.adb (Analyze_Pragma): Remove entry families restriction
11548 2017-01-06  Yannick Moy  <moy@adacore.com>
11550         * sem_util.adb, sem_util.ads (Get_Enum_Lit_From_Pos): Strengthen
11551         behavior of function, to also accept out of range positions
11552         and raise Constraint_Error in such case, and to copy sloc from
11553         literal if No_Location passed as location.
11554         * uintp.adb, uintp.ads (UI_To_Int, UI_To_CC): Strengthen behavior
11555         of functions to raise Constraint_Error in case of value not in
11556         appropriate range.
11558 2017-01-06  Tristan Gingold  <gingold@adacore.com>
11560         * sem_util.adb, s-taprop-linux.adb (Finalize_TCB): Remove call to
11561         Invalidate_Stack_Cache.
11563 2017-01-06  Eric Botcazou  <ebotcazou@adacore.com>
11565         * s-os_lib.adb: Minor fix to the signature of Readlink.
11567 2017-01-06  Javier Miranda  <miranda@adacore.com>
11569         * sem_ch6.adb (Conforming_Types): Handle another
11570         confusion between views in a nested instance with an actual
11571         private type whose full view is not in scope.
11573 2017-01-06  Arnaud Charlet  <charlet@adacore.com>
11575         * exp_ch5.adb (Expand_N_If_Statement): Obey existing comment and
11576         mark a rewritten if statement as explicit (Comes_From_Source).
11578 2017-01-06  Gary Dismukes  <dismukes@adacore.com>
11580         * sem_prag.adb, rtsfind.adb, sem_util.adb: Minor typo fixes.
11582 2017-01-06  Tristan Gingold  <gingold@adacore.com>
11584         * ada.ads, a-unccon.ads: Add pragma No_Elaboration_Code_All.
11586 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
11588         * sem_case.adb: Minor reformatting.
11590 2017-01-06  Thomas Quinot  <quinot@adacore.com>
11592         * g-socthi-mingw.adb: Remove now extraneous USE TYPE clause
11594 2017-01-06  Justin Squirek  <squirek@adacore.com>
11596         * aspects.adb: Register aspect in Canonical_Aspect.
11597         * aspects.ads: Associate qualities of Aspect_Max_Queue_Length
11598         into respective tables.
11599         * einfo.ads, einfo.adb: Add a new attribute for
11600         handling the parameters for Pragma_Max_Entry_Queue
11601         (Entry_Max_Queue_Lengths_Array) in E_Protected_Type. Subprograms
11602         for accessing and setting were added as well.
11603         * par-prag.adb (Prag): Register Pramga_Max_Entry_Queue.
11604         * exp_ch9.adb (Expand_N_Protected_Type_Declaration): Emit
11605         declaration for pramga arguments and store them in the protected
11606         type node.
11607         (Make_Initialize_Protection): Pass a reference to
11608         the Entry_Max_Queue_Lengths_Array in the protected type node to
11609         the runtime.
11610         * rtsfind.adb: Minor grammar fix.
11611         * rtsfind.ads: Register new types taken from the
11612         runtime libraries RE_Protected_Entry_Queue_Max and
11613         RE_Protected_Entry_Queue_Max_Array
11614         * s-tposen.adb, s-tpoben.adb
11615         (Initialize_Protection_Entry/Initialize_Protection_Entries):
11616         Add extra parameter and add assignment to local object.
11617         * s-tposen.ads, s-tpoben.ads: Add new types to
11618         store entry queue maximums and a field to the entry object record.
11619         * sem_ch13.adb (Analyze_Aspect_Specifications): Add case statement
11620         for Aspect_Max_Queue_Length.
11621         (Check_Aspect_At_Freeze_Point):
11622         Add aspect to list of aspects that don't require delayed analysis.
11623         * sem_prag.adb (Analyze_Pragma): Add case statement for
11624         Pragma_Max_Queue_Length, check semantics, and register arugments
11625         in the respective entry nodes.
11626         * sem_util.adb, sem_util.ads Add functions Get_Max_Queue_Length
11627         and Has_Max_Queue_Length
11628         * snames.ads-tmpl: Add constant for the new aspect-name
11629         Name_Max_Queue_Length and corrasponding pragma.
11631 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
11633         * exp_util.adb (Is_Controlled_Function_Call):
11634         Reimplemented. Consider any node which has an entity as the
11635         function call may appear in various ways.
11637 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
11639         * exp_attr.adb (Rewrite_Stream_Proc_Call): Use
11640         an unchecked type conversion when performing a view conversion
11641         to/from a private type. In all other cases use a regular type
11642         conversion to ensure that any relevant checks are properly
11643         installed.
11645 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
11647         * sem_prag.adb, sem_ch8.adb: Minor reformatting.
11649 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
11651         * sem_case.adb (Explain_Non_Static_Bound): Suppress cascaded
11652         error on case expression that is an entity, when coverage is
11653         incomplete and entity has a static value obtained by local
11654         propagation.
11655         (Handle_Static_Predicate): New procedure, subsidiary of
11656         Check_Choices, to handle case alternatives that are either
11657         subtype names or subtype indications involving subtypes that
11658         have static predicates.
11660 2017-01-06  Thomas Quinot  <quinot@adacore.com>
11662         * s-oscons-tmplt.c, g-socket.adb, g-socket.ads, g-sothco.ads:
11663         (GNAT.Socket): Add support for Busy_Polling and Generic_Option
11665 2017-01-06  Bob Duff  <duff@adacore.com>
11667         * sem_elab.adb (Activate_Elaborate_All_Desirable): Don't add
11668         Elaborate_All(P) to P itself. That could happen in obscure cases,
11669         and always introduced a cycle (P body must be elaborated before
11670         P body).
11671         * lib-writ.ads: Comment clarification.
11672         * ali-util.ads: Minor comment fix.
11673         * ali.adb: Minor reformatting.
11675 2017-01-06  Tristan Gingold  <gingold@adacore.com>
11677         * a-exexpr-gcc.adb: Improve comment.
11679 2017-01-03  James Cowgill  <James.Cowgill@imgtec.com>
11681         * s-linux-mips.ads: Use correct signal and errno constants.
11682         (sa_handler_pos, sa_mask_pos): Fix offsets for 64-bit MIPS.
11684 2017-01-03  James Cowgill  <James.Cowgill@imgtec.com>
11686         * s-linux-mips.ads: Rename from s-linux-mipsel.ads.
11687         * gcc-interface/Makefile.in (MIPS/Linux): Merge mips and mipsel
11688         sections.
11690 2017-01-01  Eric Botcazou  <ebotcazou@adacore.com>
11692         * gnatvsn.ads: Bump copyright year.
11694 2017-01-01  Jakub Jelinek  <jakub@redhat.com>
11696         * gnat_ugn.texi: Bump @copying's copyright year.
11697         * gnat_rm.texi: Likewise.
11699 Copyright (C) 2017 Free Software Foundation, Inc.
11701 Copying and distribution of this file, with or without modification,
11702 are permitted in any medium without royalty provided the copyright
11703 notice and this notice are preserved.