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