xref: /netbsd/external/gpl3/gcc.old/dist/gcc/d/d-tree.h (revision 0bfacb9b)
1760c2415Smrg /* d-tree.h -- Definitions and declarations for code generation.
2*0bfacb9bSmrg    Copyright (C) 2006-2020 Free Software Foundation, Inc.
3760c2415Smrg 
4760c2415Smrg GCC is free software; you can redistribute it and/or modify
5760c2415Smrg it under the terms of the GNU General Public License as published by
6760c2415Smrg the Free Software Foundation; either version 3, or (at your option)
7760c2415Smrg any later version.
8760c2415Smrg 
9760c2415Smrg GCC is distributed in the hope that it will be useful,
10760c2415Smrg but WITHOUT ANY WARRANTY; without even the implied warranty of
11760c2415Smrg MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
12760c2415Smrg GNU General Public License for more details.
13760c2415Smrg 
14760c2415Smrg You should have received a copy of the GNU General Public License
15760c2415Smrg along with GCC; see the file COPYING3.  If not see
16760c2415Smrg <http://www.gnu.org/licenses/>.  */
17760c2415Smrg 
18760c2415Smrg #ifndef GCC_D_TREE_H
19760c2415Smrg #define GCC_D_TREE_H
20760c2415Smrg 
21760c2415Smrg /* Forward type declarations to avoid including unnecessary headers.  */
22760c2415Smrg 
23760c2415Smrg class Dsymbol;
24760c2415Smrg class Declaration;
25760c2415Smrg class AggregateDeclaration;
26760c2415Smrg class ClassDeclaration;
27760c2415Smrg class EnumDeclaration;
28760c2415Smrg class FuncDeclaration;
29760c2415Smrg class StructDeclaration;
30760c2415Smrg class TypeInfoDeclaration;
31760c2415Smrg class VarDeclaration;
32760c2415Smrg class Expression;
33760c2415Smrg class ClassReferenceExp;
34760c2415Smrg class Module;
35760c2415Smrg class Statement;
36760c2415Smrg class Type;
37760c2415Smrg class TypeFunction;
38760c2415Smrg class Parameter;
39760c2415Smrg struct BaseClass;
40760c2415Smrg struct Scope;
41760c2415Smrg struct Loc;
42760c2415Smrg 
43760c2415Smrg template <typename TYPE> struct Array;
44760c2415Smrg typedef Array<Expression *> Expressions;
45760c2415Smrg 
46760c2415Smrg /* Usage of TREE_LANG_FLAG_?:
47760c2415Smrg    0: METHOD_CALL_EXPR
48760c2415Smrg    1: CALL_EXPR_ARGS_ORDERED (in CALL_EXPR).
49760c2415Smrg 
50760c2415Smrg    Usage of TYPE_LANG_FLAG_?:
51760c2415Smrg    0: TYPE_SHARED
52760c2415Smrg    1: TYPE_IMAGINARY_FLOAT (in REAL_TYPE).
53760c2415Smrg       ANON_AGGR_TYPE_P (in RECORD_TYPE, UNION_TYPE).
54760c2415Smrg    2: CLASS_TYPE_P (in RECORD_TYPE).
55760c2415Smrg    3: TYPE_DYNAMIC_ARRAY (in RECORD_TYPE).
56760c2415Smrg    4: TYPE_DELEGATE (in RECORD_TYPE).
57760c2415Smrg    5: TYPE_ASSOCIATIVE_ARRAY (in RECORD_TYPE).
58760c2415Smrg 
59760c2415Smrg    Usage of DECL_LANG_FLAG_?:
60760c2415Smrg    0: LABEL_VARIABLE_CASE (in LABEL_DECL).
61760c2415Smrg       DECL_BUILT_IN_CTFE (in FUNCTION_DECL).
62760c2415Smrg    1: DECL_IN_UNITTEST_CONDITION_P (in FUNCTION_DECL).  */
63760c2415Smrg 
64760c2415Smrg /* The kinds of scopes we recognize.  */
65760c2415Smrg 
66760c2415Smrg enum level_kind
67760c2415Smrg {
68760c2415Smrg   level_block,		/* An ordinary block scope.  */
69760c2415Smrg   level_try,		/* A try-block.  */
70760c2415Smrg   level_catch,		/* A catch-block.  */
71760c2415Smrg   level_finally,	/* A finally-block.  */
72760c2415Smrg   level_cond,		/* The scope for an if condition.  */
73760c2415Smrg   level_switch,		/* The scope for a switch statement.  */
74760c2415Smrg   level_loop,		/* A for, do-while, or unrolled-loop block.  */
75760c2415Smrg   level_with,		/* The scope for a with statement.  */
76760c2415Smrg   level_function	/* The block representing an entire function.  */
77760c2415Smrg };
78760c2415Smrg 
79760c2415Smrg /* List of codes for internally recognised compiler intrinsics.  */
80760c2415Smrg 
81760c2415Smrg enum intrinsic_code
82760c2415Smrg {
83760c2415Smrg #define DEF_D_INTRINSIC(CODE, A, N, M, D, C) INTRINSIC_ ## CODE,
84760c2415Smrg 
85760c2415Smrg #include "intrinsics.def"
86760c2415Smrg 
87760c2415Smrg #undef DEF_D_INTRINSIC
88760c2415Smrg   INTRINSIC_LAST
89760c2415Smrg };
90760c2415Smrg 
91760c2415Smrg /* For use with break and continue statements.  */
92760c2415Smrg 
93760c2415Smrg enum bc_kind
94760c2415Smrg {
95760c2415Smrg   bc_break    = 0,
96760c2415Smrg   bc_continue = 1
97760c2415Smrg };
98760c2415Smrg 
99760c2415Smrg /* The datatype used to implement D scope.  It is needed primarily to support
100760c2415Smrg    the back-end, but also helps debugging information for local variables.  */
101760c2415Smrg 
102760c2415Smrg struct GTY((chain_next ("%h.level_chain"))) binding_level
103760c2415Smrg {
104760c2415Smrg   /* A chain of declarations for all variables, constants and functions.
105760c2415Smrg      These are in the reverse of the order supplied.  */
106760c2415Smrg   tree names;
107760c2415Smrg 
108760c2415Smrg   /* For each level (except the global one), a chain of BLOCK nodes for
109760c2415Smrg      all the levels that were entered and exited one level down.  */
110760c2415Smrg   tree blocks;
111760c2415Smrg 
112760c2415Smrg   /* The binding level this one is contained in.  */
113760c2415Smrg   binding_level *level_chain;
114760c2415Smrg 
115760c2415Smrg   /* The kind of scope this object represents.  */
116760c2415Smrg   ENUM_BITFIELD (level_kind) kind : 4;
117760c2415Smrg };
118760c2415Smrg 
119760c2415Smrg /* The binding level currently in effect.  */
120760c2415Smrg extern GTY(()) binding_level *current_binding_level;
121760c2415Smrg extern GTY(()) binding_level *global_binding_level;
122760c2415Smrg 
123760c2415Smrg /* Used only for jumps to as-yet undefined labels, since jumps to
124760c2415Smrg    defined labels can have their validity checked immediately.  */
125760c2415Smrg 
126760c2415Smrg struct GTY((chain_next ("%h.next"))) d_label_use_entry
127760c2415Smrg {
128760c2415Smrg   d_label_use_entry *next;
129760c2415Smrg 
130760c2415Smrg   /* The frontend Statement associated with the jump.  */
131760c2415Smrg   Statement * GTY((skip)) statement;
132760c2415Smrg 
133760c2415Smrg   /* The binding level to which this entry is *currently* attached.
134760c2415Smrg      This is initially the binding level in which the goto appeared,
135760c2415Smrg      but is modified as scopes are closed.  */
136760c2415Smrg   binding_level *level;
137760c2415Smrg };
138760c2415Smrg 
139760c2415Smrg /* A list of all LABEL_DECLs in the function that have names.  Here so
140760c2415Smrg    we can clear out their names' definitions at the end of the
141760c2415Smrg    function, and so we can check the validity of jumps to these labels.  */
142760c2415Smrg 
143760c2415Smrg struct GTY(()) d_label_entry
144760c2415Smrg {
145760c2415Smrg   /* The label decl itself.  */
146760c2415Smrg   tree label;
147760c2415Smrg 
148760c2415Smrg   /* The frontend Statement associated with the label.  */
149760c2415Smrg   Statement * GTY((skip)) statement;
150760c2415Smrg 
151760c2415Smrg   /* The binding level to which the label is *currently* attached.
152760c2415Smrg      This is initially set to the binding level in which the label
153760c2415Smrg      is defined, but is modified as scopes are closed.  */
154760c2415Smrg   binding_level *level;
155760c2415Smrg 
156760c2415Smrg   /* A list of forward references of the label.  */
157760c2415Smrg   d_label_use_entry *fwdrefs;
158760c2415Smrg 
159760c2415Smrg   /* The following bits are set after the label is defined, and are
160760c2415Smrg      updated as scopes are popped.  They indicate that a backward jump
161760c2415Smrg      to the label will illegally enter a scope of the given flavor.  */
162760c2415Smrg   bool in_try_scope;
163760c2415Smrg   bool in_catch_scope;
164760c2415Smrg 
165760c2415Smrg   /* If set, the label we reference represents a break/continue pair.  */
166760c2415Smrg   bool bc_label;
167760c2415Smrg };
168760c2415Smrg 
169760c2415Smrg /* Frame information for a function declaration.  */
170760c2415Smrg 
171760c2415Smrg struct GTY(()) tree_frame_info
172760c2415Smrg {
173760c2415Smrg   struct tree_common common;
174760c2415Smrg   tree frame_type;
175760c2415Smrg };
176760c2415Smrg 
177760c2415Smrg /* True if the function creates a nested frame.  */
178760c2415Smrg #define FRAMEINFO_CREATES_FRAME(NODE) \
179760c2415Smrg   (TREE_LANG_FLAG_0 (FUNCFRAME_INFO_CHECK (NODE)))
180760c2415Smrg 
181760c2415Smrg /* True if the function has a static chain passed in its DECL_ARGUMENTS.  */
182760c2415Smrg #define FRAMEINFO_STATIC_CHAIN(NODE) \
183760c2415Smrg   (TREE_LANG_FLAG_1 (FUNCFRAME_INFO_CHECK (NODE)))
184760c2415Smrg 
185760c2415Smrg /* True if the function frame is a closure (initialized on the heap).  */
186760c2415Smrg #define FRAMEINFO_IS_CLOSURE(NODE) \
187760c2415Smrg   (TREE_LANG_FLAG_2 (FUNCFRAME_INFO_CHECK (NODE)))
188760c2415Smrg 
189760c2415Smrg #define FRAMEINFO_TYPE(NODE) \
190760c2415Smrg   (((tree_frame_info *) FUNCFRAME_INFO_CHECK (NODE))->frame_type)
191760c2415Smrg 
192760c2415Smrg /* Language-dependent contents of an identifier.  */
193760c2415Smrg 
194760c2415Smrg struct GTY(()) lang_identifier
195760c2415Smrg {
196760c2415Smrg   struct tree_identifier common;
197760c2415Smrg 
198760c2415Smrg   /* The identifier as the user sees it.  */
199760c2415Smrg   tree pretty_ident;
200760c2415Smrg 
201760c2415Smrg   /* The back-end tree associated with this identifier.  */
202760c2415Smrg   tree decl_tree;
203760c2415Smrg 
204760c2415Smrg   /* The frontend Declaration associated with this identifier.  */
205760c2415Smrg   Declaration * GTY((skip)) dsymbol;
206*0bfacb9bSmrg   AggregateDeclaration * GTY((skip)) daggregate;
207760c2415Smrg };
208760c2415Smrg 
209760c2415Smrg #define IDENTIFIER_LANG_SPECIFIC(NODE) \
210760c2415Smrg   ((struct lang_identifier *) IDENTIFIER_NODE_CHECK (NODE))
211760c2415Smrg 
212760c2415Smrg #define IDENTIFIER_PRETTY_NAME(NODE) \
213760c2415Smrg   (IDENTIFIER_LANG_SPECIFIC (NODE)->pretty_ident)
214760c2415Smrg 
215760c2415Smrg #define IDENTIFIER_DECL_TREE(NODE) \
216760c2415Smrg   (IDENTIFIER_LANG_SPECIFIC (NODE)->decl_tree)
217760c2415Smrg 
218760c2415Smrg #define IDENTIFIER_DSYMBOL(NODE) \
219760c2415Smrg   (IDENTIFIER_LANG_SPECIFIC (NODE)->dsymbol)
220760c2415Smrg 
221*0bfacb9bSmrg #define IDENTIFIER_DAGGREGATE(NODE) \
222*0bfacb9bSmrg   (IDENTIFIER_LANG_SPECIFIC (NODE)->daggregate)
223*0bfacb9bSmrg 
224760c2415Smrg /* Global state pertinent to the current function.  */
225760c2415Smrg 
226760c2415Smrg struct GTY(()) language_function
227760c2415Smrg {
228760c2415Smrg   /* Our function and enclosing module.  */
229760c2415Smrg   FuncDeclaration * GTY((skip)) function;
230760c2415Smrg   Module * GTY((skip)) module;
231760c2415Smrg 
232760c2415Smrg   /* Static chain of function, for D2, this is a closure.  */
233760c2415Smrg   tree static_chain;
234760c2415Smrg 
235760c2415Smrg   /* Stack of statement lists being collected while we are
236760c2415Smrg      compiling the function.  */
237760c2415Smrg   vec<tree, va_gc> *stmt_list;
238760c2415Smrg 
239760c2415Smrg   /* Variables that are in scope that will need destruction later.  */
240760c2415Smrg   vec<tree, va_gc> *vars_in_scope;
241760c2415Smrg 
242760c2415Smrg   /* Table of all used or defined labels in the function.  */
243760c2415Smrg   hash_map<Statement *, d_label_entry> *labels;
244760c2415Smrg };
245760c2415Smrg 
246760c2415Smrg /* The D front end types have not been integrated into the GCC garbage
247760c2415Smrg    collection system.  Handle this by using the "skip" attribute.  */
248760c2415Smrg 
249760c2415Smrg struct GTY(()) lang_decl
250760c2415Smrg {
251760c2415Smrg   Declaration * GTY((skip)) decl;
252760c2415Smrg 
253760c2415Smrg   /* FIELD_DECL in frame struct that this variable is allocated in.  */
254760c2415Smrg   tree frame_field;
255760c2415Smrg 
256760c2415Smrg   /* RESULT_DECL in a function that returns by nrvo.  */
257760c2415Smrg   tree named_result;
258760c2415Smrg 
259760c2415Smrg   /* Chain of DECL_LANG_THUNKS in a function.  */
260760c2415Smrg   tree thunks;
261760c2415Smrg 
262760c2415Smrg   /* In a FUNCTION_DECL, this is the THUNK_LANG_OFFSET.  */
263760c2415Smrg   int offset;
264760c2415Smrg 
265760c2415Smrg   /* In a FUNCTION_DECL, if this is an intrinsic, the code for it.  */
266760c2415Smrg   enum intrinsic_code intrinsic;
267760c2415Smrg 
268760c2415Smrg   /* FUNCFRAME_INFO in a function that has non-local references.  */
269760c2415Smrg   tree frame_info;
270760c2415Smrg };
271760c2415Smrg 
272760c2415Smrg /* The current D per-function global variables.  */
273760c2415Smrg 
274760c2415Smrg #define d_function_chain (cfun ? cfun->language : NULL)
275760c2415Smrg 
276760c2415Smrg /* The D frontend Declaration AST for GCC decl NODE.  */
277760c2415Smrg #define DECL_LANG_FRONTEND(NODE) \
278760c2415Smrg   (DECL_LANG_SPECIFIC (NODE) \
279760c2415Smrg    ? DECL_LANG_SPECIFIC (NODE)->decl : NULL)
280760c2415Smrg 
281760c2415Smrg #define SET_DECL_LANG_FRAME_FIELD(NODE, VAL) \
282760c2415Smrg   DECL_LANG_SPECIFIC (NODE)->frame_field = VAL
283760c2415Smrg 
284760c2415Smrg #define DECL_LANG_FRAME_FIELD(NODE) \
285760c2415Smrg   (DECL_P (NODE) \
286760c2415Smrg    ? DECL_LANG_SPECIFIC (NODE)->frame_field : NULL)
287760c2415Smrg 
288760c2415Smrg #define SET_DECL_LANG_NRVO(NODE, VAL) \
289760c2415Smrg   DECL_LANG_SPECIFIC (NODE)->named_result = VAL
290760c2415Smrg 
291760c2415Smrg #define DECL_LANG_NRVO(NODE) \
292760c2415Smrg   (DECL_P (NODE) \
293760c2415Smrg    ? DECL_LANG_SPECIFIC (NODE)->named_result : NULL)
294760c2415Smrg 
295760c2415Smrg #define DECL_LANG_THUNKS(NODE) \
296760c2415Smrg   DECL_LANG_SPECIFIC (NODE)->thunks
297760c2415Smrg 
298760c2415Smrg #define THUNK_LANG_OFFSET(NODE) \
299760c2415Smrg   DECL_LANG_SPECIFIC (NODE)->offset
300760c2415Smrg 
301760c2415Smrg #define DECL_INTRINSIC_CODE(NODE) \
302760c2415Smrg   DECL_LANG_SPECIFIC (NODE)->intrinsic
303760c2415Smrg 
304760c2415Smrg #define DECL_LANG_FRAMEINFO(NODE) \
305760c2415Smrg   DECL_LANG_SPECIFIC (NODE)->frame_info
306760c2415Smrg 
307760c2415Smrg /* The lang_type field is not set for every GCC type.  */
308760c2415Smrg 
309760c2415Smrg struct GTY(()) lang_type
310760c2415Smrg {
311760c2415Smrg   Type * GTY((skip)) type;
312760c2415Smrg };
313760c2415Smrg 
314760c2415Smrg /* The D frontend Type AST for GCC type NODE.  */
315760c2415Smrg #define TYPE_LANG_FRONTEND(NODE) \
316760c2415Smrg   (TYPE_LANG_SPECIFIC (NODE) \
317760c2415Smrg    ? TYPE_LANG_SPECIFIC (NODE)->type : NULL)
318760c2415Smrg 
319760c2415Smrg 
320760c2415Smrg enum d_tree_node_structure_enum
321760c2415Smrg {
322760c2415Smrg   TS_D_GENERIC,
323760c2415Smrg   TS_D_IDENTIFIER,
324760c2415Smrg   TS_D_FRAMEINFO,
325760c2415Smrg   LAST_TS_D_ENUM
326760c2415Smrg };
327760c2415Smrg 
328760c2415Smrg /* The resulting tree type.  */
329760c2415Smrg 
330760c2415Smrg union GTY((desc ("d_tree_node_structure (&%h)"),
331760c2415Smrg 	   chain_next ("CODE_CONTAINS_STRUCT (TREE_CODE (&%h.generic), TS_COMMON)"
332760c2415Smrg 		       " ? ((union lang_tree_node *) TREE_CHAIN (&%h.generic)) : NULL")))
333760c2415Smrg lang_tree_node
334760c2415Smrg {
335760c2415Smrg   union tree_node GTY ((tag ("TS_D_GENERIC"),
336760c2415Smrg 			desc ("tree_node_structure (&%h)"))) generic;
337760c2415Smrg   lang_identifier GTY ((tag ("TS_D_IDENTIFIER"))) identifier;
338760c2415Smrg   tree_frame_info GTY ((tag ("TS_D_FRAMEINFO"))) frameinfo;
339760c2415Smrg };
340760c2415Smrg 
341760c2415Smrg /* True if the Tdelegate typed expression is not really a variable,
342760c2415Smrg    but a literal function / method reference.  */
343760c2415Smrg #define METHOD_CALL_EXPR(NODE) \
344760c2415Smrg   (TREE_LANG_FLAG_0 (NODE))
345760c2415Smrg 
346760c2415Smrg /* True if all arguments in a call expression should be evaluated in the
347760c2415Smrg    order they are given (left to right).  */
348760c2415Smrg #define CALL_EXPR_ARGS_ORDERED(NODE) \
349760c2415Smrg   (TREE_LANG_FLAG_1 (CALL_EXPR_CHECK (NODE)))
350760c2415Smrg 
351760c2415Smrg /* True if the type was declared 'shared'.  */
352760c2415Smrg #define TYPE_SHARED(NODE) \
353760c2415Smrg   (TYPE_LANG_FLAG_0 (NODE))
354760c2415Smrg 
355760c2415Smrg /* True if the type is an imaginary float type.  */
356760c2415Smrg #define TYPE_IMAGINARY_FLOAT(NODE) \
357760c2415Smrg   (TYPE_LANG_FLAG_1 (REAL_TYPE_CHECK (NODE)))
358760c2415Smrg 
359760c2415Smrg /* True if the type is an anonymous record or union.  */
360760c2415Smrg #define ANON_AGGR_TYPE_P(NODE) \
361760c2415Smrg   (TYPE_LANG_FLAG_1 (RECORD_OR_UNION_CHECK (NODE)))
362760c2415Smrg 
363760c2415Smrg /* True if the type is the underlying record for a class.  */
364760c2415Smrg #define CLASS_TYPE_P(NODE) \
365760c2415Smrg   (TYPE_LANG_FLAG_2 (RECORD_TYPE_CHECK (NODE)))
366760c2415Smrg 
367760c2415Smrg /* True if the type is a D dynamic array.  */
368760c2415Smrg #define TYPE_DYNAMIC_ARRAY(NODE) \
369760c2415Smrg   (TYPE_LANG_FLAG_3 (RECORD_TYPE_CHECK (NODE)))
370760c2415Smrg 
371760c2415Smrg /* True if the type is a D delegate.  */
372760c2415Smrg #define TYPE_DELEGATE(NODE) \
373760c2415Smrg   (TYPE_LANG_FLAG_4 (RECORD_TYPE_CHECK (NODE)))
374760c2415Smrg 
375760c2415Smrg /* True if the type is a D associative array.  */
376760c2415Smrg #define TYPE_ASSOCIATIVE_ARRAY(NODE) \
377760c2415Smrg   (TYPE_LANG_FLAG_5 (RECORD_TYPE_CHECK (NODE)))
378760c2415Smrg 
379760c2415Smrg /* True if the decl is a variable case label decl.  */
380760c2415Smrg #define LABEL_VARIABLE_CASE(NODE) \
381760c2415Smrg   (DECL_LANG_FLAG_0 (LABEL_DECL_CHECK (NODE)))
382760c2415Smrg 
383760c2415Smrg /* True if the decl is a CTFE built-in.  */
384760c2415Smrg #define DECL_BUILT_IN_CTFE(NODE) \
385760c2415Smrg   (DECL_LANG_FLAG_0 (FUNCTION_DECL_CHECK (NODE)))
386760c2415Smrg 
387760c2415Smrg /* True if the decl is only compiled in when unittests are turned on.  */
388760c2415Smrg #define DECL_IN_UNITTEST_CONDITION_P(NODE) \
389760c2415Smrg   (DECL_LANG_FLAG_1 (FUNCTION_DECL_CHECK (NODE)))
390760c2415Smrg 
391760c2415Smrg enum d_tree_index
392760c2415Smrg {
393760c2415Smrg   DTI_VTABLE_ENTRY_TYPE,
394760c2415Smrg   DTI_VTBL_PTR_TYPE,
395760c2415Smrg   DTI_VTBL_INTERFACE_TYPE,
396760c2415Smrg 
397760c2415Smrg   DTI_BOOL_TYPE,
398760c2415Smrg   DTI_CHAR_TYPE,
399760c2415Smrg   DTI_WCHAR_TYPE,
400760c2415Smrg   DTI_DCHAR_TYPE,
401760c2415Smrg 
402760c2415Smrg   DTI_BYTE_TYPE,
403760c2415Smrg   DTI_UBYTE_TYPE,
404760c2415Smrg   DTI_SHORT_TYPE,
405760c2415Smrg   DTI_USHORT_TYPE,
406760c2415Smrg   DTI_INT_TYPE,
407760c2415Smrg   DTI_UINT_TYPE,
408760c2415Smrg   DTI_LONG_TYPE,
409760c2415Smrg   DTI_ULONG_TYPE,
410760c2415Smrg   DTI_CENT_TYPE,
411760c2415Smrg   DTI_UCENT_TYPE,
412760c2415Smrg 
413760c2415Smrg   DTI_IFLOAT_TYPE,
414760c2415Smrg   DTI_IDOUBLE_TYPE,
415760c2415Smrg   DTI_IREAL_TYPE,
416760c2415Smrg 
417760c2415Smrg   DTI_UNKNOWN_TYPE,
418760c2415Smrg 
419760c2415Smrg   DTI_ARRAY_TYPE,
420760c2415Smrg   DTI_NULL_ARRAY,
421760c2415Smrg 
422760c2415Smrg   DTI_MAX
423760c2415Smrg };
424760c2415Smrg 
425760c2415Smrg extern GTY(()) tree d_global_trees[DTI_MAX];
426760c2415Smrg 
427760c2415Smrg #define vtable_entry_type		d_global_trees[DTI_VTABLE_ENTRY_TYPE]
428760c2415Smrg #define vtbl_ptr_type_node		d_global_trees[DTI_VTBL_PTR_TYPE]
429760c2415Smrg #define vtbl_interface_type_node	d_global_trees[DTI_VTBL_INTERFACE_TYPE]
430760c2415Smrg /* D built-in language types.  */
431760c2415Smrg #define d_bool_type			d_global_trees[DTI_BOOL_TYPE]
432760c2415Smrg #define d_byte_type			d_global_trees[DTI_BYTE_TYPE]
433760c2415Smrg #define d_ubyte_type			d_global_trees[DTI_UBYTE_TYPE]
434760c2415Smrg #define d_short_type			d_global_trees[DTI_SHORT_TYPE]
435760c2415Smrg #define d_ushort_type			d_global_trees[DTI_USHORT_TYPE]
436760c2415Smrg #define d_int_type			d_global_trees[DTI_INT_TYPE]
437760c2415Smrg #define d_uint_type			d_global_trees[DTI_UINT_TYPE]
438760c2415Smrg #define d_long_type			d_global_trees[DTI_LONG_TYPE]
439760c2415Smrg #define d_ulong_type			d_global_trees[DTI_ULONG_TYPE]
440760c2415Smrg #define d_cent_type			d_global_trees[DTI_CENT_TYPE]
441760c2415Smrg #define d_ucent_type			d_global_trees[DTI_UCENT_TYPE]
442760c2415Smrg /* Imaginary floating-point types.  */
443760c2415Smrg #define ifloat_type_node		d_global_trees[DTI_IFLOAT_TYPE]
444760c2415Smrg #define idouble_type_node		d_global_trees[DTI_IDOUBLE_TYPE]
445760c2415Smrg #define ireal_type_node			d_global_trees[DTI_IREAL_TYPE]
446760c2415Smrg /* UTF-8, 16 and 32 types.  */
447760c2415Smrg #define char8_type_node			d_global_trees[DTI_CHAR_TYPE]
448760c2415Smrg #define char16_type_node		d_global_trees[DTI_DCHAR_TYPE]
449760c2415Smrg #define char32_type_node		d_global_trees[DTI_WCHAR_TYPE]
450760c2415Smrg /* Empty record type used as placeholder when real type is unknown.  */
451760c2415Smrg #define unknown_type_node		d_global_trees[DTI_UNKNOWN_TYPE]
452760c2415Smrg /* Generic dynamic array type void[].  */
453760c2415Smrg #define array_type_node			d_global_trees[DTI_ARRAY_TYPE]
454760c2415Smrg /* Null initializer for dynamic arrays.  */
455760c2415Smrg #define null_array_node			d_global_trees[DTI_NULL_ARRAY]
456760c2415Smrg 
457760c2415Smrg /* A prefix for internal variables, which are not user-visible.  */
458760c2415Smrg #if !defined (NO_DOT_IN_LABEL)
459760c2415Smrg # define GDC_PREFIX(x) "gdc." x
460760c2415Smrg #elif !defined (NO_DOLLAR_IN_LABEL)
461760c2415Smrg # define GDC_PREFIX(x) "gdc$" x
462760c2415Smrg #else
463760c2415Smrg # define GDC_PREFIX(x) "gdc_" x
464760c2415Smrg #endif
465760c2415Smrg 
466760c2415Smrg /* Internally recognised D runtime library functions.  */
467760c2415Smrg 
468760c2415Smrg enum libcall_fn
469760c2415Smrg {
470760c2415Smrg #define DEF_D_RUNTIME(CODE, N, T, P, F) LIBCALL_ ## CODE,
471760c2415Smrg 
472760c2415Smrg #include "runtime.def"
473760c2415Smrg 
474760c2415Smrg #undef DEF_D_RUNTIME
475760c2415Smrg   LIBCALL_LAST
476760c2415Smrg };
477760c2415Smrg 
478760c2415Smrg /* Gate for when the D frontend makes an early call into the codegen pass, such
479760c2415Smrg    as when it requires target information or CTFE evaluation.  As full semantic
480760c2415Smrg    may not be completed, we only want to build the superficial tree structure
481760c2415Smrg    without finishing any decls or types.  */
482760c2415Smrg extern bool doing_semantic_analysis_p;
483760c2415Smrg 
484760c2415Smrg /* In d-attribs.c.  */
485760c2415Smrg extern tree insert_type_attribute (tree, const char *, tree = NULL_TREE);
486760c2415Smrg extern tree insert_decl_attribute (tree, const char *, tree = NULL_TREE);
487*0bfacb9bSmrg extern void apply_user_attributes (Dsymbol *, tree);
488760c2415Smrg 
489760c2415Smrg /* In d-builtins.cc.  */
490760c2415Smrg extern const attribute_spec d_langhook_attribute_table[];
491760c2415Smrg extern const attribute_spec d_langhook_common_attribute_table[];
492760c2415Smrg 
493760c2415Smrg extern tree d_builtin_function (tree);
494*0bfacb9bSmrg extern tree d_builtin_function_ext_scope (tree);
495760c2415Smrg extern void d_init_builtins (void);
496760c2415Smrg extern void d_register_builtin_type (tree, const char *);
497760c2415Smrg extern void d_build_builtins_module (Module *);
498760c2415Smrg extern void d_maybe_set_builtin (Module *);
499760c2415Smrg extern Expression *d_eval_constant_expression (tree);
500760c2415Smrg extern void d_init_versions (void);
501760c2415Smrg 
502760c2415Smrg /* In d-codegen.cc.  */
503760c2415Smrg extern location_t make_location_t (const Loc &);
504760c2415Smrg extern tree d_decl_context (Dsymbol *);
505760c2415Smrg extern tree copy_aggregate_type (tree);
506760c2415Smrg extern bool declaration_reference_p (Declaration *);
507760c2415Smrg extern tree declaration_type (Declaration *);
508*0bfacb9bSmrg extern bool parameter_reference_p (Parameter *);
509*0bfacb9bSmrg extern tree parameter_type (Parameter *);
510760c2415Smrg extern tree build_integer_cst (dinteger_t, tree = d_int_type);
511760c2415Smrg extern tree build_float_cst (const real_t &, Type *);
512760c2415Smrg extern tree d_array_length (tree);
513760c2415Smrg extern tree d_array_ptr (tree);
514760c2415Smrg extern tree d_array_value (tree, tree, tree);
515760c2415Smrg extern tree get_array_length (tree, Type *);
516760c2415Smrg extern tree build_class_binfo (tree, ClassDeclaration *);
517760c2415Smrg extern tree build_interface_binfo (tree, ClassDeclaration *, unsigned &);
518760c2415Smrg extern tree delegate_method (tree);
519760c2415Smrg extern tree delegate_object (tree);
520760c2415Smrg extern tree build_delegate_cst (tree, tree, Type *);
521760c2415Smrg extern tree build_method_call (tree, tree, Type *);
522760c2415Smrg extern void extract_from_method_call (tree, tree &, tree &);
523760c2415Smrg extern tree build_typeof_null_value (Type *);
524760c2415Smrg extern tree build_vindex_ref (tree, tree, size_t);
525760c2415Smrg extern tree d_save_expr (tree);
526760c2415Smrg extern tree stabilize_expr (tree *);
527760c2415Smrg extern tree build_target_expr (tree, tree);
528760c2415Smrg extern tree force_target_expr (tree);
529760c2415Smrg extern tree build_address (tree);
530760c2415Smrg extern tree d_mark_addressable (tree);
531760c2415Smrg extern tree d_mark_used (tree);
532760c2415Smrg extern tree d_mark_read (tree);
533760c2415Smrg extern bool identity_compare_p (StructDeclaration *);
534760c2415Smrg extern tree build_float_identity (tree_code, tree, tree);
535760c2415Smrg extern tree build_struct_comparison (tree_code, StructDeclaration *,
536760c2415Smrg 				     tree, tree);
537760c2415Smrg extern tree build_array_struct_comparison (tree_code, StructDeclaration *,
538760c2415Smrg 					   tree, tree, tree);
539760c2415Smrg extern tree build_struct_literal (tree, vec<constructor_elt, va_gc> *);
540760c2415Smrg extern tree component_ref (tree, tree);
541760c2415Smrg extern tree build_assign (tree_code, tree, tree);
542760c2415Smrg extern tree modify_expr (tree, tree);
543760c2415Smrg extern tree build_nop (tree, tree);
544760c2415Smrg extern tree build_vconvert (tree, tree);
545760c2415Smrg extern tree build_boolop (tree_code, tree, tree);
546760c2415Smrg extern tree build_condition (tree, tree, tree, tree);
547760c2415Smrg extern tree build_vcondition (tree, tree, tree);
548760c2415Smrg extern tree compound_expr (tree, tree);
549760c2415Smrg extern tree return_expr (tree);
550760c2415Smrg extern tree size_mult_expr (tree, tree);
551760c2415Smrg extern tree real_part (tree);
552760c2415Smrg extern tree imaginary_part (tree);
553760c2415Smrg extern tree complex_expr (tree, tree, tree);
554760c2415Smrg extern tree indirect_ref (tree, tree);
555760c2415Smrg extern tree build_deref (tree);
556760c2415Smrg extern tree build_array_index (tree, tree);
557760c2415Smrg extern tree build_offset_op (tree_code, tree, tree);
558760c2415Smrg extern tree build_offset (tree, tree);
559760c2415Smrg extern tree build_memref (tree, tree, tree);
560760c2415Smrg extern tree build_array_set (tree, tree, tree);
561760c2415Smrg extern tree build_array_from_val (Type *, tree);
562760c2415Smrg extern tree void_okay_p (tree);
563760c2415Smrg extern tree build_bounds_condition (const Loc &, tree, tree, bool);
564760c2415Smrg extern bool array_bounds_check (void);
565760c2415Smrg extern tree bind_expr (tree, tree);
566760c2415Smrg extern TypeFunction *get_function_type (Type *);
567760c2415Smrg extern bool call_by_alias_p (FuncDeclaration *, FuncDeclaration *);
568760c2415Smrg extern tree d_build_call_expr (FuncDeclaration *, tree, Expressions *);
569760c2415Smrg extern tree d_build_call (TypeFunction *, tree, tree, Expressions *);
570760c2415Smrg extern tree d_assert_call (const Loc &, libcall_fn, tree = NULL_TREE);
571760c2415Smrg extern tree build_float_modulus (tree, tree, tree);
572760c2415Smrg extern tree build_vthis_function (tree, tree);
573*0bfacb9bSmrg extern tree error_no_frame_access (Dsymbol *);
574760c2415Smrg extern tree get_frame_for_symbol (Dsymbol *);
575760c2415Smrg extern tree build_vthis (AggregateDeclaration *);
576760c2415Smrg extern void build_closure (FuncDeclaration *);
577760c2415Smrg extern tree get_frameinfo (FuncDeclaration *);
578760c2415Smrg extern tree get_framedecl (FuncDeclaration *, FuncDeclaration *);
579760c2415Smrg 
580760c2415Smrg /* In d-convert.cc.  */
581760c2415Smrg extern bool decl_with_nonnull_addr_p (const_tree);
582760c2415Smrg extern tree d_truthvalue_conversion (tree);
583760c2415Smrg extern tree d_convert (tree, tree);
584760c2415Smrg extern tree convert_expr (tree, Type *, Type *);
585*0bfacb9bSmrg extern tree convert_for_rvalue (tree, Type *, Type *);
586760c2415Smrg extern tree convert_for_assignment (tree, Type *, Type *);
587760c2415Smrg extern tree convert_for_argument (tree, Parameter *);
588760c2415Smrg extern tree convert_for_condition (tree, Type *);
589760c2415Smrg extern tree d_array_convert (Expression *);
590*0bfacb9bSmrg extern tree d_array_convert (Type *, Expression *);
591760c2415Smrg 
592760c2415Smrg /* In d-incpath.cc.  */
593760c2415Smrg extern void add_import_paths (const char *, const char *, bool);
594760c2415Smrg 
595760c2415Smrg /* In d-lang.cc.  */
596760c2415Smrg extern void d_add_builtin_module (Module *);
597760c2415Smrg extern void d_add_entrypoint_module (Module *, Module *);
598760c2415Smrg extern d_tree_node_structure_enum d_tree_node_structure (lang_tree_node *);
599760c2415Smrg extern struct lang_type *build_lang_type (Type *);
600760c2415Smrg extern struct lang_decl *build_lang_decl (Declaration *);
601760c2415Smrg extern tree d_pushdecl (tree);
602760c2415Smrg extern tree d_unsigned_type (tree);
603760c2415Smrg extern tree d_signed_type (tree);
604760c2415Smrg extern void d_keep (tree);
605760c2415Smrg 
606760c2415Smrg /* In decl.cc.  */
607*0bfacb9bSmrg extern const char *d_mangle_decl (Dsymbol *);
608760c2415Smrg extern tree mangle_internal_decl (Dsymbol *, const char *, const char *);
609760c2415Smrg extern void build_decl_tree (Dsymbol *);
610760c2415Smrg extern tree get_symbol_decl (Declaration *);
611760c2415Smrg extern tree declare_extern_var (tree, tree);
612760c2415Smrg extern void declare_local_var (VarDeclaration *);
613760c2415Smrg extern tree build_local_temp (tree);
614760c2415Smrg extern tree get_decl_tree (Declaration *);
615760c2415Smrg extern void d_finish_decl (tree);
616760c2415Smrg extern tree make_thunk (FuncDeclaration *, int);
617760c2415Smrg extern tree start_function (FuncDeclaration *);
618760c2415Smrg extern void finish_function (tree);
619760c2415Smrg extern void mark_needed (tree);
620760c2415Smrg extern unsigned base_vtable_offset (ClassDeclaration *, BaseClass *);
621760c2415Smrg extern tree get_vtable_decl (ClassDeclaration *);
622760c2415Smrg extern tree build_new_class_expr (ClassReferenceExp *);
623760c2415Smrg extern tree aggregate_initializer_decl (AggregateDeclaration *);
624760c2415Smrg extern tree layout_struct_initializer (StructDeclaration *);
625760c2415Smrg extern tree layout_class_initializer (ClassDeclaration *);
626760c2415Smrg extern tree enum_initializer_decl (EnumDeclaration *);
627760c2415Smrg extern tree build_artificial_decl (tree, tree, const char * = NULL);
628760c2415Smrg extern tree create_field_decl (tree, const char *, int, int);
629760c2415Smrg extern void build_type_decl (tree, Dsymbol *);
630760c2415Smrg extern void d_comdat_linkage (tree);
631760c2415Smrg extern void d_linkonce_linkage (tree);
632760c2415Smrg 
633760c2415Smrg /* In expr.cc.  */
634760c2415Smrg extern tree build_expr (Expression *, bool = false);
635760c2415Smrg extern tree build_expr_dtor (Expression *);
636760c2415Smrg extern tree build_return_dtor (Expression *, Type *, TypeFunction *);
637760c2415Smrg 
638760c2415Smrg /* In imports.cc.  */
639760c2415Smrg extern tree build_import_decl (Dsymbol *);
640760c2415Smrg 
641760c2415Smrg /* In intrinsics.cc.  */
642760c2415Smrg extern void maybe_set_intrinsic (FuncDeclaration *);
643760c2415Smrg extern tree maybe_expand_intrinsic (tree);
644760c2415Smrg 
645760c2415Smrg /* In modules.cc.  */
646760c2415Smrg extern void build_module_tree (Module *);
647760c2415Smrg extern tree d_module_context (void);
648760c2415Smrg extern void register_module_decl (Declaration *);
649760c2415Smrg extern void d_finish_compilation (tree *, int);
650760c2415Smrg 
651760c2415Smrg /* In runtime.cc.  */
652760c2415Smrg extern tree build_libcall (libcall_fn, Type *, int ...);
653760c2415Smrg 
654760c2415Smrg /* In typeinfo.cc.  */
655760c2415Smrg extern bool have_typeinfo_p (ClassDeclaration *);
656760c2415Smrg extern tree layout_typeinfo (TypeInfoDeclaration *);
657760c2415Smrg extern tree layout_classinfo (ClassDeclaration *);
658760c2415Smrg extern tree get_typeinfo_decl (TypeInfoDeclaration *);
659760c2415Smrg extern tree get_classinfo_decl (ClassDeclaration *);
660*0bfacb9bSmrg extern void check_typeinfo_type (const Loc &, Scope *);
661760c2415Smrg extern tree build_typeinfo (const Loc &, Type *);
662760c2415Smrg extern void create_typeinfo (Type *, Module *);
663760c2415Smrg extern void create_tinfo_types (Module *);
664760c2415Smrg extern void layout_cpp_typeinfo (ClassDeclaration *);
665760c2415Smrg extern tree get_cpp_typeinfo_decl (ClassDeclaration *);
666760c2415Smrg extern bool speculative_type_p (Type *);
667760c2415Smrg 
668760c2415Smrg /* In toir.cc.  */
669760c2415Smrg extern void push_binding_level (level_kind);
670760c2415Smrg extern tree pop_binding_level (void);
671760c2415Smrg extern void push_stmt_list (void);
672760c2415Smrg extern tree pop_stmt_list (void);
673760c2415Smrg extern void add_stmt (tree);
674760c2415Smrg extern void build_function_body (FuncDeclaration *);
675760c2415Smrg 
676760c2415Smrg /* In types.cc.  */
677760c2415Smrg extern bool valist_array_p (Type *);
678760c2415Smrg extern bool empty_aggregate_p (tree);
679760c2415Smrg extern bool same_type_p (Type *, Type *);
680760c2415Smrg extern Type *get_object_type (void);
681760c2415Smrg extern tree make_array_type (Type *, unsigned HOST_WIDE_INT);
682760c2415Smrg extern tree make_struct_type (const char *, int n, ...);
683760c2415Smrg extern tree insert_type_modifiers (tree, unsigned);
684760c2415Smrg extern void insert_aggregate_field (tree, tree, size_t);
685*0bfacb9bSmrg extern void finish_aggregate_type (unsigned, unsigned, tree);
686760c2415Smrg extern tree build_ctype (Type *);
687760c2415Smrg 
688760c2415Smrg #endif  /* GCC_D_TREE_H  */
689