2017-04-27 Yannick Moy <moy@adacore.com>
[official-gcc.git] / gcc / ada / ChangeLog
blob7c4293d27c605db0be3b6e75d3f4386c34b4b622
1 2017-04-27  Yannick Moy  <moy@adacore.com>
3         * gnat1drv.adb (Adjust_Global_Switches): Issue
4         a warning in GNATprove mode if the runtime library does not
5         support IEEE-754 floats.
7 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
9         * sem_prag.adb (Inherit_Class_Wide_Pre): If the parent operation
10         is itself inherited it does not carry any contract information,
11         so examine its parent operation which is its Alias.
13 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
15         * sem_attr.adb (Analyze_Attribute, case 'Image): In Ada2012 the
16         prefix can be an object reference in which case Obj'Image (X)
17         can only be interpreted as an indexing of the parameterless
18         version of the attribute.
19         * par-ch4.adb (P_Name): An attribute reference can be the prefix of
20         an indexing or a slice operation if the attribute does not require
21         parameters. In Ada2012 'Image also belongs in this category,
22         and A'Image (lo .. hi) is legal and must be parsed as a slice.
24 2017-04-27  Yannick Moy  <moy@adacore.com>
26         * exp_ch4.adb: Minor reformatting.
27         * gnat1drv.adb (Adjust_Global_Switches): When in GNATprove mode,
28         disable the CodePeer and C generation modes. Similar to the
29         opposite actions done in CodePeer mode.
31 2017-04-27  Yannick Moy  <moy@adacore.com>
33         * sem_res.adb: Remove duplicate code.
34         * sem_attr.adb: Delete duplicate code.
36 2017-04-27  Bob Duff  <duff@adacore.com>
38         * g-dyntab.adb: Reduce the amount of copying in
39         Release. No need to copy items past Last.
41 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
43         * checks.adb Add with and use clauses for Sem_Disp.
44         (Install_Primitive_Elaboration_Check): New routine.
45         * checks.ads (Install_Primitive_Elaboration_Check): New routine.
46         * exp_attr.adb (Expand_N_Attribute_Reference): Clean up the
47         processing of 'Elaborated.
48         * exp_ch6.adb (Expand_N_Subprogram_Body): Install a primitive
49         elaboration check.
51 2017-04-27  Bob Duff  <duff@adacore.com>
53         * g-dyntab.ads, g-dyntab.adb, g-table.ads: Remove incorrect assertion.
54         If the table grows and then shrinks back to empty, we won't necessarily
55         point back to the empty array. Code cleanups.
56         * sinput.ads: Add 'Base to Size clause to match the declared
57         component subtypes.
59 2017-04-27  Claire Dross  <dross@adacore.com>
61         * a-cforma.adb, a-cforma.ads (=): Generic parameter removed to
62         allow the use of regular equality over elements in contracts.
63         (Formal_Model): Ghost package containing model functions that
64         are used in subprogram contracts.
65         (Current_To_Last): Removed, model functions should be used instead.
66         (First_To_Previous): Removed, model functions should be used instead.
67         (Strict_Equal): Removed, model functions should be used instead.
68         (No_Overlap): Removed, model functions should be used instead.
69         * a-cofuma.adb, a-cofuma.ads (Enable_Handling_Of_Equivalence)
70         Boolean generic parameter to disable contracts for equivalence
71         between keys.
72         (Witness): Create a witness of a key that is used for handling of
73         equivalence between keys.
74         (Has_Witness): Check whether a witness is contained in a map.
75         (W_Get): Get the element associated to a witness.
76         (Lift_Equivalent_Keys): Removed, equivalence between keys is handled
77         directly.
78         * a-cofuse.adb, a-cofuse.ads (Enable_Handling_Of_Equivalence)
79         Boolean generic parameter to disable contracts for equivalence
80         between keys.
81         * a-cfhama.adb, a-cfhama.ads (Formal_Model.P) Disable handling
82         of equivalence on functional maps.
83         * a-cfdlli.adb, a-cfdlli.ads (Formal_Model.P) Disable handling
84         of equivalence on functional maps.
86 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
88         * exp_ch9.adb (Expand_Entry_Barrier): Code
89         cleanup. Do not perform the optimization which removes the
90         declarations of the discriminant and component renamings when
91         validity checks on operands and attributes are in effect.
93 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
95         * exp_spark.adb, exp_util.adb, sem_ch7.adb, g-dyntab.adb, g-dyntab.ads,
96         freeze.adb, a-cfinve.ads, a-cofuma.adb, a-cofuma.ads, a-cfhama.adb,
97         a-cfhama.ads, a-cofove.ads: Minor reformatting.
99 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
101         * g-debpoo.adb (Dump_Gnatmem): Protect against a possible null
102         pointer dereference.
103         * g-spipat.adb (Dump): Code clean up. Protect against a possible
104         null pointer dereference.
106 2017-04-27  Bob Duff  <duff@adacore.com>
108         * g-dyntab.ads, g-dyntab.adb: Default for Table_Low_Bound.
109         Rename Empty --> Empty_Table_Ptr, and don't duplicate code for it.
110         Free renames Init, since they do the same thing.
111         * g-table.ads: Default for Table_Low_Bound.
112         * table.ads: Default for Table_Low_Bound, Table_Initial, and
113         Table_Increment.
115 2017-04-27  Bob Duff  <duff@adacore.com>
117         * g-dyntab.ads, g-dyntab.adb: Add assertions to subprograms that
118         can reallocate.
119         * atree.adb, elists.adb, fname-uf.adb, ghost.adb, inline.adb,
120         * lib.adb, namet.adb, nlists.adb, sem.adb, sinput.adb, stringt.adb:
121         Reorder code so that above assertions do not fail.
122         * table.ads: Remove obsolete comment on Locked.
124 2017-04-27  Claire Dross  <dross@adacore.com>
126         * a-cfdlli.ads: Code cleanup.
128 2017-04-27  Yannick Moy  <moy@adacore.com>
130         * exp_spark.adb (Expand_SPARK_Freeze_Type): Build a DIC procedure
131         when needed for proof.  (Expand_SPARK): Call the new procedure.
132         * exp_util.ads Fix typo.
134 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
136         * a-cofuma.ads, a-cfhama.ads: Minor reformatting, grammar, and typo
137         fixes.
139 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
141         * sem_elab.adb Add new type Visited_Element
142         and update the contents of table Elab_Visited.  Various code clean up.
143         (Check_Elab_Call): Determine whether a prior call to
144         the same subprogram was already examined within the same context.
145         (Check_Internal_Call_Continue): Register the subprogram being
146         called as examined within a particular context. Do not suppress
147         elaboration warnings.
149 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
151         * xoscons.adb, osint.ads: Minor reformatting.
153 2017-04-27  Bob Duff  <duff@adacore.com>
155         * g-dyntab.ads, g-dyntab.adb: Misc cleanup. Rename
156         Table_Count_Type --> Table_Last_Type, because the name
157         was confusing (a "count" usually starts at zero).  Add
158         functionality supported or needed by other tables packages
159         (Move, Release_Threshold).
160         * g-table.ads, g-table.adb: This is now just a thin wrapper
161         around g-dyntab.ads/g-dyntab.adb.  Add functionality supported
162         or needed by other tables packages (Save, Restore).
163         * table.ads, table.adb: This is now just a thin wrapper around
164         * g-table.ads/g-table.adb.
165         * namet.h, scos.h, uintp.h: These files are reaching into the
166         private data of some instances of g-table, whose names changed,
167         so the above change requires some adjustment here. It now uses
168         public interfaces.
170 2017-04-27  Bob Duff  <duff@adacore.com>
172         * namet.adb, namet.ads: Minor: remove unused procedures.
174 2017-04-27  Eric Botcazou  <ebotcazou@adacore.com>
176         * checks.adb (Apply_Scalar_Range_Check): Initialize Ok variable too.
177         (Minimize_Eliminate_Overflows): Initialize Llo and Lhi.
178         Add pragma Warnings on Rtype variable in nested block.  *
179         * exp_ch3.adb (Build_Init_Statements): Initialize VAR_LOC.
180         * exp_ch4.adb (Expand_Concatenate): Initialize 3 variables.
181         (Size_In_Storage_Elements): Add pragma Warnings on Res variable.
182         * exp_ch7.adb (Build_Adjust_Statements): Initialize Bod_Stmts.
183         (Process_Component_List_For_Finalize): Initialize Counter_Id.
184         (Build_Finalize_Statements): Initialize Bod_Stmts.
185         * exp_disp.adb (Expand_Dispatching_Call): Initialize SCIL_Node.
187 2017-04-27  Claire Dross  <dross@adacore.com>
189         * a-cfhama.adb, a-cfhamai.ads (=): Generic parameter removed to
190         allow the use of regular equality over elements in contracts.
191         (Formal_Model): Ghost package containing model functions that are
192         used in subprogram contracts.
193         (Current_To_Last): Removed, model
194         functions should be used instead.
195         (First_To_Previous): Removed, model functions should be used instead.
196         (Strict_Equal): Removed, model functions should be used instead.
197         (No_Overlap): Removed, model functions should be used instead.
198         (Equivalent_Keys): Functions over cursors are removed. They were
199         awkward with explicit container parameters.
200         * a-cofuma.adb, a-cofuma.ads (Lift_Equivalent_Keys): New lemma
201         (proof only) procedure to help GNATprove when equivalence over
202         keys is not equality.
204 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
206         * exp_util.adb, a-cfdlli.adb, a-cfdlli.ads, exp_ch9.adb, g-dyntab.adb,
207         sem_dim.adb, a-cfinve.adb, a-cfinve.ads, a-cofove.adb, a-cofove.ads:
208         Minor reformatting and code cleanups.
210 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
212         * freeze.adb (Build_Inherited_Condition_Pragmas): New procedure,
213         subsidiary of Check_Inherited_Conditions, to build pragmas for an
214         operation whose ancestor has classwide pre/postconditions. This
215         is used both to check the legality of the inheritance in Ada
216         and in SPARK, and to determine whether a wrapper is needed for
217         an inherited operation.
218         * exp_util.adb (Build_Class_Wide_Expression, Replace_Entity):
219         Improve placement of error message for inherited classwide
220         conditions that become illegal on type derivation.
222 2017-04-27  Yannick Moy  <moy@adacore.com>
224         * sem_ch12.adb (Analyze_Generic_Package_Declaration): Set
225         SPARK_Mode from context on generic package.
226         * sem_ch7.adb (Analyze_Package_Declaration): Simplify code to remove
227         useless test.
229 2017-04-27  Claire Dross  <dross@adacore.com>
231         * a-cofuve.ads (Range_Shifted): Rewrite precondition to avoid
232         overflows in computations.
233         * a-cofove.ads (Capacity_Range): Rewrite last bound to avoid
234         overflows in computations.
235         (Insert): Rewrite precondition to avoid overflows in computations.
236         * a-cfinve.ads (Capacity_Range): Rewrite last bound to avoid
237         overflows in computations.
238         (Insert): Rewrite precondition to avoid overflows in computations.
240 2017-04-27  Steve Baird  <baird@adacore.com>
242         * exp_ch9.adb (Expand_N_Asynchronous_Select): Initialize the Cancel
243         flag when it is declared in order to avoid confusing CodePeer about
244         the possibility of an uninitialized variable read.
246 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
248         * sem_dim.adb (Analyze_Dimension_Object_Declaration): There is
249         no dimensionality error if the subtype of the expression is
250         identical to the nominal subtype in the declaration, even though
251         the expression itself may have been constant-folded and lack a
252         dimension vector.
253         * sem_dim.ads: Add comments on setting of dimension vectors and
254         its interaction with node rewritings and side-effect removal.
256 2017-04-27  Bob Duff  <duff@adacore.com>
258         * debug.adb: Minor comment correction.
259         * sem_dim.ads: Minor reformatting and typo fixes.
261 2017-04-27  Bob Duff  <duff@adacore.com>
263         * g-table.adb, g-table.adsa, scos.h: From the C side, access First and
264         Last of the tables via function calls, rather than relying on layout
265         of data structures.
267 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
269         * exp_util.adb: No wrapper in GNATprove mode.
271 2017-04-27  Yannick Moy  <moy@adacore.com>
273         * sem_res.adb (Resolve_Comparison_Op): Always
274         evaluate comparisons between values of universal types.
276 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
278         * sem_elab.adb (Check_Internal_Call_Continue): Do not generate
279         an elaboration counter nor a check when in GNATprove mode.
280         * sem_util.adb (Build_Elaboration_Entity): Do not create an
281         elaboration counter when in GNATprove mode.
283 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
285         * freeze.adb: copy-paste typo.
287 2017-04-27  Yannick Moy  <moy@adacore.com>
289         * sem_prag.adb (Analyze_Pre_Post_In_Decl_Part):
290         Use correct test to detect call in GNATprove mode instead of
291         compilation.
293 2017-04-27  Claire Dross  <dross@adacore.com>
295         * a-cfdlli.adb, a-cfdlli.ads (Formal_Model.M_Elements_In_Union):
296         New property function expressing that the element of a
297         sequence are contained in the union of two sequences.
298         (Formal_Model.M_Elements_Included): New property function
299         expressing that the element of a sequence are another sequence.
300         (Generic_Sorting): Use new property functions to state that
301         elements are preserved by Sort and Merge.
302         * a-cofove.adb, a-cofove.ads (=): Generic parameter removed to
303         allow the use of regular equality over elements in contracts.
304         (Formal_Model): Ghost package containing model functions
305         that are used in subprogram contracts.  (Capacity):
306         On unbounded containers, return the maximal capacity.
307         (Current_To_Last): Removed, model functions should be used instead.
308         (First_To_Previous): Removed, model functions should be used instead.
309         (Append): Default parameter value replaced
310         by new wrapper to allow more precise contracts.
311         (Insert): Subprogram restored, it seems it was useful to users even if
312         it is inefficient.
313         (Delete): Subprogram restored, it seems it was useful to users even if
314         it is inefficient.
315         (Prepend): Subprogram restored, it seems it was useful to users even
316         if it is inefficient.
317         (Delete_First): Subprogram restored, it seems it
318         was useful to users even if it is inefficient.  (Delete_Last):
319         Default parameter value replaced by new wrapper to allow more
320         precise contracts.
321         (Generic_Sorting.Merge): Subprogram restored.
322         * a-cfinve.adb, a-cfinve.ads (=): Generic parameter removed to
323         allow the use of regular equality over elements in contracts.
324         (Formal_Model): Ghost package containing model functions
325         that are used in subprogram contracts.  (Capacity):
326         On unbounded containers, return the maximal capacity.
327         (Current_To_Last): Removed, model functions should be used
328         instead.
329         (First_To_Previous): Removed, model functions should be used instead.
330         (Append): Default parameter value replaced
331         by new wrapper to allow more precise contracts.
332         (Insert): Subprogram restored, it seems it was useful to users even if
333         it is inefficient.
334         (Delete): Subprogram restored, it seems it was useful to users even if
335         it is inefficient.
336         (Prepend): Subprogram restored, it seems it was useful to users even
337         if it is inefficient.
338         (Delete_First): Subprogram restored, it seems it
339         was useful to users even if it is inefficient.  (Delete_Last):
340         Default parameter value replaced by new wrapper to allow more
341         precise contracts.
342         (Generic_Sorting.Merge): Subprogram restored.
343         (Vector): Do not reuse formal vectors, as it is no longer possible
344         to supply them with an equality function over elements.
346 2017-04-27  Bob Duff  <duff@adacore.com>
348         * g-dyntab.adb (Release): When allocating the new
349         table, use the correct slice of the old table to initialize it.
351 2017-04-27  Eric Botcazou  <ebotcazou@adacore.com>
353         * einfo.ads: Minor fixes in comments.
355 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
357         * sem_prag.adb: disable clones in SPARK_Mode.
359 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
361         * sem_util.ads, contracts.adb: Minor reformatting.
363 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
365         * sem_util.adb, sem_util.ads (Build_Class_Wide_Clone_Body):
366         Build body of subprogram that has a class-wide condition that
367         contains calls to other primitives.
368         (Build_Class_Wide_Clone_Call); Build a call to the common
369         class-wide clone of a subprogram with classwide conditions. The
370         body of the subprogram becomes a wrapper for a call to the
371         clone. The inherited operation becomes a similar wrapper to which
372         modified conditions apply, and the call to the clone includes
373         the proper conversion in a call the parent operation.
374         (Build_Class_Wide_Clone_Decl (Spec_Id : Entity_Id): For a
375         subprogram that has a classwide condition that contains calls to
376         other primitives, build an internal subprogram that is invoked
377         through a type-specific wrapper for all inherited subprograms
378         that may have a modified condition.
379         * sem_prag.adb (Check_References): If subprogram has a classwide
380         condition, create entity for corresponding clone, to be invoked
381         through wrapper subprograns.
382         (Analyze_Pre_Post_Condition_In_Decl_Part): Do not emit error
383         message about placement if pragma isi internally generated.
384         * sem_ch6.adb (Analyze_Subprogram_Body_Helper): If subprogram has
385         a classwide clone, build body of clone as copy of original body,
386         and rewrite original body as a wrapper as a wrapper for a call to
387         the clone, so that it incorporates the original pre/postconditions
388         of the subprogram.
389         * freeze.adb (Check_Inherited_Conditions): For an inherited
390         subprogram that inherits a classwide condition, build spec and
391         body of corresponding wrapper so that call to inherited operation
392         gets the modified conditions.
393         * contracts.adb (Analyze_Contracts): If analysis of classwide
394         condition has created a clone for a primitive operation, analyze
395         declaration of clone.
397 2017-04-27  Steve Baird  <baird@adacore.com>
399         * exp_util.adb (Build_Allocate_Deallocate_Proc):
400         Add "Suppress => All_Checks" to avoid generating unnecessary
401         checks.
403 2017-04-27  Yannick Moy  <moy@adacore.com>
405         * debug.adb: Reserve debug flag 'm' for no inlining in GNATprove.
406         * sem_ch6.adb (Anayze_Subprogram_Body_Helper): Skip creation of
407         inlining body in GNATprove mode when switch -gnatdm used.
408         * sem_res.adb (Resolve_Call): Skip detection of lack of inlining
409         in GNATprove mode when switch -gnatdm used.
411 2017-04-27  Arnaud Charlet  <charlet@adacore.com>
413         * sem_ch13.adb (Analyze_Attribute_Definition_Clause
414         [Attribute_Address]): Call Set_Address_Taken when ignoring rep
415         clauses, so that we keep an indication of the address clause
416         before removing it from the tree.
418 2017-04-27  Yannick Moy  <moy@adacore.com>
420         * exp_util.ads, exp_util.adb (Evaluate_Name): Force evaluation
421         of expression being qualified, when not an object name, or else
422         evaluate the underlying name.
424 2017-04-27  Jerome Lambourg  <lambourg@adacore.com>
426         * bindusg.adb, bindgen.adb, gnatbind.adb, opt.ads: add -nognarl switch.
428 2017-04-27  Justin Squirek  <squirek@adacore.com>
430         * exp_ch7.adb (Build_Finalize_Statements): Move Num_Comps to
431         Process_Component_List_For_Finalization as a local variable.
432         (Process_Component_For_Finalize): Add an extra parameter to avoid
433         global references.
434         (Process_Component_List_For_Finalization): Correct calls to
435         Process_Component_For_Finalize to take Num_Comps as a parameter.
437 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
439         * sem_ch8.adb (Find_Direct_Name): Account for the case where
440         a use-visible entity is defined within a nested scope of an
441         instance when giving priority to entities which were visible in
442         the original generic.
443         * sem_util.ads, sem_util.adb (Nearest_Enclosing_Instance): New routine.
445 2017-04-27  Tristan Gingold  <gingold@adacore.com>
447         * raise-gcc.c: Don't use unwind.h while compiling
448         for the frontend, but mimic host behavior.
450 2017-04-27  Javier Miranda  <miranda@adacore.com>
452         * sem_ch3.adb (Build_Discriminated_Subtype):
453         Propagate Has_Pragma_Unreferenced_Objects to the built subtype.
455 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
457         * sem_prag.adb (Analyze_Global_Item):
458         Do not consider discriminants because they are not "entire
459         objects". Remove the discriminant-related checks because they are
460         obsolete.
461         (Analyze_Input_Output): Do not consider discriminants
462         because they are not "entire objects".
464 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
466         * sem_ch13.adb (Check_Aspect_At_End_Of_Declarations): Do not
467         perform check if the current scope does not come from source,
468         as is the case for a rewritten task body, because check has
469         been performed already, and may not be doable because of changed
470         visibility.
472 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
474         * a-cofuse.adb, a-cfdlli.adb, a-cofuse.ads, a-cfdlli.ads, a-cofuve.adb,
475         a-cofuve.ads, a-cofuma.adb, a-cofuma.ads, sem_eval.adb, a-cofuba.adb:
476         Minor reformatting.
478 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
480         * sem_ch4.adb (Analyze_Call): If the return type of a function
481         is incomplete in an context in which the full view is available,
482         replace the type of the call by the full view, to prevent spurious
483         type errors.
484         * exp_disp.adb (Check_Premature_Freezing): Disable check on an
485         abstract subprogram so that compiler does not reject a parameter
486         of a primitive operation of a tagged type being frozen, when
487         the untagged type of that parameter cannot be frozen.
489 2017-04-27  Bob Duff  <duff@adacore.com>
491         * sem_attr.adb (Compute_Type_Key): Don't walk
492         representation items for irrelevant types, which could be in a
493         different source file.
495 2017-04-27  Steve Baird  <baird@adacore.com>
497         * exp_attr.adb (Expand_N_Attribute_Reference):
498         Don't expand Image, Wide_Image, Wide_Wide_Image attributes
499         for CodePeer.
501 2017-04-27  Yannick Moy  <moy@adacore.com>
503         * exp_unst.ads: Fix typos in comments.
505 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
507         * sem_eval.adb (Choice_Matches): Handle properly a real literal
508         whose type has a defined static predicate.
510 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
512         * exp_ch4.adb (Insert_Dereference_Action):
513         Do not adjust the address of a controlled object when the
514         associated access type is subject to pragma No_Heap_Finalization.
515         Code reformatting.
517 2017-04-27  Pierre-Marie de Rodat  <derodat@adacore.com>
519         * gcc-interface/utils.c (gnat_type_for_size): Set
520         TYPE_ARTIFICIAL on created types.
522 2017-04-27  Claire Dross  <dross@adacore.com>
524         * a-cfdlli.adb, a-cfdlli.ads (Formal_Model): Adapt to
525         modifications in functional containers.
526         * a-cofuba.ads, a-cofuma.ads, a-cofuse.ads, a-cofuve.ads Reformat
527         to improve readablity. Subprograms are separated between basic
528         operations, constructors and properties. Universally quantified
529         formulas in contracts are factorized in independant functions
530         with a name and a comment.  Names of parameters are improved.
532 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
534         * exp_spark.adb, sem_elab.adb: Minor reformatting and typo fix.
536 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
538         * sem_res.adb (Resolve_Type_Conversion): Do not
539         install a predicate check here since this is already done during
540         the expansion phase. Verify whether the operand satisfies the
541         static predicate (if any) of the target type.
542         * sem_ch3.adb (Analyze_Object_Declaration): Do
543         not install a predicate check if the object is initialized by
544         means of a type conversion because the conversion is subjected
545         to the same check.
547 2017-04-27  Tristan Gingold  <gingold@adacore.com>
549         * raise.c (__gnat_builtin_longjmp): Remove.
550         (__gnat_bracktrace):
551         Add a dummy definition for the compiler (__gnat_eh_personality,
552         __gnat_rcheck_04, __gnat_rcheck_10) (__gnat_rcheck_19,
553         __gnat_rcheck_20, __gnat_rcheck_21) (__gnat_rcheck_30,
554         __gnat_rcheck_31, __gnat_rcheck_32): Likewise.
555         * a-exexpr.adb: Renamed from a-exexpr-gcc.adb
556         * a-except.ads, a-except.adb: Renamed from a-except-2005.ads
557         and a-except-2005.adb.
558         * raise-gcc.c: Allow build in compiler, compiled as a C++
559         file.
560         (__gnat_Unwind_ForcedUnwind): Adjust prototype.
561         (db): Constify msg_format.
562         (get_call_site_action_for): Don't use void arithmetic.
563         * system.ads (Frontend_Exceptions): Set to False.
564         (ZCX_By_Default): Set to True.
565         (GCC_ZC_Support): Set to True.
566         * gcc-interface/Makefile.in: No more variants for a-exexpr.adb and
567         a-except.ad[sb].
568         * gcc-interface/Make-lang.in: Add support for backend zcx exceptions
569         in gnat1 and gnatbind.
570         * gnat1, gnatbind: link with raise-gcc.o, a-exctra.o, s-addima.o,
571         s-excmac.o, s-imgint.o, s-traceb.o, s-trasym.o, s-wchstw.o
572         * s-excmac.ads, s-excmac.adb: Copy of variants.
573         * a-except.o: Adjust preequisites.
574         Add handling of s-excmac-arm.adb and s-excmac-gcc.adb.
576 2017-04-27  Claire Dross  <dross@adacore.com>
578         * a-cfdlli.adb, a-cfdlli.ads (Formal_Model): Adapt to
579         modifications in functional containers.
580         * a-cofuba.ads, a-cofuma.ads, a-cofuse.ads, a-cofuve.ads Reformat
581         to improve readablity. Subprograms are separated between basic
582         operations, constructors and properties. Universally quantified
583         formulas in contracts are factorized in independant functions
584         with a name and a comment.  Names of parameters are improved.
586 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
588         * exp_spark.adb, sem_elab.adb: Minor reformatting and typo fix.
590 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
592         * sem_res.adb (Resolve_Type_Conversion): Do not
593         install a predicate check here since this is already done during
594         the expansion phase. Verify whether the operand satisfies the
595         static predicate (if any) of the target type.
596         * sem_ch3.adb (Analyze_Object_Declaration): Do
597         not install a predicate check if the object is initialized by
598         means of a type conversion because the conversion is subjected
599         to the same check.
601 2017-04-27  Tristan Gingold  <gingold@adacore.com>
603         * a-except.ads, a-except.adb, a-exexpr.adb: Removed (will be
604         replaced by their variants).
606 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
608         * exp_prag.adb, a-cofuse.adb, a-cofuse.ads, einfo.adb, sem_prag.adb,
609         cstand.adb, par-prag.adb, a-cofuve.adb, a-cofuve.ads, a-cofuma.adb,
610         a-cofuma.ads, a-cofuba.adb, a-cofuba.ads: Minor reformatting.
612 2017-04-27  Tristan Gingold  <gingold@adacore.com>
614         * s-excmac-gcc.ads, s-excmac-gcc.adb,
615         s-excmac-arm.ads, s-excmac-arm.adb (New_Occurrence): Rewrite it in
616         Ada95.
618 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
620         * exp_ch7.adb (Establish_Transient_Scope): Rewrite
621         the loop which detects potential enclosing transient scopes. The
622         loop now terminates much earlier as transient scopes are bounded
623         by packages and subprograms.
625 2017-04-27  Claire Dross  <dross@adacore.com>
627         * a-cfdlli.adb, a-cfdlli.ads (=): Generic parameter removed to
628         allow the use of regular equality over elements in contracts.
629         (Cursor): Type is now public so that it can be used in
630         model functions.
631         (Formal_Model): Ghost package containing
632         model functions that are used in subprogram contracts.
633         (Current_To_Last): Removed, model functions should be used
634         instead.
635         (First_To_Previous): Removed, model functions should
636         be used instead.
637         (Strict_Equal): Removed, model functions
638         should be used instead.
639         (Append): Default parameter value
640         replaced by new wrapper to allow more precise contracts.
641         (Insert): Default parameter value replaced by new wrapper to
642         allow more precise contracts.
643         (Delete): Default parameter
644         value replaced by new wrapper to allow more precise contracts.
645         (Prepend): Default parameter value replaced by new wrapper to
646         allow more precise contracts.
647         (Delete_First): Default parameter
648         value replaced by new wrapper to allow more precise contracts.
649         (Delete_Last): Default parameter value replaced by new wrapper
650         to allow more precise contracts.
652 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
654         * exp_spark.adb (Expand_SPARK): Perform specialized expansion
655         for object declarations.
656         (Expand_SPARK_N_Object_Declaration): New routine.
657         * sem_elab.adb (Check_A_Call): Include calls to the
658         Default_Initial_Condition procedure of a type under the SPARK
659         elaboration checks umbrella.
661 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
663         * sem.adb (Analyze): Diagnose an illegal iterated component
664         association.
665         * sem_util.ads, sem_util.adb
666         (Diagnose_Iterated_Component_Association): New routine.
668 2017-04-27  Bob Duff  <duff@adacore.com>
670         * adaint.c (__gnat_get_current_dir): Return 0 in length if
671         getcwd fails.
672         * a-direct.adb, g-dirope.adb, osint.adb, s-os_lib.adb: Raise
673         exception if getcwd failed.
675 2017-04-27  Yannick Moy  <moy@adacore.com>
677         * exp_dbug.adb, exp_dbug.ads (Get_External_Name): Prefix ghost
678         entities with special prefix.
680 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
682         * debug.adb Change the documentation of switch -gnatd.s.
683         * exp_ch7.adb (Make_Transient_Block): Transient blocks do not need
684         to manage the secondary stack when an enclosing scope already
685         performs this functionality (aka relaxed management). Switch
686         -gnatd.s may be used to force strict management in which case
687         the block will manage the secondary stack unconditionally. Add
688         a guard to stop the traversal when encountering a package or a
689         subprogram scope.
691 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
693         * sem_res.adb (Resolve_Call): Refine further the handling of
694         limited views of return types in function calls. If the function
695         that returns a limited view appears in the current unit,
696         we do not replace its type by the non-limited view because
697         this transformation is performed int the back-end. However,
698         the type of the call itself must be the non-limited view, to
699         prevent spurious resolution errors.
701 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
703         * einfo,ads, einfo.adb (Class_Wide_Preconds, Class_Wide_Postconds):
704         Removed, proposed implementation using generics for class-wide
705         preconditions proved impractical.
706         (Class_Wide_Clone): New attribute of subprogram. Designates
707         subprogram created for primitive operations with class-wide
708         pre/postconditions that contain calls to other primitives. The
709         clone holds the body of the original primitive, but the
710         pre/postonditions do not apply to it. The original body is
711         rewritten as a wrapper for a call to the clone.
712         (Is_Class_Wide_Clone): New flag to identify a Class_Wide_Clone. If
713         the flag is set, no code for the corresponding pre/postconditions
714         is inserted into its body.
716 2017-04-27  Bob Duff  <duff@adacore.com>
718         * exp_prag.adb, par-prag.adb, sem_ch13.adb: Ignore
719         Scalar_Storage_Order if -gnatI is given.
720         * sem_prag.adb (Analyze_Pragma): Ignore
721         Default_Scalar_Storage_Order if -gnatI is given.
723 2017-04-27  Claire Dross  <dross@adacore.com>
725         * a-cofuba.ads (Add): Take as an additional input parameter
726         the position where the element should be inserted.
727         (Remove): New function that removes an element from the container.
728         * a-cofuma.ads (Add): Adapt to the new API of Base.Add.
729         * a-cofuse.ads (Add): Adapt to the new API of Base.Add.
730         (Remove): New function that removes an element from a set.
731         * a-cofuve.ads (Add): Adapt to the new API of Base.Add.
732         (Remove): New function that removes an element from a sequence.
733         (Insert): New function that adds anywhere in a sequence.
735 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
737         * checks.adb (Generate_Range_Check): Revert previous change.
739 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
741         * sem_util.adb: Minor reformatting/rewording.
743 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
745         * lib-xref.adb (Generate_Reference): The use
746         of attribute 'Result is not considered a violation of pragma
747         Unreferenced.
749 2017-04-27  Justin Squirek  <squirek@adacore.com>
751         * cstand.adb (Create_Standard): Correctly set
752         Directly_Designated_Type for Any_Access.
753         * sem_type.adb (Covers): Minor grammar fixes.
755 2017-04-27  Bob Duff  <duff@adacore.com>
757         * sem_attr.adb: Minor cleanup.
759 2017-04-27  Claire Dross  <dross@adacore.com>
761         * a-cofuba.ads, a-cofuba.adb (Ada.Containers.Functional_Base): New
762         private child of Ada.Containers used to implement all functional
763         containers.
764         * a-cofuma.ads, a-cofuma.adb (Ada.Containers.Functional_Maps): New
765         child of Ada.Containers. It provides functional indefinite unbounded
766         maps which can be used as high level models for specification
767         of data structures.
768         * a-cofuse.ads, a-cofuse.adb (Ada.Containers.Functional_Sets): New
769         child of Ada.Containers. It provides functional indefinite unbounded
770         sets which can be used as high level models for specification
771         of data structures.
772         * a-cofuve.ads, a-cofuve.adb (Ada.Containers.Functional_Vectors): New
773         child of Ada.Containers.  It provides functional indefinite unbounded
774         vectors which can be used as high level models for specification
775         of data structures.
776         * Makefile.rtl: Add new packages.
777         * impunit.adb: Add new packages.
779 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
781         * sem_ch4.adb: Minor reformatting.
783 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
785         * sem_ch12.adb (Analyze_Associations): minor reformatting.
786         (Check_Fixed_Point_Actual): Do not emit a warning on a fixed
787         point type actual that has user-defined arithmetic primitives,
788         when there is a previous actual for a formal package that defines
789         a fixed-point type with the parent user-defined operator.
791 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
793         * checks.adb (Generate_Range_Check): Reinstate part of previous change.
794         * sem_attr.adb (Resolve_Attribute): Generate a range check when
795         the component type allows range checks.
797 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
799         * sem_aux.adb (Is_Generic_Formal): Use original node to locate
800         corresponding declaration, because formal derived types are
801         rewritten as private extensions.
803 2017-04-27  Ed Schonberg  <schonberg@adacore.com>
805         * sem_dim.adb (Analyze_Dimension_Binary_Op): Do not check
806         dimensions of operands if node has been analyzed already, because
807         previous analysis and dimension checking will have removed the
808         dimension information from the operands.
810 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
812         * debug.adb: Document the use of switch -gnatd.s.
813         * einfo.ads Update the documentation on attribute
814         Sec_Stack_Needed_For_Return and attribute Uses_Sec_Stack. Remove
815         the uses of these attributes from certain entities.
816         * exp_ch7.adb (Make_Transient_Block): Reimplement the circuitry
817         which determines whether the block should continue to manage
818         the secondary stack.
819         (Manages_Sec_Stack): New routine.
821 2017-04-27  Bob Duff  <duff@adacore.com>
823         * atree.ads: Minor edit.
825 2017-04-27  Hristian Kirtchev  <kirtchev@adacore.com>
827         * sinfo.ads: Update the section on Ghost mode. Add
828         a section on SPARK mode. Update the placement of section on
829         expression functions.
831 2017-04-27  Bob Duff  <duff@adacore.com>
833         * sinput.adb (Get_Source_File_Index): Don't
834         assert that S is in the right range in the case where this is
835         a .dg file under construction.
837 2017-04-27  Yannick Moy  <moy@adacore.com>
839         * sem_util.adb (Check_Result_And_Post_State):
840         Handle more precisely each conjunct in expressions formed by
841         and'ing sub-expressions.
843 2017-04-27  Gary Dismukes  <dismukes@adacore.com>
845         * exp_ch4.adb, sem_ch4.adb: Minor typo fix and reformatting.
847 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
849         * gnat_rm.texi, gnat_ugn.texi,
850         doc/gnat_ugn/building_executable_programs_with_gnat.rst,
851         doc/gnat_ugn/platform_specific_information.rst,
852         doc/gnat_ugn/gnat_and_program_execution.rst,
853         doc/gnat_ugn/gnat_utility_programs.rst,
854         doc/gnat_ugn/the_gnat_compilation_model.rst,
855         doc/gnat_rm/implementation_defined_attributes.rst,
856         doc/gnat_rm/the_gnat_library.rst,
857         doc/gnat_rm/implementation_defined_pragmas.rst,
858         doc/gnat_rm/representation_clauses_and_pragmas.rst,
859         doc/gnat_rm/implementation_of_specific_ada_features.rst,
860         doc/gnat_rm/implementation_defined_aspects.rst,
861         doc/gnat_rm/implementation_defined_characteristics.rst: Update
862         documentation.
864 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
866         * exp_ch4.adb (Expand_N_Case_Expression): Emit error message when
867         generating C code on complex case expressions.
869 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
871         * sem_prag.adb (Analyze_Pragma): Generate a warning instead
872         of silently ignoring pragma Ada_xxx in Latest_Ada_Only mode.
873         * directio.ads, ioexcept.ads, sequenio.ads, text_io.ads: Use
874         Ada_2012 instead of Ada_2005 to be compatible with the above
875         change.
876         * bindgen.adb: Silence new warning on pragma Ada_95.
878 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
880         * checks.adb (Generate_Range_Check): Revert part of previous change.
882 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
884         * sem_ch4.adb (Try_Container_Indexing): Handle properly a
885         container indexing operation that appears as a an actual in a
886         parameter association in a procedure call.
888 2017-04-25  Olivier Ramonat  <ramonat@adacore.com>
890         * prj-proc.adb, sem_util.adb, s-stposu.adb, sem_attr.adb, prj-conf.ads:
891         Fix spelling mistakes.
893 2017-04-25  Bob Duff  <duff@adacore.com>
895         * types.ads, osint.adb, sinput-c.adb, sinput-d.adb, sinput-l.adb,
896         * sinput-p.adb: Use regular fat pointers, with bounds checking,
897         for source buffers.  Fix misc obscure bugs.
898         * sinput.ads, sinput.adb: Use regular fat pointers, with bounds
899         checking, for source buffers.  Modify representation clause for
900         Source_File_Record as appropriate.  Move Source_File_Index_Table
901         from spec to body, because it is not used outside the body.
902         Move Set_Source_File_Index_Table into the private part, because
903         it is used only in the body and in children.  Use trickery to
904         modify the dope in the generic instantiation case.  It's ugly,
905         but not as ugly as the previous method.  Fix documentation.
906         Remove obsolete code.
907         * fname-sf.adb, targparm.adb: Fix misc out-of-bounds
908         indexing in source buffers.
909         * fmap.adb: Avoid conversions from one string type to another.
910         Remove a use of global name buffer.
911         * osint.ads, sfn_scan.ads, sfn_scan.adb, sinput-c.ads: Comment
912         fixes.
914 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
916         * exp_util.adb, exp_ch4.adb: Minor reformatting.
918 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
920         * checks.adb: Code clean up in various routines.
921         (Generate_Range_Check): Do not generate a range check when the
922         expander is not active or when index/range checks are suppressed
923         on the target type.
924         (Insert_List_After_And_Analyze, Insert_List_Before_And_Analyze):
925         Remove variants that include a Supress parameter. These routines
926         are never used, and were introduced before the current scope-based
927         check suppression method.
929 2017-04-25  Vasiliy Fofanov  <fofanov@adacore.com>
931         * prj-part.adb, cstreams.c, osint.adb, osint.ads: Remove VMS specific
932         code and some subprogram calls that are now noop.
934 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
936         * exp_ch4.adb (Expand_N_Case_Expression): Take
937         Minimize_Expression_With_Actions into account when possible.
939 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
941         * exp_util.adb (Known_Non_Null): Moved to Sem_Util.
942         (Known_Null): Moved to Sem_Util.
943         * exp_util.ads (Known_Non_Null): Moved to Sem_Util.
944         (Known_Null): Moved to Sem_Util.
945         * sem_util.adb Add new enumeration type Null_Status_Kind.
946         (Known_Non_Null): Moved from Exp_Util. Most of the logic in
947         this routine is now carried out by Null_Status.
948         (Known_Null): Moved from Exp_Util. Most of the logic in this routine
949         is now carried out by Null_Status.
950         (Null_Status): New routine.
951         * sem_util.ads (Known_Non_Null): Moved from Exp_Util.
952         (Known_Null): Moved from Exp_Util.
954 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
956         * sem_ch6.adb (Analyze_Expression_Function): Do not report an
957         error on the return type of an expression function that is a
958         completion, if the type is derived from a generic formal type.
960 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
962         * sem_dim.adb (Dimensions_Of_Operand): The dimensions of a type
963         conversion are those of the target type.
965 2017-04-25  Bob Duff  <duff@adacore.com>
967         * a-clrefi.adb: Minor cleanup.
969 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
971         * exp_util.adb, exp_util.ads, types.ads: Minor reformatting.
973 2017-04-25  Bob Duff  <duff@adacore.com>
975         * err_vars.ads, fmap.adb, fmap.ads, comperr.adb, fname-sf.adb,
976         types.adb, types.ads, types.h, sinput-l.adb, targparm.adb,
977         errout.adb, sinput.adb, sinput.ads, cstand.adb, scn.adb,
978         scn.ads, gnatls.adb: Eliminate the vestigial Internal_Source_File and
979         the Internal_Source buffer. This removes the incorrect call to "="
980         the customer noticed.
981         Wrap remaining calls to "=" in Null_Source_Buffer_Ptr. We
982         eventually need to eliminate them altogether. Or else get rid
983         of zero-origin addressing.
985 2017-04-25  Claire Dross  <dross@adacore.com>
987         * exp_util.ads (Expression_Contains_Primitives_Calls_Of): New
988         function used in GNATprove to know if an expression contains
989         non-dispatching calls on primitives of a tagged type.
991 2017-04-25  Bob Duff  <duff@adacore.com>
993         * rtsfind.adb (Initialize): Initialize
994         First_Implicit_With. Building the compiler with Normalize_Scalars
995         and validity checking finds this being used as an uninitialized
996         variable.
998 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1000         * contracts.adb (Analyze_Entry_Or_Subprogram_Body_Contract):
1001         Add a warning about SPARK mode management. The routine now
1002         saves and restores both the mode and associated pragma.
1003         (Analyze_Entry_Or_Subprogram_Contract): Add a warning about
1004         SPARK mode management. The routine now saves and restores both
1005         the mode and associated pragma.
1006         (Analyze_Object_Contract):
1007         Add a warning about SPARK mode management. The routine
1008         now saves and restores both the mode and associated pragma.
1009         (Analyze_Package_Body_Contract): Add a warning about SPARK mode
1010         management.  The routine now saves and restores both the mode
1011         and associated pragma.  (Analyze_Package_Contract): Add a warning
1012         about SPARK mode management. The routine now saves and restores
1013         both the mode and associated pragma.
1014         (Analyze_Task_Contract):
1015         Add a warning about SPARK mode management. The routine now saves
1016         and restores both the mode and associated pragma.
1017         * expander.adb (Expand): Change the way the Ghost mode is saved
1018         and restored.
1019         * exp_ch3.adb (Freeze_Type): Change the way the Ghost mode is
1020         saved and restored.
1021         * exp_disp.adb (Make_DT): Change the way the Ghost mode is saved
1022         and restored.
1023         * exp_util.adb (Build_DIC_Procedure_Body):
1024         Change the way the Ghost mode is saved and restored.
1025         (Build_DIC_Procedure_Declaration): Change the way the Ghost
1026         mode is saved and restored.
1027         (Build_Invariant_Procedure_Body):
1028         Change the way the Ghost mode is saved and restored.
1029         (Build_Invariant_Procedure_Declaration): Change the way the Ghost
1030         mode is saved and restored.
1031         (Make_Predicate_Call): Change the
1032         way the Ghost mode is saved and restored.
1033         * freeze.adb (Freeze_Entity): Change the way the Ghost mode is
1034         saved and restored.
1035         * ghost.adb (Mark_And_Set_Ghost_Assignment): Remove parameter Mode
1036         and its assignment.
1037         (Mark_And_Set_Ghost_Body): Remove parameter
1038         Mode and its assignment.
1039         (Mark_And_Set_Ghost_Completion):
1040         Remove parameter Mode and its assignment.
1041         (Mark_And_Set_Ghost_Declaration): Remove parameter Mode and its
1042         assignment.
1043         (Mark_And_Set_Ghost_Instantiation): Remove parameter
1044         Mode and its assignment.
1045         (Mark_And_Set_Ghost_Procedure_Call):
1046         Remove parameter Mode and its assignment.
1047         (Set_Ghost_Mode):
1048         Remove parameter Mode and its assignment.
1049         * ghost.ads (Mark_And_Set_Ghost_Assignment): Remove parameter Mode
1050         and update the comment on usage.
1051         (Mark_And_Set_Ghost_Body):
1052         Remove parameter Mode and update the comment on usage.
1053         (Mark_And_Set_Ghost_Completion): Remove parameter Mode and
1054         update the comment on usage.
1055         (Mark_And_Set_Ghost_Declaration):
1056         Remove parameter Mode and update the comment on usage.
1057         (Mark_And_Set_Ghost_Instantiation): Remove parameter Mode and
1058         update the comment on usage.
1059         (Mark_And_Set_Ghost_Procedure_Call):
1060         Remove parameter Mode and update the comment on usage.
1061         (Set_Ghost_Mode): Remove parameter Mode and update the comment
1062         on usage.
1063         * lib.ads Remove obsolete fields SPARK_Mode_Pragma from various
1064         types.
1065         * lib-load.adb (Create_Dummy_Package_Unit): Remove the assignment
1066         of obsolete field SPARK_Mode_Pragma.
1067         (Load_Main_Source): Remove
1068         the assignment of obsolete field SPARK_Mode_Pragma.
1069         (Load_Unit): Remove the assignment of obsolete field SPARK_Mode_Pragma.
1070         * lib-writ.adb (Add_Preprocessing_Dependency): Remove
1071         the assignment of obsolete field SPARK_Mode_Pragma.
1072         (Ensure_System_Dependency): Remove the assignment of obsolete
1073         field SPARK_Mode_Pragma.
1074         * rtsfind.adb (Load_RTU): Add a warning about Ghost and SPARK
1075         mode management. Change the way Ghost and SPARK modes are saved
1076         and restored.
1077         * sem.adb (Analyze): Change the way the Ghost mode is saved
1078         and restored.
1079         * sem_ch3.adb (Analyze_Object_Declaration): Change the way the
1080         Ghost mode is saved and restored.
1081         (Process_Full_View): Change
1082         the way the Ghost mode is saved and restored.
1083         * sem_ch5.adb (Analyze_Assignment): Change the way the Ghost
1084         mode is saved and restored.
1085         * sem_ch6.adb (Analyze_Procedure_Call): Change the way the Ghost
1086         mode is saved and restored.
1087         (Analyze_Subprogram_Body_Helper):
1088         Change the way the Ghost mode is saved and restored.
1089         * sem_ch7.adb (Analyze_Package_Body_Helper): Change the way the
1090         Ghost mode is saved and restored.
1091         * sem_ch10.adb (Analyze_Subunit): Add a warning about SPARK mode
1092         management. Save the SPARK mode-related data prior to any changes
1093         to the scope stack and contexts. The mode is then reinstalled
1094         before the subunit is analyzed in order to restore the original
1095         view of the subunit.
1096         * sem_ch12.adb (Analyze_Package_Instantiation): Update the
1097         warning on region management.  Change the way the Ghost and
1098         SPARK modes are saved and restored.
1099         (Inline_Instance_Body):
1100         Add a warning about SPARK mode management. Code clean up.
1101         (Analyze_Subprogram_Instantiation): Update the warning on region
1102         management.  Change the way the Ghost and SPARK modes are saved
1103         and restored.
1104         (Instantiate_Package_Body): Update the warning
1105         on region management. Change the way the Ghost and SPARK modes
1106         are saved and restored.
1107         (Instantiate_Subprogram_Body): Update
1108         the warning on region management. Change the way the Ghost and
1109         SPARK modes are saved and restored.
1110         (Set_Instance_Env): Add a
1111         warning about SPARK mode management. Change the way SPARK mode
1112         is saved and restored.
1113         * sem_ch13.adb (Build_Predicate_Functions):
1114         Change the way the Ghost mode is saved and restored.
1115         (Build_Predicate_Function_Declaration): Change the way the Ghost
1116         mode is saved and restored.
1117         * sem_elab.adb (Check_Elab_Calls): Add a warning about SPARK
1118         mode management. Change the way SPARK mode is saved and restored.
1119         * sem_prag.adb (Analyze_Contract_Cases_In_Decl_Part):
1120         Change the way the Ghost mode is saved and restored.
1121         (Analyze_Initial_Condition_In_Decl_Part): Change the way
1122         the Ghost mode is saved and restored.
1123         (Analyze_Pragma):
1124         Change the way the Ghost mode is saved and restored.
1125         (Analyze_Pre_Post_Condition_In_Decl_Part): Change the way the
1126         Ghost mode is saved and restored.
1127         * sem_util.adb (Install_SPARK_Mode): New routine.
1128         (Restore_SPARK_Mode): New routine.
1129         (Save_SPARK_Mode_And_Set): Removed.
1130         (Set_SPARK_Mode): New routine.
1131         * sem_util.ads (Install_SPARK_Mode): New routine.
1132         (Restore_SPARK_Mode): New routine.
1133         (Save_SPARK_Mode_And_Set): Removed.
1134         (Set_SPARK_Mode): New routine.
1136 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1138         * sem_util.adb, sem_util.ads (From_Nested_Package): New predicate
1139         to determine whether a type is declared in a local package that
1140         has not yet been frozen.
1141         * freeze.adb (Freeze_Before): Use new predicate to determine
1142         whether a local package must be installed on the scope stack
1143         in order to evaluate in the proper scope actions generated by
1144         aspect specifications, such as Predicate
1145         * sem_ch13.adb: Simplify code in Analyze_Aspects_At_Freeze_Point
1146         using new predicate.
1148 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1150         * sem_warn.adb (Warn_On_Constant_Valid_Condition): Do not consider
1151         comparisons between non- scalar expressions expressions because
1152         their values cannot be invalidated.
1153         * sem_warn.ads (Warn_On_Constant_Valid_Condition): Update the
1154         comment on usage.
1156 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1158         * par_sco.adb: Minor reformatting.
1160 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1162         * sem_ch13.adb (Analyze_Aspects_At_Freeze_Point): If entity
1163         is a type from an unfrozen local package, install package to
1164         complete the analysis of delayed aspects of the type.
1166 2017-04-25  Tristan Gingold  <gingold@adacore.com>
1168         * bingen.adb (System_Version_Control_Used): New variable.
1169         (Resolve_Binder_Options): Set the above variable.
1170         (Gen_Output_File_Ada): Conditionally call Gen_Versions.
1171         (Gen_Elab_Order): Emit blank line before.
1173 2017-04-25  Justin Squirek  <squirek@adacore.com>
1175         * sem_cat.adb (Validate_RT_RAT_Component): Added
1176         an extra check to ignore incomplete types.
1178 2017-04-25  Thomas Quinot  <quinot@adacore.com>
1180         * sem_prag.adb (Analyze_Pragma, case Pragma_Check): Remove
1181         bogus circuitry for the case where Name is Predicate.
1183 2017-04-25  Thomas Quinot  <quinot@adacore.com>
1185         * par_sco.adb(Traverse_Declarations_Or_Statements.Traverse_Aspects):
1186         Create SCOs for Predicate aspects in disabled
1187         state initially, to be enabled later on by...
1188         * sem_ch13.adb (Build_Predicate_Functions.Add_Predicates): Mark
1189         SCO for predicate as enabled.
1191 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1193         * comperr.adb (Compiler_Abort): Remove now obsolete pair of
1194         pragmas Warnings Off / On.
1195         * namet.adb (Finalize): Remove now obsolete pair of pragmas
1196         Warnings Off / On.
1197         * output.adb: Remove now obsolete pair of pragmas Warnings Off / On.
1198         * sem_warn.adb (Warn_On_Constant_Valid_Condition): Do not
1199         consider comparisons between static expressions because their
1200         values cannot be invalidated.
1201         * urealp.adb (Tree_Read): Remove now obsolete pair of pragmas
1202         Warnings Off / On.
1203         (Tree_Write): Remove now obsolete pair of pragmas Warnings Off / On.
1204         * usage.adb Remove now obsolete pair of pragmas Warnings Off / On.
1206 2017-04-25  Bob Duff  <duff@adacore.com>
1208         * sem_elab.adb (In_Task_Activation): Trace internal calls in
1209         task bodies.
1211 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
1213         * sem_prag.adb, sem_warn.adb, sem_eval.adb: Minor reformatting and
1214         typo fixes.
1216 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1218         * comperr.adb (Compiler_Abort): Add a pair of pragma Warnings
1219         On/Off to defend against a spurious warning in conditional
1220         compilation.
1221         * exp_ch4.adb (Rewrite_Comparison): Reimplemented.
1222         * namet.adb (Finalize): Add a pair of pragma Warnings On/Off to
1223         defend against a spurious warning in conditional compilation.
1224         * output.adb Add a pair of pragma Warnings On/Off to defend
1225         against a spurious warning in conditional compilation.
1226         * sem_eval.adb (Eval_Relational_Op): Major code clean up.
1227         (Fold_General_Op): New routine.
1228         (Fold_Static_Real_Op): New routine.
1229         (Test_Comparison): New routine.
1230         * sem_eval.ads (Test_Comparison): New routine.
1231         * sem_warn.adb (Is_Attribute_Constant_Comparison): New routine.
1232         (Warn_On_Constant_Valid_Condition): New routine.
1233         (Warn_On_Known_Condition): Use Is_Attribute_Constant_Comparison
1234         to detect a specific case.
1235         * sem_warn.adb (Warn_On_Constant_Valid_Condition): New routine.
1236         * urealp.adb (Tree_Read): Add a pair of pragma Warnings On/Off
1237         to defend against a spurious warning in conditional compilation.
1238         (Tree_Write): Add a pair of pragma Warnings On/Off to defend
1239         against a spurious warning in conditional compilation.
1240         * usage.adb Add a pair of pragma Warnings On/Off to defend
1241         against a spurious warning in conditional compilation.
1243 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
1245         * sinfo.ads, sem_ch13.adb: Update comment.
1247 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1249         * sem_util.adb (Is_Post_State): A reference to a
1250         generic in out parameter is considered a change in the post-state
1251         of a subprogram.
1253 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1255         * sem_ch12.adb (Load_Parent_Of_Generic); When retrieving the
1256         declaration of a subprogram instance within its wrapper package,
1257         skip over null statements that may result from the rewriting of
1258         ignored pragmas.
1260 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1262         * exp_attr.adb (Expand_Attribute_Reference, case 'Read):
1263         If the type is an unchecked_union, replace the attribute with
1264         a Raise_Program_Error (rather than inserting such before the
1265         attribute reference) to handle properly the case where we are
1266         processing a component of a larger record, and we need to prevent
1267         further expansion for the unchecked union.
1268         (Expand_Attribute_Reference, case 'Write): If the type is
1269         an unchecked_union, check whether enclosing scope is a Write
1270         subprogram. Replace attribute with a Raise_Program_Error if the
1271         discriminants of the unchecked_union type have not default values
1272         because such a use is erroneous..
1274 2017-04-25  Tristan Gingold  <gingold@adacore.com>
1276         * exp_ch9.adb (Expand_N_Task_Type_Declaration):
1277         Add relative_deadline to task record on edf profile.
1278         (Make_Initialize_Protection): Pass deadline_floor value on edf profile.
1279         (Make_Task_Create_Call): Pass relative_deadline value.
1280         * par-prag.adb (Prag): Handle Pragma_Deadline_Floor.
1281         * s-rident.ads (Profile_Name): Add GNAT_Ravenscar_EDF.
1282         (Profile_Info): Add info for GNAT_Ravenscar_EDF.
1283         * sem_prag.adb (Set_Ravenscar_Profile): Handle
1284         GNAT_Ravenscar_EDF (set scheduling policy).
1285         (Analyze_Pragma): Handle GNAT_Ravenscar_EDF profile and Deadline_Floor
1286         pragma.
1287         (Sig_Flags): Add choice for Pragma_Deadline_Floor.
1288         * snames.ads-tmpl (Name_Deadline_Floor, Name_Gnat_Ravenscar_EDF):
1289         New names.
1290         (Pragma_Deadline_Floor): New pragma.
1291         * targparm.adb (Get_Target_Parameters): Recognize
1292         GNAT_Ravenscar_EDF profile.
1294 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
1296         * gnatvsn.ads (Library_Version): Bump to 8. Update comment.
1298 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1300         * sem_aux.adb (Nearest_Ancestor): Use original node of type
1301         declaration to locate nearest ancestor, because derived
1302         type declarations for record types are rewritten as record
1303         declarations.
1304         * sem_ch13.adb (Add_Call): Use an unchecked conversion to handle
1305         properly derivations that are completions of private types.
1306         (Add_Predicates): If type is private, examine rep. items of full
1307         view, which may include inherited predicates.
1308         (Build_Predicate_Functions): Ditto.
1310 2017-04-25  Javier Miranda  <miranda@adacore.com>
1312         * sem_util.adb (New_Copy_Tree.Visit_Entity): Extend previous change
1313         to generate new entities for subtype declarations located in
1314         Expression_With_Action nodes.
1316 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1318         * sem_elab.adb (Check_A_Call): Remove
1319         local variables Is_DIC_Proc and Issue_In_SPARK. Verify the
1320         need for Elaborate_All when SPARK elaboration checks are
1321         required. Update the checks for instances, variables, and calls
1322         to Default_Initial_Condition procedures.
1324 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1326         * aspects.ads, aspects.adb: Make the GNAT-specific pragma No_Inline
1327         into a boolean aspect, in analogy with the Ada aspect No_Return.
1329 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1331         * exp_ch6.adb, sem_ch13.adb, sem_ch6.adb: Minor reformatting.
1333 2017-04-25  Bob Duff  <duff@adacore.com>
1335         * sem_res.adb (Resolve_Actuals): Under -gnatd.q, reset
1336         Is_True_Constant for an array variable that is passed to a
1337         foreign function as an 'in' parameter.
1338         * debug.adb: Document -gnatd.q.
1340 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1342         * sem_ch6.adb (Analyze_Expression_Function): If expression function
1343         is completion and return type is an access type do not freeze
1344         designated type: this will be done in the process of freezing
1345         the expression if needed.
1346         (Freeze_Expr_Types): Check whether type is complete before
1347         creating freeze node, to provide a better error message if
1348         reference is premature.
1349         * sem_ch13.adb (Check_Indexing_Functions): Ignore inherited
1350         functions created by type derivations.
1352 2017-04-25  Pascal Obry  <obry@adacore.com>
1354         * g-sercom.ads: Add simple usage of GNAT.Serial_Communication.
1356 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1358         * sem_res.adb (Resolve_Type_Conversion):
1359         When resolving against any fixed type, set the type of the
1360         operand as universal real when the operand is a multiplication
1361         or a division where both operands are of any fixed type.
1362         (Unique_Fixed_Point_Type): Add local variable ErrN. Improve the
1363         placement of an error message by pointing to the operand of a
1364         type conversion rather than the conversion itself.
1366 2017-04-25  Thomas Quinot  <quinot@adacore.com>
1368         * sem_ch13.adb (Build_Predicate_Function_Declaration): Set
1369         Needs_Debug_Info when producing SCOs.
1371 2017-04-25  Thomas Quinot  <quinot@adacore.com>
1373         * exp_ch6.adb (Add_Finalization_Master_Actual_To_Build_In_Place_Call):
1374         Always pass a null finalization master for a library level named access
1375         type to which a pragme No_Heap_Finalization applies.
1377 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
1379         PR ada/78845
1381         * a-ngcoar.adb, a-ngrear.adb (Inverse): call Unit_Matrix with First_1
1382         set to A'First(2) and vice versa.
1384 2017-04-25  Yannick Moy  <moy@adacore.com>
1386         * freeze.adb (Freeze_Record_Type): Remove obsolete
1387         rule on volatile tagged record restriction on SPARK code.
1389 2017-04-25  Yannick Moy  <moy@adacore.com>
1391         * sem_prag.adb (minor) Fix SPARK RM reference.
1393 2017-04-25  Yannick Moy  <moy@adacore.com>
1395         * sem_util.adb, sem_util.ads (Unique_Defining_Entity): Update
1396         comment to reflect which entity is chosen as unique entity.
1397         (Unique_Entity): Return full view instead of private spec for
1398         protected type or task type. Fix possible incorrect access when
1399         called on entry.
1401 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
1403         * sem_res.adb (Set_Slice_Subtype): Treat specially bit-packed
1404         array types only instead of all packed array types.
1406 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1408         * sem_ch6.adb (Conforming_Types): If type of formal as a specified
1409         dimension system, verify that dimensions of both match.
1410         (Check_Conformance): Add error message in case of dimension
1411         mismatch.
1412         * sem_dim.ads, sem_dim.adb (Dimensions_Match): New utility
1413         predicate.
1415 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
1417         * gnatxref.adb, gnatfind.adb: Avoid using the term project file,
1418         confusing.
1420 2017-04-25  Yannick Moy  <moy@adacore.com>
1422         * sem_util.adb: Minor refactoring.
1423         * freeze.adb (Freeze_Record_Type): Fix checking of SPARK RM 7.1.3(5).
1425 2017-04-25  Claire Dross  <dross@adacore.com>
1427         * sem_prag.adb (Collect_Inherited_Class_Wide_Conditions): Go to
1428         ultimate alias when accessing overridden operation. Indeed, if the
1429         overridden operation is itself inherited, it won't have any explicit
1430         contract.
1432 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1434         * sem_warn.adb (Warn_On_Overlapping_Actuals): There can be no
1435         overlap if the two formals have different types, because formally
1436         the corresponding actuals cannot designate the same objects.
1438 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1440         * sem_dim.adb (Dimensions_Of_Operand): minot cleanups: a) If
1441         dimensions are present from context, use them.  b) If operand is
1442         a static constant rewritten as a literal, obtain the dimensions
1443         from the original declaration, otherwise use dimensions of type
1444         established from context.
1446 2017-04-25  Yannick Moy  <moy@adacore.com>
1448         * sem_util.adb (Is_Effectively_Volatile): Protect against base type
1449         of array that is private.
1451 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
1453         * sem_ch3.adb, exp_util.adb, sem_prag.adb, exp_ch4.adb: Minor
1454         reformatting.
1456 2017-04-25  Yannick Moy  <moy@adacore.com>
1458         * a-ngelfu.adb, a-ngelfu.ads: Add SPARK_Mode On on spec, Off
1459         on body.
1461 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1463         * sem_disp.adb (Check_Dispatching_Context): Add guard to refine
1464         the check that recognizes a call to a private overridding and
1465         replaces the called subprogram with its alias.
1467 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1469         * exp_util.adb: Minor reformatting.
1471 2017-04-25  Justin Squirek  <squirek@adacore.com>
1473         * exp_ch3.adb (Freeze_Type): Add condition to always treat
1474         interface types as a partial view of a private type for the
1475         generation of invariant procedure bodies.
1476         * exp_util.adb, exp_util.ads (Add_Inherited_Invariants):
1477         Add a condition to get the Corresponding_Record_Type for
1478         concurrent types, add condition to return in the absence of a
1479         class in the pragma, remove call to Replace_Type_References,
1480         and add call to Replace_References.
1481         (Add_Interface_Invariatns),
1482         (Add_Parent_Invariants): Modify call to Add_Inherited_Invariants
1483         to including the working type T.
1484         (Add_Own_Invariants): Remove
1485         legacy condition for separate units, remove dispatching for ASIS
1486         and save a copy of the expression in the pragma expression.
1487         (Build_Invariant_Procedure_Body): Default initalize vars,
1488         remove return condition on interfaces, always use the
1489         private type for interfaces, and move the processing of types
1490         until after the processing of invariants for the full view.
1491         (Build_Invariant_Procedure_Declaration): Remove condition
1492         to return if an interface type is encountered and add
1493         condition to convert the formal parameter to its class-wide
1494         counterpart if Work_Typ is abstract.
1495         (Replace_Type): Add call to Remove_Controlling_Arguments.
1496         (Replace_Type_Ref): Remove class-wide dispatching for the current
1497         instance of the type.
1498         (Replace_Type_References): Remove parameter "Derived"
1499         (Remove_Controlling_Arguments): Created in order to removing
1500         the controlliong argument from calls to primitives in the case
1501         of the formal parameter being an class-wide abstract type.
1502         * sem_ch3.adb (Build_Assertion_Bodies_For_Type): Almost identical
1503         to the change made to Freeze_Type in exp_ch3. Add a condition
1504         to treat interface types as a partial view.
1505         * sem_prag.adb (Analyze_Pragma): Modify parameters in the call
1506         to Build_Invariant_Procedure_Declaration to properly generate a
1507         "partial" invariant procedure when Typ is an interface.
1509 2017-04-25  Bob Duff  <duff@adacore.com>
1511         * a-numeri.ads: Go back to using brackets encoding for the Greek
1512         letter pi.
1514 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1516         * sem_ch3.adb (Derive_Subprogram): Implement rule in RM 6.1.1
1517         (10-15): if derived type T with progenitors is abstract,
1518         and primitive P of this type inherits non-trivial classwide
1519         preconditions from both a parent operation and from an interface
1520         operation, then the inherited operation is abstract if the parent
1521         operation is not null.
1522         * sem_disp.ads, sem_disp.adb: replace function Covers_Some_Interface
1523         with Covered_Interface_Op to yield the actual interface operation
1524         that is implemented by a given inherited operation.
1526 2017-04-25  Javier Miranda  <miranda@adacore.com>
1528         * exp_ch4.adb (Expand_N_Op_Expon): Relocate left
1529         and right operands after performing the validity checks. Required
1530         because validity checks may remove side effects from the operands.
1532 2017-04-25  Javier Miranda  <miranda@adacore.com>
1534         * exp_attr.adb (Attribute_Unrestricted_Access):
1535         Do not disable implicit type conversion.  Required to generate
1536         code that displaces the pointer to reference the secondary
1537         dispatch table.
1539 2017-04-25  Pascal Obry  <obry@adacore.com>
1541         * prj-attr.adb, snames.ads-tmpl: Add package Install's
1542         Required_Artifacts attribute.
1544 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1546         * sem_util.adb (Same_Value): String literals are compile-time
1547         values, and comparing them must use Expr_Value_S.
1549 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1551         * sem_ch4.adb (Complete_Object_Interpretation): If an explicit
1552         dereference is introduced for the object, and the object is
1553         overloaded, do not check whether it is aliased, because it may
1554         include an implicit dereference.
1555         * sem_type.adb (Disambiguate): If two interpretations are access
1556         attribute types with the same designated type keep either of
1557         them and do not report an ambiguity.  A true ambiguity will be
1558         reported elsewhere.
1560 2017-04-25  Bob Duff  <duff@adacore.com>
1562         * a-numeri.ads: Change the encoding of Greek letter Pi from
1563         brackets encoding to UTF-8.  Use pragma Wide_Character_Encoding
1564         to indicate the encoding. We considered using a byte order mark
1565         (BOM), but that causes various trouble (misc software eats the
1566         BOM, if you have a patch with a BOM, then it's not at the start
1567         of the patch, so it's not a BOM, the BOM affects with-ing files,
1568         etc.).
1569         * scng.adb, s-wchcnv.adb: Minor.
1571 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1573         * sem_ch3.adb, sem_ch8.adb, sem_disp.adb: Minor reformatting.
1574 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1576         * sem_ch3.adb (Add_Internal_Interface_Entities): Move
1577         Has_Non_Trivial_Precondition to sem_util. for use elsewhere.
1578         Improve error message on operations that inherit non-conforming
1579         classwide preconditions from ancestor and progenitor.
1580         * sem_util.ads, sem_util.adb (Has_Non_Trivial_Precondition):
1581         moved here from sem_ch3.
1582         * sem_ch8.adb (Analyze_Subprogram_Renaming): Implement legality
1583         check given in RM 6.1.1 (17) concerning renamings of overriding
1584         operations that inherits class-wide preconditions from ancestor
1585         or progenitor.
1587 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1589         * exp_ch7.adb (Build_Adjust_Or_Finalize_Statements): Code cleanup.
1590         (Build_Adjust_Statements): Code cleanup.
1591         (Build_Finalizer): Update the initialization of
1592         Exceptions_OK.
1593         (Build_Finalize_Statements): Code cleanup.
1594         (Build_Initialize_Statements): Code cleanup.
1595         (Make_Deep_Array_Body): Update the initialization of
1596         Exceptions_OK.
1597         (Make_Deep_Record_Body): Update the initialization of Exceptions_OK.
1598         (Process_Object_Declaration): Generate a null exception handler only
1599         when exceptions are allowed.
1600         (Process_Transients_In_Scope): Update the initialization of
1601         Exceptions_OK.
1602         * exp_util.ads, exp_util.adb (Exceptions_In_Finalization_OK): New
1603         routine.
1604         * sem_ch11.adb (Analyze_Exception_Handlers): Do not check any
1605         restrictions when the handler is internally generated and the
1606         mode is warnings.
1608 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1610         * sem_ch3.adb (Has_Non_Trivial_Precondition): New predicate to
1611         enforce legality rule on classwide preconditions inherited from
1612         both an ancestor and a progenitor (RM 6.1.1 (10-13).
1613         * sem_disp.adb (Check_Dispatching_Context): A call to an abstract
1614         subprogram need not be dispatching if it appears in a precondition
1615         for an abstract or null subprogram.
1617 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
1619         * sem_ch10.adb: Minor typo fix.
1621 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
1623         * gcc-interface/Makefile.in: Cleanup VxWorks targets.
1625 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
1627         * fname.adb (Is_Internal_File_Name): Arrange for the slices to
1628         have a length which is a power of 2.
1629         (Is_Predefined_File_Name): Likewise. Adjust comment.
1631 2017-04-25  Bob Duff  <duff@adacore.com>
1633         * exp_aggr.adb (Component_Count): Protect the
1634         arithmetic from attempting to convert a value >= 2**31 to Int,
1635         which would otherwise raise Constraint_Error.
1637 2017-04-25  Bob Duff  <duff@adacore.com>
1639         * opt.ads (Locking_Policy): Fix incorrect documentation. The
1640         first character of the policy name is not unique.
1642 2017-04-25  Bob Duff  <duff@adacore.com>
1644         * s-fileio.adb (Name): Raise Use_Error if the file is a temp file.
1645         * s-ficobl.ads (Is_Temporary_File): Remove incorrect comment
1646         about this flag not being used. It was already used, and it is
1647         now used more.
1649 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1651         * einfo.adb Flag301 is now known as Ignore_SPARK_Mode_Pragmas.
1652         (Ignore_SPARK_Mode_Pragmas): New routine.
1653         (Set_Ignore_SPARK_Mode_Pragmas): New routine.
1654         (Write_Entity_Flags): Add an entry for Ignore_SPARK_Mode_Pragmas.
1655         * einfo.ads Add new attribute Ignore_SPARK_Mode_Pragmas and update
1656         related entities.
1657         (Ignore_SPARK_Mode_Pragmas): New routine
1658         along with pragma Inline.
1659         (Set_Ignore_SPARK_Mode_Pragmas): New routine along with pragma Inline.
1660         * opt.ads Rename flag Ignore_Pragma_SPARK_Mode to
1661         Ignore_SPARK_Mode_Pragmas_In_Instance.
1662         * sem_ch6.adb (Analyze_Subprogram_Body_Helper):
1663         Save and restore the value of global flag
1664         Ignore_SPARK_Mode_Pragmas_In_Instance. Set or reinstate the value
1665         of global flag Ignore_SPARK_Mode_Pragmas_In_Instance when either
1666         the corresponding spec or the body must ignore all SPARK_Mode
1667         pragmas found within.
1668         (Analyze_Subprogram_Declaration): Mark
1669         the spec when it needs to ignore all SPARK_Mode pragmas found
1670         within to allow the body to infer this property in case it is
1671         instantiated or inlined later.
1672         * sem_ch7.adb (Analyze_Package_Body_Helper): Save and restore the
1673         value of global flag Ignore_SPARK_Mode_Pragmas_In_Instance. Set
1674         the value of global flag Ignore_SPARK_Mode_Pragmas_In_Instance
1675         when the corresponding spec also ignored all SPARK_Mode pragmas
1676         found within.
1677         (Analyze_Package_Declaration): Mark the spec when
1678         it needs to ignore all SPARK_Mode pragmas found within to allow
1679         the body to infer this property in case it is instantiated or
1680         inlined later.
1681         * sem_ch12.adb (Analyze_Formal_Package_Declaration):
1682         Save and restore the value of flag
1683         Ignore_SPARK_Mode_Pragmas_In_Instance. Mark the
1684         formal spec when it needs to ignore all SPARK_Mode
1685         pragmas found within to allow the body to infer this
1686         property in case it is instantiated or inlined later.
1687         (Analyze_Package_Instantiation): Save and restore the value
1688         of global flag Ignore_SPARK_Mode_Pragmas_In_Instance. Mark
1689         the instance spec when it needs to ignore all SPARK_Mode
1690         pragmas found within to allow the body to infer this
1691         property in case it is instantiated or inlined later.
1692         (Analyze_Subprogram_Instantiation): Save and restore the value
1693         of global flag Ignore_SPARK_Mode_Pragmas_In_Instance. Mark the
1694         instance spec and anonymous package when they need to ignore
1695         all SPARK_Mode pragmas found within to allow the body to infer
1696         this property in case it is instantiated or inlined later.
1697         (Instantiate_Package_Body): Save and restore the value of global
1698         flag Ignore_SPARK_Mode_Pragmas_In_Instance. Set the value of
1699         global flag Ignore_SPARK_Mode_Pragmas_In_Instance when the
1700         corresponding instance spec also ignored all SPARK_Mode pragmas
1701         found within.
1702         (Instantiate_Subprogram_Body): Save and restore the
1703         value of global flag Ignore_SPARK_Mode_Pragmas_In_Instance. Set
1704         the value of global flag Ignore_SPARK_Mode_Pragmas_In_Instance
1705         when the corresponding instance spec also ignored all SPARK_Mode
1706         pragmas found within.
1707         * sem_prag.adb (Analyze_Pragma): Update the reference to
1708         Ignore_Pragma_SPARK_Mode.
1709         * sem_util.adb (SPARK_Mode_Is_Off): A construct which ignored
1710         all SPARK_Mode pragmas defined within yields mode "off".
1712 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1714         * bindgen.adb, exp_dbug.adb, errout.adb, fname.adb: Minor reformatting.
1716 2017-04-25  Bob Duff  <duff@adacore.com>
1718         * exp_atag.adb (Build_CW_Membership): Add "Suppress =>
1719         All_Checks" to avoid generating unnecessary checks.
1720         * exp_ch4.adb (Expand_N_In, Make_Tag_Check): Add "Suppress =>
1721         All_Checks".
1722         * sem.ads: Fix comment.
1723         * expander.ads: Fix comment.
1724         * exp_atag.ads: Fix comment: "Index = 0" should be
1725         "Index >= 0".
1727 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
1729         * s-taprop-linux.adb: Minor editorial fixes.
1731 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
1733         * sem_util.adb (New_Copy_Tree): Put back the declarations of the
1734         hash tables at library level.  Reinstate the NCT_Hash_Tables_Used
1735         variable and set it to True whenever the main hash table is
1736         populated.  Short- circuit the Assoc function if it is false
1737         and add associated guards.
1739 2017-04-25  Olivier Hainque  <hainque@adacore.com>
1741         * bindgen.adb (Gen_Elab_Calls): Also update counter of lone
1742         specs without elaboration code that have an elaboration counter
1743         nevertheless, e.g.  when compiled with -fpreserve-control-flow.
1744         * sem_ch10.adb (Analyze_Compilation_Unit):
1745         Set_Elaboration_Entity_Required when requested to preserve
1746         control flow, to ensure the unit elaboration is materialized at
1747         bind time, resulting in the inclusion of the unit object file
1748         in the executable closure at link time.
1750 2017-04-25  Pierre-Marie de Rodat  <derodat@adacore.com>
1752         * exp_dbug.adb: In Debug_Renaming_Declaration,
1753         when dealing with indexed component, accept to produce a renaming
1754         symbol when the index is an IN parameter or when it is a name
1755         defined in an outer scope.
1757 2017-04-25  Yannick Moy  <moy@adacore.com>
1759         * errout.adb (Error_Msg): Adapt continuation
1760         message in instantiations and inlined bodies for info messages.
1762 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
1764         * fname.adb (Has_Internal_Extension): Add pragma Inline.
1765         Use direct 4-character slice comparisons.
1766         (Has_Prefix): Add
1767         pragma Inline.  (Has_Suffix): Delete.
1768         (Is_Internal_File_Name):
1769         Test Is_Predefined_File_Name first.
1770         (Is_Predefined_File_Name):
1771         Use direct slice comparisons as much as possible and limit all
1772         comparisons to at most 8 characters.
1774 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1776         * checks.adb (Insert_Valid_Check): Code cleanup.
1777         * exp_ch6.adb (Add_Validation_Call_By_Copy_Code): New routine.
1778         (Expand_Actuals): Generate proper copy-back for a validation
1779         variable when it acts as the argument of a type conversion.
1780         * sem_util.adb (Is_Validation_Variable_Reference): Augment the
1781         predicate to operate on type qualifications.
1783 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1785         * sem_prag.adb, exp_ch6.adb, binde.adb, sem_disp.adb, s-fileio.adb:
1786         Minor reformatting.
1788 2017-04-25  Bob Duff  <duff@adacore.com>
1790         * sem_prag.adb (No_Return): Give an error if the pragma applies
1791         to a body. Specialize the error for the specless body case,
1792         as is done for (e.g.) pragma Convention.
1793         * debug.adb: Add switch -gnatd.J to disable the above legality
1794         checks. This is mainly for use in our test suite, to avoid
1795         rewriting a lot of illegal (but working) code.  It might also
1796         be useful to customers. Under this switch, if a pragma No_Return
1797         applies to a body, and the procedure raises an exception (as it
1798         should), the pragma has no effect. If the procedure does return,
1799         execution is erroneous.
1801 2017-04-25  Bob Duff  <duff@adacore.com>
1803         * exp_ch6.adb (Expand_Actuals): This is the
1804         root of the problem. It took N as an 'in out' parameter, and in
1805         some cases, rewrote N, but then set N to Original_Node(N). So
1806         the node returned in N had no Parent. The caller continued
1807         processing of this orphaned node. In some cases that caused a
1808         crash (e.g. Remove_Side_Effects climbs up Parents in a loop,
1809         and trips over the Empty Parent). The solution is to make N an
1810         'in' parameter.  Instead of rewriting it, return the list of
1811         post-call actions, so the caller can do the rewriting later,
1812         after N has been fully processed.
1813         (Expand_Call_Helper): Move most of Expand_Call here. It has
1814         too many premature 'return' statements, and we want to do the
1815         rewriting on return.
1816         (Insert_Post_Call_Actions): New procedure to insert the post-call
1817         actions in the appropriate place. In the problematic case,
1818         that involves rewriting N as an Expression_With_Actions.
1819         (Expand_Call): Call the new procedures Expand_Call_Helper and
1820         Insert_Post_Call_Actions.
1822 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1824         * sem_prag.adb (Inherits_Class_Wide_Pre): Cleanup code, handle
1825         properly type derived from generic formal types, to handle
1826         properly modified version of ACATS 4.1B B611017.
1828 2017-04-25  Javier Miranda  <miranda@adacore.com>
1830         * exp_unst.adb (Subp_Index): Adding missing
1831         support for renamings and functions that return a constrained
1832         array type (i.e. functions for which the frontend built a
1833         procedure with an extra out parameter).
1835 2017-04-25  Pascal Obry  <obry@adacore.com>
1837         * s-string.adb: Minor code clean-up.
1839 2017-04-25  Bob Duff  <duff@adacore.com>
1841         * s-os_lib.ads, s-os_lib.adb (Non_Blocking_Wait_Process): New
1842         procedure.
1843         * adaint.h, adaint.c (__gnat_portable_no_block_wait): C support
1844         function for Non_Blocking_Wait_Process.
1846 2017-04-25  Bob Duff  <duff@adacore.com>
1848         * prep.adb (Preprocess): Remove incorrect
1849         Assert. Current character can be ASCII.CR.
1851 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1853         * sem_prag.adb (Set_Convention_From_Pragma): Cleanup code for
1854         convention Stdcall, which has a number of exceptions. Convention
1855         is legal on a component declaration whose type is an anonymous
1856         access to subprogram.
1858 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1860         * sem_ch4.adb: sem_ch4.adb Various reformattings.
1861         (Try_One_Prefix_Interpretation): Use the base type when dealing
1862         with a subtype created for purposes of constraining a private
1863         type with discriminants.
1865 2017-04-25  Javier Miranda  <miranda@adacore.com>
1867         * einfo.ads, einfo.adb (Has_Private_Extension): new attribute.
1868         * warnsw.ads, warnsw.adb (All_Warnings): Set warning on late
1869         dispatching primitives (Restore_Warnings): Restore warning on
1870         late dispatching primitives (Save_Warnings): Save warning on late
1871         dispatching primitives (Do_Warning_Switch): Use -gnatw.j/-gnatw.J
1872         to enable/disable this warning.
1873         (WA_Warnings): Set warning on late dispatching primitives.
1874         * sem_ch3.adb (Analyze_Private_Extension_Declaration): Remember
1875         that its parent type has a private extension.
1876         * sem_disp.adb (Warn_On_Late_Primitive_After_Private_Extension):
1877         New subprogram.
1878         * usage.adb: Document -gnatw.j and -gnatw.J.
1880 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1882         * exp_ch7.adb, checks.adb, sem_prag.adb, eval_fat.adb: Minor
1883         reformatting.
1885 2017-04-25  Bob Duff  <duff@adacore.com>
1887         * binde.adb (Validate): Do not pass dynamic strings
1888         to pragma Assert, because older compilers do not support that.
1890 2017-04-25  Bob Duff  <duff@adacore.com>
1892         * s-fileio.adb (Close): When a temp file is
1893         closed, delete it and clean up its Temp_File_Record immediately,
1894         rather than waiting until later.
1895         (Temp_File_Record): Add File
1896         component, so Close can know which Temp_File_Record corresponds
1897         to the file being closed.
1898         (Delete): Don't delete temp files,
1899         because they are deleted by Close.
1900         (Open): Set the File component
1901         of Temp_File_Record. This requires moving the creation of the
1902         Temp_File_Record to the end, after the AFCB has been created.
1904 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1906         * checks.adb (Insert_Valid_Check): Do not generate
1907         a validity check when inside a generic.
1909 2017-04-25  Yannick Moy  <moy@adacore.com>
1911         * sem_res.adb (Resolve_Type_Conversion): Fix bad logic.
1913 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
1915         * snames.ads-tmpl (Snames): More names for detecting predefined
1916         potentially blocking subprograms.
1918 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1920         * sem_prag.adb (Analyze_Pre_Post_Condition): The rules
1921         concerning inheritance of class-wide preconditions do not apply
1922         to postconditions.
1924 2017-04-25  Bob Duff  <duff@adacore.com>
1926         * s-ficobl.ads: Minor comment fix.
1928 2017-04-25  Yannick Moy  <moy@adacore.com>
1930         * checks.adb (Apply_Scalar_Range_Check): Analyze precisely
1931         conversions from float to integer in GNATprove mode.
1932         (Apply_Type_Conversion_Checks): Make sure in GNATprove mode
1933         to call Apply_Type_Conversion_Checks, so that range checks
1934         are properly positioned when needed on conversions, including
1935         when converting from float to integer.  (Determine_Range): In
1936         GNATprove mode, take into account the possibility of conversion
1937         from float to integer.
1938         * sem_res.adb (Resolve_Type_Conversion): Only enforce range
1939         check on conversions from fixed-point to integer, not anymore
1940         on conversions from floating-point to integer, when in GNATprove
1941         mode.
1943 2017-04-25  Yannick Moy  <moy@adacore.com>
1945         * checks.adb (Determine_Range_R): Special case type conversions
1946         from integer to float in order to get bounds in that case too.
1947         * eval_fat.adb (Machine): Avoid issuing warnings in GNATprove
1948         mode, for computations involved in interval checking.
1950 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1952         * checks.adb (Insert_Valid_Check): Partially reimplement validity
1953         checks.
1954         * einfo.adb Node36 is now used as Validated_Object.
1955         (Validated_Object): New routine.
1956         (Set_Validated_Object): New routine.
1957         (Write_Field36_Name): Add an entry for Validated_Object.
1958         * einfo.ads Add new attribute Validated_Object along with
1959         usage in entities.
1960         (Validated_Object): New routine along with pragma Inline.
1961         (Set_Validated_Object): New routine along with pragma Inline.
1962         * exp_attr.adb (Make_Range_Test): Add processing for validation
1963         variables to avoid extra reads and copies of the prefix.
1964         * exp_ch6.adb (Expand_Actuals): Add copy-back for validation
1965         variables in order to reflect any changes done in the variable
1966         back into the original object.
1967         * sem_util.adb (Is_Validation_Variable_Reference): New routine.
1968         * sem_util.ads (Is_Validation_Variable_Reference): New routine.
1970 2017-04-25  Steve Baird  <baird@adacore.com>
1972         * exp_ch7.adb (Build_Array_Deep_Procs,
1973         Build_Record_Deep_Procs, Make_Finalize_Address_Body): Don't
1974         generate Finalize_Address routines for CodePeer.
1976 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
1978         * sem_prag.adb (Inherits_Class_Wide_Pre): subsidiary of
1979         Analyze_Pre_Post_Condition, to implement the legality checks
1980         mandated by AI12-0131: Pre'Class shall not be specified for an
1981         overriding primitive subprogram of a tagged type T unless the
1982         Pre'Class aspect is specified for the corresponding primitive
1983         subprogram of some ancestor of T.
1985 2017-04-25  Bob Duff  <duff@adacore.com>
1987         * sem_ch8.adb (Use_One_Type): If a use_type_clause
1988         is redundant, set its Used_Operations to empty. This is only
1989         necessary for use clauses that appear in the parent of a generic
1990         child unit, because those use clauses get reanalyzed when we
1991         instantiate the generic, and we don't want the Used_Operations
1992         carried over from the original context (where it was probably
1993         not redundant).
1995 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
1997         * exp_ch6.adb: Minor reformatting.
1999 2017-04-25  Bob Duff  <duff@adacore.com>
2001         * sem_prag.adb (Process_Restrictions_Or_Restriction_Warnings):
2002         Use Source_Index (Current_Sem_Unit) to find the correct casing.
2003         * exp_prag.adb (Expand_Pragma_Check): Use Source_Index
2004         (Current_Sem_Unit) to find the correct casing.
2005         * par.adb (Par): Null out Current_Source_File, to ensure that
2006         the above bugs won't rear their ugly heads again.
2008 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2010         * sem_ch8.adb (Find_Type): For an attribute reference
2011         'Class, if prefix type is synchronized and previous errors
2012         have suppressed the creation of the corresponding record type,
2013         create a spurious class-wide for the synchonized type itself,
2014         to catch other misuses of the attribute
2016 2017-04-25  Steve Baird  <baird@adacore.com>
2018         * exp_ch6.adb (Expand_Simple_Function_Return): if CodePeer_Mode
2019         is True, then don't generate the accessibility check for the
2020         tag of a tagged result.
2021         * exp_intr.adb (Expand_Dispatching_Constructor_Call):
2022         if CodePeer_Mode is True, then don't generate the
2023         tag checks for the result of call to an instance of
2024         Ada.Tags.Generic_Dispatching_Constructor (i.e., both the "is a
2025         descendant of" check and the accessibility check).
2027 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2029         * sem_ch13.adb: Code cleanups.
2030         * a-strbou.ads: minor whitespace fix in Trim for bounded strings.
2031         * sem_ch8.ads: Minor comment fix.
2033 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
2035         * exp_ch4.adb (Library_Level_Target): New function.
2036         (Expand_Concatenate): When optimization is enabled, also expand
2037         the operation out-of-line if the concatenation is present within
2038         the expression of the declaration of a library-level object and
2039         not only if it is the expression of the declaration.
2041 2017-04-25  Bob Duff  <duff@adacore.com>
2043         * freeze.adb (Freeze_Object_Declaration): Do
2044         not Remove_Side_Effects if there is a pragma Linker_Section,
2045         because in that case we want static initialization in the
2046         appropriate section.
2048 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
2050         * exp_dbug.adb: Minor rewording and reformatting.
2052 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2054         * sem_attr.adb (Statically_Denotes_Object): New predicate, to
2055         handle the proposed changes to rules concerning potentially
2056         unevaluated expressions, to include selected components that
2057         do not depend on discriminants, and indexed components with
2058         static indices.
2059         * sem_util.adb (Is_Potentially_Unevaluated): Add check for
2060         predicate in quantified expression, and fix bugs in the handling
2061         of case expressions and membership test.
2062         (Analyze_Attribute_Old_Result): use new predicate.
2063         (Analyze_Attribute, case Loop_Entry): ditto.
2065 2017-04-25  Bob Duff  <duff@adacore.com>
2067         * s-secsta.adb (SS_Info): Add a comment
2068         explaining why we don't need to walk all the chunks in order to
2069         compute the total size.
2071 2017-04-25  Bob Duff  <duff@adacore.com>
2073         * namet.ads, namet.adb (Global_Name_Buffer): Increase the length
2074         of the global name buffer to 4*Max_Line_Length.
2076 2017-04-25  Javier Miranda  <miranda@adacore.com>
2078         * exp_ch8.adb (Expand_N_Object_Renaming_Declaration): When creating a
2079         renaming entity for debug information, mark the entity as needing debug
2080         info if it comes from sources.
2082 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2084         * sem_ch13.adb (Analyze_Attribute_Definition_Clause): Remove the
2085         restriction converning the use of 'Address where the prefix is
2086         of a controlled type.
2088 2017-04-25  Pierre-Marie de Rodat  <derodat@adacore.com>
2090         * exp_dbug.adb: In Debug_Renaming_Declaration,
2091         skip slices that are made redundant by an indexed component
2092         access.
2093         * atree.h: New definition for Original_Node.
2095 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2097         * sem_prag.adb, sem_prag.ads: Minor reformatting.
2099 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2101         * sem_ch3.adb (Check_Entry_Contract): Call
2102         Preanalyze_Spec_Expression so that resolution takes place as well.
2103         * sem_util.adb (Check_Internal_Protected_Use): Reject properly
2104         internal calls that appear in preconditions of protected
2105         operations, in default values for same, and in contract guards
2106         for contract cases in SPARK.
2108 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
2110         * a-numaux.ads: Fix description of a-numaux-darwin
2111         and a-numaux-x86.
2112         (Double): Define to Long_Float.
2113         * a-numaux-vxworks.ads (Double): Likewise.
2114         * a-numaux-darwin.ads
2115         (Double): Likewise.
2116         * a-numaux-libc-x86.ads (Double): Define to Long_Long_Float.
2117         * a-numaux-x86.ads: Fix package description.
2118         * a-numaux-x86.adb (Is_Nan): Minor tweak.
2119         (Reduce): Adjust and complete description. Call Is_Nan instead of
2120         testing manually. Use an integer temporary to hold rounded value.
2121         * a-numaux-darwin.adb (Reduce): Likewise.
2122         (Is_Nan): New function.
2124 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2126         * sem_ch4.adb (Analyze_Selected_Component): Additional refinement
2127         on analysis of prefix whose type is a current instance of a
2128         synchronized type, but where the prefix itself is an entity that
2129         is an object.
2131 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2133         * exp_ch5.adb (Replace_Target): When rewriting the RHS, preserve
2134         the identity of callable entities therein, because they have been
2135         properly resolved, and prefixed calls may have been rewritten
2136         as normal calls.
2138 2017-04-25  Patrick Bernardi  <bernardi@adacore.com>
2140         * exp_ch3.adb (Build_Init_Statements): Convert
2141         the expression of the pragma/aspect Secondary_Stack_Size to
2142         internal type System.Parameters.Size_Type before assigning
2143         it to the Secondary_Stack_Size component of the task type's
2144         corresponding record.
2146 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
2148         * sem_eval.adb (Compile_Time_Compare): Reinstate the expr+literal
2149         (etc) optimizations when the type is modular and the offsets
2150         are equal.
2152 2017-04-25  Eric Botcazou  <ebotcazou@adacore.com>
2154         * s-osinte-freebsd.ads: Minor comment tweaks
2156 2017-04-25  Javier Miranda  <miranda@adacore.com>
2158         * urealp.adb (UR_Write): Reverse previous patch
2159         adding documentation on why we generate multiplications instead
2160         of divisions (needed to avoid expressions whose computation with
2161         large numbers may cause division by 0).
2163 2017-04-25  Bob Duff  <duff@adacore.com>
2165         * erroutc.adb (Set_Specific_Warning_Off,
2166         Set_Warnings_Mode_Off): Use the correct source file for
2167         Stop. Was using Current_Source_File, which is only valid during
2168         parsing. Current_Source_File will have a leftover value from
2169         whatever file happened to be parsed last, because of a with_clause
2170         or something.
2172 2017-04-25  Bob Duff  <duff@adacore.com>
2174         * lib.ads, lib.adb (In_Internal_Unit): New functions similar
2175         to In_Predefined_Unit, but including GNAT units.
2176         * sem_util.ads, sem_util.adb (Should_Ignore_Pragma): Replace
2177         with Should_Ignore_Pragma_Par and Should_Ignore_Pragma_Sem,
2178         because Should_Ignore_Pragma was not working reliably outside
2179         the parser, because Current_Source_File is not valid.
2180         * sem_prag.adb, exp_prag.adb: Call Should_Ignore_Pragma_Sem.
2181         * par-prag.adb: Call Should_Ignore_Pragma_Par.
2183 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
2185         * gnat1drv.adb (Gnat1Drv): Disable Generate_Processed_File in
2186         codepeer mode.
2188 2017-04-25  Javier Miranda  <miranda@adacore.com>
2190         * urealp.adb (UR_Write): Fix output of constants with a base other
2191         that 10.
2193 2017-04-25  Justin Squirek  <squirek@adacore.com>
2195         * sem_ch13.adb (Get_Interfacing_Aspects): Moved to sem_util.adb.
2196         * sem_prag.adb (Analyze_Pragma, Process_Import_Or_Interface):
2197         Add extra parameter for Process_Interface_Name.
2198         (Process_Interface_Name): Add parameter for pragma to analyze
2199         corresponding aspect.
2200         * sem_util.ads, sem_util.adb (Get_Interfacing_Aspects): Added
2201         from sem_ch13.adb
2203 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
2205         * exp_ch7.adb, einfo.ads, sem_prag.adb: Minor reformatting and typo
2206         correction.
2208 2017-04-25  Yannick Moy  <moy@adacore.com>
2210         * sem_res.adb (Resolve_Comparison_Op): Do not
2211         attempt evaluation of relational operations inside assertions.
2213 2017-04-25  Justin Squirek  <squirek@adacore.com>
2215         * exp_util.adb (Add_Interface_Invariants):
2216         Restored, code moved back from Build_Invariant_Procedure_Body.
2217         (Add_Parent_Invariants): Restored, code moved back from
2218         Build_Invariant_Procedure_Body.
2219         (Build_Invariant_Procedure_Body):
2220         Remove refactored calls and integrated code from
2221         Add_Parent_Invariants and Add_Interface_Invariants.
2223 2017-04-25  Johannes Kanig  <kanig@adacore.com>
2225         * errout.adb (Output_Messages): Adjust computation of total
2226         errors
2227         * erroutc.adb (Error_Msg): In statistics counts, deal
2228         correctly with informational messages that are not warnings.
2229         * errutil.adb (Finalize): adjust computation of total errors.
2231 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
2233         * terminals.c (__gnat_terminate_pid): New.
2234         * g-exptty.ads (Terminate_Process): New. Update comments.
2236 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
2238         * a-cfinve.ads, a-cofove.ads (Empty_Vector): add Global contract.
2240 2017-04-25  Justin Squirek  <squirek@adacore.com>
2242         * sem_ch3.adb (Analyze_Declarations): Minor
2243         correction to comments, move out large conditional and scope
2244         traversal into a predicate.
2245         (Uses_Unseen_Lib_Unit_Priv): Predicate function made from extracted
2246         logic.
2248 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2250         * sem_ch4.adb (Analyze_Selected_Component): Refine analysis
2251         of prefix whose type is a current instance of a synchronized
2252         type. If the prefix is an object this is an external call (or
2253         requeue) that can only access public operations of the object. The
2254         previous predicate was too restrictive, and did not allow public
2255         protected operations, only task entries.
2257 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2259         * sem_ch5.adb, fname.adb: Minor reformatting.
2261 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2263         * einfo.adb (Is_Anonymous_Access_Type): New routine.
2264         * einfo.ads Update the placement of
2265         E_Anonymous_Access_Subprogram_Type along with all subtypes that
2266         mention the ekind.
2267         (Is_Anonymous_Access_Type): New routine.
2268         * exp_ch7.adb (Allows_Finalization_Master): Do not generate a
2269         master for an access type subject to pragma No_Heap_Finalization.
2270         * exp_util.adb (Build_Allocate_Deallocate_Proc): An object being
2271         allocated or deallocated does not finalization actions if the
2272         associated access type is subject to pragma No_Heap_Finalization.
2273         * opt.ads Add new global variable No_Heap_Finalization_Pragma.
2274         * par-prag.adb Pragma No_Heap_Finalization does not need special
2275         processing from the parser.
2276         * sem_ch6.adb (Check_Return_Subtype_Indication): Remove ancient
2277         ??? comments. Use the new predicate Is_Anonymous_Access_Type.
2278         * sem_prag.adb Add an entry in table Sig_Flags for pragma
2279         No_Heap_Finalization.
2280         (Analyze_Pragma): Add processing for
2281         pragma No_Heap_Finalization. Update various error messages to
2282         use Duplication_Error.
2283         * sem_util.ads, sem_util.adb (No_Heap_Finalization): New routine.
2284         * snames.ads-tmpl: Add new predefined name No_Heap_Finalization
2285         and corresponding pragma id.
2287 2017-04-25  Bob Duff  <duff@adacore.com>
2289         * freeze.adb (Freeze_Record_Type): Use the
2290         underlying type of the component type to determine whether it's
2291         elementary. For representation clause purposes, a private type
2292         should behave the same as its full type.
2293         * fname.ads, fname.adb (Is_Predefined_File_Name):
2294         Make sure things like "system.ali" are recognized as predefined.
2296 2017-04-25  Javier Miranda  <miranda@adacore.com>
2298         * debug.adb: Update documentation of -gnatd.6.
2300 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2302         * sem_ch5.adb (Preanalyze_Range): Handle properly an Ada2012
2303         element iterator when the name is an overloaded function call,
2304         one of whose interpretations yields an array.
2306 2017-04-25  Bob Duff  <duff@adacore.com>
2308         * uname.ads, uname.adb (Is_Predefined_Unit_Name,
2309         Is_Internal_Unit_Name): New functions for operating on unit
2310         names, as opposed to file names. There's some duplicated code
2311         with fname.adb, which is unfortunate, but it seems like we don't
2312         want to add dependencies here.
2313         * fname-uf.adb (Get_File_Name): Change Is_Predefined_File_Name
2314         to Is_Predefined_Unit_Name; the former was wrong, because Uname
2315         is not a file name at all.
2316         * fname.ads, fname.adb: Document the fact that
2317         Is_Predefined_File_Name and Is_Internal_File_Name can be called
2318         for ALI files, and fix the code so it works properly for ALI
2319         files. E.g. these should return True for "system.ali".
2321 2017-04-25  Justin Squirek  <squirek@adacore.com>
2323         * exp_util.adb (Add_Invariant): Removed,
2324         code moved to Add_Invariant_Check, Add_Inherited_Invariant,
2325         and Add_Own_Invariant.  (Add_Invariant_Check): Used
2326         for adding runtime checks from any kind of invariant.
2327         (Add_Inherited_Invariant): Generates invariant checks for
2328         class-wide invariants (Add_Interface_Invariants): Removed, code
2329         moved to Build_Invariant_Procedure_Body (Add_Own_Invariant):
2330         Create a types own invariant procedure (Add_Parent_Invariants):
2331         Removed, code moved to Build_Invariant_Procedure_Body
2332         (Build_Invariant_Procedure_Body): Add refactored calls
2333         and integrated code from Add_Parent_Invariants and
2334         Add_Interface_Invariants.
2335         (Process_Type): Removed, the
2336         relavant code was inlined into both Add_Own_Invariant and
2337         Add_Inherited_Invariant.
2339 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2341         * make.adb, par-ch2.adb, sem_util.adb, scans.ads, sem_ch8.adb,
2342         scn.adb, osint.adb, fname.adb: Minor reformatting.
2344 2017-04-25  Pascal Obry  <obry@adacore.com>
2346         * s-taprop-mingw.adb: Do not check for CloseHandle in
2347         Finalize_TCB.
2349 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2351         * sem_util.adb (Check_Part_Of_Reference):
2352         Continue to examine the context if the reference appears within
2353         an expression function.
2355 2017-04-25  Justin Squirek  <squirek@adacore.com>
2357         * exp_ch7.adb, exp_ch7.ads Remove Build_Invariant_Procedure_Body
2358         and Build_Invariant_Procedure_Declaration.
2359         * exp_util.ads, exp_util.adb Add Build_Invariant_Procedure_Body
2360         and Build_Invariant_Procedure_Declaration from exp_ch7
2361         and break-out Is_Untagged_Private_Derivation from
2362         Build_Invariant_Procedure_Body.
2363         (Replace_Type_References):
2364         Append an extra parameter to allow for dispatching replacements
2365         and add the corrasponding logic.
2366         (Type_Invariant): Remove
2367         Replace_Typ_Refs and replace its references with calls to
2368         Replace_Type_References.
2369         * sem_ch3.adb, sem_prag.adb: Remove with and use of exp_ch7.
2371 2017-04-25  Bob Duff  <duff@adacore.com>
2373         * sem_util.ads, sem_util.adb (Should_Ignore_Pragma): New function
2374         that returns True when appropriate.
2375         * par-prag.adb, exp_prag.adb, sem_prag.adb: Do not ignore pragmas
2376         when compiling predefined files.
2377         * fname.ads, fname.adb (Is_Predefined_File_Name): Fix bug:
2378         "gnat.adc" should not be considered a predefined file name.
2379         That required (or at least encouraged) a lot of cleanup of global
2380         variable usage. We shouldn't be communicating information via
2381         the global name buffer.
2382         * bindgen.adb, errout.adb, fname-uf.adb, lib-load.adb, make.adb,
2383         * restrict.adb, sem_ch10.adb, sem_ch6.adb, sem_ch8.adb: Changes
2384         required by the above-mentioned cleanup.
2386 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2388         * osint.adb (Find_File): Handle properly a request for a
2389         configuration file whose name is a directory.
2391 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2393         * sem_attr.adb, sem_ch5.adb: Minor reformatting.
2395 2017-04-25  Bob Duff  <duff@adacore.com>
2397         * types.ads: Minor: Fix '???' comment.
2398         * sem_ch8.adb: Minor comment fix.
2400 2017-04-25  Bob Duff  <duff@adacore.com>
2402         * sem_prag.adb: Remove suspicious uses of Name_Buf.
2403         * stringt.ads, stringt.adb, exp_dbug.adb, sem_dim.adb: Remove
2404         Add_String_To_Name_Buffer, to avoid using the global Name_Buf.
2405         Add String_To_Name with no side effects.
2407 2017-04-25  Justin Squirek  <squirek@adacore.com>
2409         * sem_ch3.adb (Analyze_Declarations): Add
2410         additional condition for edge case.
2412 2017-04-25  Bob Duff  <duff@adacore.com>
2414         * par-ch2.adb, scans.ads, scn.adb: Do not give an error for
2415         reserved words inside pragmas. This is necessary to allow the
2416         pragma name Interface to be used in pragma Ignore_Pragma.
2417         * par.adb: Minor comment fix.
2419 2017-04-25  Javier Miranda  <miranda@adacore.com>
2421         * a-tags.ads, a-tags.adb (Type_Is_Abstract): Renamed as Is_Abstract.
2422         * rtsfind.ads (RE_Type_Is_Abstract): Renamed as Is_Abstract.
2423         * exp_disp.adb (Make_DT): Update occurrences of RE_Type_Is_Abstract.
2424         * exp_intr.adb (Expand_Dispatching_Constructor_Call): Update
2425         occurrences of RE_Type_Is_Abstract
2427 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2429         * exp_util.adb (Build_Chain): Account for ancestor
2430         subtypes while traversing the derivation chain.
2432 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2434         * sem_attr.adb: minor reformatting.
2436 2017-04-25  Doug Rupp  <rupp@adacore.com>
2438         * sigtramp-vxworks-target.inc [PPC64]: Add a .localentry pseudo-op.
2440 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2442         * sem_ch5.adb (Analyze_Assignment): Reset Full_Analysis flag on
2443         the first pass over an assignment statement with target names,
2444         to prevent the generation of subtypes (such as discriminated
2445         record components)that may carry the target name outside of the
2446         tree for the assignment. The subtypes will be generated when
2447         the assignment is reanalyzed in full.
2448         (Analyze_Target_Name): Handle properly class-wide types.
2450 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2452         * elists.ads, elists.adb (Prepend_Unique_Elmt): New routine.
2453         * exp_ch3.adb (Freeze_Type): Signal the DIC body is created for
2454         the purposes of freezing.
2455         * exp_util.adb Update the documentation and structure of the
2456         type map used in class-wide semantics of assertion expressions.
2457         (Add_Inherited_Tagged_DIC): There is really no need to preanalyze
2458         and resolve the triaged expression because all substitutions
2459         refer to the proper entities.  Update the replacement of
2460         references.
2461         (Build_DIC_Procedure_Body): Add formal parameter
2462         For_Freeze. Add local variable Build_Body. Inherited DIC pragmas
2463         are now only processed when freezing occurs.  Build a body only
2464         when one is needed.
2465         (Entity_Hash): Removed.
2466         (Map_Types): New routine.
2467         (Replace_Object_And_Primitive_References): Removed.
2468         (Replace_References): New routine.
2469         (Replace_Type_References): Moved to the library level of Exp_Util.
2470         (Type_Map_Hash): New routine.
2471         (Update_Primitives_Mapping): Update the mapping call.
2472         (Update_Primitives_Mapping_Of_Types): Removed.
2473         * exp_util.ads (Build_DIC_Procedure_Body): Add formal
2474         parameter For_Freeze and update the comment on usage.
2475         (Map_Types): New routine.
2476         (Replace_References): New routine.
2477         (Replace_Type_References): Moved to the library level of Exp_Util.
2478         (Update_Primitives_Mapping_Of_Types): Removed.
2479         * sem_ch7.adb (Preserve_Full_Attributes): Propagate the DIC
2480         properties of the private type to the full view in case the full
2481         view derives from a parent type and inherits a DIC pragma.
2482         * sem_prag.adb (Analyze_Pragma): Guard against a case where a
2483         DIC pragma is placed at the top of a declarative region.
2485 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
2487         * a-tasatt.adb: Complete previous change and use an unsigned
2488         int to avoid overflow checks.
2490 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2492         * sem_attr.adb (Analyze_Attribute, case 'Access): Specialize
2493         the error message when the attribute reference is an actual in
2494         a call to a subprogram inherited from a generic formal type with
2495         unknown discriminants, which makes the subprogram and its formal
2496         parameters intrinsic (see RM 6.3.1 (8) and (13)).
2498 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2500         * sem_aggr.adb, inline.adb, einfo.adb, einfo.ads, scng.adb,
2501         sem_prag.adb: Minor reformatting.
2503 2017-04-25  Bob Duff  <duff@adacore.com>
2505         * sem_attr.adb (Type_Key): Add code in the
2506         recursive Compute_Type_Key to protect against fetching the source
2507         code for Standard, in case a component of the type is declared
2508         in Standard. There was already code to do this for the original
2509         type, but not for its components.
2511 2017-04-25  Javier Miranda  <miranda@adacore.com>
2513         * exp_ch3.adb (Build_Initialization_Call): Handle
2514         subtypes of private types when searching for the underlying full
2515         view of a private type.
2517 2017-04-25  Javier Miranda  <miranda@adacore.com>
2519         * sem_res.adb (Set_Mixed_Mode_Operand): A universal
2520         real conditional expression can appear in a fixed-type context
2521         and must be resolved with that context to facilitate the code
2522         generation to the backend.
2524 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2526         * einfo.adb, einfo.ads (Body_Needed_For_Inlining): New flag,
2527         to indicate whether during inline processing, when some unit U1
2528         appears in the context of a unit U2 compiled for instantiation
2529         or inlining purposes, the body of U1 needs to be compiled as well.
2530         * sem_prag.adb (Process_Inline): Set Body_Needed_For_Inlining if
2531         context is a package declaration.
2532         * sem_ch12.adb (Analyze_Generic_Subprogram_Declaration,
2533         Analyze_Generic_Package_Declaration): ditto.
2534         * inline.adb (Analyze_Inlined_Bodies): Check
2535         Body_Needed_For_Inlining.
2537 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2539         * par.adb (Current_Assign_Node): Global variable use to record
2540         the presence of a target_name in the right hand side of the
2541         assignment being parsed.
2542         * par-ch4.adb (P_Name): If the name is a target_name, mark the
2543         enclosing assignment node accordingly.
2544         * par-ch5.adb (P_Assignment_Statement): Set Current_Assign_Node
2545         appropriately.
2546         * sem_ch5.adb (Analyze_Assignment): Disable expansion before
2547         analyzing RHS if the statement has target_names.
2548         * sem_aggr.adb (Resolve_Iterated_Component_Association): Handle
2549         properly choices that are subtype marks.
2550         * exp_ch5.adb: Code cleanup.
2552 2017-04-25  Bob Duff  <duff@adacore.com>
2554         * s-memory.adb: Add a comment regarding efficiency.
2555         * atree.adb: Fix the assertion, and combine 2 assertions into one,
2556         "the source has an extension if and only if the destination does."
2557         * sem_ch3.adb, sem_ch13.adb: Address ??? comments.
2559 2017-04-25  Arnaud Charlet  <charlet@adacore.com trojanek>
2561         * a-tasatt.adb (Set_Value): Fix handling of 32bits -> 64bits
2562         conversion.
2564 2017-04-25  Doug Rupp  <rupp@adacore.com>
2566         * init.c (__gnat_error_handler) [vxworks]: Turn on sigtramp
2567         handling for ppc64-vx7.
2568         * sigtramp-vxworks-target.inc
2569         [SIGTRAMP_BODY]: Add section for ppc64-vx7.
2571 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
2573         * ada_get_targ.adb: New file.
2575 2017-04-25  Bob Duff  <duff@adacore.com>
2577         * uintp.adb (Most_Sig_2_Digits): In case Direct (Right), fetch
2578         Direct_Val (Right), instead of the incorrect Direct_Val (Left).
2579         (UI_GCD): Remove ??? comment involving possible efficiency
2580         improvements. This just isn't important after all these years.
2581         Also minor cleanup.
2582         * uintp.ads: Minor cleanup.
2584 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2586         * exp_util.adb, exp_util.ads, sem_ch7.adb, sem_prag.adb, exp_ch3.adb:
2587         Revert previous changes.
2588         * scng.adb: Minor reformatting.
2589         * s-stratt.ads: Fix unbalanced parens in comment.
2591 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2593         * sem_ch3.adb, exp_util.adb, sem_prag.adb, freeze.adb, sem_util.adb:
2594         Minor reformatting.
2596 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2598         * scng.adb (Scan): Handle '@' appropriately.
2599         * sem_ch5.adb: Code cleanup.
2601 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2603         * freeze.adb (Check_Expression_Function): Do not check for the
2604         use of deferred constants if the freezing of the expression
2605         function is triggered by its generated body, rather than a
2606         premature use.
2608 2017-04-25  Javier Miranda  <miranda@adacore.com>
2610         * exp_attr.adb (Rewrite_Stream_Proc_Call): Handle
2611         subtypes of private types when performing the view conversion.
2613 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2615         * exp_ch3.adb (Freeze_Type): Signal the DIC body is created for
2616         the purposes of freezing.
2617         * exp_util.adb Update the documentation and structure of the
2618         type map used in class-wide semantics of assertion expressions.
2619         (Add_Inherited_Tagged_DIC): There is really no need to preanalyze
2620         and resolve the triaged expression because all substitutions
2621         refer to the proper entities.  Update the replacement of
2622         references.
2623         (Build_DIC_Procedure_Body): Add formal parameter
2624         For_Freeze. Add local variable Build_Body. Inherited DIC pragmas
2625         are now only processed when freezing occurs.  Build a body only
2626         when one is needed.
2627         (Entity_Hash): Removed.
2628         (Map_Types): New routine.
2629         (Replace_Object_And_Primitive_References): Removed.
2630         (Replace_References): New routine.
2631         (Replace_Type_References): Moved to the library level of Exp_Util.
2632         (Type_Map_Hash): New routine.
2633         (Update_Primitives_Mapping): Update the mapping call.
2634         (Update_Primitives_Mapping_Of_Types): Removed.
2635         * exp_util.ads (Build_DIC_Procedure_Body): Add formal
2636         parameter For_Freeze and update the comment on usage.
2637         (Map_Types): New routine.
2638         (Replace_References): New routine.
2639         (Replace_Type_References): Moved to the library level of Exp_Util.
2640         (Update_Primitives_Mapping_Of_Types): Removed.
2641         * sem_ch7.adb (Preserve_Full_Attributes): Propagate the DIC
2642         properties of the private type to the full view in case the full
2643         view derives from a parent type and inherits a DIC pragma.
2644         * sem_prag.adb (Analyze_Pragma): Guard against a case where a
2645         DIC pragma is placed at the top of a declarative region.
2647 2017-04-25  Tristan Gingold  <gingold@adacore.com>
2649         * s-mmap.ads (Data): Add pragma Inline.
2651 2017-04-25  Hristian Kirtchev  <kirtchev@adacore.com>
2653         * checks.adb (Insert_Valid_Check): Do not use
2654         a renaming to alias a volatile name because this will lead to
2655         multiple evaluations of the volatile name. Use a constant to
2656         capture the value instead.
2658 2017-04-25  Doug Rupp  <rupp@adacore.com>
2660         * init.c [VxWorks Section]: Disable sigtramp for ppc64-vx7.
2662 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2664         * exp_util.adb, exp_util.ads (Build_Class_Wide_Expression):
2665         Add out parameter to indicate to caller that a wrapper must
2666         be constructed for an inherited primitive whose inherited
2667         pre/postcondition has called to overridden primitives.
2668         * freeze.adb (Check_Inherited_Conditions): Build wrapper body
2669         for inherited primitive that requires it.
2670         * sem_disp.adb (Check_Dispatching_Operation): Such wrappers are
2671         legal primitive operations and belong to the list of bodies
2672         generated after the freeze point of a type.
2673         * sem_prag.adb (Build_Pragma_Check_Equivalent): Use new signature
2674         of Build_Class_Wide_Expression.
2675         * sem_util.adb, sem_util.ads (Build_Overriding_Spec): New procedure
2676         to construct the specification of the wrapper subprogram created
2677         for an inherited operation.
2679 2017-04-25  Bob Duff  <duff@adacore.com>
2681         * s-osinte-linux.ads (pthread_mutexattr_setprotocol,
2682         pthread_mutexattr_setprioceiling): Add new interfaces for these
2683         pthread operations.
2684         * s-taprop-linux.adb (Initialize_Lock, Initialize_TCB): Set
2685         protocols as appropriate for Locking_Policy 'C' and 'I'.
2686         * s-taprop-posix.adb: Minor reformatting to make it more similar
2687         to s-taprop-linux.adb.
2689 2017-04-25  Ed Schonberg  <schonberg@adacore.com>
2691         * sem_ch3.adb (Get_Discriminant_Value, Search_Derivation_Levels):
2692         Handle properly a multi- level derivation involving both renamed
2693         and constrained parent discriminants, when the type to be
2694         constrained has fewer discriminants that the ultimate ancestor.
2696 2017-04-25  Bob Duff  <duff@adacore.com>
2698         * sem_util.adb (Is_Object_Reference): In the
2699         case of N_Explicit_Dereference, return False if it came from a
2700         conditional expression.
2702 2017-04-25  Bob Duff  <duff@adacore.com>
2704         * par-ch4.adb (P_Case_Expression): If a semicolon
2705         is followed by "when", assume that ";" was meant to be ",".
2707 2017-04-25  Gary Dismukes  <dismukes@adacore.com>
2709         * sem_ch9.adb, sem_ch10.adb, sem_util.adb: Minor reformatting and typo
2710         fixes.
2712 2017-04-25  Arnaud Charlet  <charlet@adacore.com>
2714         * rtsfind.ads (SPARK_Implicit_Load): New procedure for forced
2715         loading of an entity.
2716         * rtsfind.adb (SPARK_Implicit_Load): Body with a pattern
2717         previously repeated in the analysis.
2718         * sem_ch9.adb (Analyze_Protected_Type_Declaration): use new
2719         procedure SPARK_Implicit_Load.  (Analyze_Task_Type_Declaration):
2720         use new procedure SPARK_Implicit_Load.
2721         * sem_ch10.adb (Analyze_Compilation_Unit): Use new procedure
2722         SPARK_Implicit_Load.
2724 2017-04-25  Javier Miranda  <miranda@adacore.com>
2726         * sem_util.adb (New_Copy_Tree): By default
2727         copying of defining identifiers is prohibited because
2728         this would introduce an entirely new entity into the
2729         tree. This patch introduces an exception to this general
2730         rule: the declaration of constants and variables located in
2731         Expression_With_Action nodes.
2732         (Copy_Itype_With_Replacement): Renamed as Copy_Entity_With_Replacement.
2733         (In_Map): New subprogram.
2734         (Visit_Entity): New subprogram.
2735         (Visit_Node): Handle EWA_Level,
2736         EWA_Inner_Scope_Level, and take care of defining entities defined
2737         in Expression_With_Action nodes.
2739 2017-04-25  Thomas Quinot  <quinot@adacore.com>
2741         * exp_ch6.adb: minor comment edit.
2742         * sinfo.ads, sinfo.adb: New Null_Statement attribute for null
2743         procedure specifications that come from source.
2744         * par-ch6.adb (P_Subprogram, case of a null procedure): Set new
2745         Null_Statement attribute.
2746         * par_sco.adb (Traverse_Declarations_Or_Statements): For a null
2747         procedure, generate statement SCO for the generated NULL statement.
2748         * sem_ch6.adb (Analyze_Null_Procedure): Use null statement from
2749         parser, if available.
2751 2017-04-04  Andreas Krebbel  <krebbel@linux.vnet.ibm.com>
2753         * system-linux-s390.ads: Use Long_Integer'Size to define
2754         Memory_Size.
2756 2017-04-04  Eric Botcazou  <ebotcazou@adacore.com>
2758         * sem_ch3.adb (Build_Derived_Record_Type): Fix long line.
2760 2017-04-03  Jonathan Wakely  <jwakely@redhat.com>
2762         * doc/gnat_ugn/gnat_and_program_execution.rst: Fix typo.
2763         * g-socket.adb (To_Host_Entry): Fix typo in comment.
2764         * gnat_ugn.texi: Fix typo.
2765         * raise.c (_gnat_builtin_longjmp): Fix capitalization in comment.
2766         * s-stposu.adb (Allocate_Any_Controlled): Fix typo in comment.
2767         * sem_ch3.adb (Build_Derived_Record_Type): Likewise.
2768         * sem_util.adb (Mark_Coextensions): Likewise.
2769         * sem_util.ads (Available_Full_View_Of_Component): Likewise.
2771 2017-03-28  Andreas Schwab  <schwab@suse.de>
2773         PR ada/80117
2774         * system-linux-aarch64-ilp32.ads: New file.
2775         * gcc-interface/Makefile.in (LIBGNAT_TARGET_PAIRS_COMMON): Rename
2776         from LIBGNAT_TARGET_PAIRS.
2777         (LIBGNAT_TARGET_PAIRS_32, LIBGNAT_TARGET_PAIRS_64): Define.
2778         (LIBGNAT_TARGET_PAIRS): Use LIBGNAT_TARGET_PAIRS_COMMON, and
2779         LIBGNAT_TARGET_PAIRS_64 or LIBGNAT_TARGET_PAIRS_32 for -mabi=lp64
2780         or -mabi=ilp32, resp.
2782 2017-03-14  James Cowgill  <James.Cowgill@imgtec.com>
2784         * s-osinte-linux.ads (struct_sigaction): Use correct type for sa_flags.
2786 2017-03-08  Thanassis Tsiodras  <ttsiodras@gmail.com>
2788         PR ada/79903
2789         * socket.c (__gnat_gethostbyaddr): Add missing test for __rtems__.
2791 2017-03-08  Eric Botcazou  <ebotcazou@adacore.com>
2793         PR ada/79945
2794         * system-linux-ppc.ads (Default_Bit_Order): Use Standard's setting.
2796         * system-linux-arm.ads (Default_Bit_Order): Likewise.
2797         * system-linux-mips.ads (Default_Bit_Order): Likewise.
2798         * system-linux-armeb.ads: Delete.
2799         * system-linux-mipsel.ads: Likewise.
2800         * gcc-interface/Makefile.in (MIPS/Linux): Adjust.
2801         (ARM/Linux): Likewise.
2803 2017-02-24  Jakub Jelinek  <jakub@redhat.com>
2805         PR c/79677
2806         * gcc-interface/misc.c (gnat_handle_option): Pass true to
2807         handle_generated_option GENERATED_P.
2809 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
2811         * gcc-interface/decl.c (gnat_to_gnu_field): Do not remove the wrapper
2812         around a justified modular type if it doesn't have the same scalar
2813         storage order as the enclosing record type.
2815 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
2817         * gcc-interface/trans.c (gnat_to_gnu): Do not apply special handling
2818         of boolean rvalues to function calls.
2820 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
2822         * gcc-interface/utils.c (fold_bit_position): New function.
2823         (rest_of_record_type_compilation): Call it instead of bit_position to
2824         compute the field position and remove the call to remove_conversions.
2825         (compute_related_constant): Factor out the multiplication in both
2826         operands, if any, and streamline the final test.
2828 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
2830         * gcc-interface/trans.c (return_value_ok_for_nrv_p): Add sanity check.
2832 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
2834         * gcc-interface/decl.c: Include demangle.h.
2835         (is_cplusplus_method): Return again true for a primitive operation
2836         only if it is dispatching.  For a subprogram with an interface name,
2837         call the demangler to get the number of C++ parameters and compare it
2838         with the number of Ada parameters.
2840 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
2842         * gcc-interface/trans.c (Handled_Sequence_Of_Statements_to_gnu): If
2843         there is no end label, put the location of the At_End procedure on
2844         the call to the procedure.
2846 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
2848         * gcc-interface/misc.c (gnat_type_max_size): Try to return a meaningful
2849         value for array types with TYPE_INDEX_TYPE set on their domain type.
2850         * gcc-interface/utils.c (max_size): For operations and expressions, do
2851         not build a new node if the operands have not changed or are missing.
2853 2017-02-24  Eric Botcazou  <ebotcazou@adacore.com>
2855         * gcc-interface/utils.c (max_size) <tcc_expression>: Flip the second
2856         argument when recursing on TRUTH_NOT_EXPR.
2858 2017-02-12  John Marino  <gnugcc@marino.st>
2860         * system-freebsd-x86.ads: Rename into...
2861         * system-freebsd.ads: ...this.
2862         (Default_Bit_Order): Define using Standard'Default_Bit_Order.
2863         * gcc-interface/Makefile.in: Support aarch64-freebsd.
2864         (x86-64/FreeBSD): Adjust to above renaming.
2865         (i386/FreeBSD): Likewise.
2867 2017-02-09  Gerald Pfeifer  <gerald@pfeifer.com>
2869         * comperr.adb: Update FSF bug reporting URL.
2871 2017-02-01  Eric Botcazou  <ebotcazou@adacore.com>
2872             Jakub Jelinek  <jakub@redhat.com>
2874         PR ada/79309
2875         * adaint.c (__gnat_killprocesstree): Fix broken string handling.
2877 2017-01-25  Maxim Ostapenko  <m.ostapenko@samsung.com>
2879         PR lto/79061
2880         * gcc-interface/utils.c (get_global_context): Pass main_input_filename
2881         to build_translation_unit_decl.
2883 2017-01-23  Javier Miranda  <miranda@adacore.com>
2885         * sem_util.adb (New_Copy_Tree): Code cleanup:
2886         removal of the internal map (ie. variable Actual_Map, its
2887         associated local variables, and all the code handling it).
2888         * sem_ch9.adb (Analyze_Task_Type_Declaration): in GNATprove mode
2889         force loading of the System package when processing a task type.
2890         (Analyze_Protected_Type_Declaration): in GNATprove mode force
2891         loading of the System package when processing a protected type.
2892         * sem_ch10.adb (Analyze_Compilation_Unit): in GNATprove mode
2893         force loading of the System package when processing compilation
2894         unit with a main-like subprogram.
2895         * frontend.adb (Frontend): remove forced loading of the System
2896         package.
2898 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
2900         * sem_prag.adb (Default_Initial_Condition): If the desired type
2901         declaration is a derived type declaration with discriminants,
2902         it is rewritten as a private type declaration.
2903         * sem_ch13.adb (Replace_Type_References_Generic,
2904         Visible_Component): A discriminated private type with descriminnts
2905         has components that must be rewritten as selected components
2906         if they appear as identifiers in an aspect expression such as
2907         a Default_Initial_Condition.
2908         * sem_util.adb (Defining_Entity): support N_Iterator_Specification
2909         nodes.
2911 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
2913         * ghost.ads, ghost.adb (Is_Ignored_Ghost_Unit): New routine.
2914         * gnat1drv.adb Generate an empty object file for an ignored
2915         Ghost compilation unit.
2916         * inline.adb, sem_util.adb, sem_ch4.adb: Minor reformatting.
2918 2017-01-23  Yannick Moy  <moy@adacore.com>
2920         * sem_ch4.adb (Analyze_Indexed_Component_Form):
2921         Adapt to inlined prefix with string literal subtype.
2922         * inline.adb (Expand_Inlined_Call): Keep unchecked
2923         conversion inside inlined call when formal type is constrained.
2925 2017-01-23  Javier Miranda  <miranda@adacore.com>
2927         * sem_util.adb (New_Copy_Tree): Code cleanup:
2928         removal of global variables. All the global variables, global
2929         functions and tables of this subprogram are now declared locally.
2931 2017-01-23  Gary Dismukes  <dismukes@adacore.com>
2933         * exp_strm.ads: Minor reformatting and typo fixes.
2935 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
2937         * sem_aggr.adb, par_sco.adb, exp_util.adb, sem.adb, sem_ch4.adb,
2938         exp_aggr.adb: Minor reformatting.
2939         * g-diopit.adb: minor grammar/punctuation fix in comment.
2940         * g-byorma.ads: minor fix of unbalanced parens in comment.
2942 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
2944         * par.adb: Update the documentation of component Labl.
2945         * par-ch6.adb (P_Return_Statement): Set the expected label of
2946         an extended return statement to Error.
2948 2017-01-23  Tristan Gingold  <gingold@adacore.com>
2950         * s-boustr.ads, s-boustr.adb (Is_Full): New function.
2952 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
2954         * expander.adb: Handle N_Delta_Aggregate.
2956 2017-01-23  Javier Miranda  <miranda@adacore.com>
2958         * exp_ch6.adb (Expand_Call): Improve the code that
2959         checks if some formal of the called subprogram is a class-wide
2960         interface, to handle subtypes of class-wide interfaces.
2962 2017-01-23  Javier Miranda  <miranda@adacore.com>
2964         * checks.adb (Apply_Parameter_Aliasing_Checks):
2965         Remove side effects of the actuals before generating the overlap
2966         check.
2968 2017-01-23  Justin Squirek  <squirek@adacore.com>
2970         * exp_strm.ads, exp_strm.ads
2971         (Build_Record_Or_Elementary_Input_Function): Add an extra parameter so
2972         as to avoid getting the underlying type by default.
2973         * exp_attr.adb (Expand_N_Attribute_Reference): Remove use of
2974         underlying type in the Iiput and output attribute cases when
2975         building their respective functions.
2977 2017-01-23  Gary Dismukes  <dismukes@adacore.com>
2979         * scng.adb: Minor reformatting of error message.
2981 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
2983         * sem_ch6.adb (Analyze_Expression_Function): Do not attempt
2984         to freeze the return type of an expression funxtion that is a
2985         completion, if the type is a limited view and the non-limited
2986         view is available.
2988 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
2990         * par-ch4.adb (P_Aggregate_Or_Parent_Expr): Recognize delta
2991         aggregate construct.
2992         (P_Record_Or_Array_Component_Association): An array aggregate
2993         can start with an Iterated_Component_Association.
2994         * scng.adb: Modify error message on improper use of @ in earlier
2995         versions of the language.
2996         * sinfo.ads: New node kind N_Delta_Aggregate.
2997         * sinfo.adb: An N_Delta_Aggregate has component associations and
2998         an expression.
2999         * sem_res.adb (Resolve): Call Resolve_Delta_Aggregate.
3000         * sem_aggr.ads, sem_aggr.adb (Resolve_Iterated_Component_Association):
3001         Create a new index for each one of the choices in the association,
3002         to prevent spurious homonyms in the scope.
3003         (Resolve_Delta_Aggregate): New.
3004         * sem.adb: An N_Delta_Aggregate is analyzed like an aggregate.
3005         * exp_util.adb (Insert_Actions): Take into account
3006         N_Delta_Aggregate.
3007         * exp_aggr.ads: New procedure Expand_N_Delta_Aggregate.
3008         * exp_aggr.adb: New procedure Expand_N_Delta_Aggregate,
3009         and local procedures Expand_Delta_Array_Aggregate and
3010         expand_Delta_Record_Aggregate.
3011         * sprint.adb: Handle N_Delta_Aggregate.
3013 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
3015         * exp_ch11.adb (Expand_N_Exception_Declaration): Generate an
3016         empty name when the exception declaration is subject to pragma
3017         Discard_Names.
3018         (Null_String): New routine.
3020 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
3022         * par-ch9.adb (P_Protected_Definition): Parse
3023         any optional and potentially illegal pragmas which appear in
3024         a protected operation declaration list.
3025         (P_Task_Items): Parse
3026         any optional and potentially illegal pragmas which appear in a
3027         task item list.
3029 2017-01-23  Pascal Obry  <obry@adacore.com>
3031         * s-taprop-mingw.adb (Enter_Task): Initialize the Thread handle which
3032         is needed when a foreign thread call a Win32 API using a thread handle
3033         like GetThreadTimes() for example.
3035 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
3037         * sem_ch13.adb (Analyze_Attribute_Definition_Clause): Do not
3038         allow an 'Address clause to be specified on a prefix of a
3039         class-wide type.
3041 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
3043         * checks.adb (Insert_Valid_Check): Ensure that the prefix of
3044         attribute 'Valid is a renaming of the original expression when
3045         the expression denotes a name. For all other kinds of expression,
3046         use a constant to capture the value.
3047         * exp_util.adb (Is_Name_Reference): Moved to Sem_Util.
3048         * sem_util.ads, sem_util.adb (Is_Name_Reference): Moved from Exp_Util.
3050 2017-01-23  Justin Squirek  <squirek@adacore.com>
3052         * sem_eval.adb (Eval_Integer_Literal): Add special
3053         case to avoid optimizing out check if the literal appears in
3054         an if-expression.
3056 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
3058         * sem_ch13.adb (Analyze_Attribute_Definition_Clause): Do not
3059         allow an 'Address clause to be specified on a prefix of a
3060         class-wide type.
3062 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
3064         * checks.adb (Insert_Valid_Check): Ensure that the prefix of
3065         attribute 'Valid is a renaming of the original expression when
3066         the expression denotes a name. For all other kinds of expression,
3067         use a constant to capture the value.
3068         * exp_util.adb (Is_Name_Reference): Moved to Sem_Util.
3069         * sem_util.ads, sem_util.adb (Is_Name_Reference): Moved from Exp_Util.
3071 2017-01-23  Justin Squirek  <squirek@adacore.com>
3073         * sem_eval.adb (Eval_Integer_Literal): Add special
3074         case to avoid optimizing out check if the literal appears in
3075         an if-expression.
3077 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
3079         * sem_ch4.adb (Try_Primitive_Operations,
3080         Is_Valid_First_Argument_Of): argument is valid if it is a derived
3081         type with unknown discriminants that matches its underlying
3082         record view.
3083         * exp_util.adb (Expand_Subtype_From_Expr): Do not expand
3084         expression if its type is derived from a limited type with
3085         unknown discriminants, because the expansion (which is a call)
3086         must be expanded in the enclosing context to add the proper build-
3087         in-place parameters to the call.
3088         * lib.ads, exp_ch9.adb: Minor fixes in comments.
3090 2017-01-23  Yannick Moy  <moy@adacore.com>
3092         * frontend.adb (Frontend): Do not load runtime
3093         unit for GNATprove when parsing failed.
3094         * exp_ch9.adb: minor removal of extra whitespace
3095         * exp_ch6.adb: minor typo in comment
3096         * sem_util.adb: Code cleanup.
3097         * exp_ch9.ads, par-ch2.adb: minor style fixes in whitespace and comment
3098         * a-ngcefu.adb: minor style fix in whitespace
3100 2017-01-23  Thomas Quinot  <quinot@adacore.com>
3102         * scos.ads: Document usage of 'd' as default SCO kind for
3103         declarations.
3104         * par_sco.adb (Traverse_Declarations_Or_Statements.
3105         Traverse_Degenerate_Subprogram): New supporting routine for expression
3106         functions and null procedures.
3107         (Traverse_Declarations_Or_Statements.Traverse_One): Add
3108         N_Expression_Function to the subprogram case; add required
3109         support for null procedures and expression functions.
3111 2017-01-23  Bob Duff  <duff@adacore.com>
3113         * namet.ads (Bounded_String): Decrease the size of type
3114         Bounded_String to avoid running out of stack space.
3115         * namet.ads (Append): Don't ignore buffer overflow; raise
3116         Program_Error instead.
3118 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
3120         * exp_ch5.adb, freeze.adb, par-ch4.adb, scng.adb, sem_ch13.adb,
3121         sem_ch3.adb, sem_ch5.adb, sem_ch5.ads, sem_util.adb, sinfo.ads: Minor
3122         reformatting.
3123         * exp_ch9.adb: minor style fix in comment.
3125 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
3127         * sem_ch4.adb (Analyze_Allocator): Handle properly a type derived
3128         for a limited record extension with unknown discriminants whose
3129         full view has no discriminants.
3131 2017-01-23  Yannick Moy  <moy@adacore.com>
3133         * exp_spark.adb: Alphabetize with clauses.
3135 2017-01-23  Yannick Moy  <moy@adacore.com>
3137         * sem_util.adb (Has_Enabled_Property): Treat
3138         protected objects and variables differently from other variables.
3140 2017-01-23  Thomas Quinot  <quinot@adacore.com>
3142         * sem_ch13.adb (Adjust_Record_For_Reverse_Bit_Order):
3143         Split original Ada 95 part off into new subprogram
3144         below. Call that subprogram (instead of proceeding with
3145         AI95-0133 behaviour) if debug switch -gnatd.p is in use.
3146         (Adjust_Record_For_Reverse_Bit_Order_Ada_95): ... new subprogram
3147         * debug.adb Document new switch -gnatd.p
3148         * freeze.adb (Freeze_Entity.Freeze_Record_Type): Do not adjust
3149         record for reverse bit order if an error has already been posted
3150         on the record type.  This avoids generating extraneous "info:"
3151         messages for illegal code.
3153 2017-01-23  Justin Squirek  <squirek@adacore.com>
3155         * sem_ch3.adb (Analyze_Declarations): Correct comments
3156         * freeze.adb (Find_Constant): Add detection of deferred constants
3157         so they are not incorrectly flagged as premature.
3159 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
3161         * scans.ads: New token At_Sign. Remove '@' from list of illegal
3162         characters for future version of the language. '@' is legal name.
3163         * scng.ads, scng.adb (Scan):  Handle '@' appropriately.
3164         * scn.adb (Scan_Reserved_Identifier): An occurrence of '@'
3165         denotes a Target_Name.
3166         * par-ch4.adb (P_Name, P_Primary): Handle Target_Name.
3167         * sinfo.ads, sinfo.adb (N_Target_Name): New non-terminal node.
3168         (Has_Target_Names): New flag on N_Assignment_Statement, to
3169         indicate that RHS has occurrences of N_Target_Name.
3170         * sem.adb: Call Analyze_Target_Name.
3171         * sem_ch5.ads, sem_ch5.adb (Analyze_Target_Name): New subpogram.
3172         (urrent_LHS): Global variable that denotes LHS of assignment,
3173         used in the analysis of Target_Name nodes.
3174         * sem_res.adb (Resolve_Target_Name): New procedure.
3175         * exp_ch5.adb (Expand_Assign_With_Target_Names): (AI12-0125):
3176         N is an assignment statement whose RHS contains occurences of @
3177         that designate the value of the LHS of the assignment. If the
3178         LHS is side-effect free the target names can be replaced with
3179         a copy of the LHS; otherwise the semantics of the assignment
3180         is described in terms of a procedure with an in-out parameter,
3181         and expanded as such.
3182         (Expand_N_Assignment_Statement): Call
3183         Expand_Assign_With_Target_Names when needed.
3184         * exp_util.adb (Insert_Actions): Take into account N_Target_Name.
3185         * sprint.adb: Handle N_Target_Name.
3187 2017-01-23  Eric Botcazou  <ebotcazou@adacore.com>
3189         * checks.adb: Minor fix in comment.
3191 2017-01-23  Philippe Gil  <gil@adacore.com>
3193         * g-debpoo.adb (Do_Report) remove freed chunks from chunks
3194         count in Sort = Memory_Usage or Allocations_Count
3196 2017-01-23  Justin Squirek  <squirek@adacore.com>
3198         * sem_ch3.adb: Code cleanup.
3200 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
3202         * sem_prag.adb (Analyze_Refined_Depends_In_Decl_Part): Move all global
3203         variables to the local variable section. Update the profile
3204         of various nested routine that previously had visibility
3205         of those globals. One the matching phase has completed,
3206         remove certain classes of clauses which are considered noise.
3207         (Check_Dependency_Clause): Properly detect a match between two
3208         'Result attributes. Update the various post-match cases to use
3209         Is_Already_Matched as this routine now automatically recognizes
3210         a previously matched 'Result attribute.
3211         (Is_Already_Matched): New routine.
3212         (Remove_Extra_Clauses): New routine.
3213         (Report_Extra_Clauses): Remove the detection of ... => null
3214         clauses as this is now done in Remove_Extra_Clauses.
3216 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
3218         * sem_aggr.adb (Resolve_Array_Aggregate): In ASIS mode do not
3219         report on spurious overlaps between values involving a subtype
3220         with a static predicate, because the expansion of such a subtype
3221         into individual ranges in inhibited in ASIS mode.
3223 2017-01-23  Justin Squirek  <squirek@adacore.com>
3225         * sem_ch3.adb (Analyze_Declarations): Add detection
3226         of an edge case and delay freezing if it is present.
3228 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
3230         * sem_ch3.adb, exp_spark.adb, exp_attr.adb, sem_ch9.adb, sem_prag.adb,
3231         sem_util.adb, sem_warn.adb, exp_ch3.adb: Minor reformatting.
3233 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
3235         * freeze.adb (Freeze_Subprogram): Ensure that all anonymous
3236         access-to-subprogram types inherit the convention of the
3237         associated subprogram.  (Set_Profile_Convention): New routine.
3238         * sem_ch6.adb (Check_Conformance): Do not compare the conventions
3239         of the two entities directly, use Conventions_Match to account
3240         for anonymous access-to-subprogram and subprogram types.
3241         (Conventions_Match): New routine.
3243 2017-01-23  Claire Dross  <dross@adacore.com>
3245         * exp_spark.adb (Expand_SPARK_Attribute_Reference): For attributes
3246         which return Universal_Integer, force the overflow check flag for
3247         Length and Range_Length for types as big as Long_Long_Integer.
3249 2017-01-23  Claire Dross  <dross@adacore.com>
3251         * exp_spark.adb (Expand_SPARK_Attribute_Reference):  For
3252         attributes which return Universal_Integer, introduce a conversion
3253         to the expected type with the appropriate check flags set.
3254         * sem_res.adb (Resolve_Range): The higher bound can be in Typ's
3255         base type if the range is null. It may still be invalid if it
3256         is higher than the lower bound. This is checked later in the
3257         context in which the range appears.
3259 2017-01-23  Pierre-Marie de Rodat  <derodat@adacore.com>
3261         * scos.ads: Introduce a constant to represent ignored
3262         dependencies in SCO_Unit_Table_Entry.
3264 2017-01-23  Hristian Kirtchev  <kirtchev@adacore.com>
3266         * exp_ch9.adb (Expand_N_Protected_Type_Declaration): Remove extra
3267         spaces from error messages.
3269 2017-01-23  Ed Schonberg  <schonberg@adacore.com>
3271         * exp_ch3.adb (Check_Large_Modular_Array): New procedure,
3272         subsidiary to Expand_N_Object_ Declaration, to compute a guard on
3273         an object declaration for an array type with a modular index type
3274         with the size of Long_Long_Integer. Special processing is needed
3275         in this case to compute reliably the size of the object, and
3276         eventually  to raise Storage_Error, when wrap-around arithmetic
3277         might compute a meangingless size for the object.
3279 2017-01-23  Justin Squirek  <squirek@adacore.com>
3281         * a-wtenau.adb, par-endh.adb, sem_prag.adb,
3282         sem_type.adb: Code cleanups.
3284 2017-01-23  Bob Duff  <duff@adacore.com>
3286         * sem_res.adb (Resolve_Call): In the part of the code where
3287         it is deciding whether to turn the call into an indexed
3288         component, avoid doing so if the call is to an instance of
3289         Unchecked_Conversion. Otherwise, the compiler turns it into an
3290         indexed component, and resolution of that turns it back into a
3291         function call, and so on, resulting in infinite recursion.
3292         * sem_util.adb (Needs_One_Actual): If the first formal has a
3293         default, then return False.
3295 2017-01-21  Eric Botcazou  <ebotcazou@adacore.com>
3297         * sem_eval.adb (Compile_Time_Compare): Reinstate the expr+literal (etc)
3298         optimizations when the type is modular and the offsets are equal.
3300 2017-01-20  Thomas Quinot  <quinot@adacore.com>
3302         * sem_warn.adb (Warn_On_Useless_Assignment): Adjust wording of warning
3303         message.
3305 2017-01-20  Nicolas Roche  <roche@adacore.com>
3307         * terminals.c: Ignore failures on setpgid and tcsetpgrp commands.
3309 2017-01-20  Bob Duff  <duff@adacore.com>
3311         * sem_eval.adb (Compile_Time_Compare): Disable the expr+literal
3312         (etc) optimizations when the type is modular.
3314 2017-01-20  Yannick Moy  <moy@adacore.com>
3316         * sem_ch6.adb (Move_Pragmas): move some pragmas,
3317         but copy the SPARK_Mode pragma instead of moving it.
3318         (Build_Subprogram_Declaration): Ensure that the generated spec
3319         and original body share the same SPARK_Pragma aspect/pragma.
3320         * sem_util.adb, sem_util.ads (Copy_SPARK_Mode_Aspect): New
3321         procedure to copy SPARK_Mode aspect.
3323 2017-01-20  Bob Duff  <duff@adacore.com>
3325         * sem_ch3.adb (Analyze_Declarations): Disable Resolve_Aspects
3326         even in ASIS mode.
3327         * sem_ch13.adb (Resolve_Name): Enable setting the entity to
3328         Empty even in ASIS mode.
3330 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
3332         * exp_ch9.adb: minor style fixes in comments.
3333         * sem_ch9.adb (Analyze_Delay_Relative): in GNATprove mode a delay
3334         relative statement introduces an implicit dependency on
3335         Ada.Real_Time.Clock_Time.
3336         * sem_util.adb: Minor reformatting.
3338 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
3340         * sem_ch13.adb (Analyze_Aspect_Specifications): Aspect Alignment
3341         must be treated as delayed aspect even if the expression is
3342         a literal, because the aspect affects the freezing and the
3343         elaboration of the object to which it applies.
3345 2017-01-20  Tristan Gingold  <gingold@adacore.com>
3347         * s-osinte-vxworks.ads (Interrup_Range): New subtype.
3349 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
3351         * lib-xref.adb (Generate_Reference): Do not warn about the
3352         presence of a pragma Unreferenced if the entity appears as the
3353         actual in a procedure call that does not come from source.
3355 2017-01-20  Pascal Obry  <obry@adacore.com>
3357         * expect.c, terminals.c: Fix some warnings about unused variables.
3358         * gsocket.h, adaint.c, adaint.h: Fix some more warnings in the C part
3359         of the runtime.
3361 2017-01-20  Bob Duff  <duff@adacore.com>
3363         * exp_attr.adb (Constrained): Apply an access check (check that
3364         the prefix is not null) when the prefix denotes an object of an
3365         access type; that is, when there is an implicit dereference.
3367 2017-01-20  Gary Dismukes  <dismukes@adacore.com>
3369         * s-rident.ads (constant Profile_Info): Remove
3370         No_Calendar from GNAT_Extended_Ravenscar restrictions.
3372 2017-01-20  Tristan Gingold  <gingold@adacore.com>
3374         *  s-maccod.ads: Add pragma No_Elaboration_Code_All
3376 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
3378         * ghost.adb (Mark_Ghost_Clause): New routine.
3379         (Prune_Node): Do not prune compilation unit nodes.
3380         (Remove_Ignored_Ghost_Code): Prune the compilation unit node directly.
3381         This does not touch the node itself, but does prune all its fields.
3382         * ghost.ads (Mark_Ghost_Clause): New routine.
3383         * sem_ch8.adb (Analyze_Use_Package): Emit an error when a use
3384         package clause mentions Ghost and non-Ghost packages. Mark a
3385         use package clause as Ghost when it mentions a Ghost package.
3386         (Analyze_Use_Type): Emit an error when a use type clause mentions
3387         Ghost and non-Ghost types. Mark a use type clause as Ghost when
3388         it mentions a Ghost type.
3389         * sem_ch10.adb (Analyze_With_Clause): Mark a with clause as
3390         Ghost when it withs a Ghost unit.
3392 2017-01-20  Javier Miranda  <miranda@adacore.com>
3394         * sem_res.adb (Resolve_Call): If a function call
3395         returns a limited view of a type and at the point of the call the
3396         function is not declared in the extended main unit then replace
3397         it with the non-limited view, which must be available. If the
3398         called function is in the extended main unit then no action is
3399         needed since the back-end handles this case.
3401 2017-01-20  Eric Botcazou  <ebotcazou@adacore.com>
3403         * sem_ch7.adb (Contains_Subp_Or_Const_Refs): Rename into...
3404         (Contains_Subprograms_Refs): ...this.  Adjust comment
3405         for constants.  (Is_Subp_Or_Const_Ref): Rename into...
3406         (Is_Subprogram_Ref): ...this.
3407         (Has_Referencer): Rename Has_Non_Subp_Const_Referencer variable into
3408         Has_Non_Subprograms_Referencer and adjust comment.  Remove
3409         incorrect shortcut for package declarations and bodies.
3411 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
3413         * sem_ch3.adb (Complete_Private_Subtype): If the scope of the
3414         base type differs from that of the completion and the private
3415         subtype is an itype (created for a constraint on an access
3416         type e.g.), set Delayed_Freeze on both to prevent out-of-scope
3417         anomalies in gigi.
3419 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
3421         * sem_ch6.adb (Analyze_Subprogram_Body_Helper):
3422         When inheriting the SPARK_Mode of a prior expression function,
3423         look at the properly resolved entity rather than the initial
3424         candidate which may denote a homonym.
3426 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
3428         * sem_prag.adb (Rewrite_Assertion_Kind): If the name is
3429         Precondition or Postcondition, and the context is pragma
3430         Check_Policy, indicate that this Pre-Ada2012 usage is deprecated
3431         and suggest the standard names Assertion_Policy /Pre /Post
3432         instead.
3434 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
3436         * sem_ch10.adb, sem_cat.adb: Minor reformatting.
3438 2017-01-20  Javier Miranda  <miranda@adacore.com>
3440         * sem_ch3.adb (Access_Type_Declaration): Protect access to the
3441         Entity attribute.
3442         * sem_ch10.adb (Install_Siblings): Skip processing malformed trees.
3443         * sem_cat.adb (Validate_Categoriztion_Dependency): Skip processing
3444         malformed trees.
3446 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
3448         * sem_ch13.adb (Analyze_Aspect_Specification, case
3449         Dynamic_Predicate): If the entity E is a subtype that inherits
3450         a static predicate for its parent P,, the inherited and the
3451         new predicate combine in the generated predicate function,
3452         and E only has a dynamic predicate.
3454 2017-01-20  Tristan Gingold  <gingold@adacore.com>
3456         * s-boustr.ads, s-boustr.adb: New package.
3457         * Makefile.rtl: Add s-boustr.
3459 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
3461         * inline.adb (Process_Formals): Qualify the
3462         expression of a return statement when it yields a universal type.
3464 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
3466         * freeze.adb (Freeze_All): Freeze the default
3467         expressions of all eligible formal parameters that appear in
3468         entries, entry families, and protected subprograms.
3470 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
3472         * sem_ch3.adb (Check_Nonoverridable_Aspects); Refine check
3473         for illegal inherited Implicit_Dereference aspects with renamed
3474         discriminants.
3476 2017-01-20  Javier Miranda  <miranda@adacore.com>
3478         * debug.adb (switch d.6): do not avoid declaring unreferenced itypes.
3479         * nlists.ads (Lock_Lists, Unlock_Lists): New subprograms.
3480         * nlists.adb (Lock_Lists, Unlock_Lists): New subprograms.
3481         (Set_First, Set_Last, Set_List_Link, Set_Next, Set_Parent,
3482         Set_Prev, Tree_Read): Adding assertion.
3483         * atree.ads (Lock_Nodes, Unlock_Nodes): New subprograms.
3484         * atree.adb (Lock_Nodes, Unlock_Nodes): New subprograms.
3485         (Set_Analyzed, Set_Check_Actuals, Set_Comes_From_Source,
3486         Set_Ekind, Set_Error_Posted, Set_Has_Aspects,
3487         Set_Is_Ignored_Ghost_Node, Set_Original_Node, Set_Paren_Count,
3488         Set_Parent, Set_Sloc, Set_Nkind, Set_FieldNN, Set_NodeNN,
3489         Set_ListNN, Set_ElistNN, Set_NameN, Set_StrN, Set_UintNN,
3490         Set_UrealNN, Set_FlagNNN, Set_NodeN_With_Parent,
3491         Set_ListN_With_Parent): Adding assertion.
3493 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
3495         * sem_prag.adb (Process_Convention): Diagnose properly a pragma
3496         import that applies to several homograph subprograms. when one
3497         of them is declared by a subprogram body.
3499 2017-01-20  Justin Squirek  <squirek@adacore.com>
3501         * exp_ch6.adb (Expand_Call): Remove optimization
3502         that nulls out calls to null procedures.
3504 2017-01-20  Yannick Moy  <moy@adacore.com>
3506         * inline.adb (Expand_Inlined_Call): Keep more
3507         precise type of actual for inlining whenever possible. In
3508         particular, do not switch to the formal type in GNATprove mode in
3509         some case where the GNAT backend might require it for visibility.
3511 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
3513         * sem_ch3.adb (Check_Non_Overridable_Aspects): An inherited
3514         aspect Implicit_Dereference can be inherited by a full view if
3515         the partial view has no discriminants, because there is no way
3516         to apply the aspect to the partial view.
3517         (Build_Derived_Record_Type): If derived type renames discriminants
3518         of the parent, the new discriminant inherits the aspect from
3519         the old one.
3520         * sem_ch4.adb (Analyze_Call): Handle properly a parameterless
3521         call through an access discriminant designating a subprogram.
3522         * sem_ch5.adb (Analyze_Assignment): (Analyze_Call): Handle
3523         properly a parameterless call through an access discriminant on
3524         the left-hand side of an assignment.
3525         * sem_res.adb (resolve): If an interpreation involves a
3526         discriminant with an implicit dereference and the expression is an
3527         entity, resolution takes place later in the appropriate routine.
3528         * sem_ch13.adb (Analyze_Aspect_Implicit_Dereference): Recognize
3529         access discriminants that designate a subprogram type.
3531 2017-01-20  Pascal Obry  <obry@adacore.com>
3533         * a-locale.adb, a-locale.ads: Update Ada.Locales for RM 2012 COR:1:2016
3535 2017-01-20  Yannick Moy  <moy@adacore.com>
3537         * sem_ch10.adb (Check_No_Elab_Code_All): Do not issue an error
3538         on implicitly with'ed units in GNATprove mode.
3539         * sinfo.ads (Implicit_With): Document use of flag for implicitly
3540         with'ed units in GNATprove mode.
3542 2017-01-20  Ed Schonberg  <schonberg@adacore.com>
3544         * sem_cat.adb (Validate_Static_Object_Name): In a preelaborated
3545         unit Do not report an error on a non-static entity that appears
3546         in the context of a spec expression, such as an aspect expression.
3548 2017-01-20  Hristian Kirtchev  <kirtchev@adacore.com>
3550         * einfo.adb: Flag298 now denotes Is_Underlying_Full_View.
3551         (Is_Underlying_Full_View): New routine.
3552         (Set_Is_Underlying_Full_View): New routine.
3553         (Write_Entity_Flags): Add an entry for Is_Underlying_Full_View.
3554         * einfo.ads Add new attribute Is_Underlying_Full_View.
3555         (Is_Underlying_Full_View): New routine along with pragma Inline.
3556         (Set_Is_Underlying_Full_View): New routine along with pragma Inline.
3557         * exp_util.adb (Build_DIC_Procedure_Body): Do not consider
3558         class-wide types and underlying full views. The first subtype
3559         is used as the working type for all Itypes, not just array base types.
3560         (Build_DIC_Procedure_Declaration): Do not consider
3561         class-wide types and underlying full views. The first subtype
3562         is used as the working type for all Itypes, not just array
3563         base types.
3564         * freeze.adb (Freeze_Entity): Inherit the freeze node of a full
3565         view or an underlying full view without clobbering the attributes
3566         of a previous freeze node.
3567         (Inherit_Freeze_Node): New routine.
3568         * sem_ch3.adb (Build_Derived_Private_Type): Mark an underlying
3569         full view as such.
3570         (Build_Underlying_Full_View): Mark an underlying full view as such.
3571         * sem_ch7.adb (Install_Private_Declarations): Mark an underlying
3572         full view as such.
3574 2017-01-20  Yannick Moy  <moy@adacore.com>
3576         * sinfo.ads: Document lack of Do_Division_Check flag
3577         on float exponentiation.
3579 2017-01-19  Javier Miranda  <miranda@adacore.com>
3581         * ghost.adb (Propagate_Ignored_Ghost_Code): Protect access to the
3582         identifier attribute of a block-statement node. Required to avoid
3583         assertion failure when building the new containers library.
3585 2017-01-19  Bob Duff  <duff@adacore.com>
3587         * exp_ch3.adb: Update comment.
3589 2017-01-19  Vincent Celier  <celier@adacore.com>
3591         * gprep.adb (Gnatprep): Parse the definition file without
3592         "replace in comments" even when switch -C is used.
3594 2017-01-19  Justin Squirek  <squirek@adacore.com>
3596         * exp_ch9.adb (Is_Pure_Barrier): Create function
3597         Is_Count_Attribute to identify an expansion of the 'Count
3598         attribute.
3600 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
3602         * sem_ch5.adb (Analyze_Loop_Statement): In GNATprove mode the
3603         statements within an element iterator loop are only analyzed
3604         agter the loop is rewritten. Within a generic the analysis must
3605         be performed in any case to complete name capture.
3607 2017-01-19  Bob Duff  <duff@adacore.com>
3609         * sem_prag.adb (Analyze_Pragma): Check for ignored pragmas first,
3610         before checking for unrecognized pragmas.
3611         Initialize Pname on its declarations; that's always good style.
3613 2017-01-19  Claire Dross  <dross@adacore.com>
3615         * exp_ch7.adb (Build_Invariant_Procedure_Body): Semi-insert the
3616         body into the tree for GNATprove by setting its Parent field. The
3617         components invariants of composite types are not checked by
3618         the composite type's invariant procedure in GNATprove mode.
3619         (Build_Invariant_Procedure_Declaration): Semi-insert the
3620         declaration into the tree for GNATprove by setting its Parent
3621         field.
3622         * freeze.adb (Freeze_Arry_Type):In GNATprove mode, do not add
3623         the component invariants to the array type  invariant procedure
3624         so that the procedure can be used to  check the array type
3625         invariants if any.
3626         (Freeze_Record_Type): In GNATprove mode, do
3627         not add the component invariants to the record type  invariant
3628         procedure so that the procedure can be used to  check the record
3629         type invariants if any.
3631 2017-01-19  Hristian Kirtchev  <kirtchev@adacore.com>
3633         * lib-xref-spark_specific.adb: Minor reformatting.
3634         * exp_ch7.adb (Add_Parent_Invariants): Do not process array types.
3636 2017-01-19  Javier Miranda  <miranda@adacore.com>
3638         * exp_aggr.adb (Pass_Aggregate_To_Back_End): Renamed as
3639         Build_Back_End_Aggregate.
3640         (Generate_Aggregate_For_Derived_Type): Code cleanup.
3641         (Prepend_Stored_Values): Code cleanup.
3643 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
3645         * sem_ch6.adb (Analyze_Expression_Function): Check for an
3646         incomplete return type after attempting to freeze it, so that
3647         other freeze actiona are generated in the proper order.
3649 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
3651         * sem_aggr.adb (Resolve_Aggregate): If the type is a string
3652         type, ie. a type whose component is a character type, and the
3653         aggregate is positional, do not convert into a string literal
3654         if the index type is not an integer type, because the original
3655         type may be required in an enclosing operation.
3657 2017-01-19  Bob Duff  <duff@adacore.com>
3659         * binde.adb, debug.adb: Enable new elaboration order algorithm
3660         by default. -dp switch reverts to the old algorithm.
3662 2017-01-19  Hristian Kirtchev  <kirtchev@adacore.com>
3664         * sem_ch3.adb Add with and use clauses for Exp_Ch7.
3665         (Analyze_Declarations): Create the DIC and Invariant
3666         procedure bodies s after all freezing has taken place.
3667         (Build_Assertion_Bodies): New routine.
3668         * sem_ch7.adb Remove the with and use clauses for Exp_Ch7
3669         and Exp_Util.
3670         (Analyze_Package_Specification): Remove the
3671         generation of the DIC and Invariant procedure bodies. This is
3672         now done by Analyze_Declarations.
3673         * sem_disp.adb (Check_Dispatching_Operation): DIC and Invariant
3674         procedures are never treated as primitives.
3676 2017-01-19  Yannick Moy  <moy@adacore.com>
3678         * frontend.adb: Analyze inlined bodies and check elaboration
3679         rules in GNATprove mode too.
3680         * sem_elab.adb (Delay_Element): Add Boolean component to save
3681         indication that call is in SPARK code.  (Check_Elab_Calls):
3682         Check elaboration rules in GNATprove mode, and correctly set
3683         the current value of SPARK_Mode.
3684         * lib-xref-spark_specific.adb
3685         (Add_SPARK_Xrefs): Simplify iteration over dereferences.
3687 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
3689         * exp_ch4.adb (Expand_Concatenate): Do no enable overflow
3690         checks on the expression for the high bound of concatenation
3691         when checks are disabled, to suppress warnings about potential
3692         constraint errors in restricted runtimes.
3694 2017-01-19  Hristian Kirtchev  <kirtchev@adacore.com>
3696         * exp_ch3.adb (Expand_Freeze_Enumeration_Type): Mark the
3697         representation-to-position function as inlined.
3698         * sem_cat.adb (Set_Categorization_From_Scope): Do not modify
3699         the purity of an internally generated entity if it has been
3700         explicitly marked as pure for optimization purposes.
3701         * exp_aggr.adb: Minor reformatting.
3703 2017-01-19  Javier Miranda  <miranda@adacore.com>
3705         * exp_ch6.adb (Expand_Call): Remove side effects on
3706         actuals that are allocators with qualified expression since the
3707         initialization of the object is performed by means of individual
3708         statements (and hence it must be done before the call).
3710 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
3712         * sem_ch3.adb (Analyze_Declarations): Minor reformatting.
3713         (Build_Derived_Enumeration_Type): If the derived type inherits a
3714         dynamic predicate from its parent, the bounds of the type must
3715         freeze because an explicit constraint is constructed for the
3716         type and the corresponding range is elaborated now.
3718 2017-01-19  Arnaud Charlet  <charlet@adacore.com>
3720         * sem_attr.ads: minor fix of inconsistent casing in comment
3721         * lib-writ.ads: minor align comments in columns
3722         * sem_ch3.adb: Minor reformatting.
3723         * spark_xrefs.ads: minor fix typo in SPARK-related comment
3724         * table.ads: minor style fix in comment
3725         * lib-xref-spark_specific.adb
3726         (Add_SPARK_Xrefs): simplify processing of SPARK cross-references.
3727         * sem_ch12.adb: minor whitespace fix
3728         * freeze.adb: Add comment.
3729         * sem_util.adb (Unique_Name): for instances of
3730         generic subprograms ignore the name of the wrapper package.
3732 2017-01-19  Javier Miranda  <miranda@adacore.com>
3734         * exp_aggr.adb (Resolve_Record_Aggregate):
3735         Factorize code needed for aggregates of limited and unlimited
3736         types in a new routine.
3737         (Pass_Aggregate_To_Back_End): New subprogram.
3739 2017-01-19  Yannick Moy  <moy@adacore.com>
3741         * sinfo.adb (Pragma_Name): Only access up to Last_Pair of Pragma_Map.
3743 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
3745         * sem_ch4.ads, sem_ch4.adb (Try_Object_Operation): Make subprogram
3746         public, for use elsewhere.
3747         * sem_ch6.adb (Analyze_Procedure_Call): In SPARK_Mode and within
3748         an Inlined_body, recognize a call that uses object notation
3749         and has not been rewritten as a regular call because regular
3750         expansion has not taken place.
3752 2017-01-19  Bob Duff  <duff@adacore.com>
3754         * checks.adb (Apply_Type_Conversion_Checks): Disable small optimization
3755         in case of generic formal discrete types, because it causes crashes in
3756         the compiler when built with assertions on.
3758 2017-01-19  Hristian Kirtchev  <kirtchev@adacore.com>
3760         * lib-xref-spark_specific.adb, sem_util.adb, sem_util.ads,
3761         sem_ch4.adb, sem_ch8.adb, lib-xref.ads: Minor reformatting.
3763 2017-01-19  Bob Duff  <duff@adacore.com>
3765         * bcheck.adb (Check_Consistent_Dynamic_Elaboration_Checking):
3766         Increment Warnings_Detected.  It was decrementing, which is
3767         wrong since we just issued a warning message.
3768         * binderr.ads (Errors_Detected, Warnings_Detected): Declare
3769         these variables to be of subtype Nat instead of Int, because
3770         they should never be negative.
3772 2017-01-19  Javier Miranda  <miranda@adacore.com>
3774         * contracts.adb (Build_Postconditions_Procedure): Replace
3775         Generate_C_Code by Modify_Tree_For_C.
3776         * exp_aggr.adb (Build_Record_Aggr_Code, Expand_Array_Aggregate):
3777         Replace Generate_C_Code by Modify_Tree_For_C.
3778         * exp_attr.adb (Float_Valid, Is_GCC_Target): Replace Generate_C_Code by
3779         Modify_Tree_For_C.
3780         * exp_ch11.adb (Expand_N_Exception_Declaration): Replace
3781         Generate_C_Code by Modify_Tree_For_C.
3782         * exp_ch4.adb (Expand_Allocator_Expression): Replace
3783         Generate_C_Code by Modify_Tree_For_C.
3784         * exp_dbug.adb (Qualify_Entity_Name): Replace Generate_C_Code
3785         by Modify_Tree_For_C.
3786         * exp_util.adb (Remove_Side_Effects, Side_Effect_Free): Replace
3787         Generate_C_Code by Modify_Tree_For_C.
3788         * sem_res.adb (Resolve_Type_Conversion): Replace Generate_C_Code
3789         by Modify_Tree_For_C.
3790         * sinfo.ads (Modify_Tree_For_C): Adding documentation.
3792 2017-01-19  Javier Miranda  <miranda@adacore.com>
3794         * sem_util.ads, sem_util.adb (Expression_Of_Expression_Function): New
3795         subprogram.
3796         (Is_Inlinable_Expression_Function): New subprogram.
3797         * exp_ch6.ads, exp_ch6.adb (Expression_Of_Expression_Function): Moved
3798         to Sem_Util.
3799         (Is_Inlinable_Expression_Function): Moved to Sem_Util.
3801 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
3803         * sem_ch4.adb (Diagnose_Call): Improve error message when a
3804         selected component has a prefix that might be interpreted
3805         as a parameterless function call, but none of the candidate
3806         interpretations is parameterless, and there is a hidden homonym
3807         of the prefix that is a package.
3808         * sem_ch8.adb (Find_Selected_Component): If the prefix might be
3809         interpreted as a parameterless function call and its analysis
3810         fails, do not call Analyze_Selected_Component.
3812 2017-01-19  Steve Baird  <baird@adacore.com>
3814         * sem_util.ads: Add new Use_Full_View Boolean parameter to
3815         Get_Index_Bounds.
3816         * sem_util.adb (Get_Index_Bounds): replace calls to Scalar_Range with
3817         calls to a newly-defined Scalar_Range_Of_Right_View function.
3819 2017-01-19  Arnaud Charlet  <charlet@adacore.com>
3821         * gnat1drv.adb: minor fix of unbalanced parens in comment
3822         * lib-xref.ads (Traverse_Compilation_Unit): declaration moved
3823         to visible part of the package to allow re-use in GNATprove.
3824         * lib-xref-spark_specific.adb (Traverse_Stub): routine refactored
3825         from repeated code of Traverse_Compilation_Unit.
3826         (Traverse_Declaration_Or_Statement): fixed detection of
3827         generic subprograms and packages; also, iteration over case
3828         statement alternatives rewritten to avoid testing if the first
3829         alternative is present (since it must be present due to Ada
3830         syntax restrictions).
3832 2017-01-19  Hristian Kirtchev  <kirtchev@adacore.com>
3834         * exp_ch6.adb (Expand_N_Subprogram_Body): Mark the spec as
3835         returning by reference not just for subprogram body stubs,
3836         but for all subprogram cases.
3837         * sem_util.adb: Code reformatting.
3838         (Requires_Transient_Scope): Update the call to Results_Differ.
3839         (Results_Differ): Update the parameter profile and the associated
3840         comment on usage.
3842 2017-01-19  Ed Schonberg  <schonberg@adacore.com>
3844         * sem_dim.adb (Analyze_Dimension): Analyze object declaration and
3845         identifier nodes that do not come from source, to handle properly
3846         dimensionality check within an inlined body which inclddes both
3847         original operands and rewritten operands. This removes spurious
3848         dimensionality errors in the presence of front-end inlining,
3849         as well as in SPARK mode.
3851 2017-01-16  Jakub Jelinek  <jakub@redhat.com>
3853         PR driver/49726
3854         * gcc-interface/lang.opt (gant, gnatO, gnat): Add Driver flag.
3856 2017-01-13  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
3858         * gcc-interface/Makefile.in (SPARC/Solaris): Fix typo.
3860 2017-01-13  Arnaud Charlet  <charlet@adacore.com>
3862         * doc/gnat_ugn/getting_started_with_gnat.rst,
3863         doc/gnat_ugn/inline_assembler.rst,
3864         doc/gnat_ugn/building_executable_programs_with_gnat.rst,
3865         doc/gnat_ugn/elaboration_order_handling_in_gnat.rst,
3866         doc/gnat_ugn/about_this_guide.rst,
3867         doc/gnat_ugn/platform_specific_information.rst,
3868         doc/gnat_ugn/example_of_binder_output.rst,
3869         doc/gnat_ugn/gnat_and_program_execution.rst,
3870         doc/gnat_ugn/gnat_utility_programs.rst,
3871         doc/gnat_ugn/the_gnat_compilation_model.rst,
3872         doc/gnat_rm/implementation_defined_attributes.rst,
3873         doc/gnat_rm/compatibility_and_porting_guide.rst,
3874         doc/gnat_rm/standard_library_routines.rst,
3875         doc/gnat_rm/standard_and_implementation_defined_restrictions.rst,
3876         doc/gnat_rm/implementation_defined_pragmas.rst,
3877         doc/gnat_rm/the_gnat_library.rst,
3878         doc/gnat_rm/obsolescent_features.rst,
3879         doc/gnat_rm/about_this_guide.rst,
3880         doc/gnat_rm/the_implementation_of_standard_i_o.rst,
3881         doc/gnat_rm/implementation_of_ada_2012_features.rst,
3882         doc/gnat_rm/interfacing_to_other_languages.rst,
3883         doc/gnat_rm/implementation_defined_aspects.rst,
3884         doc/gnat_rm.rst: Update documentation.
3885         * gnat_rm.texi, gnat_ugn.texi: Regenerated.
3887 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
3889         * einfo.ads: minor grammar fixes in comment of Normalized_Position_Max.
3890         * scil_ll.adb: Minor style fix in comment.
3891         * sem_ch8.adb (Analyze_Expanded_Name): Perform dimension analysis
3892         even if entity is already set, because the node may be renalyzed
3893         after inlining transformations.
3895 2017-01-13  Javier Miranda  <miranda@adacore.com>
3897         * sem_res.adb (Resolve_Call): Do not establish a transient scope
3898         for a call to inlinable expression function (since the call will
3899         be replaced by its returned object).
3900         * exp_ch6.ads (Is_Inlinable_Expression_Function): New subprogram.
3901         * exp_ch6.adb (Expression_Of_Expression_Function): New subprogram.
3902         (Expand_Call): For inlinable expression function call replace the
3903         call by its returned object.
3904         (Is_Inlinable_Expression_Function): New subprogram.
3906 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
3908         * checks.adb: Minor typo fix and reformatting.
3910 2017-01-13  Javier Miranda  <miranda@adacore.com>
3912         * contracts.adb (Contract_Only_Subprograms): Remove formal.
3913         (Copy_Original_Specification): Removed.
3914         (Skip_Contract_Only_Subprogram): Move here checks previously
3915         located in the caller of this routine (to leave the code more clean).
3916         (Build_Contract_Only_Subprogram): Code cleanup.
3917         * scil_ll.ads, scil_ll.adb (Get_Contract_Only_Body_Name): Removed.
3918         (Get_Contract_Only_Missing_Body_Name): Removed.
3920 2017-01-13  Javier Miranda  <miranda@adacore.com>
3922         * sem_ch6.adb (Cloned_Expression): New subprogram.
3923         (Freeze_Expr_Types): Complete previous patch since the expression
3924         of an expression-function may have iterators and loops with
3925         defining identifiers which, as part of the preanalysis of the
3926         expression, may be left decorated with itypes that will not be
3927         available in the tree passed to the backend.
3929 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
3931         * checks.adb (Apply_Type_Conversion_Checks): Optimize a type
3932         conversion to Integer of an expression that is an attribute
3933         reference 'Pos on an enumeration type.
3935 2017-01-13  Bob Duff  <duff@adacore.com>
3937         * atree.ads: Minor comment fix.
3939 2017-01-13  Justin Squirek  <squirek@adacore.com>
3941         * sem_ch6.adb (Check_Aggregate_Accessibility): Ignore function
3942         calls in accessibility check on return statement.
3944 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
3946         * sem_ch6.adb (Analyze_Subprogram_Body_Helper):
3947         Ensure that the input body is a subprogram body before trying to
3948         determine whether it denoted an expression function.  Note that
3949         subprogram body stubs cannot denote expression functions.
3951 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
3953         * bindgen.adb, sem_ch6.adb, binde.adb, exp_ch3.adb: Minor reformatting
3954         and typo fixes.
3956 2017-01-13  Javier Miranda  <miranda@adacore.com>
3958         * einfo.ads (Component_Bit_Offset): Fix documentation.
3959         * sem_ch13.adb (Check_Record_Representation_Clause): Skip check
3960         on record holes for components with unknown compile-time offsets.
3962 2017-01-13  Bob Duff  <duff@adacore.com>
3964         * ali.ads, ali.adb (Static_Elaboration_Model_Used): Remove unused flag.
3965         * g-locfil.ads: Minor comment fix.
3967 2017-01-13  Bob Duff  <duff@adacore.com>
3969         * binde.adb (Elab_New): New elaboration order algorithm
3970         that is expected to cause fewer ABE issues. This is a work in
3971         progress. The new algorithm is currently disabled, and can be
3972         enable by the -dp switch, or by modifying the Do_Old and Do_New
3973         etc. flags and rebuilding. Experimental code is included to
3974         compare the results of the old and new algorithms.
3975         * binde.ads: Use GNAT.Dynamic_Tables instead of Table, so we
3976         can have multiple of these tables, so the old and new algorithms
3977         can coexist.
3978         * bindgen.ads (Gen_Output_File): Pass Elab_Order as an 'in'
3979         parameter of type array. This avoids the global variable, and
3980         allows bounds checking (which is normally defeated by the tables
3981         packages). It also ensures that the Elab_Order is read-only
3982         to Bindgen.
3983         * bindgen.adb: Pass Elab_Order as an 'in' parameter to all
3984         subprograms that need it, as above.
3985         * debug.adb: Document new -dp switch. Modify doc of old -do
3986         switch.
3987         * gnatbind.adb (Gnatbind): Make use of new interfaces to Binde
3988         and Bindgen.  Move writing of closure (-R and -Ra switches)
3989         to Binde; that's more convenient.
3991 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
3993         * sem_ch6.adb (Analyze_Expression_Function): If the expression
3994         function is a completion, all entities referenced in the
3995         expression are frozen. As a consequence, a reference to an
3996         uncompleted private type from an enclosing scope is illegal.
3998 2017-01-13  Javier Miranda  <miranda@adacore.com>
4000         * sem_ch6.adb (Freeze_Expr_Types): New subprogram.
4001         (Analyze_Subprogram_Body_Helper): At the occurrence of an
4002         expression function declaration that is a completion, its
4003         expression causes freezing (AI12-0103).
4005 2017-01-13  Vadim Godunko  <godunko@adacore.com>
4007         * a-coinho-shared.adb: Fix memory leaks in Constant_Reference and
4008         Reference functions of Ada.Containers.Indefinite_Holders.
4010 2017-01-13  Bob Duff  <duff@adacore.com>
4012         * s-os_lib.ads: Minor comment fixes.
4014 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
4016         * exp_ch3.adb (Default_Initialize_Object): Do not default
4017         initialize an object when it is of a task type and restriction
4018         No_Tasking is in effect because the initialization is obsolete.
4019         * exp_ch9.adb (Build_Master_Entity): Do not generate a master when
4020         restriction No_Tasking is in effect.
4021         (Build_Master_Renaming): Do not rename a master when restriction
4022         No_Tasking is in effect.
4024 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
4026         * sem_aggr.adb (Resolve_Array_Aggregate): The code that verifies
4027         the legality of An others clause applies as well to a choice in
4028         an Iterated_component_ association.
4029         (Resolve_Iterated_Component_Association): An others choice
4030         is legal.
4031         * exp_aggr.adb (Aggr_Assignment_OK_For_Backend): An
4032         Iterated_Component_Association is not static.
4034 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
4036         * exp_ch3.adb (Freeze_Type): Mark the Ghost mode as set in case
4037         control is passed to the expresion handler before the new mode
4038         is set.
4039         * sem_ch12.adb (Analyze_Package_Instantiation,
4040         Analyze_Subprogram_Instantiation): Mark the Ghost mode as set
4041         in case control is passed to the expresion handler before the
4042         new mode is set.
4044 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
4046         * sem_aggr.adb, sem_ch3.adb, inline.adb, sem_util.adb, exp_ch4.adb,
4047         exp_aggr.adb: Minor reformatting.
4049 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
4051         * inline.adb: Minor reformatting and typo fix.
4053 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
4055         * sem_util.ads, sem_util.adb (Choice_List): Move function here
4056         from sem_aggr.adb, for use elsewhere.
4057         * sem_ch3.adb (Analyze_Object_Declaration): Use Choice_List.
4058         * sem_aggr.adb (Resolve_Array_Aggregate): Remove
4059         Iterated_Component_Present.
4060         * exp_aggr.adb: Use Choice_List throughout, to handle
4061         Iterated_Component_Associations.
4062         (Gen_Loop): Generate proper loop for an
4063         Iterated_Component_Association: loop variable has the identifier
4064         of the original association. Generate a loop even for a single
4065         component choice, in order to make loop parameter visible in
4066         expression.
4067         (Flatten): An Iterated_Component_Association is not static.
4069 2017-01-13  Yannick Moy  <moy@adacore.com>
4071         * exp_ch4.adb (Expand_N_Op_Expon): Ensure that the value of
4072         float exponentiation for statically known small negative values
4073         is the reciprocal of the exponentiation for the opposite value
4074         of the exponent.
4075         * s-exnllf.adb (Exn_Float, Exn_Long_Float, Exn_Long_Long_Float):
4076         Ensure that the value of float exponentiation for negative values
4077         is the reciprocal of the exponentiation for the opposite value
4078         of the exponent.
4079         * inline.adb (Expand_Inlined_Call): Fix the count
4080         for the number of generated gotos.
4082 2017-01-13  Yannick Moy  <moy@adacore.com>
4084         * inline.adb: Code cleanup.
4085         * sem_util.adb (Is_OK_Volatile_Context): Add
4086         expression in delay statement as OK for volatile context.
4088 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
4090         * sem_aggr.adb (Resolve_Array_Aggregate): In normal compilation
4091         mode a choice that is a subtype with a static predicate is
4092         replaced by the values it covers. This transformation must not
4093         be performed in ASIS mode, to preserve the source for analysis.
4095 2017-01-13  Justin Squirek  <squirek@adacore.com>
4097         * nlists.ads: Correct minor typo.
4099 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
4101         * sem_ch13.adb: Minor reformatting and typo fix.
4103 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
4105         * par-ch4.adb (P_Aggregate_Or_Parent_Expr): An
4106         Iterated_Component_Association is a named association in an
4107         array aggregate.
4108         * sem_aggr.adb (Resolve_Iterated_Component_Association): New
4109         procedure, subsidiary of Resolve_Array_Aggregate, to analyze
4110         and resolve the discrete choices and the expression of the
4111         new construct.
4112         * sinfo.adb, sinfo.ads: In analogy with N_Component_Association,
4113         Loop_Actions and Box_Present are attributes of
4114         N_Iterated_Component_Association nodes. Box_Present is always
4115         False in this case.
4116         * sprint.adb (Sprint_Node): An Iterated_Component_Association
4117         has a Discrete_Choices list, as specified in the RM. A
4118         Component_Association for aggregate uses instead a Choices list.
4119         We have to live with this small inconsistency because the new
4120         construct also has a defining identifier, and there is no way
4121         to merge the two node structures.
4123 2017-01-13  Yannick Moy  <moy@adacore.com>
4125         * inline.adb (Remove_Aspects_And_Pragmas): Add Unused to the
4126         list of pragmas to remove.  Remove pragmas from the list of
4127         statements in the body to inline.
4128         * namet.adb, namet.ads (Nam_In): New version with 12 parameters.
4130 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
4132         * sem_ch3.adb (Resolve_Aspects): New procedure, subsidiary of
4133         Analyze_Declarations, to analyze and resolve the expressions of
4134         aspect specifications in the current declarative list, so that
4135         the expressions have proper entity and type info.  This is needed
4136         for ASIS when there is no subsequent expansion to generate this
4137         semantic information.
4138         * sem_ch13.adb (Check_Aspect_At_End_Of_Declarations): Use Etype of
4139         original expression, to suppress cascaded errors when expression
4140         has been constant-folded.
4141         (Resolve_Aspect_Expressions, Resolve_Name): Preserve entities in
4142         ASIS mode, because there is no subsequent expansion to decorate
4143         the tree.
4145 2017-01-13  Yannick Moy  <moy@adacore.com>
4147         * inline.adb, inline.ads (Call_Can_Be_Inlined_In_GNATprove_Mode):
4148         New function to detect when a call may be inlined or not in
4149         GNATprove mode.
4150         (Expand_Inlined_Call): Ensure that a temporary
4151         is always created in the cases where a type conversion may be
4152         needed on an input parameter in GNATprove mode, so that GNATprove
4153         sees the check to perform.
4154         * sem_res.adb (Resolve_Call): In GNATprove mode, skip inlining
4155         when not applicable due to actual requiring type conversion
4156         with possible check but no temporary value can be copied for
4157         GNATprove to see the check.
4159 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
4161         * sem_aggr.adb, par_sco.adb, s-osprim-mingw.adb, exp_ch5.adb,
4162         exp_prag.adb, sem_ch3.adb, xr_tabls.adb, lib-xref-spark_specific.adb,
4163         layout.adb, sem_dist.adb, exp_spark.adb, exp_ch7.adb, gnatcmd.adb,
4164         exp_util.adb, prj-proc.adb, sem_aux.adb, comperr.adb, g-memdum.adb,
4165         exp_attr.adb, s-intman-solaris.adb, exp_ch9.adb, make.adb, live.adb,
4166         g-sercom-linux.adb, sem_dim.adb, mlib-prj.adb, s-intman-posix.adb,
4167         sem_ch9.adb, sem_ch10.adb, prep.adb, einfo.adb, scng.adb, checks.adb,
4168         prj-strt.adb, sem_prag.adb, eval_fat.adb, sem_ch12.adb, sem.adb,
4169         a-numaux-x86.adb, a-stwifi.adb, i-cobol.adb, prj.adb,
4170         get_spark_xrefs.adb, s-tasini.adb, rtsfind.adb, freeze.adb,
4171         g-arrspl.adb, par-ch4.adb, sem_util.adb, sem_res.adb, expander.adb,
4172         sem_attr.adb, exp_dbug.adb, prj-pp.adb, a-stzfix.adb, s-interr.adb,
4173         s-wchcnv.adb, switch-m.adb, gnat1drv.adb, sinput-l.adb, stylesw.adb,
4174         contracts.adb, s-intman-android.adb, g-expect.adb, exp_ch4.adb,
4175         g-comlin.adb, errout.adb, sinput.adb, s-exctra.adb, repinfo.adb,
4176         g-spipat.adb, g-debpoo.adb, exp_ch6.adb, sem_ch4.adb, exp_ch13.adb,
4177         a-wtedit.adb, validsw.adb, pprint.adb, widechar.adb, makeutl.adb,
4178         ali.adb, set_targ.adb, sem_mech.adb, sem_ch6.adb, gnatdll.adb,
4179         get_scos.adb, g-pehage.adb, s-tratas-default.adb, gnatbind.adb,
4180         prj-dect.adb, g-socthi-mingw.adb, par-prag.adb, prj-nmsc.adb,
4181         exp_disp.adb, par-ch12.adb, binde.adb, sem_ch8.adb,
4182         s-tfsetr-default.adb, s-regexp.adb, gprep.adb, s-tpobop.adb,
4183         a-teioed.adb, sem_warn.adb, sem_eval.adb, g-awk.adb, s-io.adb,
4184         a-ztedit.adb, xoscons.adb, exp_intr.adb, sem_cat.adb, sprint.adb,
4185         g-socket.adb, exp_dist.adb, sem_ch13.adb, s-tfsetr-vxworks.adb,
4186         par-ch3.adb, treepr.adb, g-forstr.adb, g-catiio.adb, par-ch5.adb,
4187         uname.adb, osint.adb, exp_ch3.adb, prj-env.adb, a-strfix.adb,
4188         a-stzsup.adb, prj-tree.adb, s-fileio.adb: Update all eligible case
4189         statements to reflect the new style for case alternatives. Various
4190         code clean up and reformatting.
4192 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
4194         * exp_util.adb: Minor reformatting.
4196 2017-01-13  Yannick Moy  <moy@adacore.com>
4198         * exp_spark.adb: Code cleanup.
4199         * sem_ch9.adb (Analyze_Delay_Until): Resolve
4200         expression so that calls are identified as such inside delay
4201         until.
4203 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
4205         * exp_util.adb (Insert_Actions): Handle Iterated_Component_Association.
4206         * par-ch3.adb (P_Discrete_Choice_List): An
4207         Iterated_Component_Association is an array aggregate component.
4208         * par-ch4.adb (P_Iterated_Component_Association): New procedure.
4209         (Is_Quantified_Expression): New function that performs a lookahead
4210         to distinguish quantified expressions from iterated component
4211         associations.
4212         (P_Aggregate_Or_Paren_Expr): Recognize iterated component
4213         associations.
4214         (P_Unparen_Cond_Case_Quant_Expression, P_Primary): Ditto.
4215         * sem.adb (Analyze): Handle Iterated_Component_Association.
4216         * sem_aggr.adb (Resolve_Array_Aggregate): Dummy handling of iterated
4217         component associations.
4218         * sinfo.ads, sinfo.adb: Entries for for
4219         N_Iterated_Component_Association and its fields.
4220         * sprint.adb (Sprint_Node_Actual): Handle
4221         N_Iterated_Component_Association.
4223 2017-01-13  Justin Squirek  <squirek@adacore.com>
4225         * sem_ch12.adb (Analyze_Package_Instantiation): Move disabiling
4226         of the style check until after preanalysis of acutals.
4228 2017-01-13  Yannick Moy  <moy@adacore.com>
4230         * sem_ch13.adb: Minor reformatting.
4231         * par-ch11.adb: minor style fix in whitespace
4232         * gnatbind.adb (Gnatbind): Scope of Std_Lib_File
4233         reduced to Add_Artificial_ALI_File; style fix in declaration of
4234         Text; grammar fix in comment.
4235         * osint-c.adb (Read_Library_Info): strip trailing NUL from result.
4236         * freeze.adb: Cleanup to pass pragma instead of
4237         expression to call.
4238         * exp_spark.adb (Expand_SPARK_Attribute_Reference): New procedure to
4239         replace System'To_Address by equivalent call.
4241 2017-01-13  Arnaud Charlet  <charlet@adacore.com>
4243         * bindusg.adb: Improve usage output for -f switch.
4245 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
4247         * frontend.adb, freeze.adb, sem_res.adb, sem_attr.adb, sem_ch8.adb:
4248         Minor reformatting.
4250 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
4252         * sem_ch13.adb (Is_Predicate_Static): Following the intent of the RM,
4253         treat comparisons on strings as legal in a Static_Predicate.
4254         (Is_Predicate_Static, Is_Type_Ref): Predicate also returns true on
4255         a function call that is the expansion of a string comparison.The
4256         function call is built when compiling the corresponding predicate
4257         function, but the expression has been found legal as a static
4258         predicate during earlier analysis.
4259         * sem_eval.adb (Real_Or_String_Static_Predicate_Matches): Handle
4260         properly a function call that is the expansion of a string
4261         comparison operation, in order to recover the Static_Predicate
4262         expression and apply it to a static argument when needed.
4264 2017-01-13  Tristan Gingold  <gingold@adacore.com>
4266         * s-mmap.adb, s-mmap.ads (Open_Read_No_Exception): New function.
4267         (Open_Read): Re-implement using Open_Read_No_Exception.
4268         (Open_Write): Raise exception in case of error.
4269         * s-mmosin-mingw.adb (Open_Common): Do not raise exception.
4270         * s-mmosin-unix.adb (Open_Read, Open_Write): Do not
4271         reaise exception.
4272         * s-mmosin-mingw.ads, s-mmosin-unix.ads (Open_Read): Adjust comment.
4274 2017-01-13  Yannick Moy  <moy@adacore.com>
4276         * checks.adb: Code cleanup.
4278 2017-01-13  Yannick Moy  <moy@adacore.com>
4280         * freeze.adb (Check_Inherited_Conditions): Use analyzed pragma
4281         expression instead of unanalyzed aspect expression for checking
4282         the validity of inheriting an operation. Also copy the expression
4283         being passing it to Build_Class_Wide_Expression, as this call
4284         modifies its argument.
4285         * sem_util.ads Fix comment to reference correct function name
4286         New_Copy_Tree.
4288 2017-01-13  Javier Miranda  <miranda@adacore.com>
4290         * sem_res.adb (Resolve_Generalized_Indexing): Compiling in ASIS mode,
4291         when we propagate information about the indexes back to the original
4292         indexing mode and the prefix of the index is a function call, do not
4293         remove any parameter from such call.
4295 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
4297         * exp_ch6.ads (Needs_BIP_Finalization_Master): Update comment.
4298         * exp_ch6.adb (Needs_BIP_Finalization_Master): Return True for
4299         a build-in-place function whose result type is tagged.
4301 2017-01-13  Yannick Moy  <moy@adacore.com>
4303         * sem_ch8.adb (Analyze_Subprogram_Renaming.Build_Class_Wide_Wrapper):
4304         Do not generate a wrapper when the only candidate is a class-wide
4305         subprogram.
4306         (Analyze_Subprogram_Renaming): Do not freeze the renaming or renamed
4307         inside a generic context.
4309 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
4311         * exp_util.adb (Add_Inherited_Tagged_DIC):
4312         Pass the object parameters of both the parent and the derived
4313         type DIC procedure to the reference replacement circuitry.
4314         (Find_DIC_Type): Modify the circuitry to present the partial
4315         view of a private type in case the private type defines its own
4316         DIC pragma.
4317         (Replace_Object_And_Primitive_References): Add two
4318         optional formal parameters.  Update the comment on usage. Update
4319         the replacement of references to object parameters.
4321 2017-01-13  Gary Dismukes  <dismukes@adacore.com>
4323         * einfo.adb, sem_ch6.adb, atree.adb: Minor reformatting and typo fix.
4325 2017-01-13  Ed Schonberg  <schonberg@adacore.com>
4327         * sem_res.adb (Resolve_Actuals): Apply Scalar_Range_Check to
4328         an out parameter that is a type conversion, independently of th
4329         range check that may apply to the expression of the conversion,
4330         for use in GNATProve.
4332 2017-01-13  Yannick Moy  <moy@adacore.com>
4334         * gnat1drv.adb (Gnat1drv): Move the implicit with for System in
4335         GNATprove_Mode here to Frontend.
4336         * frontend.adb (Frontend): Move the implicit with for System
4337         in GNATprove_Mode here as it ismore correct this way; the old
4338         place only worked by chance, since there were no overloaded names.
4339         * rtsfind.ads (RE_Id, RE_Unit_Table): Add RE_Tasking_State.
4340         * sem_attr.adb (Analyze_Attribute): In GNATprove_Mode, for the
4341         four attributes identified in SRM 9(18), add an implicit with
4342         to Ada.Task_Identification.
4343         * sem_ch8.adb (Analyze_Subprogram_Renaming.Build_Class_Wide_Wrapper):
4344         Deal specially with the wrapper introduced for AI05-0071 in GNATprove
4345         mode.
4346         * checks.adb (Apply_Discriminant_Check,
4347         Apply_Selected_Length_Checks, Apply_Selected_Range_Checks):
4348         In GNATprove mode, we do not apply the checks, but we still
4349         analyze the expression to possibly issue errors on SPARK
4350         code when a run-time error can be detected at compile time.
4351         (Selected_Length_Checks, Selected_Range_Checks): Perform analysis
4352         in GNATprove mode.
4354 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
4356         * expander.adb (Expand): Add a warning about using return
4357         statements in Ghost management code.
4358         * exp_ch3.adb (Freeze_Type): Add a warning about using return
4359         statements in Ghost management code.
4360         * exp_ch7.adb (Build_Invariant_Procedure_Body,
4361         Build_Invariant_Procedure_Declaration): Add a warning about
4362         using return statements in Ghost management code.
4363         * exp_disp.adb (Make_DT): Add a warning about using return
4364         statements in Ghost management code.
4365         * exp_util.adb (Build_DIC_Procedure_Body,
4366         Build_DIC_Procedure_Declaration, Make_Predicated_Call): Add a
4367         warning about using return statements in Ghost management code.
4368         * freeze.adb (Freeze_Entity): Add a warning about using return
4369         statements in Ghost management code.
4370         * sem.adb (Analyze, Do_Analyze): Add a warning about using return
4371         statements in Ghost management code.
4372         * sem_ch3.adb (Analyze_Object_Declaration, Process_Full_View): Add
4373         a warning about using return statements in Ghost management code.
4374         * sem_ch5.adb (Analyze_Assignment): Add a warning about using
4375         return statements in Ghost management code.
4376         * sem_ch6.adb (Analyze_Procedure_Call,
4377         Analyze_Subprogram_Body_Helper): Add a warning about using return
4378         statements in Ghost management code.
4379         * sem_ch7.adb (Analyze_Package_Body_Helper): Add a warning about
4380         using return statements in Ghost management code.
4381         * sem_ch12.adb (Analyze_Package_Instantiation,
4382         Analyze_Subprogram_Instantiation, Instantiate_Package_Body,
4383         Instantiate_Subprogram_Body): Add a warning about using return
4384         statements in Ghost management code.
4385         * sem_ch13.adb (Build_Predicate_Functions,
4386         Build_Predicate_Function_Declarations): Add a warning about
4387         using return statements in Ghost management code.
4388         * sem_prag.adb (Analyze_Contract_Cases_In_Decl_Part,
4389         Analyze_Initial_Condition_In_Decl_Part, Analyze_Pragma,
4390         Analyze_Pre_Post_Condition_In_Decl_Part):  Add a warning about
4391         using return statements in Ghost management code.
4393 2017-01-13  Tristan Gingold  <gingold@adacore.com>
4395         * s-mmosin-mingw.adb: Fix pragma import.
4397 2017-01-13  Arnaud Charlet  <charlet@adacore.com>
4399         * gnat1drv.adb (Adjust_Global_Switches): Ignore -gnateE in
4400         codepeer mode.
4402 2017-01-13  Hristian Kirtchev  <kirtchev@adacore.com>
4404         * atree.adb (Allocate_Initialize_Node): A newly created node is
4405         no longer marked as Ghost at this level.
4406         (Mark_New_Ghost_Node): New routine.
4407         (New_Copy): Mark the copy as Ghost.
4408         (New_Entity): Mark the entity as Ghost.
4409         (New_Node): Mark the node as Ghost.
4410         * einfo.adb (Is_Checked_Ghost_Entity): This attribute can now
4411         apply to unanalyzed entities.
4412         (Is_Ignored_Ghost_Entity): This attribute can now apply to unanalyzed
4413         entities.
4414         (Set_Is_Checked_Ghost_Entity): This attribute now
4415         applies to all entities as well as unanalyzed entities.
4416         (Set_Is_Ignored_Ghost_Entity): This attribute now applies to
4417         all entities as well as unanalyzed entities.
4418         * expander.adb Add with and use clauses for Ghost.
4419         (Expand): Install and revert the Ghost region associated with the node
4420         being expanded.
4421         * exp_ch3.adb (Expand_Freeze_Array_Type): Remove all Ghost-related code.
4422         (Expand_Freeze_Class_Wide_Type): Remoe all Ghost-related code.
4423         (Expand_Freeze_Enumeration_Type): Remove all Ghost-related code.
4424         (Expand_Freeze_Record_Type): Remove all Ghost-related code.
4425         (Freeze_Type): Install and revert the Ghost region associated
4426         with the type being frozen.
4427         * exp_ch5.adb Remove with and use clauses for Ghost.
4428         (Expand_N_Assignment_Statement): Remove all Ghost-related code.
4429         * exp_ch6.adb Remove with and use clauses for Ghost.
4430         (Expand_N_Procedure_Call_Statement): Remove all Ghost-relatd code.
4431         (Expand_N_Subprogram_Body): Remove all Ghost-related code.
4432         * exp_ch7.adb (Build_Invariant_Procedure_Body): Install and revert the
4433         Ghost region of the working type.
4434         (Build_Invariant_Procedure_Declaration): Install and revert
4435         the Ghost region of the working type.
4436         (Expand_N_Package_Body): Remove all Ghost-related code.
4437         * exp_ch8.adb Remove with and use clauses for Ghost.
4438         (Expand_N_Exception_Renaming_Declaration): Remove all Ghost-related
4439         code.
4440         (Expand_N_Object_Renaming_Declaration): Remove all Ghost-related code.
4441         (Expand_N_Package_Renaming_Declaration): Remove all Ghost-related code.
4442         (Expand_N_Subprogram_Renaming_Declaration): Remove all Ghost-related
4443         code.
4444         * exp_ch13.adb Remove with and use clauses for Ghost.
4445         (Expand_N_Freeze_Entity): Remove all Ghost-related code.
4446         * exp_disp.adb (Make_DT): Install and revert the Ghost region of
4447         the tagged type. Move the generation of various entities within
4448         the Ghost region of the type.
4449         * exp_prag.adb Remove with and use clauses for Ghost.
4450         (Expand_Pragma_Check): Remove all Ghost-related code.
4451         (Expand_Pragma_Contract_Cases): Remove all Ghost-related code.
4452         (Expand_Pragma_Initial_Condition): Remove all Ghost-related code.
4453         (Expand_Pragma_Loop_Variant): Remove all Ghost-related code.
4454         * exp_util.adb (Build_DIC_Procedure_Body): Install
4455         and revert the Ghost region of the working types.
4456         (Build_DIC_Procedure_Declaration): Install and revert the
4457         Ghost region of the working type.
4458         (Make_Invariant_Call): Install and revert the Ghost region of the
4459         associated type.
4460         (Make_Predicate_Call): Reimplemented. Install and revert the
4461         Ghost region of the associated type.
4462         * freeze.adb (Freeze_Entity): Install and revert the Ghost region
4463         of the entity being frozen.
4464         (New_Freeze_Node): Removed.
4465         * ghost.adb Remove with and use clauses for Opt.
4466         (Check_Ghost_Completion): Update the parameter profile
4467         and all references to formal parameters.
4468         (Ghost_Entity): Update the comment on usage.
4469         (Install_Ghost_Mode): New routines.
4470         (Is_Ghost_Assignment): New routine.
4471         (Is_Ghost_Declaration): New routine.
4472         (Is_Ghost_Pragma): New routine.
4473         (Is_Ghost_Procedure_Call): New routine.
4474         (Is_Ghost_Renaming): Removed.
4475         (Is_OK_Declaration): Reimplemented.
4476         (Is_OK_Pragma): Reimplemented.
4477         (Is_OK_Statement): Reimplemented.
4478         (Is_Subject_To_Ghost): Update the comment on usage.
4479         (Mark_And_Set_Ghost_Assignment): New routine.
4480         (Mark_And_Set_Ghost_Body): New routine.
4481         (Mark_And_Set_Ghost_Completion): New routine.
4482         (Mark_And_Set_Ghost_Declaration): New routine.
4483         (Mark_And_Set_Ghost_Instantiation): New routine.
4484         (Mark_And_Set_Ghost_Procedure_Call): New routine.
4485         (Mark_Full_View_As_Ghost): Removed.
4486         (Mark_Ghost_Declaration_Or_Body): New routine.
4487         (Mark_Ghost_Pragma): New routine.
4488         (Mark_Ghost_Renaming): New routine.
4489         (Mark_Pragma_As_Ghost): Removed.
4490         (Mark_Renaming_As_Ghost): Removed.
4491         (Propagate_Ignored_Ghost_Code): Update the comment on usage.
4492         (Prune_Node): Freeze nodes no longer need special pruning, they
4493         are processed by the general ignored Ghost code mechanism.
4494         (Restore_Ghost_Mode): New routine.
4495         (Set_Ghost_Mode): Reimplemented.
4496         (Set_Ghost_Mode_From_Entity): Removed.
4497         * ghost.ads Add with and use clauses for Ghost.
4498         (Check_Ghost_Completion): Update the parameter profile
4499         along with the comment on usage.
4500         (Install_Ghost_Mode): New routine.
4501         (Is_Ghost_Assignment): New routine.
4502         (Is_Ghost_Declaration): New routine.
4503         (Is_Ghost_Pragma): New routine.
4504         (Is_Ghost_Procedure_Call): New routine.
4505         (Mark_And_Set_Ghost_Assignment): New routine.
4506         (Mark_And_Set_Ghost_Body): New routine.
4507         (Mark_And_Set_Ghost_Completion): New routine.
4508         (Mark_And_Set_Ghost_Declaration): New routine.
4509         (Mark_And_Set_Ghost_Instantiation): New routine.
4510         (Mark_And_Set_Ghost_Procedure_Call): New routine.
4511         (Mark_Full_View_As_Ghost): Removed.
4512         (Mark_Ghost_Pragma): New routine.
4513         (Mark_Ghost_Renaming): New routine.
4514         (Mark_Pragma_As_Ghost): Removed.
4515         (Mark_Renaming_As_Ghost): Removed.
4516         (Restore_Ghost_Mode): New routine.
4517         (Set_Ghost_Mode): Redefined.
4518         (Set_Ghost_Mode_From_Entity): Removed.
4519         * sem.adb (Analyze): Install and revert the Ghost region of the
4520         node being analyzed.
4521         (Do_Analyze): Change the way a clean Ghost
4522         region is installed and reverted.
4523         * sem_ch3.adb (Analyze_Full_Type_Declaration): Remove
4524         all Ghost-related code.
4525         (Analyze_Incomplete_Type_Decl): Remove all Ghost-related code.
4526         (Analyze_Number_Declaration): Remove all Ghost-related code.
4527         (Analyze_Object_Declaration): Install and revert the Ghost region of
4528         a deferred object declaration's completion.
4529         (Array_Type_Declaration): Remove all Ghost-related code.
4530         (Build_Derived_Type): Update the comment on
4531         the propagation of Ghost attributes from a parent to a derived type.
4532         (Derive_Subprogram): Remove all Ghost-related code.
4533         (Make_Class_Wide_Type): Remove all Ghost-related code.
4534         (Make_Implicit_Base): Remove all Ghost-related code.
4535         (Process_Full_View): Install and revert the Ghost region of
4536         the partial view.  There is no longer need to check the Ghost
4537         completion here.
4538         * sem_ch5.adb (Analyze_Assignment): Install and revert the Ghost
4539         region of the left hand side.
4540         * sem_ch6.adb (Analyze_Abstract_Subprogram_Declaration): Remove
4541         all Ghost-related code.
4542         (Analyze_Expression_Function): Remove all Ghost-related code.
4543         (Analyze_Generic_Subprogram_Body): Remove all Ghost-related code.
4544         (Analyze_Procedure_Call): Install and revert the Ghost region of
4545         the procedure being called.
4546         (Analyze_Subprogram_Body_Helper): Install and revert the Ghost
4547         region of the spec or body.
4548         (Analyze_Subprogram_Declaration): Remove all Ghost-related code.
4549         (Build_Subprogram_Declaration): Remove all Ghost-related code.
4550         (Find_Corresponding_Spec): Remove all Ghost-related code.
4551         (Process_Formals): Remove all Ghost-related code.
4552         * sem_ch7.adb (Analyze_Package_Body_Helper): Install and revert
4553         the Ghost region of the spec.
4554         (Analyze_Package_Declaration): Remove all Ghost-related code.
4555         * sem_ch8.adb (Analyze_Exception_Renaming): Mark a renaming as
4556         Ghost when it aliases a Ghost entity.
4557         (Analyze_Generic_Renaming): Mark a renaming as Ghost when it aliases
4558         a Ghost entity.
4559         (Analyze_Object_Renaming): Mark a renaming as Ghost when
4560         it aliases a Ghost entity.
4561         (Analyze_Package_Renaming): Mark a renaming as Ghost when it aliases
4562         a Ghost entity.
4563         (Analyze_Subprogram_Renaming): Mark a renaming as Ghost when it
4564         aliases a Ghost entity.
4565         * sem_ch11.adb Remove with and use clauses for Ghost.
4566         (Analyze_Exception_Declaration): Remove all Ghost-related code.
4567         * sem_ch12.adb (Analyze_Generic_Package_Declaration): Remove all
4568         Ghost-related code.
4569         (Analyze_Generic_Subprogram_Declaration): Remove all Ghost-related
4570         code.
4571         (Analyze_Package_Instantiation): Install and revert the Ghost region
4572         of the package instantiation.
4573         (Analyze_Subprogram_Instantiation): Install
4574         and revert the Ghost region of the subprogram instantiation.
4575         (Instantiate_Package_Body): Code clean up. Install and revert the
4576         Ghost region of the package body.
4577         (Instantiate_Subprogram_Body): Code clean up. Install and revert the
4578         Ghost region of the subprogram body.
4579         * sem_ch13.adb (Build_Predicate_Functions): Install
4580         and revert the Ghost region of the related type.
4581         (Build_Predicate_Function_Declaration): Code clean up. Install
4582         and rever the Ghost region of the related type.
4583         * sem_prag.adb (Analyze_Contract_Cases_In_Decl_Part):
4584         Install and revert the Ghost region of the pragma.
4585         (Analyze_Initial_Condition_In_Decl_Part): Install and revert the
4586         Ghost region of the pragma.
4587         (Analyze_Pragma): Install and revert the Ghost region of various
4588         pragmas.  Mark a pragma as Ghost when it is related to a Ghost entity
4589         or encloses a Ghost entity.
4590         (Analyze_Pre_Post_Condition): Install and revert the Ghost
4591         region of the pragma.
4592         (Analyze_Pre_Post_Condition_In_Decl_Part): Install and revert the
4593         Ghost region of the pragma.
4594         * sem_res.adb (Resolve): Remove all Ghost-related code.
4595         * sem_util.adb (Is_Declaration): Reimplemented.
4596         (Is_Declaration_Other_Than_Renaming): New routine.
4597         * sem_util.ads (Is_Declaration_Other_Than_Renaming): New routine.
4598         * sinfo.adb (Is_Checked_Ghost_Pragma): New routine.
4599         (Is_Ghost_Pragma): Removed.
4600         (Is_Ignored_Ghost_Pragma): New routine.
4601         (Set_Is_Checked_Ghost_Pragma): New routine.
4602         (Set_Is_Ghost_Pragma): Removed.
4603         (Set_Is_Ignored_Ghost_Pragma): New routine.
4604         * sinfo.ads: Update the documentation on Ghost mode and
4605         Ghost regions.  New attributes Is_Checked_Ghost_Pragma
4606         and Is_Ignored_Ghost_Pragma along with usages in nodes.
4607         Remove attribute Is_Ghost_Pragma along with usages in nodes.
4608         (Is_Checked_Ghost_Pragma): New routine along with pragma Inline.
4609         (Is_Ghost_Pragma): Removed along with pragma Inline.
4610         (Is_Ignored_Ghost_Pragma): New routine along with pragma Inline.
4611         (Set_Is_Checked_Ghost_Pragma): New routine along with pragma Inline.
4612         (Set_Is_Ghost_Pragma): Removed along with pragma Inline.
4613         (Set_Is_Ignored_Ghost_Pragma): New routine along with pragma Inline.
4615 2017-01-12  Tristan Gingold  <gingold@adacore.com>
4617         * s-mmap.ads, s-mmap.adb, s-mmosin-unix.ads, s-mmosin-unix.adb,
4618         s-mmauni-long.ads, s-mmosin-mingw.ads, s-mmosin-mingw.adb: New files.
4620 2017-01-12  Yannick Moy  <moy@adacore.com>
4622         * errout.adb, errout.ads (Initialize): Factor common treatment
4623         in Reset_Warnings.
4624         (Reset_Warnings): New procedure to reset counts related to warnings.
4625         (Record_Compilation_Errors): New variable to store the presence of an
4626         error, used in gnat2why to allow changing the Warning_Mode.
4627         (Compilation_Errors): Use new variable Record_Compilation_Errors to
4628         store the presence of an error.
4630 2017-01-12  Javier Miranda  <miranda@adacore.com>
4632         * sem_ch13.adb (Analyze_Aspect_Specifications):
4633         For Interrupt_Handler and Attach_ Handler aspects, decorate the
4634         internally built reference to the protected procedure as coming
4635         from sources and force its analysis.
4637 2017-01-12  Ed Schonberg  <schonberg@adacore.com>
4639         * sem_ch3.adb (Build_Derived_Type): For a scalar derived type,
4640         inherit predicates if any from the first_subtype of the parent,
4641         not from the anonymous parent type.
4642         * sem_eval.adb (Is_Static_Subtype): A type that inherits a dynamic
4643         predicate is not a static subtype.
4645 2017-01-12  Gary Dismukes  <dismukes@adacore.com>
4647         * freeze.adb (Check_Suspicious_Convention): New procedure
4648         performing a warning check on discriminated record types with
4649         convention C or C++. Factored out of procedure Freeze_Record_Type,
4650         and changed to only apply to base types (to avoid spurious
4651         warnings on subtypes). Minor improvement of warning messages
4652         to refer to discriminated rather than variant record types.
4653         (Freeze_Record_Type): Remove code for performing a suspicious
4654         convention check.
4655         (Freeze_Entity): Only call Freeze_Record_Type
4656         on types that aren't declared within any enclosing generic units
4657         (rather than just excluding the type when the innermost scope
4658         is generic). Call Check_Suspicious_Convention whether or not
4659         the type is declared within a generic unit.
4660         * sem_ch8.adb (In_Generic_Scope): Move this function to Sem_Util.
4661         * sem_util.ads, sem_util.adb (In_Generic_Scope): New function (moved
4662         from Sem_Ch8).
4664 2017-01-12  Tristan Gingold  <gingold@adacore.com>
4666         * sysdep.c, adaint.c, rtinit.c, ming32.h:
4667         (__gnat_current_codepage): Renamed from CurrentCodePage
4668         (__gnat_current_ccs_encoding): Renamed from CurrentCCSEncoding
4670 2017-01-12  Ed Schonberg  <schonberg@adacore.com>
4672         * sem_ch6.adb (Fully_Conformant_Expressions): Handle properly
4673         quantified expressions, following AI12-050: the loop parameters
4674         of two quantified expressions are conformant if they have the
4675         same identifier.
4677 2017-01-12  Arnaud Charlet  <charlet@adacore.com>
4679         * gcc-interface/Makefile.in: Clean up VxWorks targets.
4681 2017-01-12  Ed Schonberg  <schonberg@adacore.com>
4683         * sem_attr.adb (Analyze_Attribute_Reference, case Loop_Entry):
4684         Hnadle properly the attribute reference when it appears as part
4685         of an expression in another loop aspect.
4687 2017-01-12  Ed Schonberg  <schonberg@adacore.com>
4689         * exp_ch3.adb (Check_Predicated_Discriminant): New procedure,
4690         subsidiary of Build_Initialization_Call, to complete generation
4691         of predicate checks on discriminants whose (sub)types have
4692         predicates, and to add checks on variants that do not have an
4693         others clause.
4694         * sem_util.adb (Gather_Components): A missing Others alternative is
4695         not an error when the type of the discriminant is a static predicate
4696         (and coverage has been checked when analyzing the case statement). A
4697         runtime check is generated to verify that a given discriminant
4698         satisfies the predicate (RM 3.8.1. (21.1/2)).
4700 2017-01-12  Yannick Moy  <moy@adacore.com>
4702         * gnat1drv.adb (Adjust_Global_Switches): Only
4703         perform checking of exception mechanism when generating code.
4705 2017-01-12  Justin Squirek  <squirek@adacore.com>
4707         * exp_ch7.adb (Add_Type_Invariants, Process_Array_Component):
4708         Remove handling of access component with invariant.
4709         (Build_Invariant_Procedure_Declaration): Remove return on class
4710         wide type.
4711         * freeze.adb (Freeze_Array_Type, Freeze_Record_Type): Remove
4712         conditional exception for component or array so Has_Own_Invariants
4713         flag is not falsly set.
4714         * sem_ch3.adb (Make_Class_Wide_Type): Initialize copy of class
4715         wide type to have no invariant flags.
4717 2017-01-12  Hristian Kirtchev  <kirtchev@adacore.com>
4719         * exp_ch9.adb, sem_prag.adb, s-tassta.adb, sem_util.adb, s-tarest.adb,
4720         sem_ch13.adb: Minor reformatting.
4722 2017-01-12  Hristian Kirtchev  <kirtchev@adacore.com>
4724         * exp_aggr.adb (Build_Record_Aggr_Code): Guard against a missing
4725         adjustment primitive when the ancestor type was not properly frozen.
4726         (Gen_Assign): Guard against a missing initialization
4727         primitive when the component type was not properly frozen.
4728         (Initialize_Array_Component): Guard against a missing adjustment
4729         primitive when the component type was not properly frozen.
4730         (Initialize_Record_Component): Guard against a missing adjustment
4731         primitive when the component type was not properly frozen.
4732         (Process_Transient_Component_Completion): The transient object may
4733         not be finalized when its associated type was not properly frozen.
4734         * exp_ch3.adb (Build_Assignment): Guard against a missing
4735         adjustment primitive when the component type was not properly frozen.
4736         (Build_Initialization_Call): Guard against a missing
4737         initialization primitive when the associated type was not properly
4738         frozen.
4739         (Expand_N_Object_Declaration): Guard against a missing
4740         adjustment primitive when the base type was not properly frozen.
4741         (Predefined_Primitive_Bodies): Create an empty Deep_Adjust
4742         body when there is no adjustment primitive available. Create an
4743         empty Deep_Finalize body when there is no finalization primitive
4744         available.
4745         * exp_ch4.adb (Apply_Accessibility_Check): Guard against a
4746         missing finalization primitive when the designated type was
4747         not properly frozen.
4748         (Expand_N_Allocator): Guard against a missing initialization primitive
4749         when the designated type was not properly frozen.
4750         * exp_ch5.adb (Make_Tag_Ctrl_Assignment): Add the adjustment call
4751         only when the corresponding adjustment primitive is available.
4752         * exp_ch7.adb (Build_Adjust_Or_Finalize_Statements): Generate the
4753         adjustment/finalization statements only when there is an available
4754         primitive to carry out the action.
4755         (Build_Initialize_Statements): Generate the initialization/finalization
4756         statements only when there is an available primitive to carry out the
4757         action.
4758         (Make_Adjust_Call): Do not generate a call when the underlying
4759         type is not present due to a possible missing full view.
4760         (Make_Final_Call): Do not generate a call when the underlying
4761         type is not present due to a possible missing full view.
4762         (Make_Finalize_Address_Stmts): Generate an empty body when the
4763         designated type lacks a finalization primitive.
4764         (Make_Init_Call): Do not generate a call when the underlying type is
4765         not present due to a possible missing full view.
4766         (Process_Component_For_Adjust): Add the adjustment call only when the
4767         corresponding adjustment primitive is available.
4768         (Process_Component_For_Finalize): Add the finalization call only when
4769         the corresponding finalization primitive is available.
4770         (Process_Object_Declaration): Use a null statement to emulate a
4771         missing call to the finalization primitive of the object type.
4772         * exp_ch7.ads (Make_Adjust_Call): Update the comment on usage.
4773         (Make_Final_Call): Update the comment on usage.
4774         (Make_Init_Call): Update the comment on usage.
4775         * exp_util.adb (Build_Transient_Object_Statements): Code reformatting.
4777 2017-01-12  Arnaud Charlet  <charlet@adacore.com>
4779         * einfo.ads: Update documentation of Address_Taken.
4780         * sem_attr.adb (Analyze_Access_Attribute, Resolve_Attribute
4781         [Access_Attribute]): Only consider 'Access/'Unchecked_Access
4782         for subprograms when setting Address_Taken flag.
4784 2017-01-12  Patrick Bernardi  <bernardi@adacore.com>
4786         * sem_ch10.adb (Analyze_With_Clause): Removed code that turned
4787         Configurable_Run_Time_Mode off when analysing with'ed predefined
4788         libraries.
4790 2017-01-12  Gary Dismukes  <dismukes@adacore.com>
4792         * sem_prag.adb: Minor reformatting.
4793         * sem_util.adb (Unique_Entity): fix result for
4794         bodies of entry families.
4796 2017-01-12  Justin Squirek  <squirek@adacore.com>
4798         * sem_prag.adb (Analyze_Pragma): Add appropriate calls to
4799         Resolve_Suppressible in the pragma Assertion_Policy case.
4800         (Resolve_Suppressible): Created this function to factor out
4801         common code used to resolve Suppress to either Ignore or Check
4802         * snames.ads-tmpl: Add name for Suppressible.
4804 2017-01-12  Gary Dismukes  <dismukes@adacore.com>
4806         * exp_ch9.adb, s-secsta.adb, snames.ads-tmpl, exp_ch3.adb: Minor
4807         reformatting.
4808         * debug.adb: Minor comment fixes.
4810 2017-01-12  Arnaud Charlet  <charlet@adacore.com>
4812         * sem_util.adb (Unique_Entity): For concurrent
4813         bodies that are defined with stubs and complete a declaration
4814         of a single concurrent object return the entity of an implicit
4815         concurrent type, not the entity of the anonymous concurrent
4816         object.
4817         * debug.adb: -gnatd.J is no longer used.
4818         * make.adb (Globalize): Removed, no longer used.
4819         * sem_ch9.adb: minor typo in comment for entry index
4821 2017-01-12  Patrick Bernardi  <bernardi@adacore.com>
4823         * aspect.adb, aspect.ads: Added new aspect Secondary_Stack_Size.
4824         * exp_ch3.adb (Build_Init_Statements): As part of initialising
4825         the value record of a task, set its _Secondary_Stack_Size field
4826         if present.
4827         * exp_ch9.adb (Expand_N_Task_Type_Declaration): Create
4828         a _Secondary_Stack_Size field in the value record of
4829         the task if a Secondary_Stack_Size rep item is present.
4830         (Make_Task_Create_Call): Include secondary stack size
4831         parameter. If No_Secondary_Stack restriction is in place, passes
4832         stack size of 0.
4833         * par-prag.adb, sem_prag.adb, sem_prag.ads: Added new pragma
4834         Secondary_Stack_Size.
4835         * s-secsta.adb, s-secsta.ads (Minimum_Secondary_Stack_Size): New
4836         function to define the overhead of the secondary stack.
4837         * s-tarest.adb (Create_Restricted_Task,
4838         Create_Restricted_Task_Sequential): Functions now include
4839         Secondary_Stack_Size parameter to pass to Initialize_ATCB.
4840         * s-tarest.adb (Create_Restricted_Task,
4841         Create_Restricted_Task_Sequential): Calls to Initialize_ATCB now
4842         include Secondary_Stack_Size parameter.
4843         (Task_Wrapper): Secondary stack now allocated to the size specified by
4844         the Secondary_Stack_Size parameter in the task's ATCB.
4845         * s-taskin.adb, s-taskin.adb (Common_ATCB, Initialize_ATCB): New
4846         Secondary_Stack_Size component.
4847         * s-tassta.adb, s-tassta.ads (Create_Restricted_Task,
4848         Create_Restricted_Task_Sequential): Function now include
4849         Secondary_Stack_Size parameter.
4850         (Task_Wrapper): Secondary stack now allocated to the size
4851         specified by the Secondary_Stack_Size parameter in the task's
4852         ATCB.
4853         * s-tproft.adb (Register_Foreign_Thread): Amended Initialize_ATCB call
4854         to include Secondary_Stack_Size parameter.
4855         * sem_ch13.adb (Analyze_Aspect_Specification): Add support for
4856         Secondary_Stack_Size aspect, turning the aspect into its corresponding
4857         internal attribute.
4858         (Analyze_Attribute_Definition): Process Secondary_Stack_Size attribute.
4859         * snames.adb-tmpl, snames.ads-tmpl: Added names
4860         Name_Secondary_Stack_Size, Name_uSecondary_Stack_Size,
4861         Attribute_Secondary_Stack_Size and Pragma_Secondary_Stack_Size.
4863 2017-01-12  Yannick Moy  <moy@adacore.com>
4865         * exp_spark.adb (Expand_SPARK_Potential_Renaming): Fix sloc of copied
4866         subtree.
4868 2017-01-12  Justin Squirek  <squirek@adacore.com>
4870         * exp_attr.adb (Expand_N_Attribute_Reference):
4871         Fix Finalization_Size case by properly resolving the type after
4872         rewritting the node.
4874 2017-01-12  Hristian Kirtchev  <kirtchev@adacore.com>
4876         * exp_util.adb (Build_DIC_Procedure_Body): Semi-insert the body into
4877         the tree.
4878         (Build_DIC_Procedure_Declaration): Semi-insert the body into the tree.
4879         * binde.adb, exp_ch5.adb, sem_type.adb, sem.ads, sem_res.adb,
4880         exp_sel.ads: Minor reformatting.
4882 2017-01-12  Justin Squirek  <squirek@adacore.com>
4884         * exp_ch6.adb (Expand_Call): Add guard to prevent
4885         invariant checks from being created for internally generated
4886         subprograms.
4888 2017-01-12  Bob Duff  <duff@adacore.com>
4890         * lib-writ.ads: Remove incorrect comment.
4892 2017-01-12  Javier Miranda  <miranda@adacore.com>
4894         * debug.adb (-gnatd.K): Enable generation of contract-only
4895         procedures in CodePeer mode.
4896         * contracts.adb (Build_And_Analyze_Contract_Only_Subprograms):
4897         New subprogram.
4898         (Analyze_Contracts): Generate contract-only procedures if -gnatdK is
4899         set.
4900         * scil_ll.ads, scil_ll.adb (Get_Contract_Only_Body_Name): New
4901         subprogram.
4902         (Get_Contract_Only_Missing_Body_Name): New subprogram.
4903         (Get_Contract_Only_Body): New subprogram.
4904         (Set_Contract_Only_Body): New subprogram.
4905         (Is_Contract_Only_Body): New subprogram.
4906         (Set_Is_Contract_Only_Body): New subprogram.
4907         (SCIL_Nodes): Replace table by hash-table.
4909 2017-01-12  Hristian Kirtchev  <kirtchev@adacore.com>
4911         * exp_ch6.adb: Minor reformatting.
4912         * spark_xrefs.ads: minor cleanup of comments for SPARK xrefs
4914 2017-01-12  Bob Duff  <duff@adacore.com>
4916         * binde.adb (Forced): New reason for a dependence.
4917         (Force_Elab_Order): Implementation of the new switch.
4918         * binde.ads: Minor comment fixes.
4919         * bindusg.adb: Add -f switch. Apparently, there was an -f switch
4920         long ago that is no longer supported; removed comment about that.
4921         * opt.ads (Force_Elab_Order_File): Name of file specified for
4922         -f switch.
4923         * switch-b.adb: Parse -f switch.
4925 2017-01-12  Justin Squirek  <squirek@adacore.com>
4927         * exp_ch6.adb (Check_View_Conversion): Created this function
4928         to properly chain calls to check type invariants that may be
4929         present in a subprogram call after the subprogram.
4930         (Expand_Call): Add a conditional to identify when a view conversion
4931         needs to be checked.
4932         * nlists.adb, nlists.ads (Prepend_New): New routine.
4933         (Prepend_New_To): New routine.
4935 2017-01-12  Hristian Kirtchev  <kirtchev@adacore.com>
4937         * sinfo.ads: Minor reformatting.
4939 2017-01-12  Gary Dismukes  <dismukes@adacore.com>
4941         * exp_util.adb, exp_util.ads, einfo.ads: Minor typo fixes and
4942         reformatting.
4944 2017-01-12  Hristian Kirtchev  <kirtchev@adacore.com>
4946         * exp_ch6.adb (Make_Build_In_Place_Call_In_Anonymous_Context): Add new
4947         variable Definite. Create a local object and pass its 'Access to the
4948         BIP function when the result type is either definite or it does not
4949         require any finalization or secondary stack management.
4951 2017-01-12  Bob Duff  <duff@adacore.com>
4953         * contracts.adb, einfo.adb, errout.adb, exp_attr.adb,
4954         exp_ch3.adb, exp_ch7.adb, exp_ch9.adb, exp_prag.adb, freeze.adb,
4955         frontend.adb, ghost.adb, inline.adb, lib-writ.adb, lib-xref.adb,
4956         par.adb, par-ch10.adb, par-ch2.adb, par-prag.adb, par_sco.adb,
4957         sem_attr.adb, sem_aux.adb, sem_ch10.adb, sem_ch12.adb,
4958         sem_ch13.adb, sem_ch6.adb, sem_ch8.adb, sem_ch9.adb, sem_elab.adb,
4959         sem_prag.adb, sem_res.adb, sem_util.adb, sem_util.ads,
4960         sem_warn.adb, sinfo.adb, sinfo.ads, sprint.adb (Pragma_Name):
4961         Change name to Pragma_Name_Unmapped.
4962         (Pragma_Name_Mapped): Change name to Pragma_Name.
4963         This is because the "mapped" version should be the usual case.
4965 2017-01-09  Hristian Kirtchev  <kirtchev@adacore.com>
4967         * einfo.ads, einfo.adb: Remove uses of flags Has_Default_Init_Cond,
4968         Is_Default_Init_Cond_Procedure, and
4969         Has_Inherited_Default_Init_Cond.  Add uses of flags
4970         Has_Own_DIC, Is_DIC_Procedure, and Has_Inherited_DIC.
4971         (Default_Init_Cond_Procedure): Removed.
4972         (DIC_Procedure): New routine.
4973         (Has_Default_Init_Cond): Removed.
4974         (Has_DIC): New routine.
4975         (Has_Inheritable_Invariants): The attribute applies to the base type.
4976         (Has_Inherited_Default_Init_Cond): Removed.
4977         (Has_Inherited_DIC): New routine.
4978         (Has_Inherited_Invariants): The attribute applies to the base type.
4979         (Has_Own_DIC): New routine.
4980         (Has_Own_Invariants): The attribute applies to the base type.
4981         (Is_Default_Init_Cond_Procedure): Removed.
4982         (Is_DIC_Procedure): New routine.
4983         (Set_Default_Init_Cond_Procedure): Removed.
4984         (Set_DIC_Procedure): New routine.
4985         (Set_Has_Default_Init_Cond): Removed.
4986         (Set_Has_Inheritable_Invariants): The attribute applies
4987         to the base type.
4988         (Set_Has_Inherited_Default_Init_Cond): Removed.
4989         (Set_Has_Inherited_DIC): New routine.
4990         (Set_Has_Inherited_Invariants): The attribute applies to the base type.
4991         (Set_Has_Own_DIC): New routine.
4992         (Set_Has_Own_Invariants): The attribute applies to the base type.
4993         (Set_Is_Default_Init_Cond_Procedure): Removed.
4994         (Set_Is_DIC_Procedure): New routine.
4995         (Write_Entity_Flags): Update the output of all flags related to
4996         default initial condition.
4997         * exp_ch3.adb (Expand_N_Object_Declaration): Update the generation
4998         of the call to the DIC procedure.
4999         (Freeze_Type): Generate the body of the DIC procedure.
5000         * exp_ch7.adb (Build_Invariant_Procedure_Body): Replace
5001         all occurrences of Create_Append with Append_New_To. Do
5002         not generate an invariant procedure for a class-wide type.
5003         The generated body acts as a freeze action of the working type.
5004         (Build_Invariant_Procedure_Declaration): Do not generate an
5005         invariant procedure for a class-wide type.
5006         (Create_Append): Removed.
5007         * exp_util.adb: Add with and use clauses for Sem_Ch3, sem_ch6,
5008         sem_Ch12, Sem_Disp, and GNAT.HTable. Move the handling of
5009         class-wide pre/postcondition description and data structures from
5010         Sem_Prag.
5011         (Build_Class_Wide_Expression): Moved from Sem_Prag.
5012         (Build_DIC_Call): New routine.
5013         (Build_DIC_Procedure_Body): New routine.
5014         (Build_DIC_Procedure_Declaration): New routine.
5015         (Entity_Hash): Moved from Sem_Prag.
5016         (Find_DIC_Type): New routine.
5017         (Update_Primitives_Mapping): Reimplemented.
5018         (Update_Primitives_Mapping_Of_Types): New routine.
5019         * exp_util.ads (Build_Class_Wide_Expression): Moved from Sem_Prag.
5020         (Build_DIC_Call): New routine.
5021         (Build_DIC_Procedure_Body): New routine.
5022         (Build_DIC_Procedure_Declaration): New routine.
5023         (Update_Primitives_Mapping): Moved from Sem_Prag.
5024         (Update_Primitives_Mapping_Of_Types): New routine.
5025         * nlists.adb (Append_New): New routine.
5026         (Append_New_To): New routine.
5027         * nlists.ads (Append_New): New routine.
5028         (Append_New_To): New routine.
5029         * sem_ch3.adb (Analyze_Declarations): Do not generate the bodies
5030         of DIC procedures here. This is now done at the end of the
5031         visible declarations, private declarations, and at the freeze
5032         point of a type.
5033         (Analyze_Private_Extension_Declaration):
5034         A private extension inherits the DIC pragma of a parent type.
5035         (Analyze_Subtype_Declaration): No need to propagate invariant
5036         attributes to a subtype as those apply to the base type.
5037         (Build_Derived_Record_Type): No need to inherit invariants here
5038         as this is now done in Build_Derived_Type.
5039         (Build_Derived_Type): Inherit both the DIC pragma and invariants from
5040         a parent type.
5041         (Process_Full_View): Update the propagation of DIC attributes.
5042         (Propagate_Default_Init_Cond_Attributes): Removed.
5043         * sem_ch7.adb Add with and use clauses for Exp_Util.
5044         (Analyze_Package_Specification): Create the body of the DIC
5045         procedure at the end of the visible and private declarations.
5046         (Preserve_Full_Attributes): Propagate DIC attributes.
5047         * sem_ch9.adb (Analyze_Protected_Type_Declaration): Propagate
5048         DIC attributes.
5049         (Analyze_Task_Type_Declaration): Propagate DIC attributes.
5050         * sem_elab.adb (Check_A_Call): Update the call to
5051         Is_Nontrivial_Default_Init_Cond_Procedure.
5052         * sem_prag.adb Remove the with and use clauses for
5053         GNAT.HTable. Move the handling of class- wide pre/postcondition
5054         description and data structures to Exp_Util.
5055         (Analyze_Pragma): Create the declaration of the DIC procedure. There
5056         is no need to propagate invariant-related attributes at this point
5057         as this is done in Build_Invariant_Procedure_Declaration.
5058         (Build_Class_Wide_Expression): Moved to Exp_Util.
5059         (Entity_Hash): Moved to Exp_Util.
5060         (Update_Primitives_Mapping): Moved to Exp_Util.
5061         * sem_prag.ads (Build_Class_Wide_Expression): Moved to Exp_Util.
5062         (Update_Primitives_Mapping): Moved to Exp_Util.
5063         * sem_util.adb: Remove with and use clauses for Ghost
5064         and Sem_Ch13.
5065         (Build_Default_Init_Cond_Call): Removed.
5066         (Build_Default_Init_Cond_Procedure_Bodies): Removed.
5067         (Build_Default_Init_Cond_Procedure_Declaration): Removed.
5068         (Get_Views): Reimplemented.
5069         (Has_Full_Default_Initialization): Reimplement the section on DIC.
5070         (Inherit_Default_Init_Cond_Procedure): Removed.
5071         (Is_Nontrivial_Default_Init_Cond_Procedure): Removed.
5072         (Is_Nontrivial_DIC_Procedure): New routine.
5073         (Is_Verifiable_DIC_Pragma): New routine.
5074         (Propagate_DIC_Attributes): New routine.
5075         * sem_util.ads (Build_Default_Init_Cond_Call): Removed.
5076         (Build_Default_Init_Cond_Procedure_Bodies): Removed.
5077         (Build_Default_Init_Cond_Procedure_Declaration): Removed.
5078         (Inherit_Default_Init_Cond_Procedure): Removed.
5079         (Is_Nontrivial_Default_Init_Cond_Procedure): Removed.
5080         (Is_Nontrivial_DIC_Procedure): New routine.
5081         (Is_Verifiable_DIC_Pragma): New routine.
5082         (Propagate_DIC_Attributes): New routine.
5083         * sem_warn.adb (Is_OK_Fully_Initialized): Reimplement the section
5084         on DIC.
5085         * sinfo.ads, sinfo.adb: Add new attribute Expression_Copy along with
5086         usage in nodes.
5087         (Expression_Copy): New routine along with pragma Inline.
5088         (Set_Expression_Copy): New routine along with pragma Inline.
5090 2017-01-06  Bob Duff  <duff@adacore.com>
5092         * bindgen.adb (Gen_Adainit, Gen_Adafinal): Change
5093         "Bind_Main_Program" to "not Bind_For_Library", because otherwise
5094         we won't generate the call to s_stalib_adafinal when the main
5095         is not written in Ada.
5097 2017-01-06  Bob Duff  <duff@adacore.com>
5099         * sem_prag.adb: Minor: remove pragma Warnings.
5101 2017-01-06  Tristan Gingold  <gingold@adacore.com>
5103         * Makefile.rtl: Do not compile s-stchop by default.
5105 2017-01-06  Patrick Bernardi  <bernardi@adacore.com>
5107         * aspects.adb, aspects.ads, exp_ch3.adb, exp_ch9.adb, par-prag.adb,
5108         sem_ch13.adb, sem_prag.adb, sem_prag.ads, snames.adb-tmpl,
5109         snames.ads-tmpl, s-secsta.adb, s-secsta.ads, s-tarest.adb,
5110         s-tarest.ads, s-taskin.adb, s-taskin.ads, s-tassta.adb, s-tassta.ads:
5111         Reverted previous change for now.
5113 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
5115         * exp_ch3.adb (Build_Initialization_Call): Apply predicate
5116         check to default discriminant value if checks are enabled.
5117         (Build_Assignment): If type of component has static predicate,
5118         apply check to its default value, if any.
5120 2017-01-06  Patrick Bernardi  <bernardi@adacore.com>
5122         * aspect.adb, aspect.ads: Added new aspect Secondary_Stack_Size.
5123         * exp_ch3.adb (Build_Init_Statements): As part of initialising
5124         the value record of a task, set its _Secondary_Stack_Size field
5125         if present.
5126         * exp_ch9.adb (Expand_N_Task_Type_Declaration): Create
5127         a _Secondary_Stack_Size field in the value record of
5128         the task if a Secondary_Stack_Size rep item is present.
5129         (Make_Task_Create_Call): Include secondary stack size
5130         parameter. If No_Secondary_Stack restriction is in place, passes
5131         stack size of 0.
5132         * par-prag.adb, sem_prag.adb, sem_prag.ads: Added new pragma
5133         Secondary_Stack_Size.
5134         * s-secsta.adb, s-secsta.ads (Minimum_Secondary_Stack_Size): New
5135         function to define the overhead of the secondary stack.
5136         * s-tarest.adb (Create_Restricted_Task,
5137         Create_Restricted_Task_Sequential): Functions now include
5138         Secondary_Stack_Size parameter to pass to Initialize_ATCB.
5139         * s-tarest.adb (Create_Restricted_Task,
5140         Create_Restricted_Task_Sequential): Calls to Initialize_ATCB
5141         now include Secondary_Stack_Size parameter.
5142         (Task_Wrapper):
5143         Secondary stack now allocated to the size specified by the
5144         Secondary_Stack_Size parameter in the task's ATCB.
5145         * s-taskin.adb, s-taskin.adb (Common_ATCB, Initialise_ATCB): New
5146         Secondary_Stack_Size component.
5147         * s-tassta.adb, s-tassta.ads (Create_Restricted_Task,
5148         Create_Restricted_Task_Sequential): Function now include
5149         Secondary_Stack_Size parameter.
5150         (Task_Wrapper): Secondary stack
5151         now allocated to the size specified by the Secondary_Stack_Size
5152         parameter in the task's ATCB.
5153         * sem_ch13.adb (Analyze_Aspect_Specification): Add support
5154         for Secondary_Stack_Size aspect, turning the aspect into its
5155         corresponding internal attribute.
5156         (Analyze_Attribute_Definition):
5157         Process Secondary_Stack_Size attribute.
5158         * snames.adb-tmpl, snames.ads-tmpl: Added names
5159         Name_Secondary_Stack_Size, Name_uSecondary_Stack_Size,
5160         Attribute_Secondary_Stack_Size and Pragma_Secondary_Stack_Size.
5162 2017-01-06  Pascal Obry  <obry@adacore.com>
5164         * a-direio.adb, a-direio.ads, a-sequio.adb, a-sequio.ads: Add Flush to
5165         Sequential_IO and Direct_IO.
5167 2017-01-06  Bob Duff  <duff@adacore.com>
5169         * snames.ads-tmpl (Renamed): New name for the pragma argument.
5170         * par-ch2.adb: Allow the new pragma (with analysis deferred
5171         to Sem_Prag).
5172         * sinfo.ads, sinfo.adb (Map_Pragma_Name, Pragma_Name_Mapped):
5173         Keep a mapping from new pragma names to old names.
5174         * sem_prag.adb: Check legality of pragma Rename_Pragma, and
5175         implement it by calling Map_Pragma_Name.
5176         * checks.adb, contracts.adb, einfo.adb, errout.adb,
5177         * exp_attr.adb, exp_ch3.adb, exp_ch6.adb, exp_ch7.adb, exp_ch9.adb,
5178         * exp_prag.adb, exp_util.adb, freeze.adb, frontend.adb, ghost.adb,
5179         * inline.adb, lib-writ.adb, scans.adb, scans.ads, sem_attr.adb,
5180         * sem_aux.adb, sem_ch10.adb, sem_ch13.adb, sem_ch6.adb, sem_ch9.adb,
5181         * sem_elab.adb, sem_res.adb, sem_util.adb, sem_util.ads,
5182         * sem_warn.adb: Call Pragma_Name_Mapped instead of Pragma_Name
5183         as appropriate.
5185 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
5187         * exp_ch9.adb: Minor reformatting.
5189 2017-01-06  Tristan Gingold  <gingold@adacore.com>
5191         * exp_ch9.ads, exp_ch9.adb (Build_Entry_Names): Remove (unused).
5192         * rtsfind.ads (RE_Task_Entry_Names_Array, RO_ST_Set_Entry_Names)
5193         (RE_Protected_Entry_Names_Array, RO_PE_Set_Entry_Names): Remove
5194         (unused).
5195         * s-taskin.ads, s-taskin.adb (Set_Entry_Names,
5196         Task_Entry_Names_Array, Task_Entry_Names_Access): Remove.
5197         * s-tpoben.ads, s-tpoben.adb (Set_Entry_Names,
5198         Protected_Entry_Names_Array, Protected_Entry_Names_Access): Remove.
5200 2017-01-06  Bob Duff  <duff@adacore.com>
5202         * sinfo.ads, sinfo.adb (Map_Pragma_Name): Preparation work,
5203         dummy implementation of Map_Pragma_Name.
5205 2017-01-06  Tristan Gingold  <gingold@adacore.com>
5207         * exp_ch9.adb (Expand_N_Protected_Type_Declaration): Make the
5208         entry_body variable constant.
5209         * s-taprob.ads (Entry_Body_Access): Move to s-tposen.
5210         * s-tpoben.ads (Protected_Entry_Body_Access): Now access
5211         to constant.
5212         * s-tposen.ads (Entry_Body_Access): Moved from s-taprob,
5213         now access to constant.
5215 2017-01-06  Gary Dismukes  <dismukes@adacore.com>
5217         * einfo.ads, sem_res.adb, sem_attr.adb, sem_ch6.adb: Minor
5218         reformatting and typo fixes.
5220 2017-01-06  Bob Duff  <duff@adacore.com>
5222         * snames.ads-tmpl: New names for pragma renaming.
5223         * snames.adb-tmpl (Is_Configuration_Pragma_Name): Minor cleanup.
5224         * par-prag.adb: Add new pragma name to case statement.
5225         * sem_prag.adb (Rename_Pragma): Initial cut at semantic analysis
5226         of the pragma.
5227         * sinfo.ads, sinfo.adb (Pragma_Name_Mapped): Preparation work,
5228         Dummy implementation of Pragma_Name_Mapped.
5230 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
5232         * exp_ch6.adb (Expand_Protected_Subprogram_Call): Add guard to
5233         better detect call within an entry_wrapper.
5234         * sem_res.adb (Resolve_Call): A protected call within an
5235         entity_wrapper is analyzed in the context of the protected
5236         object but corresponds to a pre-analysis and is not an access
5237         before elaboration.
5238         * sem_attr.adb: Minor reformatting.
5240 2017-01-06  Justin Squirek  <squirek@adacore.com>
5242         * sem_attr.adb (Analyze_Attribute): Modify semantic checks for
5243         Finalization_Size to allow a prefix of any non-class-wide type.
5244         * sem_attr.ads Modify comment for Finalization_Size to include
5245         definite type use case.
5247 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
5249         * einfo.ads, einfo.adb (Is_Entry_Wrapper): New flag, defined
5250         on procedures that are wrappers created for entries that have
5251         preconditions.
5252         * sem_ch6.adb (Analyze_Subrogram_Body_Helper): If the subprogram
5253         body is an entry_wrapper, compile it in the context of the
5254         synchronized type, because a precondition may refer to funtions
5255         of the type.
5256         * exp_ch9.adb (Build_Contract_Wrapper): Set Is_Entry_Wrapper on
5257         body entity.
5258         * exp_ch6.adb (Expand_Protected_Subprogram_Call): if the call is
5259         within an Entry_Wrapper this is an external call whose target
5260         is the synchronized object that is the actual in the call to
5261         the wrapper.
5263 2017-01-06  Yannick Moy  <moy@adacore.com>
5265         * sem_attr.adb (Analyze_Attribute/Attribute_Loop_Entry): Analyze node
5266         in tree, which means not analyzing the previous prefix if the node has
5267         been rewritten into its prefix.
5269 2017-01-06  Gary Dismukes  <dismukes@adacore.com>
5271         * s-tpobop.adb: Minor reformatting.
5273 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
5275         * checks.adb (Ensure_Valid): Do not generate a validity check
5276         within a generated predicate function, validity checks will have
5277         been applied earlier when required.
5279 2017-01-06  Tristan Gingold  <gingold@adacore.com>
5281         * s-tpoben.ads (Protection_Entries): Add comment and reorder
5282         components for performances.
5283         * s-tpobop.adb (PO_Do_Or_Queue): Implement Max_Queue_Length runtime
5284         semantic.
5286 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
5288         * sem_eval.adb (Check_Expression_Against_Static_Predicate):
5289         If expression is compile-time known and obeys a static predicate
5290         it must be labelled as static, to prevent spurious warnings and
5291         run-time errors, e.g. in case statements. This is relevant when
5292         the expression is the result of constant-folding a type conversion
5293         whose expression is a variable with a known static value.
5295 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
5297         * exp_attr.adb, sem_attr.ads: Minor reformatting.
5299 2017-01-06  Justin Squirek  <squirek@adacore.com>
5301         * exp_attr.adb (Expand_N_Attribute_Reference): Add entry for
5302         expansion of Finalization_Size attribute.
5303         * sem_attr.adb (Analyze_Attribute): Add entry to check the
5304         semantics of Finalization_Size.
5305         (Eval_Attribute): Add null entry for Finalization_Size.
5306         * sem_attr.ads: Add Finalization_Size to the implementation
5307         dependent attribute list.
5308         * snames.ads-tmpl: Add name entry for Finalization_Size attribute.
5310 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
5312         * sem_ch5.adb (Analyze_Loop_Statement): If the loop includes an
5313         iterator specification with a serious syntactic error, transform
5314         construct into an infinite loop in order to continue analysis
5315         and prevent a compiler abort.
5317 2017-01-06  Tristan Gingold  <gingold@adacore.com>
5319         * exp_ch9.adb (Expand_N_Protected_Type_Declaration): Do not generate
5320         max_queue_lengths_array if unused.
5322 2017-01-06  Bob Duff  <duff@adacore.com>
5324         * errout.adb (Set_Msg_Text): Protect against out-of-bounds
5325         array access, in case "\" is at the end of Text.
5326         * stylesw.adb (Set_Style_Check_Options): Don't include input
5327         characters in the error message template, because they could
5328         be control characters such as "\", which Errout will try to
5329         interpret.
5331 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
5333         * sem_ch4.adb (Find_Indexing_Operations, Inspect_Declarations):
5334         For a private type examine the visible declarations that follow
5335         the partial view, not just the private declarations that follow
5336         the full view.
5338 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
5340         * exp_ch5.adb, sem_ch3.adb, checks.adb: Minor reformatting and
5341         code cleanup.
5343 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
5345         * exp_ch5.adb (Get_Default_Iterator): For a derived type, the
5346         alias of the inherited op is the parent iterator, no need to
5347         examine dispatch table positions which might not be established
5348         yet if type is not frozen.
5349         * sem_disp.adb (Check_Controlling_Formals): The formal of a
5350         predicate function may be a subtype of a tagged type.
5351         * sem_ch3.adb (Complete_Private_Subtype): Adjust inheritance
5352         of representation items for the completion of a type extension
5353         where a predicate applies to the partial view.
5354         * checks.ads, checks.adb (Apply_Predicate_Check): Add optional
5355         parameter that designates function whose actual receives a
5356         predicate check, to improve warning message when the check will
5357         lead to infinite recursion.
5358         * sem_res.adb (Resolve_Actuals): Pass additional parameter to
5359         Apply_Predicate_Check.
5361 2017-01-06  Tristan Gingold  <gingold@adacore.com>
5363         * s-rident.ads (Profile_Info): Remove No_Entry_Queue from
5364         Gnat_Extended_Ravenscar.
5365         * exp_ch9.adb, s-tpoben.adb, s-tpoben.ads: Fix spelling.
5367 2017-01-06  Gary Dismukes  <dismukes@adacore.com>
5369         * sem_util.ads: Minor typo fix and reformatting.
5371 2017-01-06  Yannick Moy  <moy@adacore.com>
5373         * ghost.adb Minor fixing of references to SPARK RM.
5374         (Check_Ghost_Context): Check whether reference is to a lvalue
5375         before issuing an error about violation of SPARK RM 6.9(13)
5376         when declaration has Ghost policy Check and reference has Ghost
5377         policy Ignore.
5378         * sem_util.adb Minor indentation.
5379         * sem_ch10.adb (Analyze_Package_Body_Stub, Analyze_Protected_Body_Stub,
5380         Analyze_Task_Body_Stub): Set Ekind of the defining identifier.
5381         * sem_util.ads (Unique_Defining_Entity): Document the result
5382         for package body stubs.
5384 2017-01-06  Tristan Gingold  <gingold@adacore.com>
5386         * raise-gcc.c (abort): Macro to call Abort_Propagation.
5387         * s-tpoben.ads (Protected_Entry_Queue_Max_Access): Make it access
5388         constant.
5389         * exp_ch9.adb (Expand_N_Protected_Type_Declaration):
5390         Do not generate the Entry_Max_Queue_Lengths_Array if all default
5391         values.
5392         * exp_util.adb (Corresponding_Runtime_Package): Consider
5393         Max_Queue_Length pragma.
5395 2017-01-06  Justin Squirek  <squirek@adacore.com>
5397         * exp_ch9.adb (Expand_N_Protected_Type_Declaration):
5398         Remove declaration generation in the case of
5399         System_Tasking_Protected_Objects_Single_Entry being used,
5400         and add a warning message when this is detected to occur.
5401         (Make_Initialize_Protection): Remove reference pass in the case
5402         of System_Tasking_Protected_Objects_Single_Entry.
5403         * rtsfind.ads: Remove RE_Protected_Entry_Queue_Max
5404         * s-tposen.adb (Initialize_Protection_Entry): Remove
5405         Entry_Queue_Max parameter.
5406         * s-tposen.ads: Remove the types use to store the entry queue
5407         maximum.
5408         * sem_prag.adb (Analyze_Pragma): Remove entry families restriction
5410 2017-01-06  Yannick Moy  <moy@adacore.com>
5412         * sem_util.adb, sem_util.ads (Get_Enum_Lit_From_Pos): Strengthen
5413         behavior of function, to also accept out of range positions
5414         and raise Constraint_Error in such case, and to copy sloc from
5415         literal if No_Location passed as location.
5416         * uintp.adb, uintp.ads (UI_To_Int, UI_To_CC): Strengthen behavior
5417         of functions to raise Constraint_Error in case of value not in
5418         appropriate range.
5420 2017-01-06  Tristan Gingold  <gingold@adacore.com>
5422         * sem_util.adb, s-taprop-linux.adb (Finalize_TCB): Remove call to
5423         Invalidate_Stack_Cache.
5425 2017-01-06  Eric Botcazou  <ebotcazou@adacore.com>
5427         * s-os_lib.adb: Minor fix to the signature of Readlink.
5429 2017-01-06  Javier Miranda  <miranda@adacore.com>
5431         * sem_ch6.adb (Conforming_Types): Handle another
5432         confusion between views in a nested instance with an actual
5433         private type whose full view is not in scope.
5435 2017-01-06  Arnaud Charlet  <charlet@adacore.com>
5437         * exp_ch5.adb (Expand_N_If_Statement): Obey existing comment and
5438         mark a rewritten if statement as explicit (Comes_From_Source).
5440 2017-01-06  Gary Dismukes  <dismukes@adacore.com>
5442         * sem_prag.adb, rtsfind.adb, sem_util.adb: Minor typo fixes.
5444 2017-01-06  Tristan Gingold  <gingold@adacore.com>
5446         * ada.ads, a-unccon.ads: Add pragma No_Elaboration_Code_All.
5448 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
5450         * sem_case.adb: Minor reformatting.
5452 2017-01-06  Thomas Quinot  <quinot@adacore.com>
5454         * g-socthi-mingw.adb: Remove now extraneous USE TYPE clause
5456 2017-01-06  Justin Squirek  <squirek@adacore.com>
5458         * aspects.adb: Register aspect in Canonical_Aspect.
5459         * aspects.ads: Associate qualities of Aspect_Max_Queue_Length
5460         into respective tables.
5461         * einfo.ads, einfo.adb: Add a new attribute for
5462         handling the parameters for Pragma_Max_Entry_Queue
5463         (Entry_Max_Queue_Lengths_Array) in E_Protected_Type. Subprograms
5464         for accessing and setting were added as well.
5465         * par-prag.adb (Prag): Register Pramga_Max_Entry_Queue.
5466         * exp_ch9.adb (Expand_N_Protected_Type_Declaration): Emit
5467         declaration for pramga arguments and store them in the protected
5468         type node.
5469         (Make_Initialize_Protection): Pass a reference to
5470         the Entry_Max_Queue_Lengths_Array in the protected type node to
5471         the runtime.
5472         * rtsfind.adb: Minor grammar fix.
5473         * rtsfind.ads: Register new types taken from the
5474         runtime libraries RE_Protected_Entry_Queue_Max and
5475         RE_Protected_Entry_Queue_Max_Array
5476         * s-tposen.adb, s-tpoben.adb
5477         (Initialize_Protection_Entry/Initialize_Protection_Entries):
5478         Add extra parameter and add assignment to local object.
5479         * s-tposen.ads, s-tpoben.ads: Add new types to
5480         store entry queue maximums and a field to the entry object record.
5481         * sem_ch13.adb (Analyze_Aspect_Specifications): Add case statement
5482         for Aspect_Max_Queue_Length.
5483         (Check_Aspect_At_Freeze_Point):
5484         Add aspect to list of aspects that don't require delayed analysis.
5485         * sem_prag.adb (Analyze_Pragma): Add case statement for
5486         Pragma_Max_Queue_Length, check semantics, and register arugments
5487         in the respective entry nodes.
5488         * sem_util.adb, sem_util.ads Add functions Get_Max_Queue_Length
5489         and Has_Max_Queue_Length
5490         * snames.ads-tmpl: Add constant for the new aspect-name
5491         Name_Max_Queue_Length and corrasponding pragma.
5493 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
5495         * exp_util.adb (Is_Controlled_Function_Call):
5496         Reimplemented. Consider any node which has an entity as the
5497         function call may appear in various ways.
5499 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
5501         * exp_attr.adb (Rewrite_Stream_Proc_Call): Use
5502         an unchecked type conversion when performing a view conversion
5503         to/from a private type. In all other cases use a regular type
5504         conversion to ensure that any relevant checks are properly
5505         installed.
5507 2017-01-06  Hristian Kirtchev  <kirtchev@adacore.com>
5509         * sem_prag.adb, sem_ch8.adb: Minor reformatting.
5511 2017-01-06  Ed Schonberg  <schonberg@adacore.com>
5513         * sem_case.adb (Explain_Non_Static_Bound): Suppress cascaded
5514         error on case expression that is an entity, when coverage is
5515         incomplete and entity has a static value obtained by local
5516         propagation.
5517         (Handle_Static_Predicate): New procedure, subsidiary of
5518         Check_Choices, to handle case alternatives that are either
5519         subtype names or subtype indications involving subtypes that
5520         have static predicates.
5522 2017-01-06  Thomas Quinot  <quinot@adacore.com>
5524         * s-oscons-tmplt.c, g-socket.adb, g-socket.ads, g-sothco.ads:
5525         (GNAT.Socket): Add support for Busy_Polling and Generic_Option
5527 2017-01-06  Bob Duff  <duff@adacore.com>
5529         * sem_elab.adb (Activate_Elaborate_All_Desirable): Don't add
5530         Elaborate_All(P) to P itself. That could happen in obscure cases,
5531         and always introduced a cycle (P body must be elaborated before
5532         P body).
5533         * lib-writ.ads: Comment clarification.
5534         * ali-util.ads: Minor comment fix.
5535         * ali.adb: Minor reformatting.
5537 2017-01-06  Tristan Gingold  <gingold@adacore.com>
5539         * a-exexpr-gcc.adb: Improve comment.
5541 2017-01-03  James Cowgill  <James.Cowgill@imgtec.com>
5543         * s-linux-mips.ads: Use correct signal and errno constants.
5544         (sa_handler_pos, sa_mask_pos): Fix offsets for 64-bit MIPS.
5546 2017-01-03  James Cowgill  <James.Cowgill@imgtec.com>
5548         * s-linux-mips.ads: Rename from s-linux-mipsel.ads.
5549         * gcc-interface/Makefile.in (MIPS/Linux): Merge mips and mipsel
5550         sections.
5552 2017-01-01  Eric Botcazou  <ebotcazou@adacore.com>
5554         * gnatvsn.ads: Bump copyright year.
5556 2017-01-01  Jakub Jelinek  <jakub@redhat.com>
5558         * gnat_ugn.texi: Bump @copying's copyright year.
5559         * gnat_rm.texi: Likewise.
5561 Copyright (C) 2017 Free Software Foundation, Inc.
5563 Copying and distribution of this file, with or without modification,
5564 are permitted in any medium without royalty provided the copyright
5565 notice and this notice are preserved.