Skip to content
Snippets Groups Projects
Commit 0b7673ae authored by Steve Baird's avatar Steve Baird Committed by Marc Poulhiès
Browse files

ada: Reduce generated code duplication for streaming and Put_Image subprograms

In the case of an untagged composite type, the compiler does not generate
streaming-related subprograms or a Put_Image procedure when the type is
declared. Instead, these subprograms are declared "on demand" when a
corresponding attribute reference is encountered. In this case, hoist the
declaration of the implicitly declared subprogram out as far as possible
in order to maximize the chances that it can be reused (as opposed to
generating an identical second subprogram) in the case where a second
reference to the same attribute is encountered. Also relax some
privacy-related rules to allow these procedures to do what they need to do
even when constructed in a scope where some of those actions would
normally be illegal.

gcc/ada/

	* exp_attr.adb: Change name of package Cached_Streaming_Ops to
	reflect the fact that it is now also used for Put_Image
	procedures. Similarly change other "Streaming_Op" names therein.
	Add Validate_Cached_Candidate procedure to detect case where a
	subprogram found in the cache cannot be reused. Add new generic
	procedure Build_And_Insert_Type_Attr_Subp; the "Build" part is
	handled by just calling a formal procedure; the bulk of this
	(generic) procedure's code has to with deciding where in the tree
	to insert the newly-constructed subprogram. Replace each later
	"Build" call (and the following Insert_Action or
	Compile_Stream_Body_In_Scope call) with a declare block that
	instantiates and then calls this generic procedure. Delete the
	now-unused procedure Compile_Stream_Body_In_Scope. A constructed
	subprogram is entered in the appropriate cache if the
	corresponding type is untagged; this replaces more complex tests.
	A new function Interunit_Ref_OK is added to determine whether an
	attribute reference occuring in one unit can safely refer to a
	cached subprogram declared in another unit.
	* exp_ch3.adb (Build_Predefined_Primitive_Bodies): A formal
	parameter was deleted, so delete the corresponding actual in a
	call.
	* exp_put_image.adb (Build_Array_Put_Image_Procedure): Because the
	procedure being built may be referenced more than once, the
	generated procedure takes its source position info from the type
	declaration instead of the (first) attribute reference.
	(Build_Record_Put_Image_Procedure): Likewise.
	* exp_put_image.ads (Build_Array_Put_Image_Procedure): Eliminate
	now-unused Nod parameter.
	(Build_Record_Put_Image_Procedure): Eliminate now-unused Loc parameter.
	* sem_ch3.adb (Constrain_Discriminated_Type): For declaring a
	subtype with a discriminant constraint, ignore privacy if
	Comes_From_Source is false (as is already done if Is_Instance is
	true).
	* sem_res.adb (Resolve): When passed two type entities that have
	the same underlying base type, Sem_Type.Covers may return False in
	some cases because of privacy. [This can happen even if
	Is_Private_Type returns False both for Etype (N) and for Typ;
	Covers calls Base_Type, which can take a non-private argument and
	yield a private result.] If Comes_From_Source (N) is False
	(e.g., for a compiler-generated Put_Image or streaming subprogram), then
	avoid that scenario by not calling Covers. Covers already has tests for
	doing this sort of thing (see the calls therein to Full_View_Covers),
	but the Comes_From_Source test is too coarse to apply there. So instead
	we handle the problem here at the call site.
	(Original_Implementation_Base_Type): A new function. Same as
	Implementation_Base_Type except if the Original_Node attribute of
	a non-derived type declaration indicates that it once was a derived
	type declaration. Needed for looking through privacy.
	(Valid Conversion): Ignore privacy when converting between different views
	of the same type if Comes_From_Source is False for the conversion.
	(Valid_Tagged_Conversion): An ancestor-to-descendant conversion is not an
	illegal downward conversion if there is no type extension involved
	(because the derivation was from an untagged view of the parent type).
parent 33541b88
No related branches found
No related tags found
Loading
Loading
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment