hppa: Export main in pr104869.C on hpux
[official-gcc.git] / gcc / d / d-builtins.cc
blobf6ea026bdcfeb343967ff58240c38dfc8af046df
1 /* d-builtins.cc -- GCC builtins support for D.
2 Copyright (C) 2006-2023 Free Software Foundation, Inc.
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.
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.
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/>. */
18 #include "config.h"
19 #include "system.h"
20 #include "coretypes.h"
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 #include "dmd/target.h"
32 #include "tree.h"
33 #include "fold-const.h"
34 #include "diagnostic.h"
35 #include "langhooks.h"
36 #include "target.h"
37 #include "common/common-target.h"
38 #include "stringpool.h"
39 #include "stor-layout.h"
40 #include "builtins.h"
42 #include "d-tree.h"
43 #include "d-frontend.h"
44 #include "d-target.h"
47 static GTY(()) vec <tree, va_gc> *gcc_builtins_functions = NULL;
48 static GTY(()) vec <tree, va_gc> *gcc_builtins_types = NULL;
50 /* Record built-in types and their associated decls for re-use when
51 generating the `gcc.builtins' module. */
53 struct builtin_data
55 Type *dtype;
56 tree ctype;
57 Dsymbol *dsym;
59 builtin_data (Type *t, tree c, Dsymbol *d = NULL)
60 : dtype(t), ctype(c), dsym(d)
61 { }
64 static vec <builtin_data> builtin_converted_decls;
66 /* Build D frontend type from tree TYPE type given. This will set the
67 back-end type symbol directly for complex types to save build_ctype()
68 the work. For other types, it is not useful or will cause errors, such
69 as casting from `C char' to `D char', which also means that `char *`
70 needs to be specially handled. */
72 Type *
73 build_frontend_type (tree type)
75 Type *dtype;
76 MOD mod = 0;
78 if (TYPE_READONLY (type))
79 mod |= MODconst;
80 if (TYPE_VOLATILE (type))
81 mod |= MODshared;
83 /* If we've seen the type before, re-use the converted decl. */
84 unsigned saved_builtin_decls_length = builtin_converted_decls.length ();
85 for (size_t i = 0; i < saved_builtin_decls_length; ++i)
87 tree t = builtin_converted_decls[i].ctype;
88 if (TYPE_MAIN_VARIANT (t) == TYPE_MAIN_VARIANT (type))
89 return builtin_converted_decls[i].dtype;
92 switch (TREE_CODE (type))
94 case POINTER_TYPE:
95 dtype = build_frontend_type (TREE_TYPE (type));
96 if (dtype)
98 /* Check for char * first. Needs to be done for chars/string. */
99 if (TYPE_MAIN_VARIANT (TREE_TYPE (type)) == char_type_node)
100 return Type::tchar->addMod (dtype->mod)->pointerTo ()->addMod (mod);
102 if (dtype->ty == TY::Tfunction)
103 return (TypePointer::create (dtype))->addMod (mod);
105 return dtype->pointerTo ()->addMod (mod);
107 break;
109 case REFERENCE_TYPE:
110 dtype = build_frontend_type (TREE_TYPE (type));
111 if (dtype)
113 /* Want to assign ctype directly so that the REFERENCE_TYPE code
114 can be turned into as an `inout' argument. Can't use pointerTo(),
115 because the returned Type is shared. */
116 dtype = (TypePointer::create (dtype))->addMod (mod);
117 dtype->ctype = type;
118 builtin_converted_decls.safe_push (builtin_data (dtype, type));
119 return dtype;
121 break;
123 case BOOLEAN_TYPE:
124 /* Should be no need for size checking. */
125 return Type::tbool->addMod (mod);
127 case INTEGER_TYPE:
129 unsigned size = TREE_INT_CST_LOW (TYPE_SIZE_UNIT (type));
130 bool unsignedp = TYPE_UNSIGNED (type);
132 /* For now, skip support for cent/ucent until the frontend
133 has better support for handling it. */
134 for (size_t i = (size_t) TY::Tint8; i <= (size_t) TY::Tuns64; i++)
136 dtype = Type::basic[i];
138 /* Search for type matching size and signedness. */
139 if (unsignedp != dtype->isunsigned ()
140 || size != dtype->size ())
141 continue;
143 return dtype->addMod (mod);
145 break;
148 case REAL_TYPE:
150 unsigned size = TREE_INT_CST_LOW (TYPE_SIZE_UNIT (type));
152 for (size_t i = (size_t) TY::Tfloat32; i <= (size_t) TY::Tfloat80; i++)
154 dtype = Type::basic[i];
156 /* Search for type matching size. */
157 if (dtype->size () != size)
158 continue;
160 return dtype->addMod (mod);
162 break;
165 case COMPLEX_TYPE:
167 unsigned size = TREE_INT_CST_LOW (TYPE_SIZE_UNIT (type));
168 for (size_t i = (size_t) TY::Tcomplex32; i <= (size_t) TY::Tcomplex80;
169 i++)
171 dtype = Type::basic[i];
173 /* Search for type matching size. */
174 if (dtype->size () != size)
175 continue;
177 return dtype->addMod (mod);
179 break;
182 case VOID_TYPE:
183 return Type::tvoid->addMod (mod);
185 case ARRAY_TYPE:
186 dtype = build_frontend_type (TREE_TYPE (type));
187 if (dtype)
189 tree index = TYPE_DOMAIN (type);
190 tree ub = TYPE_MAX_VALUE (index);
191 tree lb = TYPE_MIN_VALUE (index);
193 tree length = fold_build2 (MINUS_EXPR, TREE_TYPE (lb), ub, lb);
194 length = size_binop (PLUS_EXPR, size_one_node,
195 convert (sizetype, length));
197 dtype = dtype->sarrayOf (TREE_INT_CST_LOW (length))->addMod (mod);
198 builtin_converted_decls.safe_push (builtin_data (dtype, type));
199 return dtype;
201 break;
203 case VECTOR_TYPE:
205 unsigned HOST_WIDE_INT nunits;
206 if (!TYPE_VECTOR_SUBPARTS (type).is_constant (&nunits))
207 break;
209 dtype = build_frontend_type (TREE_TYPE (type));
210 if (!dtype)
211 break;
213 dtype = dtype->sarrayOf (nunits)->addMod (mod);
214 if (target.isVectorTypeSupported (dtype->size (), dtype->nextOf ()))
215 break;
217 dtype = (TypeVector::create (dtype))->addMod (mod);
218 builtin_converted_decls.safe_push (builtin_data (dtype, type));
219 return dtype;
222 case RECORD_TYPE:
224 Identifier *ident = TYPE_IDENTIFIER (type) ?
225 Identifier::idPool (IDENTIFIER_POINTER (TYPE_IDENTIFIER (type))) : NULL;
227 /* Neither the `object' and `gcc.builtins' modules will not exist when
228 this is called. Use a stub `object' module parent in the meantime.
229 If `gcc.builtins' is later imported, the parent will be overridden
230 with the correct module symbol. */
231 static Identifier *object = Identifier::idPool ("object");
232 static Module *stubmod = Module::create ("object.d", object, 0, 0);
234 StructDeclaration *sdecl = StructDeclaration::create (Loc (), ident,
235 false);
236 sdecl->parent = stubmod;
237 sdecl->structsize = int_size_in_bytes (type);
238 sdecl->alignsize = TYPE_ALIGN_UNIT (type);
239 sdecl->alignment.setDefault ();
240 sdecl->sizeok = Sizeok::done;
241 sdecl->type = (TypeStruct::create (sdecl))->addMod (mod);
242 sdecl->type->ctype = type;
243 sdecl->type->merge2 ();
245 /* Add both named and anonymous fields as members of the struct.
246 Anonymous fields still need a name in D, so call them "__pad%u". */
247 unsigned anonfield_id = 0;
248 sdecl->members = d_gc_malloc<Dsymbols> ();
250 for (tree field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
252 Type *ftype = build_frontend_type (TREE_TYPE (field));
253 if (!ftype)
255 /* Drop any field types that got cached before the conversion
256 of this record type failed. */
257 builtin_converted_decls.truncate (saved_builtin_decls_length);
258 return NULL;
261 Identifier *fident;
262 if (DECL_NAME (field) == NULL_TREE)
264 char name[16];
265 snprintf (name, sizeof (name), "__pad%u", anonfield_id++);
266 fident = Identifier::idPool (name);
268 else
270 const char *name = IDENTIFIER_POINTER (DECL_NAME (field));
271 fident = Identifier::idPool (name);
274 VarDeclaration *vd = VarDeclaration::create (Loc (), ftype, fident,
275 NULL);
276 vd->parent = sdecl;
277 vd->offset = tree_to_uhwi (byte_position (field));
278 vd->semanticRun = PASS::semanticdone;
279 vd->csym = field;
280 sdecl->members->push (vd);
281 sdecl->fields.push (vd);
284 dtype = sdecl->type;
285 builtin_converted_decls.safe_push (builtin_data (dtype, type, sdecl));
286 return dtype;
289 case FUNCTION_TYPE:
290 dtype = build_frontend_type (TREE_TYPE (type));
291 if (dtype)
293 tree parms = TYPE_ARG_TYPES (type);
294 VarArg varargs_p = VARARGvariadic;
296 Parameters *args = d_gc_malloc<Parameters> ();
297 args->reserve (list_length (parms));
299 /* Attempt to convert all parameter types. */
300 for (tree parm = parms; parm != NULL_TREE; parm = TREE_CHAIN (parm))
302 tree argtype = TREE_VALUE (parm);
303 if (argtype == void_type_node)
305 varargs_p = VARARGnone;
306 break;
309 StorageClass sc = STCundefined;
310 if (TREE_CODE (argtype) == REFERENCE_TYPE)
312 argtype = TREE_TYPE (argtype);
313 sc |= STCref;
316 Type *targ = build_frontend_type (argtype);
317 if (!targ)
319 /* Drop any parameter types that got cached before the
320 conversion of this function type failed. */
321 builtin_converted_decls.truncate (saved_builtin_decls_length);
322 return NULL;
325 args->push (Parameter::create (Loc (), sc, targ,
326 NULL, NULL, NULL));
329 /* GCC generic and placeholder built-ins are marked as variadic, yet
330 have no named parameters, and so can't be represented in D. */
331 if (args->length != 0 || varargs_p == VARARGnone)
333 dtype = TypeFunction::create (args, dtype, varargs_p, LINK::c);
334 return dtype->addMod (mod);
337 break;
339 default:
340 break;
343 return NULL;
346 /* Attempt to convert GCC evaluated CST to a D Frontend Expression.
347 LOC is the location in the source file where this CST is being evaluated.
348 This is used for getting the CTFE value out of a const-folded builtin,
349 returns NULL if it cannot convert CST. */
351 Expression *
352 d_eval_constant_expression (const Loc &loc, tree cst)
354 STRIP_TYPE_NOPS (cst);
355 Type *type = build_frontend_type (TREE_TYPE (cst));
357 if (type)
359 /* Convert our GCC CST tree into a D Expression. This seems like we are
360 trying too hard, as these will only be converted back to a tree again
361 later in the codegen pass, but satisfies the need to have GCC built-ins
362 CTFE-able in the frontend. */
363 tree_code code = TREE_CODE (cst);
364 if (code == COMPLEX_CST)
366 real_value re = TREE_REAL_CST (TREE_REALPART (cst));
367 real_value im = TREE_REAL_CST (TREE_IMAGPART (cst));
368 complex_t value = complex_t (ldouble (re), ldouble (im));
369 return ComplexExp::create (loc, value, type);
371 else if (code == INTEGER_CST)
373 dinteger_t value = TREE_INT_CST_LOW (cst);
374 return IntegerExp::create (loc, value, type);
376 else if (code == REAL_CST)
378 real_value value = TREE_REAL_CST (cst);
379 return RealExp::create (loc, ldouble (value), type);
381 else if (code == STRING_CST)
383 const void *string = TREE_STRING_POINTER (cst);
384 size_t len = TREE_STRING_LENGTH (cst) - 1;
385 return StringExp::create (loc, CONST_CAST (void *, string), len);
387 else if (code == VECTOR_CST)
389 dinteger_t nunits = VECTOR_CST_NELTS (cst).to_constant ();
390 Expressions *elements = d_gc_malloc<Expressions> ();
391 elements->setDim (nunits);
393 for (size_t i = 0; i < nunits; i++)
395 Expression *elem
396 = d_eval_constant_expression (loc, VECTOR_CST_ELT (cst, i));
397 if (elem == NULL)
398 return NULL;
400 (*elements)[i] = elem;
403 Expression *e = ArrayLiteralExp::create (loc, elements);
404 e->type = type->isTypeVector ()->basetype;
406 return VectorExp::create (loc, e, type);
408 else if (code == ADDR_EXPR)
410 /* Special handling for trees constructed by build_string_literal.
411 What we receive is an `&"string"[0]' expression, strip off the
412 outer ADDR_EXPR and ARRAY_REF to get to the underlying CST. */
413 tree pointee = TREE_OPERAND (cst, 0);
415 if (TREE_CODE (pointee) != ARRAY_REF
416 || TREE_OPERAND (pointee, 1) != integer_zero_node
417 || TREE_CODE (TREE_OPERAND (pointee, 0)) != STRING_CST)
418 return NULL;
420 return d_eval_constant_expression (loc, TREE_OPERAND (pointee, 0));
424 return NULL;
427 /* Callback for TARGET_D_CPU_VERSIONS and TARGET_D_OS_VERSIONS.
428 Adds IDENT to the list of predefined version identifiers. */
430 void
431 d_add_builtin_version (const char* ident)
433 VersionCondition::addPredefinedGlobalIdent (ident);
436 /* Initialize the list of all the predefined version identifiers. */
438 void
439 d_init_versions (void)
441 VersionCondition::addPredefinedGlobalIdent ("GNU");
442 VersionCondition::addPredefinedGlobalIdent ("D_Version2");
444 if (BYTES_BIG_ENDIAN)
445 VersionCondition::addPredefinedGlobalIdent ("BigEndian");
446 else
447 VersionCondition::addPredefinedGlobalIdent ("LittleEndian");
449 if (targetm_common.except_unwind_info (&global_options) == UI_SJLJ)
450 VersionCondition::addPredefinedGlobalIdent ("GNU_SjLj_Exceptions");
451 else if (targetm_common.except_unwind_info (&global_options) == UI_SEH)
452 VersionCondition::addPredefinedGlobalIdent ("GNU_SEH_Exceptions");
453 else if (targetm_common.except_unwind_info (&global_options) == UI_DWARF2)
454 VersionCondition::addPredefinedGlobalIdent ("GNU_DWARF2_Exceptions");
456 if (!targetm.have_tls)
457 VersionCondition::addPredefinedGlobalIdent ("GNU_EMUTLS");
459 if (STACK_GROWS_DOWNWARD)
460 VersionCondition::addPredefinedGlobalIdent ("GNU_StackGrowsDown");
462 /* Should define this anyway to set us apart from the competition. */
463 VersionCondition::addPredefinedGlobalIdent ("GNU_InlineAsm");
465 /* LP64 only means 64bit pointers in D. */
466 if (POINTER_SIZE == 64)
467 VersionCondition::addPredefinedGlobalIdent ("D_LP64");
469 /* Setting `global.params.cov' forces module info generation which is
470 not needed for the GCC coverage implementation. Instead, just
471 test flag_test_coverage while leaving `global.params.cov' unset. */
472 if (flag_test_coverage)
473 VersionCondition::addPredefinedGlobalIdent ("D_Coverage");
474 if (flag_pic)
475 VersionCondition::addPredefinedGlobalIdent ("D_PIC");
476 if (flag_pie)
477 VersionCondition::addPredefinedGlobalIdent ("D_PIE");
479 if (global.params.ddoc.doOutput)
480 VersionCondition::addPredefinedGlobalIdent ("D_Ddoc");
482 if (global.params.useUnitTests)
483 VersionCondition::addPredefinedGlobalIdent ("unittest");
485 if (global.params.useAssert == CHECKENABLEon)
486 VersionCondition::addPredefinedGlobalIdent ("assert");
488 if (global.params.useIn == CHECKENABLEon)
489 VersionCondition::addPredefinedGlobalIdent("D_PreConditions");
491 if (global.params.useOut == CHECKENABLEon)
492 VersionCondition::addPredefinedGlobalIdent("D_PostConditions");
494 if (global.params.useInvariants == CHECKENABLEon)
495 VersionCondition::addPredefinedGlobalIdent("D_Invariants");
497 if (global.params.useArrayBounds == CHECKENABLEoff)
498 VersionCondition::addPredefinedGlobalIdent ("D_NoBoundsChecks");
500 if (global.params.betterC)
501 VersionCondition::addPredefinedGlobalIdent ("D_BetterC");
502 else
504 if (global.params.useModuleInfo)
505 VersionCondition::addPredefinedGlobalIdent ("D_ModuleInfo");
506 if (global.params.useExceptions)
507 VersionCondition::addPredefinedGlobalIdent ("D_Exceptions");
508 if (global.params.useTypeInfo)
509 VersionCondition::addPredefinedGlobalIdent ("D_TypeInfo");
512 if (optimize)
513 VersionCondition::addPredefinedGlobalIdent ("D_Optimized");
515 VersionCondition::addPredefinedGlobalIdent ("all");
517 /* Emit all target-specific version identifiers. */
518 targetdm.d_cpu_versions ();
519 targetdm.d_os_versions ();
521 VersionCondition::addPredefinedGlobalIdent ("CppRuntime_Gcc");
524 /* A helper for d_build_builtins_module. Return a new ALIAS for TYPE.
525 Analogous to `alias ALIAS = TYPE' in D code. */
527 static AliasDeclaration *
528 build_alias_declaration (const char *alias, Type *type)
530 return AliasDeclaration::create (Loc (), Identifier::idPool (alias), type);
533 /* A helper function for Target::loadModule. Generates all code for the
534 `gcc.builtins' module, whose frontend symbol should be M. */
536 void
537 d_build_builtins_module (Module *m)
539 Dsymbols *members = d_gc_malloc<Dsymbols> ();
540 tree decl;
542 for (size_t i = 0; vec_safe_iterate (gcc_builtins_functions, i, &decl); ++i)
544 const char *name = IDENTIFIER_POINTER (DECL_NAME (decl));
545 Type *t = build_frontend_type (TREE_TYPE (decl));
546 TypeFunction *tf = t ? t->isTypeFunction () : NULL;
548 /* Cannot create built-in function type for DECL. */
549 if (!tf)
550 continue;
552 /* A few notes on D2 attributes applied to builtin functions:
553 - It is assumed that built-ins solely provided by the compiler are
554 considered @safe and pure.
555 - Built-ins that correspond to `extern(C)' functions in the standard
556 library that have `__attribute__(nothrow)' are considered `@trusted'.
557 - The purity of a built-in can vary depending on compiler flags set
558 upon initialization, or by the `-foptions' passed, such as
559 flag_unsafe_math_optimizations.
560 - Built-ins never use the GC or raise a D exception, and so are always
561 marked as `nothrow' and `@nogc'. */
562 tf->purity = DECL_PURE_P (decl) ? PURE::const_
563 : TREE_READONLY (decl) ? PURE::const_
564 : DECL_IS_NOVOPS (decl) ? PURE::weak
565 : !DECL_ASSEMBLER_NAME_SET_P (decl) ? PURE::weak
566 : PURE::impure;
567 tf->trust = !DECL_ASSEMBLER_NAME_SET_P (decl) ? TRUST::safe
568 : TREE_NOTHROW (decl) ? TRUST::trusted
569 : TRUST::system;
570 tf->isnothrow (true);
571 tf->isnogc (true);
573 FuncDeclaration *func
574 = FuncDeclaration::create (Loc (), Loc (),
575 Identifier::idPool (name),
576 STCextern, tf);
577 DECL_LANG_SPECIFIC (decl) = build_lang_decl (func);
578 func->csym = decl;
579 func->builtin = BUILTIN::gcc;
581 members->push (func);
584 for (size_t i = 0; vec_safe_iterate (gcc_builtins_types, i, &decl); ++i)
586 const char *name = IDENTIFIER_POINTER (DECL_NAME (decl));
587 Type *t = build_frontend_type (TREE_TYPE (decl));
589 /* Cannot create built-in type for DECL. */
590 if (!t)
591 continue;
593 members->push (build_alias_declaration (name, t));
596 /* Iterate through the target-specific builtin types for va_list. */
597 if (targetm.enum_va_list_p)
599 const char *name;
600 tree type;
602 for (int i = 0; targetm.enum_va_list_p (i, &name, &type); ++i)
604 Type *t = build_frontend_type (type);
605 /* Cannot create built-in type. */
606 if (!t)
607 continue;
609 members->push (build_alias_declaration (name, t));
613 /* Push out declarations for any RECORD_TYPE types encountered when building
614 all builtin functions and types. */
615 for (size_t i = 0; i < builtin_converted_decls.length (); ++i)
617 /* Currently, there is no need to run semantic, but we do want to output
618 initializers, typeinfo, and others on demand. */
619 Dsymbol *dsym = builtin_converted_decls[i].dsym;
620 if (dsym != NULL && !dsym->isAnonymous ())
622 dsym->parent = m;
623 members->push (dsym);
627 /* Expose target-specific va_list type. */
628 Type *tvalist = target.va_listType (Loc (), NULL);
629 TypeStruct *ts = tvalist->isTypeStruct ();
630 if (ts == NULL || !ts->sym->isAnonymous ())
631 members->push (build_alias_declaration ("__builtin_va_list", tvalist));
632 else
634 ts->sym->ident = Identifier::idPool ("__builtin_va_list");
635 members->push (ts->sym);
638 /* Expose target-specific integer types to the builtins module. */
640 Type *t = build_frontend_type (long_integer_type_node);
641 members->push (build_alias_declaration ("__builtin_clong", t));
643 t = build_frontend_type (long_unsigned_type_node);
644 members->push (build_alias_declaration ("__builtin_culong", t));
646 t = build_frontend_type (long_long_integer_type_node);
647 members->push (build_alias_declaration ("__builtin_clonglong", t));
649 t = build_frontend_type (long_long_unsigned_type_node);
650 members->push (build_alias_declaration ("__builtin_culonglong", t));
652 t = build_frontend_type (lang_hooks.types.type_for_mode (byte_mode, 0));
653 members->push (build_alias_declaration ("__builtin_machine_byte", t));
655 t = build_frontend_type (lang_hooks.types.type_for_mode (byte_mode, 1));
656 members->push (build_alias_declaration ("__builtin_machine_ubyte", t));
658 t = build_frontend_type (lang_hooks.types.type_for_mode (word_mode, 0));
659 members->push (build_alias_declaration ("__builtin_machine_int", t));
661 t = build_frontend_type (lang_hooks.types.type_for_mode (word_mode, 1));
662 members->push (build_alias_declaration ("__builtin_machine_uint", t));
664 t = build_frontend_type (lang_hooks.types.type_for_mode (ptr_mode, 0));
665 members->push (build_alias_declaration ("__builtin_pointer_int", t));
667 t = build_frontend_type (lang_hooks.types.type_for_mode (ptr_mode, 1));
668 members->push (build_alias_declaration ("__builtin_pointer_uint", t));
670 /* _Unwind_Word has its own target specific mode. */
671 machine_mode mode = targetm.unwind_word_mode ();
672 t = build_frontend_type (lang_hooks.types.type_for_mode (mode, 0));
673 members->push (build_alias_declaration ("__builtin_unwind_int", t));
675 t = build_frontend_type (lang_hooks.types.type_for_mode (mode, 1));
676 members->push (build_alias_declaration ("__builtin_unwind_uint", t));
679 m->members->push (LinkDeclaration::create (Loc (), LINK::c, members));
682 /* Remove all type modifiers from TYPE, returning the naked type. */
684 static Type *
685 strip_type_modifiers (Type *type)
687 if (type->ty == TY::Tpointer)
689 Type *tnext = strip_type_modifiers (type->nextOf ());
690 return tnext->pointerTo ();
693 return type->castMod (0);
696 /* Returns true if types T1 and T2 representing return types or types of
697 function arguments are close enough to be considered interchangeable. */
699 static bool
700 matches_builtin_type (Type *t1, Type *t2)
702 Type *tb1 = strip_type_modifiers (t1);
703 Type *tb2 = strip_type_modifiers (t2);
705 if (same_type_p (t1, t2))
706 return true;
708 if (((tb1->isTypePointer () && tb2->isTypePointer ())
709 || (tb1->isTypeVector () && tb2->isTypeVector ()))
710 && tb1->implicitConvTo (tb2) != MATCH::nomatch)
711 return true;
713 if (tb1->isintegral () == tb2->isintegral ()
714 && tb1->size () == tb2->size ())
715 return true;
717 return false;
720 /* Check whether the declared function type T1 is covariant with the built-in
721 function type T2. Returns true if they are covariant. */
723 static bool
724 covariant_with_builtin_type_p (Type *t1, Type *t2)
726 /* Check whether the declared function matches the built-in. */
727 if (same_type_p (t1, t2) || t1->covariant (t2) == Covariant::yes)
728 return true;
730 /* May not be covariant because of D attributes applied on t1.
731 Strip them all off and compare again. */
732 TypeFunction *tf1 = t1->isTypeFunction ();
733 TypeFunction *tf2 = t2->isTypeFunction ();
735 /* Check for obvious reasons why types may be distinct. */
736 if (tf1 == NULL || tf2 == NULL
737 || tf1->isref () != tf2->isref ()
738 || tf1->parameterList.varargs != tf2->parameterList.varargs
739 || tf1->parameterList.length () != tf2->parameterList.length ())
740 return false;
742 /* Check return type and each parameter type for mismatch. */
743 if (!matches_builtin_type (tf1->next, tf2->next))
744 return false;
746 const size_t nparams = tf1->parameterList.length ();
747 for (size_t i = 0; i < nparams; i++)
749 Parameter *fparam1 = tf1->parameterList[i];
750 Parameter *fparam2 = tf2->parameterList[i];
752 if (fparam1->isReference () != fparam2->isReference ()
753 || fparam1->isLazy () != fparam2->isLazy ())
754 return false;
756 if (!matches_builtin_type (fparam1->type, fparam2->type))
757 return false;
760 return true;
763 /* Search for any `extern(C)' functions that match any known GCC library builtin
764 function in D and override its internal back-end symbol. */
766 static void
767 maybe_set_builtin_1 (Dsymbol *d)
769 AttribDeclaration *ad = d->isAttribDeclaration ();
770 FuncDeclaration *fd = d->isFuncDeclaration ();
772 if (ad != NULL)
774 /* Recursively search through attribute decls. */
775 Dsymbols *decls = ad->include (NULL);
776 if (decls && decls->length)
778 for (size_t i = 0; i < decls->length; i++)
780 Dsymbol *sym = (*decls)[i];
781 maybe_set_builtin_1 (sym);
785 else if (fd && !fd->fbody && fd->resolvedLinkage () == LINK::c)
787 tree ident = get_identifier (fd->ident->toChars ());
788 tree decl = IDENTIFIER_DECL_TREE (ident);
790 if (decl && TREE_CODE (decl) == FUNCTION_DECL
791 && DECL_ASSEMBLER_NAME_SET_P (decl)
792 && fndecl_built_in_p (decl, BUILT_IN_NORMAL))
794 /* Found a match, tell the frontend this is a builtin. */
795 DECL_LANG_SPECIFIC (decl) = build_lang_decl (fd);
796 fd->csym = decl;
797 fd->builtin = BUILTIN::gcc;
799 /* Copy front-end attributes to the builtin. */
800 apply_user_attributes (fd, fd->csym);
802 /* Function has `pragma(mangle)' specified, override its name. */
803 if (fd->mangleOverride.length)
805 tree mangle =
806 get_identifier_with_length (fd->mangleOverride.ptr,
807 fd->mangleOverride.length);
808 const char *asmname = IDENTIFIER_POINTER (mangle);
809 set_builtin_user_assembler_name (decl, asmname);
812 /* Warn when return and argument types of the user defined function is
813 not covariant with the built-in function type. */
814 if (Type *type = build_frontend_type (TREE_TYPE (decl)))
816 if (!covariant_with_builtin_type_p (fd->type, type))
818 warning_at (make_location_t (fd->loc),
819 OPT_Wbuiltin_declaration_mismatch,
820 "conflicting types for built-in function %qs; "
821 "expected %qs",
822 fd->toChars (), type->toChars ());
829 /* A helper function for Target::loadModule. Traverse all members in module M
830 to search for any functions that can be mapped to any GCC builtin. */
832 void
833 d_maybe_set_builtin (Module *m)
835 if (!m || !m->members)
836 return;
838 for (size_t i = 0; i < m->members->length; i++)
840 Dsymbol *sym = (*m->members)[i];
841 maybe_set_builtin_1 (sym);
845 /* Used to help initialize the builtin-types.def table. When a type of
846 the correct size doesn't exist, use error_mark_node instead of NULL.
847 The latter results in segfaults even when a decl using the type doesn't
848 get invoked. */
850 static tree
851 builtin_type_for_size (int size, bool unsignedp)
853 tree type = lang_hooks.types.type_for_size (size, unsignedp);
854 return type ? type : error_mark_node;
857 /* Support for DEF_BUILTIN. */
859 static void
860 do_build_builtin_fn (built_in_function fncode,
861 const char *name,
862 built_in_class fnclass,
863 tree fntype, bool both_p, bool fallback_p,
864 tree fnattrs, bool implicit_p)
866 tree decl;
867 const char *libname;
869 if (fntype == error_mark_node)
870 return;
872 gcc_assert ((!both_p && !fallback_p)
873 || startswith (name, "__builtin_"));
875 libname = name + strlen ("__builtin_");
877 decl = add_builtin_function (name, fntype, fncode, fnclass,
878 fallback_p ? libname : NULL, fnattrs);
880 set_builtin_decl (fncode, decl, implicit_p);
883 /* Standard data types to be used in builtin argument declarations. */
885 static GTY(()) tree string_type_node;
886 static GTY(()) tree const_string_type_node;
887 static GTY(()) tree wint_type_node;
888 static GTY(()) tree intmax_type_node;
889 static GTY(()) tree uintmax_type_node;
890 static GTY(()) tree signed_size_type_node;
893 /* Build nodes that would have been created by the C front-end; necessary
894 for including builtin-types.def and ultimately builtins.def. */
896 static void
897 d_build_c_type_nodes (void)
899 string_type_node = build_pointer_type (char_type_node);
900 const_string_type_node
901 = build_pointer_type (build_qualified_type (char_type_node,
902 TYPE_QUAL_CONST));
904 if (strcmp (UINTMAX_TYPE, "unsigned int") == 0)
906 intmax_type_node = integer_type_node;
907 uintmax_type_node = unsigned_type_node;
909 else if (strcmp (UINTMAX_TYPE, "long unsigned int") == 0)
911 intmax_type_node = long_integer_type_node;
912 uintmax_type_node = long_unsigned_type_node;
914 else if (strcmp (UINTMAX_TYPE, "long long unsigned int") == 0)
916 intmax_type_node = long_long_integer_type_node;
917 uintmax_type_node = long_long_unsigned_type_node;
919 else
920 gcc_unreachable ();
922 signed_size_type_node = signed_type_for (size_type_node);
923 wint_type_node = unsigned_type_node;
924 pid_type_node = integer_type_node;
927 /* Build nodes that are used by the D front-end.
928 These are distinct from C types. */
930 static void
931 d_build_d_type_nodes (void)
933 /* Integral types. */
934 d_byte_type = make_signed_type (8);
935 d_ubyte_type = make_unsigned_type (8);
937 d_short_type = make_signed_type (16);
938 d_ushort_type = make_unsigned_type (16);
940 d_int_type = make_signed_type (32);
941 d_uint_type = make_unsigned_type (32);
943 d_long_type = make_signed_type (64);
944 d_ulong_type = make_unsigned_type (64);
946 d_cent_type = make_signed_type (128);
947 d_ucent_type = make_unsigned_type (128);
950 /* Re-define size_t as a D type. */
951 machine_mode type_mode = TYPE_MODE (size_type_node);
952 size_type_node = lang_hooks.types.type_for_mode (type_mode, 1);
955 /* Bool and Character types. */
956 d_bool_type = make_unsigned_type (1);
957 TREE_SET_CODE (d_bool_type, BOOLEAN_TYPE);
959 d_bool_false_node = TYPE_MIN_VALUE (d_bool_type);
960 d_bool_true_node = TYPE_MAX_VALUE (d_bool_type);
962 char8_type_node = make_unsigned_type (8);
963 TYPE_STRING_FLAG (char8_type_node) = 1;
965 char16_type_node = make_unsigned_type (16);
966 TYPE_STRING_FLAG (char16_type_node) = 1;
968 char32_type_node = make_unsigned_type (32);
969 TYPE_STRING_FLAG (char32_type_node) = 1;
971 /* Imaginary types. */
972 ifloat_type_node = build_distinct_type_copy (float_type_node);
973 TYPE_IMAGINARY_FLOAT (ifloat_type_node) = 1;
975 idouble_type_node = build_distinct_type_copy (double_type_node);
976 TYPE_IMAGINARY_FLOAT (idouble_type_node) = 1;
978 ireal_type_node = build_distinct_type_copy (long_double_type_node);
979 TYPE_IMAGINARY_FLOAT (ireal_type_node) = 1;
981 /* Noreturn type. */
982 noreturn_type_node = build_distinct_type_copy (void_type_node);
984 /* Calling build_ctype() links the front-end Type to the GCC node,
985 and sets the TYPE_NAME to the D language type. */
986 for (unsigned ty = 0; ty < (unsigned) TY::TMAX; ty++)
988 if (Type::basic[ty] != NULL)
989 build_ctype (Type::basic[ty]);
992 /* Used for ModuleInfo, ClassInfo, and Interface decls. */
993 unknown_type_node = make_node (RECORD_TYPE);
995 /* Make sure we get a unique function type, so we can give
996 its pointer type a name. (This wins for gdb). */
998 tree vfunc_type = make_node (FUNCTION_TYPE);
999 TREE_TYPE (vfunc_type) = d_int_type;
1000 TYPE_ARG_TYPES (vfunc_type) = NULL_TREE;
1001 layout_type (vfunc_type);
1003 vtable_entry_type = build_pointer_type (vfunc_type);
1006 vtbl_ptr_type_node = build_pointer_type (vtable_entry_type);
1007 layout_type (vtbl_ptr_type_node);
1009 /* When an object is accessed via an interface, this type appears
1010 as the first entry in its vtable. */
1012 tree domain = build_index_type (size_int (3));
1013 vtbl_interface_type_node = build_array_type (ptr_type_node, domain);
1016 /* Use `void[]' as a generic dynamic array type. */
1017 array_type_node = make_struct_type ("__builtin_void[]", 2,
1018 get_identifier ("length"), size_type_node,
1019 get_identifier ("ptr"), ptr_type_node);
1020 TYPE_DYNAMIC_ARRAY (array_type_node) = 1;
1022 null_array_node = d_array_value (array_type_node, size_zero_node,
1023 null_pointer_node);
1026 /* Handle default attributes. */
1028 enum built_in_attribute
1030 #define DEF_ATTR_NULL_TREE(ENUM) ENUM,
1031 #define DEF_ATTR_INT(ENUM, VALUE) ENUM,
1032 #define DEF_ATTR_STRING(ENUM, VALUE) ENUM,
1033 #define DEF_ATTR_IDENT(ENUM, STRING) ENUM,
1034 #define DEF_ATTR_TREE_LIST(ENUM, PURPOSE, VALUE, CHAIN) ENUM,
1035 #include "builtin-attrs.def"
1036 #undef DEF_ATTR_NULL_TREE
1037 #undef DEF_ATTR_INT
1038 #undef DEF_ATTR_STRING
1039 #undef DEF_ATTR_IDENT
1040 #undef DEF_ATTR_TREE_LIST
1041 ATTR_LAST
1044 static GTY(()) tree built_in_attributes[(int) ATTR_LAST];
1046 /* Initialize the attribute table for all the supported builtins. */
1048 static void
1049 d_init_attributes (void)
1051 /* Fill in the built_in_attributes array. */
1052 #define DEF_ATTR_NULL_TREE(ENUM) \
1053 built_in_attributes[(int) ENUM] = NULL_TREE;
1054 # define DEF_ATTR_INT(ENUM, VALUE) \
1055 built_in_attributes[(int) ENUM] = build_int_cst (NULL_TREE, VALUE);
1056 #define DEF_ATTR_STRING(ENUM, VALUE) \
1057 built_in_attributes[(int) ENUM] = build_string (strlen (VALUE), VALUE);
1058 #define DEF_ATTR_IDENT(ENUM, STRING) \
1059 built_in_attributes[(int) ENUM] = get_identifier (STRING);
1060 #define DEF_ATTR_TREE_LIST(ENUM, PURPOSE, VALUE, CHAIN) \
1061 built_in_attributes[(int) ENUM] \
1062 = tree_cons (built_in_attributes[(int) PURPOSE], \
1063 built_in_attributes[(int) VALUE], \
1064 built_in_attributes[(int) CHAIN]);
1065 #include "builtin-attrs.def"
1066 #undef DEF_ATTR_NULL_TREE
1067 #undef DEF_ATTR_INT
1068 #undef DEF_ATTR_STRING
1069 #undef DEF_ATTR_IDENT
1070 #undef DEF_ATTR_TREE_LIST
1073 /* Builtin types. */
1075 enum d_builtin_type
1077 #define DEF_PRIMITIVE_TYPE(NAME, VALUE) NAME,
1078 #define DEF_FUNCTION_TYPE_0(NAME, RETURN) NAME,
1079 #define DEF_FUNCTION_TYPE_1(NAME, RETURN, ARG1) NAME,
1080 #define DEF_FUNCTION_TYPE_2(NAME, RETURN, ARG1, ARG2) NAME,
1081 #define DEF_FUNCTION_TYPE_3(NAME, RETURN, ARG1, ARG2, ARG3) NAME,
1082 #define DEF_FUNCTION_TYPE_4(NAME, RETURN, ARG1, ARG2, ARG3, ARG4) NAME,
1083 #define DEF_FUNCTION_TYPE_5(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5) NAME,
1084 #define DEF_FUNCTION_TYPE_6(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1085 ARG6) NAME,
1086 #define DEF_FUNCTION_TYPE_7(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1087 ARG6, ARG7) NAME,
1088 #define DEF_FUNCTION_TYPE_8(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1089 ARG6, ARG7, ARG8) NAME,
1090 #define DEF_FUNCTION_TYPE_9(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1091 ARG6, ARG7, ARG8, ARG9) NAME,
1092 #define DEF_FUNCTION_TYPE_10(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1093 ARG6, ARG7, ARG8, ARG9, ARG10) NAME,
1094 #define DEF_FUNCTION_TYPE_11(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1095 ARG6, ARG7, ARG8, ARG9, ARG10, ARG11) NAME,
1096 #define DEF_FUNCTION_TYPE_VAR_0(NAME, RETURN) NAME,
1097 #define DEF_FUNCTION_TYPE_VAR_1(NAME, RETURN, ARG1) NAME,
1098 #define DEF_FUNCTION_TYPE_VAR_2(NAME, RETURN, ARG1, ARG2) NAME,
1099 #define DEF_FUNCTION_TYPE_VAR_3(NAME, RETURN, ARG1, ARG2, ARG3) NAME,
1100 #define DEF_FUNCTION_TYPE_VAR_4(NAME, RETURN, ARG1, ARG2, ARG3, ARG4) NAME,
1101 #define DEF_FUNCTION_TYPE_VAR_5(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5) \
1102 NAME,
1103 #define DEF_FUNCTION_TYPE_VAR_6(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1104 ARG6) NAME,
1105 #define DEF_FUNCTION_TYPE_VAR_7(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1106 ARG6, ARG7) NAME,
1107 #define DEF_FUNCTION_TYPE_VAR_11(NAME, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1108 ARG6, ARG7, ARG8, ARG9, ARG10, ARG11) NAME,
1109 #define DEF_POINTER_TYPE(NAME, TYPE) NAME,
1110 #include "builtin-types.def"
1111 #undef DEF_PRIMITIVE_TYPE
1112 #undef DEF_FUNCTION_TYPE_0
1113 #undef DEF_FUNCTION_TYPE_1
1114 #undef DEF_FUNCTION_TYPE_2
1115 #undef DEF_FUNCTION_TYPE_3
1116 #undef DEF_FUNCTION_TYPE_4
1117 #undef DEF_FUNCTION_TYPE_5
1118 #undef DEF_FUNCTION_TYPE_6
1119 #undef DEF_FUNCTION_TYPE_7
1120 #undef DEF_FUNCTION_TYPE_8
1121 #undef DEF_FUNCTION_TYPE_9
1122 #undef DEF_FUNCTION_TYPE_10
1123 #undef DEF_FUNCTION_TYPE_11
1124 #undef DEF_FUNCTION_TYPE_VAR_0
1125 #undef DEF_FUNCTION_TYPE_VAR_1
1126 #undef DEF_FUNCTION_TYPE_VAR_2
1127 #undef DEF_FUNCTION_TYPE_VAR_3
1128 #undef DEF_FUNCTION_TYPE_VAR_4
1129 #undef DEF_FUNCTION_TYPE_VAR_5
1130 #undef DEF_FUNCTION_TYPE_VAR_6
1131 #undef DEF_FUNCTION_TYPE_VAR_7
1132 #undef DEF_FUNCTION_TYPE_VAR_11
1133 #undef DEF_POINTER_TYPE
1134 BT_LAST
1137 typedef enum d_builtin_type builtin_type;
1139 /* A temporary array used in communication with def_fn_type. */
1140 static GTY(()) tree builtin_types[(int) BT_LAST + 1];
1142 /* A helper function for d_init_builtins. Build function type for DEF with
1143 return type RET and N arguments. If VAR is true, then the function should
1144 be variadic after those N arguments.
1146 Takes special care not to ICE if any of the types involved are
1147 error_mark_node, which indicates that said type is not in fact available
1148 (see builtin_type_for_size). In which case the function type as a whole
1149 should be error_mark_node. */
1151 static void
1152 def_fn_type (builtin_type def, builtin_type ret, bool var, int n, ...)
1154 tree t;
1155 tree *args = XALLOCAVEC (tree, n);
1156 va_list list;
1157 int i;
1159 va_start (list, n);
1160 for (i = 0; i < n; ++i)
1162 builtin_type a = (builtin_type) va_arg (list, int);
1163 t = builtin_types[a];
1164 if (t == error_mark_node)
1165 goto egress;
1166 args[i] = t;
1169 t = builtin_types[ret];
1170 if (t == error_mark_node)
1171 goto egress;
1172 if (var)
1173 t = build_varargs_function_type_array (t, n, args);
1174 else
1175 t = build_function_type_array (t, n, args);
1177 egress:
1178 builtin_types[def] = t;
1179 va_end (list);
1182 /* Create builtin types and functions. VA_LIST_REF_TYPE_NODE and
1183 VA_LIST_ARG_TYPE_NODE are used in builtin-types.def. */
1185 static void
1186 d_define_builtins (tree va_list_ref_type_node ATTRIBUTE_UNUSED,
1187 tree va_list_arg_type_node ATTRIBUTE_UNUSED)
1189 #define DEF_PRIMITIVE_TYPE(ENUM, VALUE) \
1190 builtin_types[(int) ENUM] = VALUE;
1191 #define DEF_FUNCTION_TYPE_0(ENUM, RETURN) \
1192 def_fn_type (ENUM, RETURN, 0, 0);
1193 #define DEF_FUNCTION_TYPE_1(ENUM, RETURN, ARG1) \
1194 def_fn_type (ENUM, RETURN, 0, 1, ARG1);
1195 #define DEF_FUNCTION_TYPE_2(ENUM, RETURN, ARG1, ARG2) \
1196 def_fn_type (ENUM, RETURN, 0, 2, ARG1, ARG2);
1197 #define DEF_FUNCTION_TYPE_3(ENUM, RETURN, ARG1, ARG2, ARG3) \
1198 def_fn_type (ENUM, RETURN, 0, 3, ARG1, ARG2, ARG3);
1199 #define DEF_FUNCTION_TYPE_4(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4) \
1200 def_fn_type (ENUM, RETURN, 0, 4, ARG1, ARG2, ARG3, ARG4);
1201 #define DEF_FUNCTION_TYPE_5(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5) \
1202 def_fn_type (ENUM, RETURN, 0, 5, ARG1, ARG2, ARG3, ARG4, ARG5);
1203 #define DEF_FUNCTION_TYPE_6(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1204 ARG6) \
1205 def_fn_type (ENUM, RETURN, 0, 6, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6);
1206 #define DEF_FUNCTION_TYPE_7(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1207 ARG6, ARG7) \
1208 def_fn_type (ENUM, RETURN, 0, 7, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6, ARG7);
1209 #define DEF_FUNCTION_TYPE_8(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1210 ARG6, ARG7, ARG8) \
1211 def_fn_type (ENUM, RETURN, 0, 8, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6, \
1212 ARG7, ARG8);
1213 #define DEF_FUNCTION_TYPE_9(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1214 ARG6, ARG7, ARG8, ARG9) \
1215 def_fn_type (ENUM, RETURN, 0, 9, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6, \
1216 ARG7, ARG8, ARG9);
1217 #define DEF_FUNCTION_TYPE_10(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1218 ARG6, ARG7, ARG8, ARG9, ARG10) \
1219 def_fn_type (ENUM, RETURN, 0, 10, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6, \
1220 ARG7, ARG8, ARG9, ARG10);
1221 #define DEF_FUNCTION_TYPE_11(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1222 ARG6, ARG7, ARG8, ARG9, ARG10, ARG11) \
1223 def_fn_type (ENUM, RETURN, 0, 11, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6, \
1224 ARG7, ARG8, ARG9, ARG10, ARG11);
1225 #define DEF_FUNCTION_TYPE_VAR_0(ENUM, RETURN) \
1226 def_fn_type (ENUM, RETURN, 1, 0);
1227 #define DEF_FUNCTION_TYPE_VAR_1(ENUM, RETURN, ARG1) \
1228 def_fn_type (ENUM, RETURN, 1, 1, ARG1);
1229 #define DEF_FUNCTION_TYPE_VAR_2(ENUM, RETURN, ARG1, ARG2) \
1230 def_fn_type (ENUM, RETURN, 1, 2, ARG1, ARG2);
1231 #define DEF_FUNCTION_TYPE_VAR_3(ENUM, RETURN, ARG1, ARG2, ARG3) \
1232 def_fn_type (ENUM, RETURN, 1, 3, ARG1, ARG2, ARG3);
1233 #define DEF_FUNCTION_TYPE_VAR_4(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4) \
1234 def_fn_type (ENUM, RETURN, 1, 4, ARG1, ARG2, ARG3, ARG4);
1235 #define DEF_FUNCTION_TYPE_VAR_5(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5) \
1236 def_fn_type (ENUM, RETURN, 1, 5, ARG1, ARG2, ARG3, ARG4, ARG5);
1237 #define DEF_FUNCTION_TYPE_VAR_6(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1238 ARG6) \
1239 def_fn_type (ENUM, RETURN, 1, 6, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6);
1240 #define DEF_FUNCTION_TYPE_VAR_7(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1241 ARG6, ARG7) \
1242 def_fn_type (ENUM, RETURN, 1, 7, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6, ARG7);
1243 #define DEF_FUNCTION_TYPE_VAR_11(ENUM, RETURN, ARG1, ARG2, ARG3, ARG4, ARG5, \
1244 ARG6, ARG7, ARG8, ARG9, ARG10, ARG11) \
1245 def_fn_type (ENUM, RETURN, 1, 11, ARG1, ARG2, ARG3, ARG4, ARG5, ARG6, \
1246 ARG7, ARG8, ARG9, ARG10, ARG11);
1247 #define DEF_POINTER_TYPE(ENUM, TYPE) \
1248 builtin_types[(int) ENUM] = build_pointer_type (builtin_types[(int) TYPE]);
1250 #include "builtin-types.def"
1252 #undef DEF_PRIMITIVE_TYPE
1253 #undef DEF_FUNCTION_TYPE_1
1254 #undef DEF_FUNCTION_TYPE_2
1255 #undef DEF_FUNCTION_TYPE_3
1256 #undef DEF_FUNCTION_TYPE_4
1257 #undef DEF_FUNCTION_TYPE_5
1258 #undef DEF_FUNCTION_TYPE_6
1259 #undef DEF_FUNCTION_TYPE_7
1260 #undef DEF_FUNCTION_TYPE_8
1261 #undef DEF_FUNCTION_TYPE_9
1262 #undef DEF_FUNCTION_TYPE_10
1263 #undef DEF_FUNCTION_TYPE_11
1264 #undef DEF_FUNCTION_TYPE_VAR_0
1265 #undef DEF_FUNCTION_TYPE_VAR_1
1266 #undef DEF_FUNCTION_TYPE_VAR_2
1267 #undef DEF_FUNCTION_TYPE_VAR_3
1268 #undef DEF_FUNCTION_TYPE_VAR_4
1269 #undef DEF_FUNCTION_TYPE_VAR_5
1270 #undef DEF_FUNCTION_TYPE_VAR_6
1271 #undef DEF_FUNCTION_TYPE_VAR_7
1272 #undef DEF_FUNCTION_TYPE_VAR_11
1273 #undef DEF_POINTER_TYPE
1274 builtin_types[(int) BT_LAST] = NULL_TREE;
1276 d_init_attributes ();
1278 #define DEF_BUILTIN(ENUM, NAME, CLASS, TYPE, LIBTYPE, BOTH_P, FALLBACK_P, \
1279 NONANSI_P, ATTRS, IMPLICIT, COND) \
1280 if (NAME && COND) \
1281 do_build_builtin_fn (ENUM, NAME, CLASS, \
1282 builtin_types[(int) TYPE], \
1283 BOTH_P, FALLBACK_P, \
1284 built_in_attributes[(int) ATTRS], IMPLICIT);
1285 #include "builtins.def"
1286 #undef DEF_BUILTIN
1289 /* Build builtin functions and types for the D language frontend. */
1291 void
1292 d_init_builtins (void)
1294 d_build_c_type_nodes ();
1295 d_build_d_type_nodes ();
1297 if (TREE_CODE (va_list_type_node) == ARRAY_TYPE)
1299 /* It might seem natural to make the argument type a pointer, but there
1300 is no implicit casting from arrays to pointers in D. */
1301 d_define_builtins (va_list_type_node, va_list_type_node);
1303 else
1305 d_define_builtins (build_reference_type (va_list_type_node),
1306 va_list_type_node);
1309 targetm.init_builtins ();
1310 build_common_builtin_nodes ();
1313 /* Registration of machine- or os-specific builtin types.
1314 Add to builtin types list for maybe processing later
1315 if `gcc.builtins' was imported into the current module. */
1317 void
1318 d_register_builtin_type (tree type, const char *name)
1320 tree decl = build_decl (UNKNOWN_LOCATION, TYPE_DECL,
1321 get_identifier (name), type);
1322 DECL_ARTIFICIAL (decl) = 1;
1324 if (!TYPE_NAME (type))
1325 TYPE_NAME (type) = decl;
1327 vec_safe_push (gcc_builtins_types, decl);
1330 /* Add DECL to builtin functions list for maybe processing later
1331 if `gcc.builtins' was imported into the current module. */
1333 tree
1334 d_builtin_function (tree decl)
1336 if (!flag_no_builtin && DECL_ASSEMBLER_NAME_SET_P (decl))
1338 /* Associate the assembler identifier with the built-in. */
1339 tree ident = DECL_ASSEMBLER_NAME (decl);
1340 IDENTIFIER_DECL_TREE (ident) = decl;
1343 vec_safe_push (gcc_builtins_functions, decl);
1344 return decl;
1347 /* Same as d_builtin_function, but used to delay putting in back-end builtin
1348 functions until the ISA that defines the builtin has been declared.
1349 However in D, there is no global namespace. All builtins get pushed into the
1350 `gcc.builtins' module, which is constructed during the semantic analysis
1351 pass, which has already finished by the time target attributes are evaluated.
1352 So builtins are not pushed because they would be ultimately ignored.
1353 The purpose of having this function then is to improve compile-time
1354 reflection support to allow user-code to determine whether a given back end
1355 function is enabled by the ISA. */
1357 tree
1358 d_builtin_function_ext_scope (tree decl)
1360 return decl;
1363 #include "gt-d-d-builtins.h"