1 /* d-builtins.cc -- GCC builtins support for D.
2    Copyright (C) 2006-2019 Free Software Foundation, Inc.
3 
4 GCC is free software; you can redistribute it and/or modify
5 it under the terms of the GNU General Public License as published by
6 the Free Software Foundation; either version 3, or (at your option)
7 any later version.
8 
9 GCC is distributed in the hope that it will be useful,
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
12 GNU General Public License for more details.
13 
14 You should have received a copy of the GNU General Public License
15 along with GCC; see the file COPYING3.  If not see
16 <http://www.gnu.org/licenses/>.  */
17 
18 #include "config.h"
19 #include "system.h"
20 #include "coretypes.h"
21 
22 #include "dmd/attrib.h"
23 #include "dmd/aggregate.h"
24 #include "dmd/cond.h"
25 #include "dmd/declaration.h"
26 #include "dmd/expression.h"
27 #include "dmd/identifier.h"
28 #include "dmd/module.h"
29 #include "dmd/mtype.h"
30 
31 #include "tree.h"
32 #include "fold-const.h"
33 #include "diagnostic.h"
34 #include "langhooks.h"
35 #include "target.h"
36 #include "common/common-target.h"
37 #include "stringpool.h"
38 #include "stor-layout.h"
39 
40 #include "d-tree.h"
41 #include "d-target.h"
42 
43 
44 static GTY(()) vec<tree, va_gc> *gcc_builtins_functions = NULL;
45 static GTY(()) vec<tree, va_gc> *gcc_builtins_libfuncs = NULL;
46 static GTY(()) vec<tree, va_gc> *gcc_builtins_types = NULL;
47 
48 /* Record built-in types and their associated decls for re-use when
49    generating the `gcc.builtins' module.  */
50 
51 struct builtin_data
52 {
53   Type *dtype;
54   tree ctype;
55   Dsymbol *dsym;
56 
builtin_databuiltin_data57   builtin_data (Type *t, tree c, Dsymbol *d = NULL)
58     : dtype(t), ctype(c), dsym(d)
59   { }
60 };
61 
62 static vec<builtin_data> builtin_converted_decls;
63 
64 /* Build D frontend type from tree TYPE type given.  This will set the
65    back-end type symbol directly for complex types to save build_ctype()
66    the work.  For other types, it is not useful or will cause errors, such
67    as casting from `C char' to `D char', which also means that `char *`
68    needs to be specially handled.  */
69 
70 static Type *
build_frontend_type(tree type)71 build_frontend_type (tree type)
72 {
73   Type *dtype;
74   MOD mod = 0;
75 
76   if (TYPE_READONLY (type))
77     mod |= MODconst;
78   if (TYPE_VOLATILE (type))
79     mod |= MODshared;
80 
81   /* If we've seen the type before, re-use the converted decl.  */
82   for (size_t i = 0; i < builtin_converted_decls.length (); ++i)
83     {
84       tree t = builtin_converted_decls[i].ctype;
85       if (TYPE_MAIN_VARIANT (t) == TYPE_MAIN_VARIANT (type))
86 	return builtin_converted_decls[i].dtype;
87     }
88 
89   switch (TREE_CODE (type))
90     {
91     case POINTER_TYPE:
92       dtype = build_frontend_type (TREE_TYPE (type));
93       if (dtype)
94 	{
95 	  /* Check for char * first.  Needs to be done for chars/string.  */
96 	  if (TYPE_MAIN_VARIANT (TREE_TYPE (type)) == char_type_node)
97 	    return Type::tchar->addMod (dtype->mod)->pointerTo ()->addMod (mod);
98 
99 	  if (dtype->ty == Tfunction)
100 	    return (TypePointer::create (dtype))->addMod (mod);
101 
102 	  return dtype->pointerTo ()->addMod (mod);
103 	}
104       break;
105 
106     case REFERENCE_TYPE:
107       dtype = build_frontend_type (TREE_TYPE (type));
108       if (dtype)
109 	{
110 	  /* Want to assign ctype directly so that the REFERENCE_TYPE code
111 	     can be turned into as an `inout' argument.  Can't use pointerTo(),
112 	     because the returned Type is shared.  */
113 	  dtype = (TypePointer::create (dtype))->addMod (mod);
114 	  dtype->ctype = type;
115 	  builtin_converted_decls.safe_push (builtin_data (dtype, type));
116 	  return dtype;
117 	}
118       break;
119 
120     case BOOLEAN_TYPE:
121       /* Should be no need for size checking.  */
122       return Type::tbool->addMod (mod);
123 
124     case INTEGER_TYPE:
125     {
126       unsigned size = TREE_INT_CST_LOW (TYPE_SIZE_UNIT (type));
127       bool unsignedp = TYPE_UNSIGNED (type);
128 
129       /* For now, skip support for cent/ucent until the frontend
130 	 has better support for handling it.  */
131       for (size_t i = Tint8; i <= Tuns64; i++)
132 	{
133 	  dtype = Type::basic[i];
134 
135 	  /* Search for type matching size and signedness.  */
136 	  if (unsignedp != dtype->isunsigned ()
137 	      || size != dtype->size ())
138 	    continue;
139 
140 	  return dtype->addMod (mod);
141 	}
142       break;
143     }
144 
145     case REAL_TYPE:
146     {
147       unsigned size = TREE_INT_CST_LOW (TYPE_SIZE_UNIT (type));
148 
149       for (size_t i = Tfloat32; i <= Tfloat80; i++)
150 	{
151 	  dtype = Type::basic[i];
152 
153 	  /* Search for type matching size.  */
154 	  if (dtype->size () != size)
155 	    continue;
156 
157 	  return dtype->addMod (mod);
158 	}
159       break;
160     }
161 
162     case COMPLEX_TYPE:
163     {
164       unsigned size = TREE_INT_CST_LOW (TYPE_SIZE_UNIT (type));
165       for (size_t i = Tcomplex32; i <= Tcomplex80; i++)
166 	{
167 	  dtype = Type::basic[i];
168 
169 	  /* Search for type matching size.  */
170 	  if (dtype->size () != size)
171 	    continue;
172 
173 	  return dtype->addMod (mod);
174 	}
175       break;
176     }
177 
178     case VOID_TYPE:
179       return Type::tvoid->addMod (mod);
180 
181     case ARRAY_TYPE:
182       dtype = build_frontend_type (TREE_TYPE (type));
183       if (dtype)
184 	{
185 	  tree index = TYPE_DOMAIN (type);
186 	  tree ub = TYPE_MAX_VALUE (index);
187 	  tree lb = TYPE_MIN_VALUE (index);
188 
189 	  tree length = fold_build2 (MINUS_EXPR, TREE_TYPE (lb), ub, lb);
190 	  length = size_binop (PLUS_EXPR, size_one_node,
191 			       convert (sizetype, length));
192 
193 	  dtype = dtype->sarrayOf (TREE_INT_CST_LOW (length))->addMod (mod);
194 	  builtin_converted_decls.safe_push (builtin_data (dtype, type));
195 	  return dtype;
196 	}
197       break;
198 
199     case VECTOR_TYPE:
200       dtype = build_frontend_type (TREE_TYPE (type));
201       if (dtype)
202 	{
203 	  poly_uint64 nunits = TYPE_VECTOR_SUBPARTS (type);
204 	  dtype = dtype->sarrayOf (nunits.to_constant ())->addMod (mod);
205 
206 	  if (dtype->nextOf ()->isTypeBasic () == NULL)
207 	    break;
208 
209 	  dtype = (TypeVector::create (Loc (), dtype))->addMod (mod);
210 	  builtin_converted_decls.safe_push (builtin_data (dtype, type));
211 	  return dtype;
212 	}
213       break;
214 
215     case RECORD_TYPE:
216       if (TYPE_NAME (type))
217 	{
218 	  tree structname = DECL_NAME (TYPE_NAME (type));
219 	  Identifier *ident
220 	    = Identifier::idPool (IDENTIFIER_POINTER (structname));
221 
222 	  /* Neither the `object' and `gcc.builtins' modules will not exist when
223 	     this is called.  Use a stub 'object' module parent in the meantime.
224 	     If `gcc.builtins' is later imported, the parent will be overridden
225 	     with the correct module symbol.  */
226 	  static Identifier *object = Identifier::idPool ("object");
227 	  static Module *stubmod = Module::create ("object.d", object, 0, 0);
228 
229 	  StructDeclaration *sdecl = StructDeclaration::create (Loc (), ident,
230 								false);
231 	  sdecl->parent = stubmod;
232 	  sdecl->structsize = int_size_in_bytes (type);
233 	  sdecl->alignsize = TYPE_ALIGN_UNIT (type);
234 	  sdecl->alignment = STRUCTALIGN_DEFAULT;
235 	  sdecl->sizeok = SIZEOKdone;
236 	  sdecl->type = (TypeStruct::create (sdecl))->addMod (mod);
237 	  sdecl->type->ctype = type;
238 	  sdecl->type->merge2 ();
239 
240 	  /* Does not seem necessary to convert fields, but the members field
241 	     must be non-null for the above size setting to stick.  */
242 	  sdecl->members = new Dsymbols;
243 	  dtype = sdecl->type;
244 	  builtin_converted_decls.safe_push (builtin_data (dtype, type, sdecl));
245 	  return dtype;
246 	}
247       break;
248 
249     case FUNCTION_TYPE:
250       dtype = build_frontend_type (TREE_TYPE (type));
251       if (dtype)
252 	{
253 	  tree parms = TYPE_ARG_TYPES (type);
254 	  int varargs_p = 1;
255 
256 	  Parameters *args = new Parameters;
257 	  args->reserve (list_length (parms));
258 
259 	  /* Attempt to convert all parameter types.  */
260 	  for (tree parm = parms; parm != NULL_TREE; parm = TREE_CHAIN (parm))
261 	    {
262 	      tree argtype = TREE_VALUE (parm);
263 	      if (argtype == void_type_node)
264 		{
265 		  varargs_p = 0;
266 		  break;
267 		}
268 
269 	      StorageClass sc = STCundefined;
270 	      if (TREE_CODE (argtype) == REFERENCE_TYPE)
271 		{
272 		  argtype = TREE_TYPE (argtype);
273 		  sc |= STCref;
274 		}
275 
276 	      Type *targ = build_frontend_type (argtype);
277 	      if (!targ)
278 		{
279 		  delete args;
280 		  return NULL;
281 		}
282 
283 	      args->push (Parameter::create (sc, targ, NULL, NULL));
284 	    }
285 
286 	  /* GCC generic and placeholder built-ins are marked as variadic, yet
287 	     have no named parameters, and so can't be represented in D.  */
288 	  if (args->dim != 0 || !varargs_p)
289 	    {
290 	      dtype = TypeFunction::create (args, dtype, varargs_p, LINKc);
291 	      return dtype->addMod (mod);
292 	    }
293 	}
294       break;
295 
296     default:
297       break;
298     }
299 
300   return NULL;
301 }
302 
303 /* Attempt to convert GCC evaluated CST to a D Frontend Expression.
304    This is used for getting the CTFE value out of a const-folded builtin,
305    returns NULL if it cannot convert CST.  */
306 
307 Expression *
d_eval_constant_expression(tree cst)308 d_eval_constant_expression (tree cst)
309 {
310   STRIP_TYPE_NOPS (cst);
311   Type *type = build_frontend_type (TREE_TYPE (cst));
312 
313   if (type)
314     {
315       /* Convert our GCC CST tree into a D Expression.  This seems like we are
316 	 trying too hard, as these will only be converted back to a tree again
317 	 later in the codegen pass, but satisfies the need to have GCC built-ins
318 	 CTFE-able in the frontend.  */
319       tree_code code = TREE_CODE (cst);
320       if (code == COMPLEX_CST)
321 	{
322 	  real_value re = TREE_REAL_CST (TREE_REALPART (cst));
323 	  real_value im = TREE_REAL_CST (TREE_IMAGPART (cst));
324 	  complex_t value = complex_t (ldouble (re), ldouble (im));
325 	  return ComplexExp::create (Loc (), value, type);
326 	}
327       else if (code == INTEGER_CST)
328 	{
329 	  dinteger_t value = TREE_INT_CST_LOW (cst);
330 	  return IntegerExp::create (Loc (), value, type);
331 	}
332       else if (code == REAL_CST)
333 	{
334 	  real_value value = TREE_REAL_CST (cst);
335 	  return RealExp::create (Loc (), ldouble (value), type);
336 	}
337       else if (code == STRING_CST)
338 	{
339 	  const void *string = TREE_STRING_POINTER (cst);
340 	  size_t len = TREE_STRING_LENGTH (cst);
341 	  return StringExp::create (Loc (), CONST_CAST (void *, string), len);
342 	}
343       else if (code == VECTOR_CST)
344 	{
345 	  dinteger_t nunits = VECTOR_CST_NELTS (cst).to_constant ();
346 	  Expressions *elements = new Expressions;
347 	  elements->setDim (nunits);
348 
349 	  for (size_t i = 0; i < nunits; i++)
350 	    {
351 	      Expression *elem
352 		= d_eval_constant_expression (VECTOR_CST_ELT (cst, i));
353 	      if (elem == NULL)
354 		return NULL;
355 
356 	      (*elements)[i] = elem;
357 	    }
358 
359 	  Expression *e = ArrayLiteralExp::create (Loc (), elements);
360 	  e->type = ((TypeVector *) type)->basetype;
361 
362 	  return VectorExp::create (Loc (), e, type);
363 	}
364     }
365 
366   return NULL;
367 }
368 
369 /* Callback for TARGET_D_CPU_VERSIONS and TARGET_D_OS_VERSIONS.
370    Adds IDENT to the list of predefined version identifiers.  */
371 
372 void
d_add_builtin_version(const char * ident)373 d_add_builtin_version (const char* ident)
374 {
375   /* For now, we need to tell the D frontend what platform is being targeted.
376      This should be removed once the frontend has been fixed.  */
377   if (strcmp (ident, "linux") == 0)
378     global.params.isLinux = true;
379   else if (strcmp (ident, "OSX") == 0)
380     global.params.isOSX = true;
381   else if (strcmp (ident, "Windows") == 0)
382     global.params.isWindows = true;
383   else if (strcmp (ident, "FreeBSD") == 0)
384     global.params.isFreeBSD = true;
385   else if (strcmp (ident, "OpenBSD") == 0)
386     global.params.isOpenBSD = true;
387   else if (strcmp (ident, "Solaris") == 0)
388     global.params.isSolaris = true;
389   /* The is64bit field only refers to x86_64 target.  */
390   else if (strcmp (ident, "X86_64") == 0)
391     global.params.is64bit = true;
392   /* No other fields are required to be set for the frontend.  */
393 
394   VersionCondition::addPredefinedGlobalIdent (ident);
395 }
396 
397 /* Initialize the list of all the predefined version identifiers.  */
398 
399 void
d_init_versions(void)400 d_init_versions (void)
401 {
402   VersionCondition::addPredefinedGlobalIdent ("GNU");
403   VersionCondition::addPredefinedGlobalIdent ("D_Version2");
404 
405   if (BYTES_BIG_ENDIAN)
406     VersionCondition::addPredefinedGlobalIdent ("BigEndian");
407   else
408     VersionCondition::addPredefinedGlobalIdent ("LittleEndian");
409 
410   if (targetm_common.except_unwind_info (&global_options) == UI_SJLJ)
411     VersionCondition::addPredefinedGlobalIdent ("GNU_SjLj_Exceptions");
412   else if (targetm_common.except_unwind_info (&global_options) == UI_SEH)
413     VersionCondition::addPredefinedGlobalIdent ("GNU_SEH_Exceptions");
414   else if (targetm_common.except_unwind_info (&global_options) == UI_DWARF2)
415     VersionCondition::addPredefinedGlobalIdent ("GNU_DWARF2_Exceptions");
416 
417   if (!targetm.have_tls)
418     VersionCondition::addPredefinedGlobalIdent ("GNU_EMUTLS");
419 
420   if (STACK_GROWS_DOWNWARD)
421     VersionCondition::addPredefinedGlobalIdent ("GNU_StackGrowsDown");
422 
423   /* Should define this anyway to set us apart from the competition.  */
424   VersionCondition::addPredefinedGlobalIdent ("GNU_InlineAsm");
425 
426   /* LP64 only means 64bit pointers in D.  */
427   if (global.params.isLP64)
428     VersionCondition::addPredefinedGlobalIdent ("D_LP64");
429 
430   /* Setting `global.params.cov' forces module info generation which is
431      not needed for the GCC coverage implementation.  Instead, just
432      test flag_test_coverage while leaving `global.params.cov' unset.  */
433   if (flag_test_coverage)
434     VersionCondition::addPredefinedGlobalIdent ("D_Coverage");
435   if (flag_pic)
436     VersionCondition::addPredefinedGlobalIdent ("D_PIC");
437 
438   if (global.params.doDocComments)
439     VersionCondition::addPredefinedGlobalIdent ("D_Ddoc");
440 
441   if (global.params.useUnitTests)
442     VersionCondition::addPredefinedGlobalIdent ("unittest");
443 
444   if (global.params.useAssert)
445     VersionCondition::addPredefinedGlobalIdent ("assert");
446 
447   if (global.params.useArrayBounds == BOUNDSCHECKoff)
448     VersionCondition::addPredefinedGlobalIdent ("D_NoBoundsChecks");
449 
450   if (global.params.betterC)
451     VersionCondition::addPredefinedGlobalIdent ("D_BetterC");
452   else
453     {
454       VersionCondition::addPredefinedGlobalIdent ("D_ModuleInfo");
455       VersionCondition::addPredefinedGlobalIdent ("D_Exceptions");
456       VersionCondition::addPredefinedGlobalIdent ("D_TypeInfo");
457     }
458 
459   VersionCondition::addPredefinedGlobalIdent ("all");
460 
461   /* Emit all target-specific version identifiers.  */
462   targetdm.d_cpu_versions ();
463   targetdm.d_os_versions ();
464 
465   VersionCondition::addPredefinedGlobalIdent ("CppRuntime_Gcc");
466 }
467 
468 /* A helper for d_build_builtins_module.  Return a new ALIAS for TYPE.
469    Analogous to `alias ALIAS = TYPE' in D code.  */
470 
471 static AliasDeclaration *
build_alias_declaration(const char * alias,Type * type)472 build_alias_declaration (const char *alias, Type *type)
473 {
474   return AliasDeclaration::create (Loc (), Identifier::idPool (alias), type);
475 }
476 
477 /* A helper function for Target::loadModule.  Generates all code for the
478    `gcc.builtins' module, whose frontend symbol should be M.  */
479 
480 void
d_build_builtins_module(Module * m)481 d_build_builtins_module (Module *m)
482 {
483   Dsymbols *members = new Dsymbols;
484   tree decl;
485 
486   for (size_t i = 0; vec_safe_iterate (gcc_builtins_functions, i, &decl); ++i)
487     {
488       const char *name = IDENTIFIER_POINTER (DECL_NAME (decl));
489       TypeFunction *tf
490 	= (TypeFunction *) build_frontend_type (TREE_TYPE (decl));
491 
492       /* Cannot create built-in function type for DECL.  */
493       if (!tf)
494 	continue;
495 
496       /* A few notes on D2 attributes applied to builtin functions:
497 	 - It is assumed that built-ins solely provided by the compiler are
498 	   considered @safe and pure.
499 	 - Built-ins that correspond to `extern(C)' functions in the standard
500 	   library that have `__attribute__(nothrow)' are considered `@trusted'.
501 	 - The purity of a built-in can vary depending on compiler flags set
502 	   upon initialization, or by the `-foptions' passed, such as
503 	   flag_unsafe_math_optimizations.
504 	 - Built-ins never use the GC or raise a D exception, and so are always
505 	   marked as `nothrow' and `@nogc'.  */
506       tf->purity = DECL_PURE_P (decl) ? PUREstrong
507 	: TREE_READONLY (decl) ? PUREconst
508 	: DECL_IS_NOVOPS (decl) ? PUREweak
509 	: !DECL_ASSEMBLER_NAME_SET_P (decl) ? PUREweak
510 	: PUREimpure;
511       tf->trust = !DECL_ASSEMBLER_NAME_SET_P (decl) ? TRUSTsafe
512 	: TREE_NOTHROW (decl) ? TRUSTtrusted
513 	: TRUSTsystem;
514       tf->isnothrow = true;
515       tf->isnogc = true;
516 
517       FuncDeclaration *func
518 	= FuncDeclaration::create (Loc (), Loc (),
519 				   Identifier::idPool (name),
520 				   STCextern, tf);
521       DECL_LANG_SPECIFIC (decl) = build_lang_decl (func);
522       func->csym = decl;
523       func->builtin = BUILTINyes;
524 
525       members->push (func);
526     }
527 
528   for (size_t i = 0; vec_safe_iterate (gcc_builtins_types, i, &decl); ++i)
529     {
530       const char *name = IDENTIFIER_POINTER (DECL_NAME (decl));
531       Type *t = build_frontend_type (TREE_TYPE (decl));
532 
533       /* Cannot create built-in type for DECL.  */
534       if (!t)
535 	continue;
536 
537       members->push (build_alias_declaration (name, t));
538     }
539 
540   /* Iterate through the target-specific builtin types for va_list.  */
541   if (targetm.enum_va_list_p)
542     {
543       const char *name;
544       tree type;
545 
546       for (int i = 0; targetm.enum_va_list_p (i, &name, &type); ++i)
547 	{
548 	  Type *t = build_frontend_type (type);
549 	  /* Cannot create built-in type.  */
550 	  if (!t)
551 	    continue;
552 
553 	  members->push (build_alias_declaration (name, t));
554 	}
555     }
556 
557   /* Push out declarations for any RECORD_TYPE types encountered when building
558      all builtin functions and types.  */
559   for (size_t i = 0; i < builtin_converted_decls.length (); ++i)
560     {
561       /* Currently, there is no need to run semantic, but we do want to output
562 	 initializers, typeinfo, and others on demand.  */
563       Dsymbol *dsym = builtin_converted_decls[i].dsym;
564       if (dsym != NULL)
565 	{
566 	  dsym->parent = m;
567 	  members->push (dsym);
568 	}
569     }
570 
571   /* va_list should already be built, so no need to convert to D type again.  */
572   members->push (build_alias_declaration ("__builtin_va_list", Type::tvalist));
573 
574   /* Expose target-specific integer types to the builtins module.  */
575   {
576     Type *t = build_frontend_type (long_integer_type_node);
577     members->push (build_alias_declaration ("__builtin_clong", t));
578 
579     t = build_frontend_type (long_unsigned_type_node);
580     members->push (build_alias_declaration ("__builtin_culong", t));
581 
582     t = build_frontend_type (long_long_integer_type_node);
583     members->push (build_alias_declaration ("__builtin_clonglong", t));
584 
585     t = build_frontend_type (long_long_unsigned_type_node);
586     members->push (build_alias_declaration ("__builtin_culonglong", t));
587 
588     t = build_frontend_type (lang_hooks.types.type_for_mode (byte_mode, 0));
589     members->push (build_alias_declaration ("__builtin_machine_byte", t));
590 
591     t = build_frontend_type (lang_hooks.types.type_for_mode (byte_mode, 1));
592     members->push (build_alias_declaration ("__builtin_machine_ubyte", t));
593 
594     t = build_frontend_type (lang_hooks.types.type_for_mode (word_mode, 0));
595     members->push (build_alias_declaration ("__builtin_machine_int", t));
596 
597     t = build_frontend_type (lang_hooks.types.type_for_mode (word_mode, 1));
598     members->push (build_alias_declaration ("__builtin_machine_uint", t));
599 
600     t = build_frontend_type (lang_hooks.types.type_for_mode (ptr_mode, 0));
601     members->push (build_alias_declaration ("__builtin_pointer_int", t));
602 
603     t = build_frontend_type (lang_hooks.types.type_for_mode (ptr_mode, 1));
604     members->push (build_alias_declaration ("__builtin_pointer_uint", t));
605 
606     /* _Unwind_Word has its own target specific mode.  */
607     machine_mode mode = targetm.unwind_word_mode ();
608     t = build_frontend_type (lang_hooks.types.type_for_mode (mode, 0));
609     members->push (build_alias_declaration ("__builtin_unwind_int", t));
610 
611     t = build_frontend_type (lang_hooks.types.type_for_mode (mode, 1));
612     members->push (build_alias_declaration ("__builtin_unwind_uint", t));
613   }
614 
615   m->members->push (LinkDeclaration::create (LINKc, members));
616 }
617 
618 /* Search for any `extern(C)' functions that match any known GCC library builtin
619    function in D and override its internal back-end symbol.  */
620 
621 static void
maybe_set_builtin_1(Dsymbol * d)622 maybe_set_builtin_1 (Dsymbol *d)
623 {
624   AttribDeclaration *ad = d->isAttribDeclaration ();
625   FuncDeclaration *fd = d->isFuncDeclaration ();
626 
627   if (ad != NULL)
628     {
629       /* Recursively search through attribute decls.  */
630       Dsymbols *decls = ad->include (NULL, NULL);
631       if (decls && decls->dim)
632 	{
633 	  for (size_t i = 0; i < decls->dim; i++)
634 	    {
635 	      Dsymbol *sym = (*decls)[i];
636 	      maybe_set_builtin_1 (sym);
637 	    }
638 	}
639     }
640   else if (fd && !fd->fbody)
641     {
642       tree t;
643 
644       for (size_t i = 0; vec_safe_iterate (gcc_builtins_libfuncs, i, &t); ++i)
645 	{
646 	  gcc_assert (DECL_ASSEMBLER_NAME_SET_P (t));
647 
648 	  const char *name = IDENTIFIER_POINTER (DECL_ASSEMBLER_NAME (t));
649 	  if (fd->ident != Identifier::idPool (name))
650 	    continue;
651 
652 	  /* Found a match, tell the frontend this is a builtin.  */
653 	  DECL_LANG_SPECIFIC (t) = build_lang_decl (fd);
654 	  fd->csym = t;
655 	  fd->builtin = BUILTINyes;
656 	  return;
657 	}
658     }
659 }
660 
661 /* A helper function for Target::loadModule.  Traverse all members in module M
662    to search for any functions that can be mapped to any GCC builtin.  */
663 
664 void
d_maybe_set_builtin(Module * m)665 d_maybe_set_builtin (Module *m)
666 {
667   if (!m || !m->members)
668     return;
669 
670   for (size_t i = 0; i < m->members->dim; i++)
671     {
672       Dsymbol *sym = (*m->members)[i];
673       maybe_set_builtin_1 (sym);
674     }
675 }
676 
677 /* Used to help initialize the builtin-types.def table.  When a type of
678    the correct size doesn't exist, use error_mark_node instead of NULL.
679    The latter results in segfaults even when a decl using the type doesn't
680    get invoked.  */
681 
682 static tree
builtin_type_for_size(int size,bool unsignedp)683 builtin_type_for_size (int size, bool unsignedp)
684 {
685   tree type = lang_hooks.types.type_for_size (size, unsignedp);
686   return type ? type : error_mark_node;
687 }
688 
689 /* Support for DEF_BUILTIN.  */
690 
691 static void
do_build_builtin_fn(built_in_function fncode,const char * name,built_in_class fnclass,tree fntype,bool both_p,bool fallback_p,tree fnattrs,bool implicit_p)692 do_build_builtin_fn (built_in_function fncode,
693 		     const char *name,
694 		     built_in_class fnclass,
695 		     tree fntype, bool both_p, bool fallback_p,
696 		     tree fnattrs, bool implicit_p)
697 {
698   tree decl;
699   const char *libname;
700 
701   if (fntype == error_mark_node)
702     return;
703 
704   gcc_assert ((!both_p && !fallback_p)
705 	      || !strncmp (name, "__builtin_",
706 			   strlen ("__builtin_")));
707 
708   libname = name + strlen ("__builtin_");
709 
710   decl = add_builtin_function (name, fntype, fncode, fnclass,
711 			       fallback_p ? libname : NULL, fnattrs);
712 
713   set_builtin_decl (fncode, decl, implicit_p);
714 }
715 
716 /* Standard data types to be used in builtin argument declarations.  */
717 
718 static GTY(()) tree string_type_node;
719 static GTY(()) tree const_string_type_node;
720 static GTY(()) tree wint_type_node;
721 static GTY(()) tree intmax_type_node;
722 static GTY(()) tree uintmax_type_node;
723 static GTY(()) tree signed_size_type_node;
724 
725 
726 /* Build nodes that would have been created by the C front-end; necessary
727    for including builtin-types.def and ultimately builtins.def.  */
728 
729 static void
d_build_c_type_nodes(void)730 d_build_c_type_nodes (void)
731 {
732   void_list_node = build_tree_list (NULL_TREE, void_type_node);
733   string_type_node = build_pointer_type (char_type_node);
734   const_string_type_node
735     = build_pointer_type (build_qualified_type (char_type_node,
736 						TYPE_QUAL_CONST));
737 
738   if (strcmp (SIZE_TYPE, "unsigned int") == 0)
739     {
740       intmax_type_node = integer_type_node;
741       uintmax_type_node = unsigned_type_node;
742       signed_size_type_node = integer_type_node;
743     }
744   else if (strcmp (SIZE_TYPE, "long unsigned int") == 0)
745     {
746       intmax_type_node = long_integer_type_node;
747       uintmax_type_node = long_unsigned_type_node;
748       signed_size_type_node = long_integer_type_node;
749     }
750   else if (strcmp (SIZE_TYPE, "long long unsigned int") == 0)
751     {
752       intmax_type_node = long_long_integer_type_node;
753       uintmax_type_node = long_long_unsigned_type_node;
754       signed_size_type_node = long_long_integer_type_node;
755     }
756   else
757     gcc_unreachable ();
758 
759   wint_type_node = unsigned_type_node;
760   pid_type_node = integer_type_node;
761 }
762 
763 /* Build nodes that are used by the D front-end.
764    These are distinct from C types.  */
765 
766 static void
d_build_d_type_nodes(void)767 d_build_d_type_nodes (void)
768 {
769   /* Integral types.  */
770   d_byte_type = make_signed_type (8);
771   d_ubyte_type = make_unsigned_type (8);
772 
773   d_short_type = make_signed_type (16);
774   d_ushort_type = make_unsigned_type (16);
775 
776   d_int_type = make_signed_type (32);
777   d_uint_type = make_unsigned_type (32);
778 
779   d_long_type = make_signed_type (64);
780   d_ulong_type = make_unsigned_type (64);
781 
782   d_cent_type = make_signed_type (128);
783   d_ucent_type = make_unsigned_type (128);
784 
785   {
786     /* Re-define size_t as a D type.  */
787     machine_mode type_mode = TYPE_MODE (size_type_node);
788     size_type_node = lang_hooks.types.type_for_mode (type_mode, 1);
789   }
790 
791   /* Bool and Character types.  */
792   d_bool_type = make_unsigned_type (1);
793   TREE_SET_CODE (d_bool_type, BOOLEAN_TYPE);
794 
795   char8_type_node = make_unsigned_type (8);
796   TYPE_STRING_FLAG (char8_type_node) = 1;
797 
798   char16_type_node = make_unsigned_type (16);
799   TYPE_STRING_FLAG (char16_type_node) = 1;
800 
801   char32_type_node = make_unsigned_type (32);
802   TYPE_STRING_FLAG (char32_type_node) = 1;
803 
804   /* Imaginary types.  */
805   ifloat_type_node = build_distinct_type_copy (float_type_node);
806   TYPE_IMAGINARY_FLOAT (ifloat_type_node) = 1;
807 
808   idouble_type_node = build_distinct_type_copy (double_type_node);
809   TYPE_IMAGINARY_FLOAT (idouble_type_node) = 1;
810 
811   ireal_type_node = build_distinct_type_copy (long_double_type_node);
812   TYPE_IMAGINARY_FLOAT (ireal_type_node) = 1;
813 
814   /* Used for ModuleInfo, ClassInfo, and Interface decls.  */
815   unknown_type_node = make_node (RECORD_TYPE);
816 
817   /* Make sure we get a unique function type, so we can give
818      its pointer type a name.  (This wins for gdb).  */
819   {
820     tree vfunc_type = make_node (FUNCTION_TYPE);
821     TREE_TYPE (vfunc_type) = d_int_type;
822     TYPE_ARG_TYPES (vfunc_type) = NULL_TREE;
823     layout_type (vfunc_type);
824 
825     vtable_entry_type = build_pointer_type (vfunc_type);
826   }
827 
828   vtbl_ptr_type_node = build_pointer_type (vtable_entry_type);
829   layout_type (vtbl_ptr_type_node);
830 
831   /* When an object is accessed via an interface, this type appears
832      as the first entry in its vtable.  */
833   {
834     tree domain = build_index_type (size_int (3));
835     vtbl_interface_type_node = build_array_type (ptr_type_node, domain);
836   }
837 
838   /* Use `void[]' as a generic dynamic array type.  */
839   array_type_node = make_struct_type ("__builtin_void[]", 2,
840 				      get_identifier ("length"), size_type_node,
841 				      get_identifier ("ptr"), ptr_type_node);
842   TYPE_DYNAMIC_ARRAY (array_type_node) = 1;
843 
844   null_array_node = d_array_value (array_type_node, size_zero_node,
845 				   null_pointer_node);
846 }
847 
848 /* Handle default attributes.  */
849 
850 enum built_in_attribute
851 {
852 #define DEF_ATTR_NULL_TREE(ENUM) ENUM,
853 #define DEF_ATTR_INT(ENUM, VALUE) ENUM,
854 #define DEF_ATTR_STRING(ENUM, VALUE) ENUM,
855 #define DEF_ATTR_IDENT(ENUM, STRING) ENUM,
856 #define DEF_ATTR_TREE_LIST(ENUM, PURPOSE, VALUE, CHAIN) ENUM,
857 #include "builtin-attrs.def"
858 #undef DEF_ATTR_NULL_TREE
859 #undef DEF_ATTR_INT
860 #undef DEF_ATTR_STRING
861 #undef DEF_ATTR_IDENT
862 #undef DEF_ATTR_TREE_LIST
863   ATTR_LAST
864 };
865 
866 static GTY(()) tree built_in_attributes[(int) ATTR_LAST];
867 
868 /* Initialize the attribute table for all the supported builtins.  */
869 
870 static void
d_init_attributes(void)871 d_init_attributes (void)
872 {
873   /* Fill in the built_in_attributes array.  */
874 #define DEF_ATTR_NULL_TREE(ENUM)	\
875   built_in_attributes[(int) ENUM] = NULL_TREE;
876 # define DEF_ATTR_INT(ENUM, VALUE)	\
877   built_in_attributes[(int) ENUM] = build_int_cst (NULL_TREE, VALUE);
878 #define DEF_ATTR_STRING(ENUM, VALUE)	\
879   built_in_attributes[(int) ENUM] = build_string (strlen (VALUE), VALUE);
880 #define DEF_ATTR_IDENT(ENUM, STRING)	\
881   built_in_attributes[(int) ENUM] = get_identifier (STRING);
882 #define DEF_ATTR_TREE_LIST(ENUM, PURPOSE, VALUE, CHAIN)	\
883   built_in_attributes[(int) ENUM]			\
884   = tree_cons (built_in_attributes[(int) PURPOSE],	\
885 	       built_in_attributes[(int) VALUE],	\
886 	       built_in_attributes[(int) CHAIN]);
887 #include "builtin-attrs.def"
888 #undef DEF_ATTR_NULL_TREE
889 #undef DEF_ATTR_INT
890 #undef DEF_ATTR_STRING
891 #undef DEF_ATTR_IDENT
892 #undef DEF_ATTR_TREE_LIST
893 }
894 
895 /* Builtin types.  */
896 
897 enum d_builtin_type
898 {
899 #define DEF_PRIMITIVE_TYPE(NAME, VALUE) NAME,
900 #define DEF_FUNCTION_TYPE_0(NAME, RETURN) NAME,
901 #define DEF_FUNCTION_TYPE_1(NAME, RETURN, ARG1) NAME,
902 #define DEF_FUNCTION_TYPE_2(NAME, RETURN, ARG1, ARG2) NAME,
903 #define DEF_FUNCTION_TYPE_3(NAME, RETURN, ARG1, ARG2, ARG3) NAME,
904 #define DEF_FUNCTION_TYPE_4(NAME, RETURN, ARG1, ARG2, ARG3, ARG4) NAME,
905 #define DEF_FUNCTION_TYPE_5(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5) NAME,
906 #define DEF_FUNCTION_TYPE_6(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
907 			    ARG6) NAME,
908 #define DEF_FUNCTION_TYPE_7(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
909 			    ARG6, ARG7) NAME,
910 #define DEF_FUNCTION_TYPE_8(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
911 			    ARG6, ARG7, ARG8) NAME,
912 #define DEF_FUNCTION_TYPE_9(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
913 			    ARG6, ARG7, ARG8, ARG9) NAME,
914 #define DEF_FUNCTION_TYPE_10(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
915 			     ARG6, ARG7, ARG8, ARG9, ARG10) NAME,
916 #define DEF_FUNCTION_TYPE_11(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
917 			     ARG6, ARG7, ARG8, ARG9, ARG10, ARG11) NAME,
918 #define DEF_FUNCTION_TYPE_VAR_0(NAME, RETURN) NAME,
919 #define DEF_FUNCTION_TYPE_VAR_1(NAME, RETURN, ARG1) NAME,
920 #define DEF_FUNCTION_TYPE_VAR_2(NAME, RETURN, ARG1, ARG2) NAME,
921 #define DEF_FUNCTION_TYPE_VAR_3(NAME, RETURN, ARG1, ARG2, ARG3) NAME,
922 #define DEF_FUNCTION_TYPE_VAR_4(NAME, RETURN, ARG1, ARG2, ARG3, ARG4) NAME,
923 #define DEF_FUNCTION_TYPE_VAR_5(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5) \
924 				NAME,
925 #define DEF_FUNCTION_TYPE_VAR_6(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
926 				ARG6) NAME,
927 #define DEF_FUNCTION_TYPE_VAR_7(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
928 				ARG6, ARG7) NAME,
929 #define DEF_FUNCTION_TYPE_VAR_11(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
930 				 ARG6, ARG7, ARG8, ARG9, ARG10, ARG11) NAME,
931 #define DEF_POINTER_TYPE(NAME, TYPE) NAME,
932 #include "builtin-types.def"
933 #undef DEF_PRIMITIVE_TYPE
934 #undef DEF_FUNCTION_TYPE_0
935 #undef DEF_FUNCTION_TYPE_1
936 #undef DEF_FUNCTION_TYPE_2
937 #undef DEF_FUNCTION_TYPE_3
938 #undef DEF_FUNCTION_TYPE_4
939 #undef DEF_FUNCTION_TYPE_5
940 #undef DEF_FUNCTION_TYPE_6
941 #undef DEF_FUNCTION_TYPE_7
942 #undef DEF_FUNCTION_TYPE_8
943 #undef DEF_FUNCTION_TYPE_9
944 #undef DEF_FUNCTION_TYPE_10
945 #undef DEF_FUNCTION_TYPE_11
946 #undef DEF_FUNCTION_TYPE_VAR_0
947 #undef DEF_FUNCTION_TYPE_VAR_1
948 #undef DEF_FUNCTION_TYPE_VAR_2
949 #undef DEF_FUNCTION_TYPE_VAR_3
950 #undef DEF_FUNCTION_TYPE_VAR_4
951 #undef DEF_FUNCTION_TYPE_VAR_5
952 #undef DEF_FUNCTION_TYPE_VAR_6
953 #undef DEF_FUNCTION_TYPE_VAR_7
954 #undef DEF_FUNCTION_TYPE_VAR_11
955 #undef DEF_POINTER_TYPE
956   BT_LAST
957 };
958 
959 typedef enum d_builtin_type builtin_type;
960 
961 /* A temporary array used in communication with def_fn_type.  */
962 static GTY(()) tree builtin_types[(int) BT_LAST + 1];
963 
964 /* A helper function for d_init_builtins.  Build function type for DEF with
965    return type RET and N arguments.  If VAR is true, then the function should
966    be variadic after those N arguments.
967 
968    Takes special care not to ICE if any of the types involved are
969    error_mark_node, which indicates that said type is not in fact available
970    (see builtin_type_for_size).  In which case the function type as a whole
971    should be error_mark_node.  */
972 
973 static void
def_fn_type(builtin_type def,builtin_type ret,bool var,int n,...)974 def_fn_type (builtin_type def, builtin_type ret, bool var, int n, ...)
975 {
976   tree t;
977   tree *args = XALLOCAVEC (tree, n);
978   va_list list;
979   int i;
980 
981   va_start (list, n);
982   for (i = 0; i < n; ++i)
983     {
984       builtin_type a = (builtin_type) va_arg (list, int);
985       t = builtin_types[a];
986       if (t == error_mark_node)
987 	goto egress;
988       args[i] = t;
989     }
990 
991   t = builtin_types[ret];
992   if (t == error_mark_node)
993     goto egress;
994   if (var)
995     t = build_varargs_function_type_array (t, n, args);
996   else
997     t = build_function_type_array (t, n, args);
998 
999  egress:
1000   builtin_types[def] = t;
1001   va_end (list);
1002 }
1003 
1004 /* Create builtin types and functions.  VA_LIST_REF_TYPE_NODE and
1005    VA_LIST_ARG_TYPE_NODE are used in builtin-types.def.  */
1006 
1007 static void
d_define_builtins(tree va_list_ref_type_node ATTRIBUTE_UNUSED,tree va_list_arg_type_node ATTRIBUTE_UNUSED)1008 d_define_builtins (tree va_list_ref_type_node ATTRIBUTE_UNUSED,
1009 		   tree va_list_arg_type_node ATTRIBUTE_UNUSED)
1010 {
1011 #define DEF_PRIMITIVE_TYPE(ENUM, VALUE) \
1012   builtin_types[(int) ENUM] = VALUE;
1013 #define DEF_FUNCTION_TYPE_0(ENUM, RETURN) \
1014   def_fn_type (ENUM, RETURN, 0, 0);
1015 #define DEF_FUNCTION_TYPE_1(ENUM, RETURN, ARG1) \
1016   def_fn_type (ENUM, RETURN, 0, 1, ARG1);
1017 #define DEF_FUNCTION_TYPE_2(ENUM, RETURN, ARG1, ARG2) \
1018   def_fn_type (ENUM, RETURN, 0, 2, ARG1, ARG2);
1019 #define DEF_FUNCTION_TYPE_3(ENUM, RETURN, ARG1, ARG2, ARG3) \
1020   def_fn_type (ENUM, RETURN, 0, 3, ARG1, ARG2, ARG3);
1021 #define DEF_FUNCTION_TYPE_4(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4) \
1022   def_fn_type (ENUM, RETURN, 0, 4, ARG1, ARG2, ARG3, ARG4);
1023 #define DEF_FUNCTION_TYPE_5(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5) \
1024   def_fn_type (ENUM, RETURN, 0, 5, ARG1, ARG2, ARG3, ARG4, ARG5);
1025 #define DEF_FUNCTION_TYPE_6(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1026 			    ARG6)					\
1027   def_fn_type (ENUM, RETURN, 0, 6, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6);
1028 #define DEF_FUNCTION_TYPE_7(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1029 			    ARG6, ARG7)					\
1030   def_fn_type (ENUM, RETURN, 0, 7, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6, ARG7);
1031 #define DEF_FUNCTION_TYPE_8(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1032 			    ARG6, ARG7, ARG8)				\
1033   def_fn_type (ENUM, RETURN, 0, 8, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6,  \
1034 	       ARG7, ARG8);
1035 #define DEF_FUNCTION_TYPE_9(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1036 			    ARG6, ARG7, ARG8, ARG9)			\
1037   def_fn_type (ENUM, RETURN, 0, 9, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6,  \
1038 	       ARG7, ARG8, ARG9);
1039 #define DEF_FUNCTION_TYPE_10(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1040 			    ARG6, ARG7, ARG8, ARG9, ARG10)		 \
1041   def_fn_type (ENUM, RETURN, 0, 10, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6,  \
1042 	       ARG7, ARG8, ARG9, ARG10);
1043 #define DEF_FUNCTION_TYPE_11(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1044 			    ARG6, ARG7, ARG8, ARG9, ARG10, ARG11)	 \
1045   def_fn_type (ENUM, RETURN, 0, 11, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6,  \
1046 	       ARG7, ARG8, ARG9, ARG10, ARG11);
1047 #define DEF_FUNCTION_TYPE_VAR_0(ENUM, RETURN) \
1048   def_fn_type (ENUM, RETURN, 1, 0);
1049 #define DEF_FUNCTION_TYPE_VAR_1(ENUM, RETURN, ARG1) \
1050   def_fn_type (ENUM, RETURN, 1, 1, ARG1);
1051 #define DEF_FUNCTION_TYPE_VAR_2(ENUM, RETURN, ARG1, ARG2) \
1052   def_fn_type (ENUM, RETURN, 1, 2, ARG1, ARG2);
1053 #define DEF_FUNCTION_TYPE_VAR_3(ENUM, RETURN, ARG1, ARG2, ARG3) \
1054   def_fn_type (ENUM, RETURN, 1, 3, ARG1, ARG2, ARG3);
1055 #define DEF_FUNCTION_TYPE_VAR_4(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4) \
1056   def_fn_type (ENUM, RETURN, 1, 4, ARG1, ARG2, ARG3, ARG4);
1057 #define DEF_FUNCTION_TYPE_VAR_5(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5) \
1058   def_fn_type (ENUM, RETURN, 1, 5, ARG1, ARG2, ARG3, ARG4, ARG5);
1059 #define DEF_FUNCTION_TYPE_VAR_6(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1060 				ARG6)					    \
1061   def_fn_type (ENUM, RETURN, 1, 6, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6);
1062 #define DEF_FUNCTION_TYPE_VAR_7(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1063 				ARG6, ARG7)				    \
1064   def_fn_type (ENUM, RETURN, 1, 7, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6, ARG7);
1065 #define DEF_FUNCTION_TYPE_VAR_11(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1066 				 ARG6, ARG7, ARG8, ARG9, ARG10, ARG11)       \
1067   def_fn_type (ENUM, RETURN, 1, 11, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6,      \
1068 	       ARG7, ARG8, ARG9, ARG10, ARG11);
1069 #define DEF_POINTER_TYPE(ENUM, TYPE) \
1070   builtin_types[(int) ENUM] = build_pointer_type (builtin_types[(int) TYPE]);
1071 
1072 #include "builtin-types.def"
1073 
1074 #undef DEF_PRIMITIVE_TYPE
1075 #undef DEF_FUNCTION_TYPE_1
1076 #undef DEF_FUNCTION_TYPE_2
1077 #undef DEF_FUNCTION_TYPE_3
1078 #undef DEF_FUNCTION_TYPE_4
1079 #undef DEF_FUNCTION_TYPE_5
1080 #undef DEF_FUNCTION_TYPE_6
1081 #undef DEF_FUNCTION_TYPE_7
1082 #undef DEF_FUNCTION_TYPE_8
1083 #undef DEF_FUNCTION_TYPE_9
1084 #undef DEF_FUNCTION_TYPE_10
1085 #undef DEF_FUNCTION_TYPE_11
1086 #undef DEF_FUNCTION_TYPE_VAR_0
1087 #undef DEF_FUNCTION_TYPE_VAR_1
1088 #undef DEF_FUNCTION_TYPE_VAR_2
1089 #undef DEF_FUNCTION_TYPE_VAR_3
1090 #undef DEF_FUNCTION_TYPE_VAR_4
1091 #undef DEF_FUNCTION_TYPE_VAR_5
1092 #undef DEF_FUNCTION_TYPE_VAR_6
1093 #undef DEF_FUNCTION_TYPE_VAR_7
1094 #undef DEF_FUNCTION_TYPE_VAR_11
1095 #undef DEF_POINTER_TYPE
1096   builtin_types[(int) BT_LAST] = NULL_TREE;
1097 
1098   d_init_attributes ();
1099 
1100 #define DEF_BUILTIN(ENUM, NAME, CLASS, TYPE, LIBTYPE, BOTH_P, FALLBACK_P, \
1101 		    NONANSI_P, ATTRS, IMPLICIT, COND)			  \
1102   if (NAME && COND)							  \
1103     do_build_builtin_fn (ENUM, NAME, CLASS,				  \
1104 			 builtin_types[(int) TYPE],			  \
1105 			 BOTH_P, FALLBACK_P,				  \
1106 			 built_in_attributes[(int) ATTRS], IMPLICIT);
1107 #include "builtins.def"
1108 #undef DEF_BUILTIN
1109 }
1110 
1111 /* Build builtin functions and types for the D language frontend.  */
1112 
1113 void
d_init_builtins(void)1114 d_init_builtins (void)
1115 {
1116   /* Build the "standard" abi va_list.  */
1117   Type::tvalist = build_frontend_type (va_list_type_node);
1118   if (!Type::tvalist)
1119     {
1120       error ("cannot represent built-in va_list type in D");
1121       gcc_unreachable ();
1122     }
1123 
1124   /* Map the va_list type to the D frontend Type.  This is to prevent both
1125      errors in gimplification or an ICE in targetm.canonical_va_list_type.  */
1126   Type::tvalist->ctype = va_list_type_node;
1127   TYPE_LANG_SPECIFIC (va_list_type_node) = build_lang_type (Type::tvalist);
1128 
1129   d_build_c_type_nodes ();
1130   d_build_d_type_nodes ();
1131 
1132   if (TREE_CODE (va_list_type_node) == ARRAY_TYPE)
1133     {
1134       /* It might seem natural to make the argument type a pointer, but there
1135 	 is no implicit casting from arrays to pointers in D.  */
1136       d_define_builtins (va_list_type_node, va_list_type_node);
1137     }
1138   else
1139     {
1140       d_define_builtins (build_reference_type (va_list_type_node),
1141 			 va_list_type_node);
1142     }
1143 
1144   targetm.init_builtins ();
1145   build_common_builtin_nodes ();
1146 }
1147 
1148 /* Registration of machine- or os-specific builtin types.
1149    Add to builtin types list for maybe processing later
1150    if `gcc.builtins' was imported into the current module.  */
1151 
1152 void
d_register_builtin_type(tree type,const char * name)1153 d_register_builtin_type (tree type, const char *name)
1154 {
1155   tree decl = build_decl (UNKNOWN_LOCATION, TYPE_DECL,
1156 			  get_identifier (name), type);
1157   DECL_ARTIFICIAL (decl) = 1;
1158 
1159   if (!TYPE_NAME (type))
1160     TYPE_NAME (type) = decl;
1161 
1162   vec_safe_push (gcc_builtins_types, decl);
1163 }
1164 
1165 /* Add DECL to builtin functions list for maybe processing later
1166    if `gcc.builtins' was imported into the current module.  */
1167 
1168 tree
d_builtin_function(tree decl)1169 d_builtin_function (tree decl)
1170 {
1171   if (!flag_no_builtin && DECL_ASSEMBLER_NAME_SET_P (decl))
1172     vec_safe_push (gcc_builtins_libfuncs, decl);
1173 
1174   vec_safe_push (gcc_builtins_functions, decl);
1175   return decl;
1176 }
1177 
1178 /* Same as d_builtin_function, but used to delay putting in back-end builtin
1179    functions until the ISA that defines the builtin has been declared.
1180    However in D, there is no global namespace.  All builtins get pushed into the
1181    `gcc.builtins' module, which is constructed during the semantic analysis
1182    pass, which has already finished by the time target attributes are evaluated.
1183    So builtins are not pushed because they would be ultimately ignored.
1184    The purpose of having this function then is to improve compile-time
1185    reflection support to allow user-code to determine whether a given back end
1186    function is enabled by the ISA.  */
1187 
1188 tree
d_builtin_function_ext_scope(tree decl)1189 d_builtin_function_ext_scope (tree decl)
1190 {
1191   return decl;
1192 }
1193 
1194 #include "gt-d-d-builtins.h"
1195