From c428454ecee141937a6810dd6213716602d563ca Mon Sep 17 00:00:00 2001 From: Iain Buclaw <ibuclaw@gdcproject.org> Date: Sat, 3 Feb 2024 14:00:24 +0100 Subject: [PATCH] d: Merge dmd, druntime a6f1083699, phobos 31dedd7da D front-end changes: - Import dmd v2.107.0. - Character postfixes can now also be used for integers of size two or four. D run-time changes: - Import druntime v2.107.0. Phobos changes: - Import phobos v2.107.0. gcc/d/ChangeLog: * dmd/MERGE: Merge upstream dmd a6f1083699. * dmd/VERSION: Bump version to v2.107.0 * Make-lang.in (D_FRONTEND_OBJS): Add d/pragmasem.o. * d-builtins.cc (strip_type_modifiers): Update for new front-end interface. * d-codegen.cc (declaration_type): Likewise. (parameter_type): Likewise. * d-target.cc (TargetCPP::parameterType): Likewise. * expr.cc (ExprVisitor::visit (IndexExp *)): Likewise. (ExprVisitor::visit (VarExp *)): Likewise. (ExprVisitor::visit (AssocArrayLiteralExp *)): Likewise. * runtime.cc (get_libcall_type): Likewise. * typeinfo.cc (TypeInfoVisitor::visit (TypeInfoConstDeclaration *)): Likewise. (TypeInfoVisitor::visit (TypeInfoInvariantDeclaration *)): Likewise. (TypeInfoVisitor::visit (TypeInfoSharedDeclaration *)): Likewise. (TypeInfoVisitor::visit (TypeInfoWildDeclaration *)): Likewise. * types.cc (build_ctype): Likewise. libphobos/ChangeLog: * libdruntime/MERGE: Merge upstream druntime a6f1083699. * src/MERGE: Merge upstream phobos 31dedd7da. --- gcc/d/Make-lang.in | 1 + gcc/d/d-builtins.cc | 2 +- gcc/d/d-codegen.cc | 4 +- gcc/d/d-target.cc | 4 +- gcc/d/dmd/MERGE | 2 +- gcc/d/dmd/README.md | 1 + gcc/d/dmd/VERSION | 2 +- gcc/d/dmd/constfold.d | 6 +- gcc/d/dmd/cparse.d | 2 +- gcc/d/dmd/ctfeexpr.d | 2 +- gcc/d/dmd/dcast.d | 20 +- gcc/d/dmd/dclass.d | 1 + gcc/d/dmd/declaration.h | 1 - gcc/d/dmd/denum.d | 7 +- gcc/d/dmd/dinterpret.d | 43 +- gcc/d/dmd/dmangle.d | 20 +- gcc/d/dmd/dsymbol.h | 2 +- gcc/d/dmd/dsymbolsem.d | 1888 ++--------------- gcc/d/dmd/dtemplate.d | 759 +------ gcc/d/dmd/dtoh.d | 1 + gcc/d/dmd/enumsem.d | 6 + gcc/d/dmd/expression.d | 3 +- gcc/d/dmd/expression.h | 3 +- gcc/d/dmd/expressionsem.d | 31 +- gcc/d/dmd/func.d | 172 +- gcc/d/dmd/funcsem.d | 1150 ++++++++++ gcc/d/dmd/hdrgen.d | 3 +- gcc/d/dmd/initsem.d | 86 +- gcc/d/dmd/mtype.d | 353 +-- gcc/d/dmd/mtype.h | 26 +- gcc/d/dmd/opover.d | 1 + gcc/d/dmd/optimize.d | 3 +- gcc/d/dmd/pragmasem.d | 650 ++++++ gcc/d/dmd/scope.h | 2 +- gcc/d/dmd/semantic2.d | 23 +- gcc/d/dmd/sideeffect.d | 10 + gcc/d/dmd/statementsem.d | 181 +- gcc/d/dmd/templatesem.d | 909 +++++++- gcc/d/dmd/typesem.d | 304 ++- gcc/d/dmd/utils.d | 41 + gcc/d/expr.cc | 9 +- gcc/d/runtime.cc | 6 +- gcc/d/typeinfo.cc | 8 +- gcc/d/types.cc | 2 +- gcc/testsuite/gdc.test/compilable/ddoc4162.d | 2 +- gcc/testsuite/gdc.test/compilable/ddoc5446.d | 2 +- gcc/testsuite/gdc.test/compilable/ddoc7795.d | 2 +- .../compilable/{ddoc12.d => ddoc_bom_UTF8.d} | 0 gcc/testsuite/gdc.test/compilable/test24338.d | 10 + .../gdc.test/fail_compilation/discard_value.d | 34 + .../gdc.test/fail_compilation/fail12390.d | 16 - .../gdc.test/fail_compilation/gag4269a.d | 2 +- .../gdc.test/fail_compilation/gag4269b.d | 2 +- .../gdc.test/fail_compilation/gag4269c.d | 2 +- .../gdc.test/fail_compilation/gag4269d.d | 2 +- .../gdc.test/fail_compilation/gag4269e.d | 2 +- .../gdc.test/fail_compilation/gag4269f.d | 2 +- .../gdc.test/fail_compilation/gag4269g.d | 2 +- .../gdc.test/fail_compilation/hexstring.d | 8 +- .../gdc.test/fail_compilation/ice10599.d | 2 +- .../gdc.test/fail_compilation/test24365.d | 20 + gcc/testsuite/gdc.test/runnable/helloUTF8.d | 16 - gcc/testsuite/gdc.test/runnable/literal.d | 13 + gcc/testsuite/gdc.test/runnable/staticaa.d | 12 + gcc/testsuite/gdc.test/runnable/xtestenum.d | 14 + libphobos/libdruntime/MERGE | 2 +- libphobos/libdruntime/core/atomic.d | 44 +- libphobos/libdruntime/core/demangle.d | 936 +++++--- libphobos/libdruntime/core/internal/atomic.d | 650 +++--- libphobos/libdruntime/core/internal/traits.d | 4 +- libphobos/libdruntime/core/stdc/stdatomic.d | 577 ++--- libphobos/libdruntime/core/thread/fiber.d | 21 +- libphobos/src/MERGE | 2 +- libphobos/src/std/algorithm/searching.d | 14 +- 74 files changed, 4713 insertions(+), 4452 deletions(-) create mode 100644 gcc/d/dmd/pragmasem.d rename gcc/testsuite/gdc.test/compilable/{ddoc12.d => ddoc_bom_UTF8.d} (100%) create mode 100644 gcc/testsuite/gdc.test/compilable/test24338.d create mode 100644 gcc/testsuite/gdc.test/fail_compilation/discard_value.d delete mode 100644 gcc/testsuite/gdc.test/fail_compilation/fail12390.d create mode 100644 gcc/testsuite/gdc.test/fail_compilation/test24365.d delete mode 100644 gcc/testsuite/gdc.test/runnable/helloUTF8.d diff --git a/gcc/d/Make-lang.in b/gcc/d/Make-lang.in index 176105b9a46f..d379ef14f806 100644 --- a/gcc/d/Make-lang.in +++ b/gcc/d/Make-lang.in @@ -163,6 +163,7 @@ D_FRONTEND_OBJS = \ d/parsetimevisitor.o \ d/permissivevisitor.o \ d/postordervisitor.o \ + d/pragmasem.o \ d/printast.o \ d/root-aav.o \ d/root-array.o \ diff --git a/gcc/d/d-builtins.cc b/gcc/d/d-builtins.cc index 1b5b3bea8ca7..4ed8751079bf 100644 --- a/gcc/d/d-builtins.cc +++ b/gcc/d/d-builtins.cc @@ -690,7 +690,7 @@ strip_type_modifiers (Type *type) return tnext->pointerTo (); } - return type->castMod (0); + return castMod (type, 0); } /* Returns true if types T1 and T2 representing return types or types of diff --git a/gcc/d/d-codegen.cc b/gcc/d/d-codegen.cc index af938ddc04aa..95dc8b6327ef 100644 --- a/gcc/d/d-codegen.cc +++ b/gcc/d/d-codegen.cc @@ -157,7 +157,7 @@ declaration_type (Declaration *decl) if (decl->isParameter () && valist_array_p (decl->type)) { Type *valist = decl->type->nextOf ()->pointerTo (); - valist = valist->castMod (decl->type->mod); + valist = castMod (valist, decl->type->mod); return build_ctype (valist); } @@ -207,7 +207,7 @@ parameter_type (Parameter *arg) if (valist_array_p (arg->type)) { Type *valist = arg->type->nextOf ()->pointerTo (); - valist = valist->castMod (arg->type->mod); + valist = castMod (valist, arg->type->mod); return build_ctype (valist); } diff --git a/gcc/d/d-target.cc b/gcc/d/d-target.cc index 157253e0cca8..ff3489c6cf4e 100644 --- a/gcc/d/d-target.cc +++ b/gcc/d/d-target.cc @@ -381,11 +381,11 @@ TargetCPP::parameterType (Type *type) Type *tvalist = target.va_listType (Loc (), NULL); if (type->ty == TY::Tsarray && tvalist->ty == TY::Tsarray) { - Type *tb = type->toBasetype ()->mutableOf (); + Type *tb = mutableOf (type->toBasetype ()); if (tb == tvalist) { tb = type->nextOf ()->pointerTo (); - type = tb->castMod (type->mod); + type = castMod (tb, type->mod); } } diff --git a/gcc/d/dmd/MERGE b/gcc/d/dmd/MERGE index 9217c654225b..57ac2dc69e75 100644 --- a/gcc/d/dmd/MERGE +++ b/gcc/d/dmd/MERGE @@ -1,4 +1,4 @@ -e7709452775d374c1e2dfb67566668ada3dec5fc +a6f10836997d0b5526c8c363d781b4029c77f09f The first line of this file holds the git revision number of the last merge done from the dlang/dmd repository. diff --git a/gcc/d/dmd/README.md b/gcc/d/dmd/README.md index 23f3333198d8..282e81837833 100644 --- a/gcc/d/dmd/README.md +++ b/gcc/d/dmd/README.md @@ -119,6 +119,7 @@ Note that these groups have no strict meaning, the category assignments are a bi | [expressionsem.d](https://github.com/dlang/dmd/blob/master/compiler/src/dmd/expressionsem.d) | Do semantic analysis for expressions | | [statementsem.d](https://github.com/dlang/dmd/blob/master/compiler/src/dmd/statementsem.d) | Do semantic analysis for statements | | [initsem.d](https://github.com/dlang/dmd/blob/master/compiler/src/dmd/initsem.d) | Do semantic analysis for initializers | +| [pragmasem.d](https://github.com/dlang/dmd/blob/master/compiler/src/dmd/pragmasem.d) | Do semantic analysis for pragmas | | [templatesem.d](https://github.com/dlang/dmd/blob/master/compiler/src/dmd/templatesem.d) | Do semantic analysis for templates | | [templateparamsem.d](https://github.com/dlang/dmd/blob/master/compiler/src/dmd/templateparamsem.d) | Do semantic analysis for template parameters | | [typesem.d](https://github.com/dlang/dmd/blob/master/compiler/src/dmd/typesem.d) | Do semantic analysis for types | diff --git a/gcc/d/dmd/VERSION b/gcc/d/dmd/VERSION index b9813c7ff3b0..8463aee451ce 100644 --- a/gcc/d/dmd/VERSION +++ b/gcc/d/dmd/VERSION @@ -1 +1 @@ -v2.107.0-beta.1 +v2.107.0 diff --git a/gcc/d/dmd/constfold.d b/gcc/d/dmd/constfold.d index 41fed9cae496..f5d2b60f45b9 100644 --- a/gcc/d/dmd/constfold.d +++ b/gcc/d/dmd/constfold.d @@ -1331,9 +1331,9 @@ int sliceCmpStringWithArray(const StringExp se1, ArrayLiteralExp ae2, size_t lo1 { foreach (j; 0 .. len) { - const val2 = cast(dchar)ae2[j + lo2].toInteger(); - const val1 = se1.getCodeUnit(j + lo1); - const int c = val1 - val2; + const val2 = ae2[j + lo2].toInteger(); + const val1 = se1.getIndex(j + lo1); + const int c = (val1 > val2) - (val1 < val2); if (c) return c; } diff --git a/gcc/d/dmd/cparse.d b/gcc/d/dmd/cparse.d index e0cdc87b7fd2..d46235058163 100644 --- a/gcc/d/dmd/cparse.d +++ b/gcc/d/dmd/cparse.d @@ -5291,7 +5291,7 @@ final class CParser(AST) : Parser!AST auto ifn = new AST.ExpInitializer(loc, efn); auto lenfn = new AST.IntegerExp(loc, fn.length + 1, AST.Type.tuns32); // +1 for terminating 0 auto tfn = new AST.TypeSArray(AST.Type.tchar, lenfn); - efn.type = tfn.immutableOf(); + efn.type = tfn.makeImmutable(); efn.committed = true; auto sfn = new AST.VarDeclaration(loc, tfn, Id.__func__, ifn, STC.gshared | STC.immutable_); auto e = new AST.DeclarationExp(loc, sfn); diff --git a/gcc/d/dmd/ctfeexpr.d b/gcc/d/dmd/ctfeexpr.d index af83aad55454..d2fcf5f79608 100644 --- a/gcc/d/dmd/ctfeexpr.d +++ b/gcc/d/dmd/ctfeexpr.d @@ -34,6 +34,7 @@ import dmd.root.ctfloat; import dmd.root.port; import dmd.root.rmem; import dmd.tokens; +import dmd.typesem; import dmd.visitor; /****************************************************************/ @@ -640,7 +641,6 @@ bool isSafePointerCast(Type srcPointee, Type destPointee) // It's OK if function pointers differ only in safe/pure/nothrow if (srcPointee.ty == Tfunction && destPointee.ty == Tfunction) { - import dmd.typesem : covariant; return srcPointee.covariant(destPointee) == Covariant.yes || destPointee.covariant(srcPointee) == Covariant.yes; } diff --git a/gcc/d/dmd/dcast.d b/gcc/d/dmd/dcast.d index 628c688979f3..9ee8e8c48642 100644 --- a/gcc/d/dmd/dcast.d +++ b/gcc/d/dmd/dcast.d @@ -30,6 +30,7 @@ import dmd.escape; import dmd.expression; import dmd.expressionsem; import dmd.func; +import dmd.funcsem; import dmd.globals; import dmd.hdrgen; import dmd.location; @@ -720,11 +721,6 @@ extern(C++) MATCH implicitConvTo(Expression e, Type t) return m; case Tint8: case Tuns8: - if (e.hexString) - { - m = MATCH.convert; - return m; - } break; case Tenum: if (tn.isTypeEnum().sym.isSpecial()) @@ -739,6 +735,14 @@ extern(C++) MATCH implicitConvTo(Expression e, Type t) break; } } + if (e.hexString) + { + if (tn.isintegral && tn.size == e.sz) + { + m = MATCH.convert; + return m; + } + } break; default: @@ -2185,7 +2189,7 @@ Expression castTo(Expression e, Scope* sc, Type t, Type att = null) if (auto f = isFuncAddress(e)) { - if (f.checkForwardRef(e.loc)) + if (checkForwardRef(f, e.loc)) { return ErrorExp.get(); } @@ -2441,7 +2445,7 @@ Expression castTo(Expression e, Scope* sc, Type t, Type att = null) if (auto f = isFuncAddress(e)) { - if (f.checkForwardRef(e.loc)) + if (checkForwardRef(f, e.loc)) { return ErrorExp.get(); } @@ -2496,7 +2500,7 @@ Expression castTo(Expression e, Scope* sc, Type t, Type att = null) if (auto f = isFuncAddress(e)) { - if (f.checkForwardRef(e.loc)) + if (checkForwardRef(f, e.loc)) { return ErrorExp.get(); } diff --git a/gcc/d/dmd/dclass.d b/gcc/d/dmd/dclass.d index 7e5e7e441789..8bac1f4ea266 100644 --- a/gcc/d/dmd/dclass.d +++ b/gcc/d/dmd/dclass.d @@ -33,6 +33,7 @@ import dmd.mtype; import dmd.objc; import dmd.root.rmem; import dmd.target; +import dmd.typesem; import dmd.visitor; /*********************************************************** diff --git a/gcc/d/dmd/declaration.h b/gcc/d/dmd/declaration.h index e4efbbcc91be..afbb9975cc9c 100644 --- a/gcc/d/dmd/declaration.h +++ b/gcc/d/dmd/declaration.h @@ -703,7 +703,6 @@ public: Expressions *fdensureParams(Expressions *fdep); bool equals(const RootObject * const o) const override final; - int findVtblIndex(Dsymbols *vtbl, int dim); bool overloadInsert(Dsymbol *s) override; bool inUnittest(); static MATCH leastAsSpecialized(FuncDeclaration *f, FuncDeclaration *g, Identifiers *names); diff --git a/gcc/d/dmd/denum.d b/gcc/d/dmd/denum.d index 9abdebd6adcf..36799766eced 100644 --- a/gcc/d/dmd/denum.d +++ b/gcc/d/dmd/denum.d @@ -18,19 +18,16 @@ import core.stdc.stdio; import dmd.astenums; import dmd.attrib; -import dmd.errors; import dmd.gluelayer; import dmd.declaration; import dmd.dscope; import dmd.dsymbol; -import dmd.dsymbolsem; import dmd.expression; import dmd.id; import dmd.identifier; import dmd.init; import dmd.location; import dmd.mtype; -import dmd.typesem; import dmd.visitor; /*********************************************************** @@ -66,6 +63,8 @@ extern (C++) final class EnumDeclaration : ScopeDsymbol import dmd.common.bitfields : generateBitFields; mixin(generateBitFields!(BitFields, ubyte)); + Symbol* sinit; + extern (D) this(const ref Loc loc, Identifier ident, Type memtype) { super(loc, ident); @@ -127,8 +126,6 @@ extern (C++) final class EnumDeclaration : ScopeDsymbol return this; } - Symbol* sinit; - override void accept(Visitor v) { v.visit(this); diff --git a/gcc/d/dmd/dinterpret.d b/gcc/d/dmd/dinterpret.d index d8069c63a56b..b0785424f3cd 100644 --- a/gcc/d/dmd/dinterpret.d +++ b/gcc/d/dmd/dinterpret.d @@ -50,6 +50,8 @@ import dmd.rootobject; import dmd.root.utf; import dmd.statement; import dmd.tokens; +import dmd.typesem : mutableOf; +import dmd.utils : arrayCastBigEndian; import dmd.visitor; /************************************* @@ -7744,44 +7746,3 @@ private void removeHookTraceImpl(ref CallExp ce, ref FuncDeclaration fd) if (global.params.v.verbose) message("strip %s =>\n %s", oldCE.toChars(), ce.toChars()); } - -/** - * Cast a `ubyte[]` to an array of larger integers as if we are on a big endian architecture - * Params: - * data = array with big endian data - * size = 1 for ubyte[], 2 for ushort[], 4 for uint[], 8 for ulong[] - * Returns: copy of `data`, with bytes shuffled if compiled for `version(LittleEndian)` - */ -ubyte[] arrayCastBigEndian(const ubyte[] data, size_t size) -{ - ubyte[] impl(T)() - { - auto result = new T[](data.length / T.sizeof); - foreach (i; 0 .. result.length) - { - result[i] = 0; - foreach (j; 0 .. T.sizeof) - { - result[i] |= T(data[i * T.sizeof + j]) << ((T.sizeof - 1 - j) * 8); - } - } - return cast(ubyte[]) result; - } - switch (size) - { - case 1: return data.dup; - case 2: return impl!ushort; - case 4: return impl!uint; - case 8: return impl!ulong; - default: assert(0); - } -} - -unittest -{ - ubyte[] data = [0xAA, 0xBB, 0xCC, 0xDD, 0xEE, 0xFF, 0x11, 0x22]; - assert(cast(ulong[]) arrayCastBigEndian(data, 8) == [0xAABBCCDDEEFF1122]); - assert(cast(uint[]) arrayCastBigEndian(data, 4) == [0xAABBCCDD, 0xEEFF1122]); - assert(cast(ushort[]) arrayCastBigEndian(data, 2) == [0xAABB, 0xCCDD, 0xEEFF, 0x1122]); - assert(cast(ubyte[]) arrayCastBigEndian(data, 1) == data); -} diff --git a/gcc/d/dmd/dmangle.d b/gcc/d/dmd/dmangle.d index 5bd1379d1705..1d016479e1d9 100644 --- a/gcc/d/dmd/dmangle.d +++ b/gcc/d/dmd/dmangle.d @@ -951,6 +951,14 @@ public: OutBuffer tmp; const(char)[] q; + void mangleAsArray() + { + buf.writeByte('A'); + buf.print(e.len); + foreach (i; 0 .. e.len) + mangleInteger(e.getIndex(i)); + } + /* Write string in UTF-8 format */ switch (e.sz) @@ -967,7 +975,7 @@ public: { dchar c; if (const s = utf_decodeWchar(slice, u, c)) - error(e.loc, "%.*s", cast(int)s.length, s.ptr); + return mangleAsArray(); else tmp.writeUTF8(c); } @@ -981,7 +989,7 @@ public: foreach (c; slice) { if (!utf_isValidDchar(c)) - error(e.loc, "invalid UCS-32 char \\U%08x", c); + return mangleAsArray(); else tmp.writeUTF8(c); } @@ -990,13 +998,7 @@ public: } case 8: // String of size 8 has to be hexstring cast to long[], mangle as array literal - buf.writeByte('A'); - buf.print(e.len); - foreach (i; 0 .. e.len) - { - mangleInteger(e.getIndex(i)); - } - return; + return mangleAsArray(); default: assert(0); } diff --git a/gcc/d/dmd/dsymbol.h b/gcc/d/dmd/dsymbol.h index 7d715b47b310..e463d3d9005e 100644 --- a/gcc/d/dmd/dsymbol.h +++ b/gcc/d/dmd/dsymbol.h @@ -147,7 +147,7 @@ enum /* Flags for symbol search */ -typedef uint SearchOptFlags; +typedef unsigned SearchOptFlags; enum class SearchOpt : SearchOptFlags { all = 0x00, // default diff --git a/gcc/d/dmd/dsymbolsem.d b/gcc/d/dmd/dsymbolsem.d index 658beafdf839..33a397a87b0f 100644 --- a/gcc/d/dmd/dsymbolsem.d +++ b/gcc/d/dmd/dsymbolsem.d @@ -21,17 +21,14 @@ import dmd.arraytypes; import dmd.astcodegen; import dmd.astenums; import dmd.attrib; -import dmd.blockexit; import dmd.clone; import dmd.cond; -import dmd.compiler; import dmd.dcast; import dmd.dclass; import dmd.declaration; import dmd.denum; import dmd.dimport; import dmd.dinterpret; -import dmd.dmangle; import dmd.dmodule; import dmd.dscope; import dmd.dstruct; @@ -56,7 +53,6 @@ import dmd.hdrgen; import dmd.location; import dmd.mtype; import dmd.mustuse; -import dmd.nogc; import dmd.nspace; import dmd.objc; import dmd.opover; @@ -67,17 +63,16 @@ import dmd.root.filename; import dmd.common.outbuffer; import dmd.root.rmem; import dmd.rootobject; -import dmd.root.utf; import dmd.semantic2; import dmd.semantic3; import dmd.sideeffect; -import dmd.statementsem; import dmd.staticassert; import dmd.tokens; import dmd.utils; import dmd.statement; import dmd.target; import dmd.templateparamsem; +import dmd.templatesem; import dmd.typesem; import dmd.visitor; @@ -87,48 +82,6 @@ else version = MARS; enum LOG = false; -package uint setMangleOverride(Dsymbol s, const(char)[] sym) -{ - if (s.isFuncDeclaration() || s.isVarDeclaration()) - { - s.isDeclaration().mangleOverride = sym; - return 1; - } - - if (auto ad = s.isAttribDeclaration()) - { - uint nestedCount = 0; - - ad.include(null).foreachDsymbol( (s) { nestedCount += setMangleOverride(s, sym); } ); - - return nestedCount; - } - return 0; -} - -/** - * Apply pragma printf/scanf to FuncDeclarations under `s`, - * poking through attribute declarations such as `extern(C)` - * but not through aggregates or function bodies. - * - * Params: - * s = symbol to apply - * printf = `true` for printf, `false` for scanf - */ -private void setPragmaPrintf(Dsymbol s, bool printf) -{ - if (auto fd = s.isFuncDeclaration()) - { - fd.printf = printf; - fd.scanf = !printf; - } - - if (auto ad = s.isAttribDeclaration()) - { - ad.include(null).foreachDsymbol( (s) { setPragmaPrintf(s, printf); } ); - } -} - /************************************* * Does semantic analysis on the public face of declarations. */ @@ -1346,9 +1299,10 @@ private extern(C++) final class DsymbolSemanticVisitor : Visitor dsym._init = dsym._init.initializerSemantic(sc, dsym.type, sc.intypeof == 1 ? INITnointerpret : INITinterpret); import dmd.semantic2 : lowerStaticAAs; lowerStaticAAs(dsym, sc); - const init_err = dsym._init.isExpInitializer(); + auto init_err = dsym._init.isExpInitializer(); if (init_err && init_err.exp.op == EXP.showCtfeContext) { + init_err.exp = ErrorExp.get(); errorSupplemental(dsym.loc, "compile time context created here"); } } @@ -1800,311 +1754,8 @@ private extern(C++) final class DsymbolSemanticVisitor : Visitor override void visit(PragmaDeclaration pd) { - StringExp verifyMangleString(ref Expression e) - { - auto se = semanticString(sc, e, "mangled name"); - if (!se) - return null; - e = se; - if (!se.len) - { - .error(pd.loc, "%s `%s` - zero-length string not allowed for mangled name", pd.kind, pd.toPrettyChars); - return null; - } - if (se.sz != 1) - { - .error(pd.loc, "%s `%s` - mangled name characters can only be of type `char`", pd.kind, pd.toPrettyChars); - return null; - } - version (all) - { - /* Note: D language specification should not have any assumption about backend - * implementation. Ideally pragma(mangle) can accept a string of any content. - * - * Therefore, this validation is compiler implementation specific. - */ - auto slice = se.peekString(); - for (size_t i = 0; i < se.len;) - { - dchar c = slice[i]; - if (c < 0x80) - { - if (c.isValidMangling) - { - ++i; - continue; - } - else - { - .error(pd.loc, "%s `%s` char 0x%02x not allowed in mangled name", pd.kind, pd.toPrettyChars, c); - break; - } - } - if (const msg = utf_decodeChar(slice, i, c)) - { - .error(pd.loc, "%s `%s` %.*s", pd.kind, pd.toPrettyChars, cast(int)msg.length, msg.ptr); - break; - } - if (!isUniAlpha(c)) - { - .error(pd.loc, "%s `%s` char `0x%04x` not allowed in mangled name", pd.kind, pd.toPrettyChars, c); - break; - } - } - } - return se; - } - void declarations() - { - if (!pd.decl) - return; - - Scope* sc2 = pd.newScope(sc); - scope(exit) - if (sc2 != sc) - sc2.pop(); - - foreach (s; (*pd.decl)[]) - { - if (pd.ident == Id.printf || pd.ident == Id.scanf) - { - s.setPragmaPrintf(pd.ident == Id.printf); - s.dsymbolSemantic(sc2); - continue; - } - - s.dsymbolSemantic(sc2); - if (pd.ident != Id.mangle) - continue; - assert(pd.args); - if (auto ad = s.isAggregateDeclaration()) - { - Expression e = (*pd.args)[0]; - sc2 = sc2.startCTFE(); - e = e.expressionSemantic(sc); - e = resolveProperties(sc2, e); - sc2 = sc2.endCTFE(); - AggregateDeclaration agg; - if (auto tc = e.type.isTypeClass()) - agg = tc.sym; - else if (auto ts = e.type.isTypeStruct()) - agg = ts.sym; - ad.pMangleOverride = new MangleOverride; - void setString(ref Expression e) - { - if (auto se = verifyMangleString(e)) - { - const name = (cast(const(char)[])se.peekData()).xarraydup; - ad.pMangleOverride.id = Identifier.idPool(name); - e = se; - } - else - error(e.loc, "must be a string"); - } - if (agg) - { - ad.pMangleOverride.agg = agg; - if (pd.args.length == 2) - { - setString((*pd.args)[1]); - } - else - ad.pMangleOverride.id = agg.ident; - } - else - setString((*pd.args)[0]); - } - else if (auto td = s.isTemplateDeclaration()) - { - .error(pd.loc, "%s `%s` cannot apply to a template declaration", pd.kind, pd.toPrettyChars); - errorSupplemental(pd.loc, "use `template Class(Args...){ pragma(mangle, \"other_name\") class Class {} }`"); - } - else if (auto se = verifyMangleString((*pd.args)[0])) - { - const name = (cast(const(char)[])se.peekData()).xarraydup; - uint cnt = setMangleOverride(s, name); - if (cnt > 1) - .error(pd.loc, "%s `%s` can only apply to a single declaration", pd.kind, pd.toPrettyChars); - } - } - } - - void noDeclarations() - { - if (pd.decl) - { - .error(pd.loc, "%s `%s` is missing a terminating `;`", pd.kind, pd.toPrettyChars); - declarations(); - // do them anyway, to avoid segfaults. - } - } - - // Should be merged with PragmaStatement - //printf("\tPragmaDeclaration::semantic '%s'\n", pd.toChars()); - if (target.supportsLinkerDirective()) - { - if (pd.ident == Id.linkerDirective) - { - if (!pd.args || pd.args.length != 1) - .error(pd.loc, "%s `%s` one string argument expected for pragma(linkerDirective)", pd.kind, pd.toPrettyChars); - else - { - auto se = semanticString(sc, (*pd.args)[0], "linker directive"); - if (!se) - return noDeclarations(); - (*pd.args)[0] = se; - if (global.params.v.verbose) - message("linkopt %.*s", cast(int)se.len, se.peekString().ptr); - } - return noDeclarations(); - } - } - if (pd.ident == Id.msg) - { - if (!pd.args) - return noDeclarations(); - - if (!pragmaMsgSemantic(pd.loc, sc, pd.args)) - return; - - return noDeclarations(); - } - else if (pd.ident == Id.lib) - { - if (!pd.args || pd.args.length != 1) - .error(pd.loc, "%s `%s` string expected for library name", pd.kind, pd.toPrettyChars); - else - { - auto se = semanticString(sc, (*pd.args)[0], "library name"); - if (!se) - return noDeclarations(); - (*pd.args)[0] = se; - - auto name = se.peekString().xarraydup; - if (global.params.v.verbose) - message("library %s", name.ptr); - if (global.params.moduleDeps.buffer && !global.params.moduleDeps.name) - { - OutBuffer* ob = global.params.moduleDeps.buffer; - Module imod = sc._module; - ob.writestring("depsLib "); - ob.writestring(imod.toPrettyChars()); - ob.writestring(" ("); - escapePath(ob, imod.srcfile.toChars()); - ob.writestring(") : "); - ob.writestring(name); - ob.writenl(); - } - mem.xfree(name.ptr); - } - return noDeclarations(); - } - else if (pd.ident == Id.startaddress) - { - pragmaStartAddressSemantic(pd.loc, sc, pd.args); - return noDeclarations(); - } - else if (pd.ident == Id.Pinline) - { - // this pragma now gets evaluated on demand in function semantic - - return declarations(); - } - else if (pd.ident == Id.mangle) - { - if (!pd.args) - pd.args = new Expressions(); - if (pd.args.length == 0 || pd.args.length > 2) - { - .error(pd.loc, pd.args.length == 0 ? "%s `%s` - string expected for mangled name" - : "%s `%s` expected 1 or 2 arguments", pd.kind, pd.toPrettyChars); - pd.args.setDim(1); - (*pd.args)[0] = ErrorExp.get(); // error recovery - } - return declarations(); - } - else if (pd.ident == Id.crt_constructor || pd.ident == Id.crt_destructor) - { - if (pd.args && pd.args.length != 0) - .error(pd.loc, "%s `%s` takes no argument", pd.kind, pd.toPrettyChars); - else - { - immutable isCtor = pd.ident == Id.crt_constructor; - - static uint recurse(Dsymbol s, bool isCtor) - { - if (auto ad = s.isAttribDeclaration()) - { - uint nestedCount; - auto decls = ad.include(null); - if (decls) - { - for (size_t i = 0; i < decls.length; ++i) - nestedCount += recurse((*decls)[i], isCtor); - } - return nestedCount; - } - else if (auto f = s.isFuncDeclaration()) - { - if (isCtor) - f.isCrtCtor = true; - else - f.isCrtDtor = true; - - return 1; - } - else - return 0; - assert(0); - } - - if (recurse(pd, isCtor) > 1) - .error(pd.loc, "%s `%s` can only apply to a single declaration", pd.kind, pd.toPrettyChars); - } - return declarations(); - } - else if (pd.ident == Id.printf || pd.ident == Id.scanf) - { - if (pd.args && pd.args.length != 0) - .error(pd.loc, "%s `%s` takes no argument", pd.kind, pd.toPrettyChars); - return declarations(); - } - else if (!global.params.ignoreUnsupportedPragmas) - { - error(pd.loc, "unrecognized `pragma(%s)`", pd.ident.toChars()); - return declarations(); - } - - if (!global.params.v.verbose) - return declarations(); - - /* Print unrecognized pragmas - */ - OutBuffer buf; - buf.writestring(pd.ident.toString()); - if (pd.args) - { - const errors_save = global.startGagging(); - for (size_t i = 0; i < pd.args.length; i++) - { - Expression e = (*pd.args)[i]; - sc = sc.startCTFE(); - e = e.expressionSemantic(sc); - e = resolveProperties(sc, e); - sc = sc.endCTFE(); - e = e.ctfeInterpret(); - if (i == 0) - buf.writestring(" ("); - else - buf.writeByte(','); - buf.writestring(e.toChars()); - } - if (pd.args.length) - buf.writeByte(')'); - global.endGagging(errors_save); - } - message("pragma %s", buf.peekChars()); - return declarations(); + import dmd.pragmasem : pragmaDeclSemantic; + pragmaDeclSemantic(pd, sc); } override void visit(StaticIfDeclaration sid) @@ -2314,143 +1965,7 @@ private extern(C++) final class DsymbolSemanticVisitor : Visitor override void visit(TemplateDeclaration tempdecl) { - static if (LOG) - { - printf("TemplateDeclaration.dsymbolSemantic(this = %p, id = '%s')\n", this, tempdecl.ident.toChars()); - printf("sc.stc = %llx\n", sc.stc); - printf("sc.module = %s\n", sc._module.toChars()); - } - if (tempdecl.semanticRun != PASS.initial) - return; // semantic() already run - - if (tempdecl._scope) - { - sc = tempdecl._scope; - tempdecl._scope = null; - } - if (!sc) - return; - - // Remember templates defined in module object that we need to know about - if (sc._module && sc._module.ident == Id.object) - { - if (tempdecl.ident == Id.RTInfo) - Type.rtinfo = tempdecl; - } - - /* Remember Scope for later instantiations, but make - * a copy since attributes can change. - */ - if (!tempdecl._scope) - { - tempdecl._scope = sc.copy(); - tempdecl._scope.setNoFree(); - } - - tempdecl.semanticRun = PASS.semantic; - - tempdecl.parent = sc.parent; - tempdecl.visibility = sc.visibility; - tempdecl.userAttribDecl = sc.userAttribDecl; - tempdecl.cppnamespace = sc.namespace; - tempdecl.isstatic = tempdecl.toParent().isModule() || (tempdecl._scope.stc & STC.static_); - tempdecl.deprecated_ = !!(sc.stc & STC.deprecated_); - - UserAttributeDeclaration.checkGNUABITag(tempdecl, sc.linkage); - - if (!tempdecl.isstatic) - { - if (auto ad = tempdecl.parent.pastMixin().isAggregateDeclaration()) - ad.makeNested(); - } - - // Set up scope for parameters - auto paramsym = new ScopeDsymbol(); - paramsym.parent = tempdecl.parent; - Scope* paramscope = sc.push(paramsym); - paramscope.stc = 0; - - if (global.params.ddoc.doOutput) - { - tempdecl.origParameters = new TemplateParameters(tempdecl.parameters.length); - for (size_t i = 0; i < tempdecl.parameters.length; i++) - { - TemplateParameter tp = (*tempdecl.parameters)[i]; - (*tempdecl.origParameters)[i] = tp.syntaxCopy(); - } - } - - for (size_t i = 0; i < tempdecl.parameters.length; i++) - { - TemplateParameter tp = (*tempdecl.parameters)[i]; - if (!tp.declareParameter(paramscope)) - { - error(tp.loc, "parameter `%s` multiply defined", tp.ident.toChars()); - tempdecl.errors = true; - } - if (!tp.tpsemantic(paramscope, tempdecl.parameters)) - { - tempdecl.errors = true; - } - if (i + 1 != tempdecl.parameters.length && tp.isTemplateTupleParameter()) - { - .error(tempdecl.loc, "%s `%s` template sequence parameter must be the last one", tempdecl.kind, tempdecl.toPrettyChars); - tempdecl.errors = true; - } - } - - /* Calculate TemplateParameter.dependent - */ - TemplateParameters tparams = TemplateParameters(1); - for (size_t i = 0; i < tempdecl.parameters.length; i++) - { - TemplateParameter tp = (*tempdecl.parameters)[i]; - tparams[0] = tp; - - for (size_t j = 0; j < tempdecl.parameters.length; j++) - { - // Skip cases like: X(T : T) - if (i == j) - continue; - - if (TemplateTypeParameter ttp = (*tempdecl.parameters)[j].isTemplateTypeParameter()) - { - if (reliesOnTident(ttp.specType, &tparams)) - tp.dependent = true; - } - else if (TemplateAliasParameter tap = (*tempdecl.parameters)[j].isTemplateAliasParameter()) - { - if (reliesOnTident(tap.specType, &tparams) || - reliesOnTident(isType(tap.specAlias), &tparams)) - { - tp.dependent = true; - } - } - } - } - - paramscope.pop(); - - // Compute again - tempdecl.onemember = null; - if (tempdecl.members) - { - Dsymbol s; - if (Dsymbol.oneMembers(tempdecl.members, s, tempdecl.ident) && s) - { - tempdecl.onemember = s; - s.parent = tempdecl; - } - } - - /* BUG: should check: - * 1. template functions must not introduce virtual functions, as they - * cannot be accomodated in the vtbl[] - * 2. templates cannot introduce non-static data members (i.e. fields) - * as they would change the instance size of the aggregate. - */ - - tempdecl.semanticRun = PASS.semanticdone; + templateDeclarationSemantic(sc, tempdecl); } override void visit(TemplateInstance ti) @@ -2569,1200 +2084,235 @@ private extern(C++) final class DsymbolSemanticVisitor : Visitor else if (ea) { Expression tme = isExpression(tmo); - if (!tme || !ea.equals(tme)) - goto Lcontinue; - } - else if (sa) - { - Dsymbol tmsa = isDsymbol(tmo); - if (sa != tmsa) - goto Lcontinue; - } - else - assert(0); - } - .error(tm.loc, "%s `%s` recursive mixin instantiation", tm.kind, tm.toPrettyChars); - return; - - Lcontinue: - continue; - } - - // Copy the syntax trees from the TemplateDeclaration - tm.members = Dsymbol.arraySyntaxCopy(tempdecl.members); - if (!tm.members) - return; - - tm.symtab = new DsymbolTable(); - - sc.getScopesym().importScope(tm, Visibility(Visibility.Kind.public_)); - - static if (LOG) - { - printf("\tcreate scope for template parameters '%s'\n", tm.toChars()); - } - Scope* scy = sc.push(tm); - scy.parent = tm; - - /* https://issues.dlang.org/show_bug.cgi?id=930 - * - * If the template that is to be mixed in is in the scope of a template - * instance, we have to also declare the type aliases in the new mixin scope. - */ - auto parentInstance = tempdecl.parent ? tempdecl.parent.isTemplateInstance() : null; - if (parentInstance) - parentInstance.declareParameters(scy); - - tm.argsym = new ScopeDsymbol(); - tm.argsym.parent = scy.parent; - Scope* argscope = scy.push(tm.argsym); - - uint errorsave = global.errors; - - // Declare each template parameter as an alias for the argument type - tm.declareParameters(argscope); - - // Add members to enclosing scope, as well as this scope - tm.members.foreachDsymbol(s => s.addMember(argscope, tm)); - - // Do semantic() analysis on template instance members - static if (LOG) - { - printf("\tdo semantic() on template instance members '%s'\n", tm.toChars()); - } - Scope* sc2 = argscope.push(tm); - //size_t deferred_dim = Module.deferred.length; - - __gshared int nest; - //printf("%d\n", nest); - if (++nest > global.recursionLimit) - { - global.gag = 0; // ensure error message gets printed - .error(tm.loc, "%s `%s` recursive expansion", tm.kind, tm.toPrettyChars); - fatal(); - } - - tm.members.foreachDsymbol( s => s.setScope(sc2) ); - - tm.members.foreachDsymbol( s => s.importAll(sc2) ); - - tm.members.foreachDsymbol( s => s.dsymbolSemantic(sc2) ); - - nest--; - - /* In DeclDefs scope, TemplateMixin does not have to handle deferred symbols. - * Because the members would already call Module.addDeferredSemantic() for themselves. - * See Struct, Class, Interface, and EnumDeclaration.dsymbolSemantic(). - */ - //if (!sc.func && Module.deferred.length > deferred_dim) {} - - AggregateDeclaration ad = tm.isMember(); - if (sc.func && !ad) - { - tm.semantic2(sc2); - tm.semantic3(sc2); - } - - // Give additional context info if error occurred during instantiation - if (global.errors != errorsave) - { - .error(tm.loc, "%s `%s` error instantiating", tm.kind, tm.toPrettyChars); - tm.errors = true; - } - - sc2.pop(); - argscope.pop(); - scy.pop(); - - static if (LOG) - { - printf("-TemplateMixin.dsymbolSemantic('%s', this=%p)\n", tm.toChars(), tm); - } - } - - override void visit(Nspace ns) - { - if (ns.semanticRun != PASS.initial) - return; - static if (LOG) - { - printf("+Nspace::semantic('%s')\n", ns.toChars()); - scope(exit) printf("-Nspace::semantic('%s')\n", ns.toChars()); - } - if (ns._scope) - { - sc = ns._scope; - ns._scope = null; - } - if (!sc) - return; - - bool repopulateMembers = false; - if (ns.identExp) - { - // resolve the namespace identifier - sc = sc.startCTFE(); - Expression resolved = ns.identExp.expressionSemantic(sc); - resolved = resolveProperties(sc, resolved); - sc = sc.endCTFE(); - resolved = resolved.ctfeInterpret(); - StringExp name = resolved.toStringExp(); - TupleExp tup = name ? null : resolved.isTupleExp(); - if (!tup && !name) - { - error(ns.loc, "expected string expression for namespace name, got `%s`", ns.identExp.toChars()); - return; - } - ns.identExp = resolved; // we don't need to keep the old AST around - if (name) - { - const(char)[] ident = name.toStringz(); - if (ident.length == 0 || !Identifier.isValidIdentifier(ident)) - { - error(ns.loc, "expected valid identifier for C++ namespace but got `%.*s`", cast(int)ident.length, ident.ptr); - return; - } - ns.ident = Identifier.idPool(ident); - } - else - { - // create namespace stack from the tuple - Nspace parentns = ns; - foreach (i, exp; *tup.exps) - { - name = exp.toStringExp(); - if (!name) - { - error(ns.loc, "expected string expression for namespace name, got `%s`", exp.toChars()); - return; - } - const(char)[] ident = name.toStringz(); - if (ident.length == 0 || !Identifier.isValidIdentifier(ident)) - { - error(ns.loc, "expected valid identifier for C++ namespace but got `%.*s`", cast(int)ident.length, ident.ptr); - return; - } - if (i == 0) - { - ns.ident = Identifier.idPool(ident); - } - else - { - // insert the new namespace - Nspace childns = new Nspace(ns.loc, Identifier.idPool(ident), null, parentns.members); - parentns.members = new Dsymbols; - parentns.members.push(childns); - parentns = childns; - repopulateMembers = true; - } - } - } - } - - ns.semanticRun = PASS.semantic; - ns.parent = sc.parent; - // Link does not matter here, if the UDA is present it will error - UserAttributeDeclaration.checkGNUABITag(ns, LINK.cpp); - - if (!ns.members) - { - ns.semanticRun = PASS.semanticdone; - return; - } - assert(sc); - sc = sc.push(ns); - sc.linkage = LINK.cpp; // note that namespaces imply C++ linkage - sc.parent = ns; - foreach (s; *ns.members) - { - if (repopulateMembers) - { - s.addMember(sc, sc.scopesym); - s.setScope(sc); - } - s.importAll(sc); - } - foreach (s; *ns.members) - { - static if (LOG) - { - printf("\tmember '%s', kind = '%s'\n", s.toChars(), s.kind()); - } - s.dsymbolSemantic(sc); - } - sc.pop(); - ns.semanticRun = PASS.semanticdone; - } - - void funcDeclarationSemantic(FuncDeclaration funcdecl) - { - version (none) - { - printf("FuncDeclaration::semantic(sc = %p, this = %p, '%s', linkage = %d)\n", sc, funcdecl, funcdecl.toPrettyChars(), sc.linkage); - if (funcdecl.isFuncLiteralDeclaration()) - printf("\tFuncLiteralDeclaration()\n"); - printf("sc.parent = %s, parent = %s\n", sc.parent.toChars(), funcdecl.parent ? funcdecl.parent.toChars() : ""); - printf("type: %p, %s\n", funcdecl.type, funcdecl.type.toChars()); - } - - if (funcdecl.semanticRun != PASS.initial && funcdecl.isFuncLiteralDeclaration()) - { - /* Member functions that have return types that are - * forward references can have semantic() run more than - * once on them. - * See test\interface2.d, test20 - */ - return; - } - - if (funcdecl.semanticRun >= PASS.semanticdone) - return; - assert(funcdecl.semanticRun <= PASS.semantic); - funcdecl.semanticRun = PASS.semantic; - - if (funcdecl._scope) - { - sc = funcdecl._scope; - funcdecl._scope = null; - } - - if (!sc || funcdecl.errors) - return; - - funcdecl.cppnamespace = sc.namespace; - funcdecl.parent = sc.parent; - Dsymbol parent = funcdecl.toParent(); - - funcdecl.foverrides.setDim(0); // reset in case semantic() is being retried for this function - - funcdecl.storage_class |= sc.stc & ~STC.ref_; - AggregateDeclaration ad = funcdecl.isThis(); - // Don't nest structs b/c of generated methods which should not access the outer scopes. - // https://issues.dlang.org/show_bug.cgi?id=16627 - if (ad && !funcdecl.isGenerated()) - { - funcdecl.storage_class |= ad.storage_class & (STC.TYPECTOR | STC.synchronized_); - ad.makeNested(); - } - if (sc.func) - funcdecl.storage_class |= sc.func.storage_class & STC.disable; - // Remove prefix storage classes silently. - if ((funcdecl.storage_class & STC.TYPECTOR) && !(ad || funcdecl.isNested())) - funcdecl.storage_class &= ~STC.TYPECTOR; - - //printf("function storage_class = x%llx, sc.stc = x%llx, %x\n", storage_class, sc.stc, Declaration.isFinal()); - - if (sc.flags & SCOPE.compile) - funcdecl.skipCodegen = true; - - funcdecl._linkage = sc.linkage; - if (sc.flags & SCOPE.Cfile && funcdecl.isFuncLiteralDeclaration()) - funcdecl._linkage = LINK.d; // so they are uniquely mangled - - if (auto fld = funcdecl.isFuncLiteralDeclaration()) - { - if (fld.treq) - { - Type treq = fld.treq; - assert(treq.nextOf().ty == Tfunction); - if (treq.ty == Tdelegate) - fld.tok = TOK.delegate_; - else if (treq.isPtrToFunction()) - fld.tok = TOK.function_; - else - assert(0); - funcdecl._linkage = treq.nextOf().toTypeFunction().linkage; - } - } - - // evaluate pragma(inline) - if (auto pragmadecl = sc.inlining) - funcdecl.inlining = evalPragmaInline(pragmadecl.loc, sc, pragmadecl.args); - - funcdecl.visibility = sc.visibility; - funcdecl.userAttribDecl = sc.userAttribDecl; - UserAttributeDeclaration.checkGNUABITag(funcdecl, funcdecl._linkage); - checkMustUseReserved(funcdecl); - - if (!funcdecl.originalType) - funcdecl.originalType = funcdecl.type.syntaxCopy(); - - static TypeFunction getFunctionType(FuncDeclaration fd) - { - if (auto tf = fd.type.isTypeFunction()) - return tf; - - if (!fd.type.isTypeError()) - { - .error(fd.loc, "%s `%s` `%s` must be a function instead of `%s`", fd.kind, fd.toPrettyChars, fd.toChars(), fd.type.toChars()); - fd.type = Type.terror; - } - fd.errors = true; - return null; - } - - if (sc.flags & SCOPE.Cfile) - { - /* C11 allows a function to be declared with a typedef, D does not. - */ - if (auto ti = funcdecl.type.isTypeIdentifier()) - { - auto tj = ti.typeSemantic(funcdecl.loc, sc); - if (auto tjf = tj.isTypeFunction()) - { - /* Copy the type instead of just pointing to it, - * as we don't merge function types - */ - auto tjf2 = new TypeFunction(tjf.parameterList, tjf.next, tjf.linkage); - funcdecl.type = tjf2; - funcdecl.originalType = tjf2; - } - } - } - - if (!getFunctionType(funcdecl)) - return; - - if (!funcdecl.type.deco) - { - sc = sc.push(); - sc.stc |= funcdecl.storage_class & (STC.disable | STC.deprecated_); // forward to function type - - TypeFunction tf = funcdecl.type.toTypeFunction(); - if (sc.func) - { - /* If the nesting parent is pure without inference, - * then this function defaults to pure too. - * - * auto foo() pure { - * auto bar() {} // become a weak purity function - * class C { // nested class - * auto baz() {} // become a weak purity function - * } - * - * static auto boo() {} // typed as impure - * // Even though, boo cannot call any impure functions. - * // See also Expression::checkPurity(). - * } - */ - if (tf.purity == PURE.impure && (funcdecl.isNested() || funcdecl.isThis())) - { - FuncDeclaration fd = null; - for (Dsymbol p = funcdecl.toParent2(); p; p = p.toParent2()) - { - if (AggregateDeclaration adx = p.isAggregateDeclaration()) - { - if (adx.isNested()) - continue; - break; - } - if ((fd = p.isFuncDeclaration()) !is null) - break; - } - - /* If the parent's purity is inferred, then this function's purity needs - * to be inferred first. - */ - if (fd && fd.isPureBypassingInference() >= PURE.weak && !funcdecl.isInstantiated()) - { - tf.purity = PURE.fwdref; // default to pure - } - } - } - - if (tf.isref) - sc.stc |= STC.ref_; - if (tf.isScopeQual) - sc.stc |= STC.scope_; - if (tf.isnothrow) - sc.stc |= STC.nothrow_; - if (tf.isnogc) - sc.stc |= STC.nogc; - if (tf.isproperty) - sc.stc |= STC.property; - if (tf.purity == PURE.fwdref) - sc.stc |= STC.pure_; - - if (tf.trust != TRUST.default_) - { - sc.stc &= ~STC.safeGroup; - if (tf.trust == TRUST.safe) - sc.stc |= STC.safe; - else if (tf.trust == TRUST.system) - sc.stc |= STC.system; - else if (tf.trust == TRUST.trusted) - sc.stc |= STC.trusted; - } - - if (funcdecl.isCtorDeclaration()) - { - tf.isctor = true; - Type tret = ad.handleType(); - assert(tret); - tret = tret.addStorageClass(funcdecl.storage_class | sc.stc); - tret = tret.addMod(funcdecl.type.mod); - tf.next = tret; - if (ad.isStructDeclaration()) - sc.stc |= STC.ref_; - } - - // 'return' on a non-static class member function implies 'scope' as well - if (ad && ad.isClassDeclaration() && (tf.isreturn || sc.stc & STC.return_) && !(sc.stc & STC.static_)) - sc.stc |= STC.scope_; - - // If 'this' has no pointers, remove 'scope' as it has no meaning - // Note: this is already covered by semantic of `VarDeclaration` and `TypeFunction`, - // but existing code relies on `hasPointers()` being called here to resolve forward references: - // https://github.com/dlang/dmd/pull/14232#issuecomment-1162906573 - if (sc.stc & STC.scope_ && ad && ad.isStructDeclaration() && !ad.type.hasPointers()) - { - sc.stc &= ~STC.scope_; - tf.isScopeQual = false; - if (tf.isreturnscope) - { - sc.stc &= ~(STC.return_ | STC.returnScope); - tf.isreturn = false; - tf.isreturnscope = false; - } - } - - sc.linkage = funcdecl._linkage; - - if (!tf.isNaked() && !(funcdecl.isThis() || funcdecl.isNested())) - { - import core.bitop : popcnt; - auto mods = MODtoChars(tf.mod); - .error(funcdecl.loc, "%s `%s` without `this` cannot be `%s`", funcdecl.kind, funcdecl.toPrettyChars, mods); - if (tf.next && tf.next.ty != Tvoid && popcnt(tf.mod) == 1) - .errorSupplemental(funcdecl.loc, - "did you mean to use `%s(%s)` as the return type?", mods, tf.next.toChars()); - - tf.mod = 0; // remove qualifiers - } - - /* Apply const, immutable, wild and shared storage class - * to the function type. Do this before type semantic. - */ - auto stc = funcdecl.storage_class; - if (funcdecl.type.isImmutable()) - stc |= STC.immutable_; - if (funcdecl.type.isConst()) - stc |= STC.const_; - if (funcdecl.type.isShared() || funcdecl.storage_class & STC.synchronized_) - stc |= STC.shared_; - if (funcdecl.type.isWild()) - stc |= STC.wild; - funcdecl.type = funcdecl.type.addSTC(stc); - - funcdecl.type = funcdecl.type.typeSemantic(funcdecl.loc, sc); - sc = sc.pop(); - } - - auto f = getFunctionType(funcdecl); - if (!f) - return; // funcdecl's type is not a function - - { - // Merge back function attributes into 'originalType'. - // It's used for mangling, ddoc, and json output. - TypeFunction tfo = funcdecl.originalType.toTypeFunction(); - tfo.mod = f.mod; - tfo.isScopeQual = f.isScopeQual; - tfo.isreturninferred = f.isreturninferred; - tfo.isscopeinferred = f.isscopeinferred; - tfo.isref = f.isref; - tfo.isnothrow = f.isnothrow; - tfo.isnogc = f.isnogc; - tfo.isproperty = f.isproperty; - tfo.purity = f.purity; - tfo.trust = f.trust; - - funcdecl.storage_class &= ~(STC.TYPECTOR | STC.FUNCATTR); - } - - // check pragma(crt_constructor) signature - if (funcdecl.isCrtCtor || funcdecl.isCrtDtor) - { - const idStr = funcdecl.isCrtCtor ? "crt_constructor" : "crt_destructor"; - if (f.nextOf().ty != Tvoid) - .error(funcdecl.loc, "%s `%s` must return `void` for `pragma(%s)`", funcdecl.kind, funcdecl.toPrettyChars, idStr.ptr); - if (funcdecl._linkage != LINK.c && f.parameterList.length != 0) - .error(funcdecl.loc, "%s `%s` must be `extern(C)` for `pragma(%s)` when taking parameters", funcdecl.kind, funcdecl.toPrettyChars, idStr.ptr); - if (funcdecl.isThis()) - .error(funcdecl.loc, "%s `%s` cannot be a non-static member function for `pragma(%s)`", funcdecl.kind, funcdecl.toPrettyChars, idStr.ptr); - } - - if (funcdecl.overnext && funcdecl.isCsymbol()) - { - /* C does not allow function overloading, but it does allow - * redeclarations of the same function. If .overnext points - * to a redeclaration, ok. Error if it is an overload. - */ - auto fnext = funcdecl.overnext.isFuncDeclaration(); - funcDeclarationSemantic(fnext); - auto fn = fnext.type.isTypeFunction(); - if (!fn || !cFuncEquivalence(f, fn)) - { - .error(funcdecl.loc, "%s `%s` redeclaration with different type", funcdecl.kind, funcdecl.toPrettyChars); - //printf("t1: %s\n", f.toChars()); - //printf("t2: %s\n", fn.toChars()); - } - funcdecl.overnext = null; // don't overload the redeclarations - } - - if ((funcdecl.storage_class & STC.auto_) && !f.isref && !funcdecl.inferRetType) - .error(funcdecl.loc, "%s `%s` storage class `auto` has no effect if return type is not inferred", funcdecl.kind, funcdecl.toPrettyChars); - - if (f.isreturn && !funcdecl.needThis() && !funcdecl.isNested()) - { - /* Non-static nested functions have a hidden 'this' pointer to which - * the 'return' applies - */ - if (sc.scopesym && sc.scopesym.isAggregateDeclaration()) - .error(funcdecl.loc, "%s `%s` `static` member has no `this` to which `return` can apply", funcdecl.kind, funcdecl.toPrettyChars); - else - error(funcdecl.loc, "top-level function `%s` has no `this` to which `return` can apply", funcdecl.toChars()); - } - - if (funcdecl.isAbstract() && !funcdecl.isVirtual()) - { - const(char)* sfunc; - if (funcdecl.isStatic()) - sfunc = "static"; - else if (funcdecl.visibility.kind == Visibility.Kind.private_ || funcdecl.visibility.kind == Visibility.Kind.package_) - sfunc = visibilityToChars(funcdecl.visibility.kind); - else - sfunc = "final"; - .error(funcdecl.loc, "%s `%s` `%s` functions cannot be `abstract`", funcdecl.kind, funcdecl.toPrettyChars, sfunc); - } - - if (funcdecl.isOverride() && !funcdecl.isVirtual() && !funcdecl.isFuncLiteralDeclaration()) - { - Visibility.Kind kind = funcdecl.visible().kind; - if ((kind == Visibility.Kind.private_ || kind == Visibility.Kind.package_) && funcdecl.isMember()) - .error(funcdecl.loc, "%s `%s` `%s` method is not virtual and cannot override", funcdecl.kind, funcdecl.toPrettyChars, visibilityToChars(kind)); - else - .error(funcdecl.loc, "%s `%s` cannot override a non-virtual function", funcdecl.kind, funcdecl.toPrettyChars); - } - - if (funcdecl.isAbstract() && funcdecl.isFinalFunc()) - .error(funcdecl.loc, "%s `%s` cannot be both `final` and `abstract`", funcdecl.kind, funcdecl.toPrettyChars); - - if (funcdecl.printf || funcdecl.scanf) - { - checkPrintfScanfSignature(funcdecl, f, sc); - } - - if (auto id = parent.isInterfaceDeclaration()) - { - funcdecl.storage_class |= STC.abstract_; - if (funcdecl.isCtorDeclaration() || funcdecl.isPostBlitDeclaration() || funcdecl.isDtorDeclaration() || funcdecl.isInvariantDeclaration() || funcdecl.isNewDeclaration() || funcdecl.isDelete()) - .error(funcdecl.loc, "%s `%s` constructors, destructors, postblits, invariants, new and delete functions are not allowed in interface `%s`", funcdecl.kind, funcdecl.toPrettyChars, id.toChars()); - if (funcdecl.fbody && funcdecl.isVirtual()) - .error(funcdecl.loc, "%s `%s` function body only allowed in `final` functions in interface `%s`", funcdecl.kind, funcdecl.toPrettyChars, id.toChars()); - } - - if (UnionDeclaration ud = parent.isUnionDeclaration()) - { - if (funcdecl.isPostBlitDeclaration() || funcdecl.isDtorDeclaration() || funcdecl.isInvariantDeclaration()) - .error(funcdecl.loc, "%s `%s` destructors, postblits and invariants are not allowed in union `%s`", funcdecl.kind, funcdecl.toPrettyChars, ud.toChars()); - } - - if (StructDeclaration sd = parent.isStructDeclaration()) - { - if (funcdecl.isCtorDeclaration()) - { - goto Ldone; - } - } - - if (ClassDeclaration cd = parent.isClassDeclaration()) - { - parent = cd = objc.getParent(funcdecl, cd); - - if (funcdecl.isCtorDeclaration()) - { - goto Ldone; - } - - if (funcdecl.storage_class & STC.abstract_) - cd.isabstract = ThreeState.yes; - - // if static function, do not put in vtbl[] - if (!funcdecl.isVirtual()) - { - //printf("\tnot virtual\n"); - goto Ldone; - } - // Suppress further errors if the return type is an error - if (funcdecl.type.nextOf() == Type.terror) - goto Ldone; - - bool may_override = false; - for (size_t i = 0; i < cd.baseclasses.length; i++) - { - BaseClass* b = (*cd.baseclasses)[i]; - ClassDeclaration cbd = b.type.toBasetype().isClassHandle(); - if (!cbd) - continue; - for (size_t j = 0; j < cbd.vtbl.length; j++) - { - FuncDeclaration f2 = cbd.vtbl[j].isFuncDeclaration(); - if (!f2 || f2.ident != funcdecl.ident) - continue; - if (cbd.parent && cbd.parent.isTemplateInstance()) - { - if (!functionSemantic(f2)) - goto Ldone; - } - may_override = true; - } - } - if (may_override && funcdecl.type.nextOf() is null) - { - /* If same name function exists in base class but 'this' is auto return, - * cannot find index of base class's vtbl[] to override. - */ - .error(funcdecl.loc, "%s `%s` return type inference is not supported if may override base class function", funcdecl.kind, funcdecl.toPrettyChars); - } - - /* Find index of existing function in base class's vtbl[] to override - * (the index will be the same as in cd's current vtbl[]) - */ - int vi = cd.baseClass ? funcdecl.findVtblIndex(&cd.baseClass.vtbl, cast(int)cd.baseClass.vtbl.length) : -1; - - bool doesoverride = false; - switch (vi) - { - case -1: - Lintro: - /* Didn't find one, so - * This is an 'introducing' function which gets a new - * slot in the vtbl[]. - */ - - // Verify this doesn't override previous final function - if (cd.baseClass) - { - Dsymbol s = cd.baseClass.search(funcdecl.loc, funcdecl.ident); - if (s) - { - if (auto f2 = s.isFuncDeclaration()) - { - f2 = f2.overloadExactMatch(funcdecl.type); - if (f2 && f2.isFinalFunc() && f2.visible().kind != Visibility.Kind.private_) - .error(funcdecl.loc, "%s `%s` cannot override `final` function `%s`", funcdecl.kind, funcdecl.toPrettyChars, f2.toPrettyChars()); - } - } - } - - /* These quirky conditions mimic what happens when virtual - inheritance is implemented by producing a virtual base table - with offsets to each of the virtual bases. - */ - if (target.cpp.splitVBasetable && cd.classKind == ClassKind.cpp && - cd.baseClass && cd.baseClass.vtbl.length) - { - /* if overriding an interface function, then this is not - * introducing and don't put it in the class vtbl[] - */ - funcdecl.interfaceVirtual = funcdecl.overrideInterface(); - if (funcdecl.interfaceVirtual) - { - //printf("\tinterface function %s\n", toChars()); - cd.vtblFinal.push(funcdecl); - goto Linterfaces; - } - } - - if (funcdecl.isFinalFunc()) - { - // Don't check here, as it may override an interface function - //if (isOverride()) - // error("is marked as override, but does not override any function"); - cd.vtblFinal.push(funcdecl); - } - else - { - //printf("\tintroducing function %s\n", funcdecl.toChars()); - funcdecl.isIntroducing = true; - if (cd.classKind == ClassKind.cpp && target.cpp.reverseOverloads) - { - /* Overloaded functions with same name are grouped and in reverse order. - * Search for first function of overload group, and insert - * funcdecl into vtbl[] immediately before it. - */ - funcdecl.vtblIndex = cast(int)cd.vtbl.length; - bool found; - foreach (const i, s; cd.vtbl) - { - if (found) - // the rest get shifted forward - ++s.isFuncDeclaration().vtblIndex; - else if (s.ident == funcdecl.ident && s.parent == parent) - { - // found first function of overload group - funcdecl.vtblIndex = cast(int)i; - found = true; - ++s.isFuncDeclaration().vtblIndex; - } - } - cd.vtbl.insert(funcdecl.vtblIndex, funcdecl); - - debug foreach (const i, s; cd.vtbl) - { - // a C++ dtor gets its vtblIndex later (and might even be added twice to the vtbl), - // e.g. when compiling druntime with a debug compiler, namely with core.stdcpp.exception. - if (auto fd = s.isFuncDeclaration()) - assert(fd.vtblIndex == i || - (cd.classKind == ClassKind.cpp && fd.isDtorDeclaration) || - funcdecl.parent.isInterfaceDeclaration); // interface functions can be in multiple vtbls - } - } - else - { - // Append to end of vtbl[] - vi = cast(int)cd.vtbl.length; - cd.vtbl.push(funcdecl); - funcdecl.vtblIndex = vi; - } - } - break; - - case -2: - // can't determine because of forward references - funcdecl.errors = true; - return; - - default: - { - if (vi >= cd.vtbl.length) - { - /* the derived class cd doesn't have its vtbl[] allocated yet. - * https://issues.dlang.org/show_bug.cgi?id=21008 - */ - .error(funcdecl.loc, "%s `%s` circular reference to class `%s`", funcdecl.kind, funcdecl.toPrettyChars, cd.toChars()); - funcdecl.errors = true; - return; - } - FuncDeclaration fdv = cd.baseClass.vtbl[vi].isFuncDeclaration(); - FuncDeclaration fdc = cd.vtbl[vi].isFuncDeclaration(); - // This function is covariant with fdv - - if (fdc == funcdecl) - { - doesoverride = true; - break; - } - - auto vtf = getFunctionType(fdv); - if (vtf.trust > TRUST.system && f.trust == TRUST.system) - .error(funcdecl.loc, "%s `%s` cannot override `@safe` method `%s` with a `@system` attribute", funcdecl.kind, funcdecl.toPrettyChars, - fdv.toPrettyChars); - - if (fdc.toParent() == parent) - { - //printf("vi = %d,\tthis = %p %s %s @ [%s]\n\tfdc = %p %s %s @ [%s]\n\tfdv = %p %s %s @ [%s]\n", - // vi, this, this.toChars(), this.type.toChars(), this.loc.toChars(), - // fdc, fdc .toChars(), fdc .type.toChars(), fdc .loc.toChars(), - // fdv, fdv .toChars(), fdv .type.toChars(), fdv .loc.toChars()); - - // fdc overrides fdv exactly, then this introduces new function. - if (fdc.type.mod == fdv.type.mod && funcdecl.type.mod != fdv.type.mod) - goto Lintro; - } - - if (fdv.isDeprecated && !funcdecl.isDeprecated) - deprecation(funcdecl.loc, "`%s` is overriding the deprecated method `%s`", - funcdecl.toPrettyChars, fdv.toPrettyChars); - - // This function overrides fdv - if (fdv.isFinalFunc()) - .error(funcdecl.loc, "%s `%s` cannot override `final` function `%s`", funcdecl.kind, funcdecl.toPrettyChars, fdv.toPrettyChars()); - - if (!funcdecl.isOverride()) - { - if (fdv.isFuture()) - { - deprecation(funcdecl.loc, "`@__future` base class method `%s` is being overridden by `%s`; rename the latter", fdv.toPrettyChars(), funcdecl.toPrettyChars()); - // Treat 'this' as an introducing function, giving it a separate hierarchy in the vtbl[] - goto Lintro; - } - else - { - // https://issues.dlang.org/show_bug.cgi?id=17349 - error(funcdecl.loc, "cannot implicitly override base class method `%s` with `%s`; add `override` attribute", - fdv.toPrettyChars(), funcdecl.toPrettyChars()); - } - } - doesoverride = true; - if (fdc.toParent() == parent) - { - // If both are mixins, or both are not, then error. - // If either is not, the one that is not overrides the other. - bool thismixin = funcdecl.parent.isClassDeclaration() !is null; - bool fdcmixin = fdc.parent.isClassDeclaration() !is null; - if (thismixin == fdcmixin) - { - .error(funcdecl.loc, "%s `%s` multiple overrides of same function", funcdecl.kind, funcdecl.toPrettyChars); - } - /* - * https://issues.dlang.org/show_bug.cgi?id=711 - * - * If an overriding method is introduced through a mixin, - * we need to update the vtbl so that both methods are - * present. - */ - else if (thismixin) - { - /* if the mixin introduced the overriding method, then reintroduce it - * in the vtbl. The initial entry for the mixined method - * will be updated at the end of the enclosing `if` block - * to point to the current (non-mixined) function. - */ - auto vitmp = cast(int)cd.vtbl.length; - cd.vtbl.push(fdc); - fdc.vtblIndex = vitmp; - } - else if (fdcmixin) - { - /* if the current overriding function is coming from a - * mixined block, then push the current function in the - * vtbl, but keep the previous (non-mixined) function as - * the overriding one. - */ - auto vitmp = cast(int)cd.vtbl.length; - cd.vtbl.push(funcdecl); - funcdecl.vtblIndex = vitmp; - break; - } - else // fdc overrides fdv - { - // this doesn't override any function - break; - } - } - cd.vtbl[vi] = funcdecl; - funcdecl.vtblIndex = vi; - - /* Remember which functions this overrides - */ - funcdecl.foverrides.push(fdv); - - /* This works by whenever this function is called, - * it actually returns tintro, which gets dynamically - * cast to type. But we know that tintro is a base - * of type, so we could optimize it by not doing a - * dynamic cast, but just subtracting the isBaseOf() - * offset if the value is != null. - */ - - if (fdv.tintro) - funcdecl.tintro = fdv.tintro; - else if (!funcdecl.type.equals(fdv.type)) - { - auto tnext = funcdecl.type.nextOf(); - if (auto handle = tnext.isClassHandle()) - { - if (handle.semanticRun < PASS.semanticdone && !handle.isBaseInfoComplete()) - handle.dsymbolSemantic(null); - } - /* Only need to have a tintro if the vptr - * offsets differ - */ - int offset; - if (fdv.type.nextOf().isBaseOf(tnext, &offset)) - { - funcdecl.tintro = fdv.type; - } - } - break; - } - } - - /* Go through all the interface bases. - * If this function is covariant with any members of those interface - * functions, set the tintro. - */ - Linterfaces: - bool foundVtblMatch = false; - - for (ClassDeclaration bcd = cd; !foundVtblMatch && bcd; bcd = bcd.baseClass) - { - foreach (b; bcd.interfaces) - { - vi = funcdecl.findVtblIndex(&b.sym.vtbl, cast(int)b.sym.vtbl.length); - switch (vi) - { - case -1: - break; - - case -2: - // can't determine because of forward references - funcdecl.errors = true; - return; - - default: - { - auto fdv = cast(FuncDeclaration)b.sym.vtbl[vi]; - Type ti = null; - - foundVtblMatch = true; - - /* Remember which functions this overrides - */ - funcdecl.foverrides.push(fdv); - - if (fdv.tintro) - ti = fdv.tintro; - else if (!funcdecl.type.equals(fdv.type)) - { - /* Only need to have a tintro if the vptr - * offsets differ - */ - int offset; - if (fdv.type.nextOf().isBaseOf(funcdecl.type.nextOf(), &offset)) - { - ti = fdv.type; - } - } - if (ti) - { - if (funcdecl.tintro) - { - if (!funcdecl.tintro.nextOf().equals(ti.nextOf()) && !funcdecl.tintro.nextOf().isBaseOf(ti.nextOf(), null) && !ti.nextOf().isBaseOf(funcdecl.tintro.nextOf(), null)) - { - .error(funcdecl.loc, "%s `%s` incompatible covariant types `%s` and `%s`", funcdecl.kind, funcdecl.toPrettyChars, funcdecl.tintro.toChars(), ti.toChars()); - } - } - else - { - funcdecl.tintro = ti; - } - } - } - } + if (!tme || !ea.equals(tme)) + goto Lcontinue; } - } - if (foundVtblMatch) - { - goto L2; - } - - if (!doesoverride && funcdecl.isOverride() && (funcdecl.type.nextOf() || !may_override)) - { - BaseClass* bc = null; - Dsymbol s = null; - for (size_t i = 0; i < cd.baseclasses.length; i++) + else if (sa) { - bc = (*cd.baseclasses)[i]; - s = bc.sym.search_correct(funcdecl.ident); - if (s) - break; + Dsymbol tmsa = isDsymbol(tmo); + if (sa != tmsa) + goto Lcontinue; } + else + assert(0); + } + .error(tm.loc, "%s `%s` recursive mixin instantiation", tm.kind, tm.toPrettyChars); + return; - if (s) - { - HdrGenState hgs; - OutBuffer buf; + Lcontinue: + continue; + } - auto fd = s.isFuncDeclaration(); - functionToBufferFull(cast(TypeFunction)(funcdecl.type), buf, - new Identifier(funcdecl.toPrettyChars()), hgs, null); - const(char)* funcdeclToChars = buf.peekChars(); + // Copy the syntax trees from the TemplateDeclaration + tm.members = Dsymbol.arraySyntaxCopy(tempdecl.members); + if (!tm.members) + return; - if (fd) - { - OutBuffer buf1; + tm.symtab = new DsymbolTable(); - if (fd.ident == funcdecl.ident) - hgs.fullQual = true; + sc.getScopesym().importScope(tm, Visibility(Visibility.Kind.public_)); - // https://issues.dlang.org/show_bug.cgi?id=23745 - // If the potentially overridden function contains errors, - // inform the user to fix that one first - if (fd.errors) - { - error(funcdecl.loc, "function `%s` does not override any function, did you mean to override `%s`?", - funcdecl.toChars(), fd.toPrettyChars()); - errorSupplemental(fd.loc, "Function `%s` contains errors in its declaration, therefore it cannot be correctly overridden", - fd.toPrettyChars()); - } - else - { - functionToBufferFull(cast(TypeFunction)(fd.type), buf1, - new Identifier(fd.toPrettyChars()), hgs, null); + static if (LOG) + { + printf("\tcreate scope for template parameters '%s'\n", tm.toChars()); + } + Scope* scy = sc.push(tm); + scy.parent = tm; - error(funcdecl.loc, "function `%s` does not override any function, did you mean to override `%s`?", - funcdeclToChars, buf1.peekChars()); - } - } - else - { - error(funcdecl.loc, "function `%s` does not override any function, did you mean to override %s `%s`?", - funcdeclToChars, s.kind, s.toPrettyChars()); - errorSupplemental(funcdecl.loc, "Functions are the only declarations that may be overridden"); - } - } - else - .error(funcdecl.loc, "%s `%s` does not override any function", funcdecl.kind, funcdecl.toPrettyChars); - } + /* https://issues.dlang.org/show_bug.cgi?id=930 + * + * If the template that is to be mixed in is in the scope of a template + * instance, we have to also declare the type aliases in the new mixin scope. + */ + auto parentInstance = tempdecl.parent ? tempdecl.parent.isTemplateInstance() : null; + if (parentInstance) + parentInstance.declareParameters(scy); - L2: - objc.setSelector(funcdecl, sc); - objc.checkLinkage(funcdecl); - objc.addToClassMethodList(funcdecl, cd); - objc.setAsOptional(funcdecl, sc); + tm.argsym = new ScopeDsymbol(); + tm.argsym.parent = scy.parent; + Scope* argscope = scy.push(tm.argsym); - /* Go through all the interface bases. - * Disallow overriding any final functions in the interface(s). - */ - foreach (b; cd.interfaces) - { - if (b.sym) - { - if (auto s = search_function(b.sym, funcdecl.ident)) - { - if (auto f2 = s.isFuncDeclaration()) - { - f2 = f2.overloadExactMatch(funcdecl.type); - if (f2 && f2.isFinalFunc() && f2.visible().kind != Visibility.Kind.private_) - .error(funcdecl.loc, "%s `%s` cannot override `final` function `%s.%s`", funcdecl.kind, funcdecl.toPrettyChars, b.sym.toChars(), f2.toPrettyChars()); - } - } - } - } + uint errorsave = global.errors; - if (funcdecl.isOverride) - { - if (funcdecl.storage_class & STC.disable) - deprecation(funcdecl.loc, - "`%s` cannot be annotated with `@disable` because it is overriding a function in the base class", - funcdecl.toPrettyChars); + // Declare each template parameter as an alias for the argument type + tm.declareParameters(argscope); - if (funcdecl.isDeprecated && !(funcdecl.foverrides.length && funcdecl.foverrides[0].isDeprecated)) - deprecation(funcdecl.loc, - "`%s` cannot be marked as `deprecated` because it is overriding a function in the base class", - funcdecl.toPrettyChars); - } + // Add members to enclosing scope, as well as this scope + tm.members.foreachDsymbol(s => s.addMember(argscope, tm)); + // Do semantic() analysis on template instance members + static if (LOG) + { + printf("\tdo semantic() on template instance members '%s'\n", tm.toChars()); } - else if (funcdecl.isOverride() && !parent.isTemplateInstance()) - .error(funcdecl.loc, "%s `%s` `override` only applies to class member functions", funcdecl.kind, funcdecl.toPrettyChars); + Scope* sc2 = argscope.push(tm); + //size_t deferred_dim = Module.deferred.length; - if (auto ti = parent.isTemplateInstance) + __gshared int nest; + //printf("%d\n", nest); + if (++nest > global.recursionLimit) { - objc.setSelector(funcdecl, sc); - objc.setAsOptional(funcdecl, sc); + global.gag = 0; // ensure error message gets printed + .error(tm.loc, "%s `%s` recursive expansion", tm.kind, tm.toPrettyChars); + fatal(); } - objc.validateSelector(funcdecl); - objc.validateOptional(funcdecl); - // Reflect this.type to f because it could be changed by findVtblIndex - f = funcdecl.type.toTypeFunction(); - - Ldone: - if (!funcdecl.fbody && !funcdecl.allowsContractWithoutBody()) - .error(funcdecl.loc, "%s `%s` `in` and `out` contracts can only appear without a body when they are virtual interface functions or abstract", funcdecl.kind, funcdecl.toPrettyChars); + tm.members.foreachDsymbol( s => s.setScope(sc2) ); - /* Do not allow template instances to add virtual functions - * to a class. - */ - if (funcdecl.isVirtual()) - { - if (auto ti = parent.isTemplateInstance()) - { - // Take care of nested templates - while (1) - { - TemplateInstance ti2 = ti.tempdecl.parent.isTemplateInstance(); - if (!ti2) - break; - ti = ti2; - } + tm.members.foreachDsymbol( s => s.importAll(sc2) ); - // If it's a member template - ClassDeclaration cd = ti.tempdecl.isClassMember(); - if (cd) - { - .error(funcdecl.loc, "%s `%s` cannot use template to add virtual function to class `%s`", funcdecl.kind, funcdecl.toPrettyChars, cd.toChars()); - } - } - } + tm.members.foreachDsymbol( s => s.dsymbolSemantic(sc2) ); - funcdecl.checkMain(); // Check main() parameters and return type + nest--; - /* Purity and safety can be inferred for some functions by examining - * the function body. + /* In DeclDefs scope, TemplateMixin does not have to handle deferred symbols. + * Because the members would already call Module.addDeferredSemantic() for themselves. + * See Struct, Class, Interface, and EnumDeclaration.dsymbolSemantic(). */ - if (funcdecl.canInferAttributes(sc)) - funcdecl.initInferAttributes(); - - funcdecl.semanticRun = PASS.semanticdone; + //if (!sc.func && Module.deferred.length > deferred_dim) {} - /* Save scope for possible later use (if we need the - * function internals) - */ - funcdecl._scope = sc.copy(); - funcdecl._scope.setNoFree(); + AggregateDeclaration ad = tm.isMember(); + if (sc.func && !ad) + { + tm.semantic2(sc2); + tm.semantic3(sc2); + } - __gshared bool printedMain = false; // semantic might run more than once - if (global.params.v.verbose && !printedMain) + // Give additional context info if error occurred during instantiation + if (global.errors != errorsave) { - const(char)* type = funcdecl.isMain() ? "main" : funcdecl.isWinMain() ? "winmain" : funcdecl.isDllMain() ? "dllmain" : cast(const(char)*)null; - Module mod = sc._module; + .error(tm.loc, "%s `%s` error instantiating", tm.kind, tm.toPrettyChars); + tm.errors = true; + } - if (type && mod) - { - printedMain = true; - auto name = mod.srcfile.toChars(); - auto path = FileName.searchPath(global.path, name, true); - message("entry %-10s\t%s", type, path ? path : name); - } + sc2.pop(); + argscope.pop(); + scy.pop(); + + static if (LOG) + { + printf("-TemplateMixin.dsymbolSemantic('%s', this=%p)\n", tm.toChars(), tm); } + } - if (funcdecl.fbody && sc._module.isRoot() && - (funcdecl.isMain() || funcdecl.isWinMain() || funcdecl.isDllMain() || funcdecl.isCMain())) - global.hasMainFunction = true; + override void visit(Nspace ns) + { + if (ns.semanticRun != PASS.initial) + return; + static if (LOG) + { + printf("+Nspace::semantic('%s')\n", ns.toChars()); + scope(exit) printf("-Nspace::semantic('%s')\n", ns.toChars()); + } + if (ns._scope) + { + sc = ns._scope; + ns._scope = null; + } + if (!sc) + return; - if (funcdecl.fbody && funcdecl.isMain() && sc._module.isRoot()) + bool repopulateMembers = false; + if (ns.identExp) { - // check if `_d_cmain` is defined - bool cmainTemplateExists() + // resolve the namespace identifier + sc = sc.startCTFE(); + Expression resolved = ns.identExp.expressionSemantic(sc); + resolved = resolveProperties(sc, resolved); + sc = sc.endCTFE(); + resolved = resolved.ctfeInterpret(); + StringExp name = resolved.toStringExp(); + TupleExp tup = name ? null : resolved.isTupleExp(); + if (!tup && !name) { - Dsymbol pscopesym; - auto rootSymbol = sc.search(funcdecl.loc, Id.empty, pscopesym); - if (auto moduleSymbol = rootSymbol.search(funcdecl.loc, Id.object)) - if (moduleSymbol.search(funcdecl.loc, Id.CMain)) - return true; - - return false; + error(ns.loc, "expected string expression for namespace name, got `%s`", ns.identExp.toChars()); + return; } - - // Only mixin `_d_cmain` if it is defined - if (cmainTemplateExists()) + ns.identExp = resolved; // we don't need to keep the old AST around + if (name) + { + const(char)[] ident = name.toStringz(); + if (ident.length == 0 || !Identifier.isValidIdentifier(ident)) + { + error(ns.loc, "expected valid identifier for C++ namespace but got `%.*s`", cast(int)ident.length, ident.ptr); + return; + } + ns.ident = Identifier.idPool(ident); + } + else { - // add `mixin _d_cmain!();` to the declaring module - auto tqual = new TypeIdentifier(funcdecl.loc, Id.CMain); - auto tm = new TemplateMixin(funcdecl.loc, null, tqual, null); - sc._module.members.push(tm); + // create namespace stack from the tuple + Nspace parentns = ns; + foreach (i, exp; *tup.exps) + { + name = exp.toStringExp(); + if (!name) + { + error(ns.loc, "expected string expression for namespace name, got `%s`", exp.toChars()); + return; + } + const(char)[] ident = name.toStringz(); + if (ident.length == 0 || !Identifier.isValidIdentifier(ident)) + { + error(ns.loc, "expected valid identifier for C++ namespace but got `%.*s`", cast(int)ident.length, ident.ptr); + return; + } + if (i == 0) + { + ns.ident = Identifier.idPool(ident); + } + else + { + // insert the new namespace + Nspace childns = new Nspace(ns.loc, Identifier.idPool(ident), null, parentns.members); + parentns.members = new Dsymbols; + parentns.members.push(childns); + parentns = childns; + repopulateMembers = true; + } + } } } - assert(funcdecl.type.ty != Terror || funcdecl.errors); + ns.semanticRun = PASS.semantic; + ns.parent = sc.parent; + // Link does not matter here, if the UDA is present it will error + UserAttributeDeclaration.checkGNUABITag(ns, LINK.cpp); - // semantic for parameters' UDAs - foreach (i, param; f.parameterList) + if (!ns.members) + { + ns.semanticRun = PASS.semanticdone; + return; + } + assert(sc); + sc = sc.push(ns); + sc.linkage = LINK.cpp; // note that namespaces imply C++ linkage + sc.parent = ns; + foreach (s; *ns.members) + { + if (repopulateMembers) + { + s.addMember(sc, sc.scopesym); + s.setScope(sc); + } + s.importAll(sc); + } + foreach (s; *ns.members) { - if (param && param.userAttribDecl) - param.userAttribDecl.dsymbolSemantic(sc); + static if (LOG) + { + printf("\tmember '%s', kind = '%s'\n", s.toChars(), s.kind()); + } + s.dsymbolSemantic(sc); } + sc.pop(); + ns.semanticRun = PASS.semanticdone; } /// Do the semantic analysis on the external interface to the function. override void visit(FuncDeclaration funcdecl) { - funcDeclarationSemantic(funcdecl); + funcDeclarationSemantic(sc, funcdecl); } override void visit(CtorDeclaration ctd) @@ -3799,7 +2349,7 @@ private extern(C++) final class DsymbolSemanticVisitor : Visitor sc.stc &= ~STC.static_; // not a static constructor - funcDeclarationSemantic(ctd); + funcDeclarationSemantic(sc, ctd); sc.pop(); @@ -3898,7 +2448,7 @@ private extern(C++) final class DsymbolSemanticVisitor : Visitor sc.stc &= ~STC.static_; // not static sc.linkage = LINK.d; - funcDeclarationSemantic(pbd); + funcDeclarationSemantic(sc, pbd); sc.pop(); } @@ -3964,7 +2514,7 @@ private extern(C++) final class DsymbolSemanticVisitor : Visitor if (sc.linkage != LINK.cpp) sc.linkage = LINK.d; - funcDeclarationSemantic(dd); + funcDeclarationSemantic(sc, dd); sc.pop(); } @@ -4052,7 +2602,7 @@ private extern(C++) final class DsymbolSemanticVisitor : Visitor // Just correct it sc.linkage = LINK.d; } - funcDeclarationSemantic(scd); + funcDeclarationSemantic(sc, scd); sc.linkage = save; // We're going to need ModuleInfo @@ -4168,7 +2718,7 @@ private extern(C++) final class DsymbolSemanticVisitor : Visitor // Just correct it sc.linkage = LINK.d; } - funcDeclarationSemantic(sdd); + funcDeclarationSemantic(sc, sdd); sc.linkage = save; // We're going to need ModuleInfo @@ -4219,7 +2769,7 @@ private extern(C++) final class DsymbolSemanticVisitor : Visitor sc.flags = (sc.flags & ~SCOPE.contract) | SCOPE.invariant_; sc.linkage = LINK.d; - funcDeclarationSemantic(invd); + funcDeclarationSemantic(sc, invd); sc.pop(); } @@ -4252,7 +2802,7 @@ private extern(C++) final class DsymbolSemanticVisitor : Visitor utd.type = new TypeFunction(ParameterList(), Type.tvoid, LINK.d, utd.storage_class); Scope* sc2 = sc.push(); sc2.linkage = LINK.d; - funcDeclarationSemantic(utd); + funcDeclarationSemantic(sc, utd); sc2.pop(); } @@ -4281,7 +2831,7 @@ private extern(C++) final class DsymbolSemanticVisitor : Visitor if (!nd.type) nd.type = new TypeFunction(ParameterList(), Type.tvoid.pointerTo(), LINK.d, nd.storage_class); - funcDeclarationSemantic(nd); + funcDeclarationSemantic(sc, nd); } override void visit(StructDeclaration sd) @@ -7278,50 +5828,6 @@ private CallExp doAtomicOp (string op, Identifier var, Expression arg) return CallExp.create(loc, dti, args); } -/*************************************** - * Interpret a `pragma(inline, x)` - * - * Params: - * loc = location for error messages - * sc = scope for evaluation of argument - * args = pragma arguments - * Returns: corresponding `PINLINE` state - */ -PINLINE evalPragmaInline(Loc loc, Scope* sc, Expressions* args) -{ - if (!args || args.length == 0) - return PINLINE.default_; - - if (args && args.length > 1) - { - .error(loc, "one boolean expression expected for `pragma(inline)`, not %llu", cast(ulong) args.length); - args.setDim(1); - (*args)[0] = ErrorExp.get(); - } - - Expression e = (*args)[0]; - if (!e.type) - { - sc = sc.startCTFE(); - e = e.expressionSemantic(sc); - e = resolveProperties(sc, e); - sc = sc.endCTFE(); - e = e.ctfeInterpret(); - e = e.toBoolean(sc); - if (e.isErrorExp()) - .error(loc, "pragma(`inline`, `true` or `false`) expected, not `%s`", (*args)[0].toChars()); - (*args)[0] = e; - } - - const opt = e.toBool(); - if (opt.isEmpty()) - return PINLINE.default_; - else if (opt.get()) - return PINLINE.always; - else - return PINLINE.never; -} - /*************************************************** * Set up loc for a parse of a mixin. Append the input text to the mixin. * Params: diff --git a/gcc/d/dmd/dtemplate.d b/gcc/d/dmd/dtemplate.d index 465ae7453cdc..4a195e3e7c25 100644 --- a/gcc/d/dmd/dtemplate.d +++ b/gcc/d/dmd/dtemplate.d @@ -816,194 +816,6 @@ extern (C++) final class TemplateDeclaration : ScopeDsymbol return buf.extractChars(); } - /************************************************** - * Declare template parameter tp with value o, and install it in the scope sc. - */ - extern (D) RootObject declareParameter(Scope* sc, TemplateParameter tp, RootObject o) - { - //printf("TemplateDeclaration.declareParameter('%s', o = %p)\n", tp.ident.toChars(), o); - Type ta = isType(o); - Expression ea = isExpression(o); - Dsymbol sa = isDsymbol(o); - Tuple va = isTuple(o); - - Declaration d; - VarDeclaration v = null; - - if (ea) - { - if (ea.op == EXP.type) - ta = ea.type; - else if (auto se = ea.isScopeExp()) - sa = se.sds; - else if (auto te = ea.isThisExp()) - sa = te.var; - else if (auto se = ea.isSuperExp()) - sa = se.var; - else if (auto fe = ea.isFuncExp()) - { - if (fe.td) - sa = fe.td; - else - sa = fe.fd; - } - } - - if (ta) - { - //printf("type %s\n", ta.toChars()); - auto ad = new AliasDeclaration(Loc.initial, tp.ident, ta); - ad.storage_class |= STC.templateparameter; - d = ad; - } - else if (sa) - { - //printf("Alias %s %s;\n", sa.ident.toChars(), tp.ident.toChars()); - auto ad = new AliasDeclaration(Loc.initial, tp.ident, sa); - ad.storage_class |= STC.templateparameter; - d = ad; - } - else if (ea) - { - // tdtypes.data[i] always matches ea here - Initializer _init = new ExpInitializer(loc, ea); - TemplateValueParameter tvp = tp.isTemplateValueParameter(); - Type t = tvp ? tvp.valType : null; - v = new VarDeclaration(loc, t, tp.ident, _init); - v.storage_class = STC.manifest | STC.templateparameter; - d = v; - } - else if (va) - { - //printf("\ttuple\n"); - d = new TupleDeclaration(loc, tp.ident, &va.objects); - } - else - { - assert(0); - } - d.storage_class |= STC.templateparameter; - - if (ta) - { - Type t = ta; - // consistent with Type.checkDeprecated() - while (t.ty != Tenum) - { - if (!t.nextOf()) - break; - t = (cast(TypeNext)t).next; - } - if (Dsymbol s = t.toDsymbol(sc)) - { - if (s.isDeprecated()) - d.storage_class |= STC.deprecated_; - } - } - else if (sa) - { - if (sa.isDeprecated()) - d.storage_class |= STC.deprecated_; - } - - if (!sc.insert(d)) - .error(loc, "%s `%s` declaration `%s` is already defined", kind, toPrettyChars, tp.ident.toChars()); - d.dsymbolSemantic(sc); - /* So the caller's o gets updated with the result of semantic() being run on o - */ - if (v) - o = v._init.initializerToExpression(); - return o; - } - - /************************************************* - * Limited function template instantiation for using fd.leastAsSpecialized() - */ - extern (D) FuncDeclaration doHeaderInstantiation(TemplateInstance ti, Scope* sc2, FuncDeclaration fd, Type tthis, Expressions* fargs) - { - assert(fd); - version (none) - { - printf("doHeaderInstantiation this = %s\n", toChars()); - } - - // function body and contracts are not need - if (fd.isCtorDeclaration()) - fd = new CtorDeclaration(fd.loc, fd.endloc, fd.storage_class, fd.type.syntaxCopy()); - else - fd = new FuncDeclaration(fd.loc, fd.endloc, fd.ident, fd.storage_class, fd.type.syntaxCopy()); - fd.parent = ti; - - assert(fd.type.ty == Tfunction); - auto tf = fd.type.isTypeFunction(); - tf.fargs = fargs; - - if (tthis) - { - // Match 'tthis' to any TemplateThisParameter's - bool hasttp = false; - foreach (tp; *parameters) - { - TemplateThisParameter ttp = tp.isTemplateThisParameter(); - if (ttp) - hasttp = true; - } - if (hasttp) - { - tf = tf.addSTC(ModToStc(tthis.mod)).isTypeFunction(); - assert(!tf.deco); - } - } - - Scope* scx = sc2.push(); - - // Shouldn't run semantic on default arguments and return type. - foreach (ref params; *tf.parameterList.parameters) - params.defaultArg = null; - tf.incomplete = true; - - if (fd.isCtorDeclaration()) - { - // For constructors, emitting return type is necessary for - // isReturnIsolated() in functionResolve. - tf.isctor = true; - - Dsymbol parent = toParentDecl(); - Type tret; - AggregateDeclaration ad = parent.isAggregateDeclaration(); - if (!ad || parent.isUnionDeclaration()) - { - tret = Type.tvoid; - } - else - { - tret = ad.handleType(); - assert(tret); - tret = tret.addStorageClass(fd.storage_class | scx.stc); - tret = tret.addMod(tf.mod); - } - tf.next = tret; - if (ad && ad.isStructDeclaration()) - tf.isref = 1; - //printf("tf = %s\n", tf.toChars()); - } - else - tf.next = null; - fd.type = tf; - fd.type = fd.type.addSTC(scx.stc); - fd.type = fd.type.typeSemantic(fd.loc, scx); - scx = scx.pop(); - - if (fd.type.ty != Tfunction) - return null; - - fd.originalType = fd.type; // for mangling - //printf("\t[%s] fd.type = %s, mod = %x, ", loc.toChars(), fd.type.toChars(), fd.type.mod); - //printf("fd.needThis() = %d\n", fd.needThis()); - - return fd; - } - debug (FindExistingInstance) { __gshared uint nFound, nNotFound, nAdded, nRemoved; @@ -1145,575 +957,6 @@ extern (C++) final class TypeDeduced : Type } -/************************************************* - * Given function arguments, figure out which template function - * to expand, and return matching result. - * Params: - * m = matching result - * dstart = the root of overloaded function templates - * loc = instantiation location - * sc = instantiation scope - * tiargs = initial list of template arguments - * tthis = if !NULL, the 'this' pointer argument - * argumentList= arguments to function - * errorHelper = delegate to send error message to if not null - */ -void functionResolve(ref MatchAccumulator m, Dsymbol dstart, Loc loc, Scope* sc, Objects* tiargs, - Type tthis, ArgumentList argumentList, void delegate(const(char)*) scope errorHelper = null) -{ - version (none) - { - printf("functionResolve() dstart = %s\n", dstart.toChars()); - printf(" tiargs:\n"); - if (tiargs) - { - for (size_t i = 0; i < tiargs.length; i++) - { - RootObject arg = (*tiargs)[i]; - printf("\t%s\n", arg.toChars()); - } - } - printf(" fargs:\n"); - for (size_t i = 0; i < (fargs ? fargs.length : 0); i++) - { - Expression arg = (*fargs)[i]; - printf("\t%s %s\n", arg.type.toChars(), arg.toChars()); - //printf("\tty = %d\n", arg.type.ty); - } - //printf("stc = %llx\n", dstart._scope.stc); - //printf("match:t/f = %d/%d\n", ta_last, m.last); - } - - // results - int property = 0; // 0: uninitialized - // 1: seen @property - // 2: not @property - size_t ov_index = 0; - TemplateDeclaration td_best; - TemplateInstance ti_best; - MATCH ta_last = m.last != MATCH.nomatch ? MATCH.exact : MATCH.nomatch; - Type tthis_best; - - int applyFunction(FuncDeclaration fd) - { - // skip duplicates - if (fd == m.lastf) - return 0; - // explicitly specified tiargs never match to non template function - if (tiargs && tiargs.length > 0) - return 0; - - // constructors need a valid scope in order to detect semantic errors - if (!fd.isCtorDeclaration && - fd.semanticRun < PASS.semanticdone) - { - Ungag ungag = fd.ungagSpeculative(); - fd.dsymbolSemantic(null); - } - if (fd.semanticRun < PASS.semanticdone) - { - .error(loc, "forward reference to template `%s`", fd.toChars()); - return 1; - } - //printf("fd = %s %s, fargs = %s\n", fd.toChars(), fd.type.toChars(), fargs.toChars()); - auto tf = fd.type.isTypeFunction(); - - int prop = tf.isproperty ? 1 : 2; - if (property == 0) - property = prop; - else if (property != prop) - error(fd.loc, "cannot overload both property and non-property functions"); - - /* For constructors, qualifier check will be opposite direction. - * Qualified constructor always makes qualified object, then will be checked - * that it is implicitly convertible to tthis. - */ - Type tthis_fd = fd.needThis() ? tthis : null; - bool isCtorCall = tthis_fd && fd.isCtorDeclaration(); - if (isCtorCall) - { - //printf("%s tf.mod = x%x tthis_fd.mod = x%x %d\n", tf.toChars(), - // tf.mod, tthis_fd.mod, fd.isReturnIsolated()); - if (MODimplicitConv(tf.mod, tthis_fd.mod) || - tf.isWild() && tf.isShared() == tthis_fd.isShared() || - fd.isReturnIsolated()) - { - /* && tf.isShared() == tthis_fd.isShared()*/ - // Uniquely constructed object can ignore shared qualifier. - // TODO: Is this appropriate? - tthis_fd = null; - } - else - return 0; // MATCH.nomatch - } - /* Fix Issue 17970: - If a struct is declared as shared the dtor is automatically - considered to be shared, but when the struct is instantiated - the instance is no longer considered to be shared when the - function call matching is done. The fix makes it so that if a - struct declaration is shared, when the destructor is called, - the instantiated struct is also considered shared. - */ - if (auto dt = fd.isDtorDeclaration()) - { - auto dtmod = dt.type.toTypeFunction(); - auto shared_dtor = dtmod.mod & MODFlags.shared_; - auto shared_this = tthis_fd !is null ? - tthis_fd.mod & MODFlags.shared_ : 0; - if (shared_dtor && !shared_this) - tthis_fd = dtmod; - else if (shared_this && !shared_dtor && tthis_fd !is null) - tf.mod = tthis_fd.mod; - } - const(char)* failMessage; - const(char)** pMessage = errorHelper ? &failMessage : null; - MATCH mfa = tf.callMatch(tthis_fd, argumentList, 0, errorHelper, sc); - //printf("test1: mfa = %d\n", mfa); - if (failMessage) - errorHelper(failMessage); - if (mfa == MATCH.nomatch) - return 0; - - int firstIsBetter() - { - td_best = null; - ti_best = null; - ta_last = MATCH.exact; - m.last = mfa; - m.lastf = fd; - tthis_best = tthis_fd; - ov_index = 0; - m.count = 1; - return 0; - } - - if (mfa > m.last) return firstIsBetter(); - if (mfa < m.last) return 0; - - /* See if one of the matches overrides the other. - */ - assert(m.lastf); - if (m.lastf.overrides(fd)) return 0; - if (fd.overrides(m.lastf)) return firstIsBetter(); - - /* Try to disambiguate using template-style partial ordering rules. - * In essence, if f() and g() are ambiguous, if f() can call g(), - * but g() cannot call f(), then pick f(). - * This is because f() is "more specialized." - */ - { - MATCH c1 = FuncDeclaration.leastAsSpecialized(fd, m.lastf, argumentList.names); - MATCH c2 = FuncDeclaration.leastAsSpecialized(m.lastf, fd, argumentList.names); - //printf("c1 = %d, c2 = %d\n", c1, c2); - if (c1 > c2) return firstIsBetter(); - if (c1 < c2) return 0; - } - - /* The 'overrides' check above does covariant checking only - * for virtual member functions. It should do it for all functions, - * but in order to not risk breaking code we put it after - * the 'leastAsSpecialized' check. - * In the future try moving it before. - * I.e. a not-the-same-but-covariant match is preferred, - * as it is more restrictive. - */ - if (!m.lastf.type.equals(fd.type)) - { - //printf("cov: %d %d\n", m.lastf.type.covariant(fd.type), fd.type.covariant(m.lastf.type)); - const lastCovariant = m.lastf.type.covariant(fd.type); - const firstCovariant = fd.type.covariant(m.lastf.type); - - if (lastCovariant == Covariant.yes || lastCovariant == Covariant.no) - { - if (firstCovariant != Covariant.yes && firstCovariant != Covariant.no) - { - return 0; - } - } - else if (firstCovariant == Covariant.yes || firstCovariant == Covariant.no) - { - return firstIsBetter(); - } - } - - /* If the two functions are the same function, like: - * int foo(int); - * int foo(int x) { ... } - * then pick the one with the body. - * - * If none has a body then don't care because the same - * real function would be linked to the decl (e.g from object file) - */ - if (tf.equals(m.lastf.type) && - fd.storage_class == m.lastf.storage_class && - fd.parent == m.lastf.parent && - fd.visibility == m.lastf.visibility && - fd._linkage == m.lastf._linkage) - { - if (fd.fbody && !m.lastf.fbody) - return firstIsBetter(); - if (!fd.fbody) - return 0; - } - - // https://issues.dlang.org/show_bug.cgi?id=14450 - // Prefer exact qualified constructor for the creating object type - if (isCtorCall && tf.mod != m.lastf.type.mod) - { - if (tthis.mod == tf.mod) return firstIsBetter(); - if (tthis.mod == m.lastf.type.mod) return 0; - } - - m.nextf = fd; - m.count++; - return 0; - } - - int applyTemplate(TemplateDeclaration td) - { - //printf("applyTemplate(): td = %s\n", td.toChars()); - if (td == td_best) // skip duplicates - return 0; - - if (!sc) - sc = td._scope; // workaround for Type.aliasthisOf - - if (td.semanticRun == PASS.initial && td._scope) - { - // Try to fix forward reference. Ungag errors while doing so. - Ungag ungag = td.ungagSpeculative(); - td.dsymbolSemantic(td._scope); - } - if (td.semanticRun == PASS.initial) - { - .error(loc, "forward reference to template `%s`", td.toChars()); - Lerror: - m.lastf = null; - m.count = 0; - m.last = MATCH.nomatch; - return 1; - } - //printf("td = %s\n", td.toChars()); - - if (argumentList.hasNames) - { - .error(loc, "named arguments with Implicit Function Template Instantiation are not supported yet"); - goto Lerror; - } - auto f = td.onemember ? td.onemember.isFuncDeclaration() : null; - if (!f) - { - if (!tiargs) - tiargs = new Objects(); - auto ti = new TemplateInstance(loc, td, tiargs); - Objects dedtypes = Objects(td.parameters.length); - assert(td.semanticRun != PASS.initial); - MATCH mta = matchWithInstance(sc, td, ti, dedtypes, argumentList, 0); - //printf("matchWithInstance = %d\n", mta); - if (mta == MATCH.nomatch || mta < ta_last) // no match or less match - return 0; - - ti.templateInstanceSemantic(sc, argumentList); - if (!ti.inst) // if template failed to expand - return 0; - - Dsymbol s = ti.inst.toAlias(); - FuncDeclaration fd; - if (auto tdx = s.isTemplateDeclaration()) - { - Objects dedtypesX; // empty tiargs - - // https://issues.dlang.org/show_bug.cgi?id=11553 - // Check for recursive instantiation of tdx. - for (TemplatePrevious* p = tdx.previous; p; p = p.prev) - { - if (arrayObjectMatch(*p.dedargs, dedtypesX)) - { - //printf("recursive, no match p.sc=%p %p %s\n", p.sc, this, this.toChars()); - /* It must be a subscope of p.sc, other scope chains are not recursive - * instantiations. - */ - for (Scope* scx = sc; scx; scx = scx.enclosing) - { - if (scx == p.sc) - { - error(loc, "recursive template expansion while looking for `%s.%s`", ti.toChars(), tdx.toChars()); - goto Lerror; - } - } - } - /* BUG: should also check for ref param differences - */ - } - - TemplatePrevious pr; - pr.prev = tdx.previous; - pr.sc = sc; - pr.dedargs = &dedtypesX; - tdx.previous = ≺ // add this to threaded list - - fd = resolveFuncCall(loc, sc, s, null, tthis, argumentList, FuncResolveFlag.quiet); - - tdx.previous = pr.prev; // unlink from threaded list - } - else if (s.isFuncDeclaration()) - { - fd = resolveFuncCall(loc, sc, s, null, tthis, argumentList, FuncResolveFlag.quiet); - } - else - goto Lerror; - - if (!fd) - return 0; - - if (fd.type.ty != Tfunction) - { - m.lastf = fd; // to propagate "error match" - m.count = 1; - m.last = MATCH.nomatch; - return 1; - } - - Type tthis_fd = fd.needThis() && !fd.isCtorDeclaration() ? tthis : null; - - auto tf = fd.type.isTypeFunction(); - MATCH mfa = tf.callMatch(tthis_fd, argumentList, 0, null, sc); - if (mfa < m.last) - return 0; - - if (mta < ta_last) goto Ltd_best2; - if (mta > ta_last) goto Ltd2; - - if (mfa < m.last) goto Ltd_best2; - if (mfa > m.last) goto Ltd2; - - // td_best and td are ambiguous - //printf("Lambig2\n"); - m.nextf = fd; - m.count++; - return 0; - - Ltd_best2: - return 0; - - Ltd2: - // td is the new best match - assert(td._scope); - td_best = td; - ti_best = null; - property = 0; // (backward compatibility) - ta_last = mta; - m.last = mfa; - m.lastf = fd; - tthis_best = tthis_fd; - ov_index = 0; - m.nextf = null; - m.count = 1; - return 0; - } - - //printf("td = %s\n", td.toChars()); - for (size_t ovi = 0; f; f = f.overnext0, ovi++) - { - if (f.type.ty != Tfunction || f.errors) - goto Lerror; - - /* This is a 'dummy' instance to evaluate constraint properly. - */ - auto ti = new TemplateInstance(loc, td, tiargs); - ti.parent = td.parent; // Maybe calculating valid 'enclosing' is unnecessary. - - auto fd = f; - MATCHpair x = td.deduceFunctionTemplateMatch(ti, sc, fd, tthis, argumentList); - MATCH mta = x.mta; - MATCH mfa = x.mfa; - //printf("match:t/f = %d/%d\n", mta, mfa); - if (!fd || mfa == MATCH.nomatch) - continue; - - Type tthis_fd = fd.needThis() ? tthis : null; - - bool isCtorCall = tthis_fd && fd.isCtorDeclaration(); - if (isCtorCall) - { - // Constructor call requires additional check. - auto tf = fd.type.isTypeFunction(); - assert(tf.next); - if (MODimplicitConv(tf.mod, tthis_fd.mod) || - tf.isWild() && tf.isShared() == tthis_fd.isShared() || - fd.isReturnIsolated()) - { - tthis_fd = null; - } - else - continue; // MATCH.nomatch - - // need to check here whether the constructor is the member of a struct - // declaration that defines a copy constructor. This is already checked - // in the semantic of CtorDeclaration, however, when matching functions, - // the template instance is not expanded. - // https://issues.dlang.org/show_bug.cgi?id=21613 - auto ad = fd.isThis(); - auto sd = ad.isStructDeclaration(); - if (checkHasBothRvalueAndCpCtor(sd, fd.isCtorDeclaration(), ti)) - continue; - } - - if (mta < ta_last) goto Ltd_best; - if (mta > ta_last) goto Ltd; - - if (mfa < m.last) goto Ltd_best; - if (mfa > m.last) goto Ltd; - - if (td_best) - { - // Disambiguate by picking the most specialized TemplateDeclaration - MATCH c1 = leastAsSpecialized(sc, td, td_best, argumentList); - MATCH c2 = leastAsSpecialized(sc, td_best, td, argumentList); - //printf("1: c1 = %d, c2 = %d\n", c1, c2); - if (c1 > c2) goto Ltd; - if (c1 < c2) goto Ltd_best; - } - assert(fd && m.lastf); - { - // Disambiguate by tf.callMatch - auto tf1 = fd.type.isTypeFunction(); - auto tf2 = m.lastf.type.isTypeFunction(); - MATCH c1 = tf1.callMatch(tthis_fd, argumentList, 0, null, sc); - MATCH c2 = tf2.callMatch(tthis_best, argumentList, 0, null, sc); - //printf("2: c1 = %d, c2 = %d\n", c1, c2); - if (c1 > c2) goto Ltd; - if (c1 < c2) goto Ltd_best; - } - { - // Disambiguate by picking the most specialized FunctionDeclaration - MATCH c1 = FuncDeclaration.leastAsSpecialized(fd, m.lastf, argumentList.names); - MATCH c2 = FuncDeclaration.leastAsSpecialized(m.lastf, fd, argumentList.names); - //printf("3: c1 = %d, c2 = %d\n", c1, c2); - if (c1 > c2) goto Ltd; - if (c1 < c2) goto Ltd_best; - } - - // https://issues.dlang.org/show_bug.cgi?id=14450 - // Prefer exact qualified constructor for the creating object type - if (isCtorCall && fd.type.mod != m.lastf.type.mod) - { - if (tthis.mod == fd.type.mod) goto Ltd; - if (tthis.mod == m.lastf.type.mod) goto Ltd_best; - } - - m.nextf = fd; - m.count++; - continue; - - Ltd_best: // td_best is the best match so far - //printf("Ltd_best\n"); - continue; - - Ltd: // td is the new best match - //printf("Ltd\n"); - assert(td._scope); - td_best = td; - ti_best = ti; - property = 0; // (backward compatibility) - ta_last = mta; - m.last = mfa; - m.lastf = fd; - tthis_best = tthis_fd; - ov_index = ovi; - m.nextf = null; - m.count = 1; - continue; - } - return 0; - } - - auto td = dstart.isTemplateDeclaration(); - if (td && td.funcroot) - dstart = td.funcroot; - overloadApply(dstart, (Dsymbol s) - { - if (s.errors) - return 0; - if (auto fd = s.isFuncDeclaration()) - return applyFunction(fd); - if (auto td = s.isTemplateDeclaration()) - return applyTemplate(td); - return 0; - }, sc); - - //printf("td_best = %p, m.lastf = %p\n", td_best, m.lastf); - if (td_best && ti_best && m.count == 1) - { - // Matches to template function - assert(td_best.onemember && td_best.onemember.isFuncDeclaration()); - /* The best match is td_best with arguments tdargs. - * Now instantiate the template. - */ - assert(td_best._scope); - if (!sc) - sc = td_best._scope; // workaround for Type.aliasthisOf - - auto ti = new TemplateInstance(loc, td_best, ti_best.tiargs); - ti.templateInstanceSemantic(sc, argumentList); - - m.lastf = ti.toAlias().isFuncDeclaration(); - if (!m.lastf) - goto Lnomatch; - if (ti.errors) - { - Lerror: - m.count = 1; - assert(m.lastf); - m.last = MATCH.nomatch; - return; - } - - // look forward instantiated overload function - // Dsymbol.oneMembers is alredy called in TemplateInstance.semantic. - // it has filled overnext0d - while (ov_index--) - { - m.lastf = m.lastf.overnext0; - assert(m.lastf); - } - - tthis_best = m.lastf.needThis() && !m.lastf.isCtorDeclaration() ? tthis : null; - - if (m.lastf.type.ty == Terror) - goto Lerror; - auto tf = m.lastf.type.isTypeFunction(); - if (!tf.callMatch(tthis_best, argumentList, 0, null, sc)) - goto Lnomatch; - - /* As https://issues.dlang.org/show_bug.cgi?id=3682 shows, - * a template instance can be matched while instantiating - * that same template. Thus, the function type can be incomplete. Complete it. - * - * https://issues.dlang.org/show_bug.cgi?id=9208 - * For auto function, completion should be deferred to the end of - * its semantic3. Should not complete it in here. - */ - if (tf.next && !m.lastf.inferRetType) - { - m.lastf.type = tf.typeSemantic(loc, sc); - } - } - else if (m.lastf) - { - // Matches to non template function, - // or found matches were ambiguous. - assert(m.count >= 1); - } - else - { - Lnomatch: - m.count = 0; - m.lastf = null; - m.last = MATCH.nomatch; - } -} - /* ======================== Type ============================================ */ /**** @@ -6101,7 +5344,7 @@ extern (C++) class TemplateInstance : ScopeDsymbol { TemplateParameter tp = (*tempdecl.parameters)[i]; //printf("\ttdtypes[%d] = %p\n", i, o); - tempdecl.declareParameter(sc, tp, o); + declareParameter(tempdecl, sc, tp, o); } } diff --git a/gcc/d/dmd/dtoh.d b/gcc/d/dmd/dtoh.d index 2bfa96cf76b0..4a1ff055157a 100644 --- a/gcc/d/dmd/dtoh.d +++ b/gcc/d/dmd/dtoh.d @@ -30,6 +30,7 @@ import dmd.location; import dmd.root.filename; import dmd.visitor; import dmd.tokens; +import dmd.typesem; import dmd.common.outbuffer; import dmd.utils; diff --git a/gcc/d/dmd/enumsem.d b/gcc/d/dmd/enumsem.d index 060396026e90..3886ca25e97b 100644 --- a/gcc/d/dmd/enumsem.d +++ b/gcc/d/dmd/enumsem.d @@ -503,6 +503,8 @@ void enumMemberSemantic(Scope* sc, EnumMember em) { Expression e = em.value; assert(e.dyncast() == DYNCAST.expression); + if (em.ed.memtype) + e = inferType(e, em.ed.memtype); e = e.expressionSemantic(sc); e = resolveProperties(sc, e); e = e.ctfeInterpret(); @@ -571,6 +573,10 @@ void enumMemberSemantic(Scope* sc, EnumMember em) em.origValue = e; } em.value = e; + // https://issues.dlang.org/show_bug.cgi?id=24311 + // First enum member is .init value, which gets put into static segment + if (first) + lowerStaticAAs(e, sc); } else if (first) { diff --git a/gcc/d/dmd/expression.d b/gcc/d/dmd/expression.d index 1603f2bbb535..82de837ef750 100644 --- a/gcc/d/dmd/expression.d +++ b/gcc/d/dmd/expression.d @@ -48,6 +48,7 @@ import dmd.root.string; import dmd.root.utf; import dmd.target; import dmd.tokens; +import dmd.typesem; import dmd.visitor; enum LOGSEMANTIC = false; @@ -3851,7 +3852,7 @@ extern (C++) final class CastExp : UnaExp if (!e1.isLvalue()) return false; return (to.ty == Tsarray && (e1.type.ty == Tvector || e1.type.ty == Tsarray)) || - e1.type.mutableOf().unSharedOf().equals(to.mutableOf().unSharedOf()); + e1.type.mutableOf.unSharedOf().equals(to.mutableOf().unSharedOf()); } override void accept(Visitor v) diff --git a/gcc/d/dmd/expression.h b/gcc/d/dmd/expression.h index d53cc3e85cc5..f713d25a7390 100644 --- a/gcc/d/dmd/expression.h +++ b/gcc/d/dmd/expression.h @@ -55,6 +55,7 @@ Expression *resolveLoc(Expression *exp, const Loc &loc, Scope *sc); MATCH implicitConvTo(Expression *e, Type *t); Expression *toLvalue(Expression *_this, Scope *sc, const char* action); Expression *modifiableLvalue(Expression* exp, Scope *sc); +Expression *optimize(Expression *exp, int result, bool keepLvalue = false); typedef unsigned char OwnedBy; enum @@ -108,8 +109,6 @@ public: Expression *addressOf(); Expression *deref(); - Expression *optimize(int result, bool keepLvalue = false); - int isConst(); virtual bool isIdentical(const Expression *e) const; virtual Optional<bool> toBool(); diff --git a/gcc/d/dmd/expressionsem.d b/gcc/d/dmd/expressionsem.d index f2133037a230..d7377dbdea89 100644 --- a/gcc/d/dmd/expressionsem.d +++ b/gcc/d/dmd/expressionsem.d @@ -85,6 +85,7 @@ import dmd.traits; import dmd.typesem; import dmd.typinf; import dmd.utils; +import dmd.utils : arrayCastBigEndian; import dmd.visitor; enum LOGSEMANTIC = false; @@ -4242,7 +4243,33 @@ private extern (C++) final class ExpressionSemanticVisitor : Visitor size_t u; dchar c; - switch (e.postfix) + if (e.hexString) + { + const data = cast(const ubyte[]) e.peekString(); + switch (e.postfix) + { + case 'd': + e.sz = 4; + e.type = Type.tdstring; + break; + case 'w': + e.sz = 2; + e.type = Type.twstring; + break; + case 'c': + default: + e.type = Type.tstring; + e.sz = 1; + break; + } + if ((e.len % e.sz) != 0) + error(e.loc, "hex string with `%s` type needs to be multiple of %d bytes, not %d", + e.type.toChars(), e.sz, cast(int) e.len); + + e.setData(arrayCastBigEndian(data, e.sz).ptr, e.len / e.sz, e.sz); + e.committed = true; + } + else switch (e.postfix) { case 'd': for (u = 0; u < e.len;) @@ -6263,7 +6290,7 @@ private extern (C++) final class ExpressionSemanticVisitor : Visitor auto ad2 = b.sym; ue.e1 = ue.e1.castTo(sc, ad2.type.addMod(ue.e1.type.mod)); ue.e1 = ue.e1.expressionSemantic(sc); - auto vi = exp.f.findVtblIndex(&ad2.vtbl, cast(int)ad2.vtbl.length); + auto vi = findVtblIndex(exp.f, ad2.vtbl[]); assert(vi >= 0); exp.f = ad2.vtbl[vi].isFuncDeclaration(); assert(exp.f); diff --git a/gcc/d/dmd/func.d b/gcc/d/dmd/func.d index adfecc83a178..ddf21a2079f4 100644 --- a/gcc/d/dmd/func.d +++ b/gcc/d/dmd/func.d @@ -58,6 +58,7 @@ import dmd.semantic3; import dmd.statement_rewrite_walker; import dmd.statement; import dmd.statementsem; +import dmd.templatesem; import dmd.tokens; import dmd.visitor; @@ -467,29 +468,6 @@ extern (C++) class FuncDeclaration : Declaration return f; } - /**************************************************** - * Check that this function type is properly resolved. - * If not, report "forward reference error" and return true. - */ - extern (D) final bool checkForwardRef(const ref Loc loc) - { - if (!functionSemantic(this)) - return true; - - /* No deco means the functionSemantic() call could not resolve - * forward referenes in the type of this function. - */ - if (!type.deco) - { - bool inSemantic3 = (inferRetType && semanticRun >= PASS.semantic3); - .error(loc, "forward reference to %s`%s`", - (inSemantic3 ? "inferred return type of function " : "").ptr, - toChars()); - return true; - } - return false; - } - override final bool equals(const RootObject o) const { if (this == o) @@ -553,154 +531,6 @@ extern (C++) class FuncDeclaration : Declaration return result; } - /************************************************* - * Find index of function in vtbl[0..length] that - * this function overrides. - * Prefer an exact match to a covariant one. - * Params: - * vtbl = vtable to use - * dim = maximal vtable dimension - * Returns: - * -1 didn't find one - * -2 can't determine because of forward references - */ - final int findVtblIndex(Dsymbols* vtbl, int dim) - { - //printf("findVtblIndex() %s\n", toChars()); - import dmd.typesem : covariant; - - FuncDeclaration mismatch = null; - StorageClass mismatchstc = 0; - int mismatchvi = -1; - int exactvi = -1; - int bestvi = -1; - for (int vi = 0; vi < dim; vi++) - { - FuncDeclaration fdv = (*vtbl)[vi].isFuncDeclaration(); - if (fdv && fdv.ident == ident) - { - if (type.equals(fdv.type)) // if exact match - { - if (fdv.parent.isClassDeclaration()) - { - if (fdv.isFuture()) - { - bestvi = vi; - continue; // keep looking - } - return vi; // no need to look further - } - - if (exactvi >= 0) - { - .error(loc, "%s `%s` cannot determine overridden function", kind, toPrettyChars); - return exactvi; - } - exactvi = vi; - bestvi = vi; - continue; - } - - StorageClass stc = 0; - const cov = type.covariant(fdv.type, &stc); - //printf("\tbaseclass cov = %d\n", cov); - final switch (cov) - { - case Covariant.distinct: - // types are distinct - break; - - case Covariant.yes: - bestvi = vi; // covariant, but not identical - break; - // keep looking for an exact match - - case Covariant.no: - mismatchvi = vi; - mismatchstc = stc; - mismatch = fdv; // overrides, but is not covariant - break; - // keep looking for an exact match - - case Covariant.fwdref: - return -2; // forward references - } - } - } - if (_linkage == LINK.cpp && bestvi != -1) - { - StorageClass stc = 0; - FuncDeclaration fdv = (*vtbl)[bestvi].isFuncDeclaration(); - assert(fdv && fdv.ident == ident); - if (type.covariant(fdv.type, &stc, /*cppCovariant=*/true) == Covariant.no) - { - /* https://issues.dlang.org/show_bug.cgi?id=22351 - * Under D rules, `type` and `fdv.type` are covariant, but under C++ rules, they are not. - * For now, continue to allow D covariant rules to apply when `override` has been used, - * but issue a deprecation warning that this behaviour will change in the future. - * Otherwise, follow the C++ covariant rules, which will create a new vtable entry. - */ - if (isOverride()) - { - /* @@@DEPRECATED_2.110@@@ - * After deprecation period has ended, be sure to remove this entire `LINK.cpp` branch, - * but also the `cppCovariant` parameter from Type.covariant, and update the function - * so that both `LINK.cpp` covariant conditions within are always checked. - */ - .deprecation(loc, "overriding `extern(C++)` function `%s%s` with `const` qualified function `%s%s%s` is deprecated", - fdv.toPrettyChars(), fdv.type.toTypeFunction().parameterList.parametersTypeToChars(), - toPrettyChars(), type.toTypeFunction().parameterList.parametersTypeToChars(), type.modToChars()); - - const char* where = type.isNaked() ? "parameters" : "type"; - deprecationSupplemental(loc, "Either remove `override`, or adjust the `const` qualifiers of the " - ~ "overriding function %s", where); - } - else - { - // Treat as if Covariant.no - mismatchvi = bestvi; - mismatchstc = stc; - mismatch = fdv; - bestvi = -1; - } - } - } - if (bestvi == -1 && mismatch) - { - //type.print(); - //mismatch.type.print(); - //printf("%s %s\n", type.deco, mismatch.type.deco); - //printf("stc = %llx\n", mismatchstc); - if (mismatchstc) - { - // Fix it by modifying the type to add the storage classes - type = type.addStorageClass(mismatchstc); - bestvi = mismatchvi; - } - } - return bestvi; - } - - /********************************* - * If function a function in a base class, - * return that base class. - * Returns: - * base class if overriding, null if not - */ - extern (D) final BaseClass* overrideInterface() - { - for (ClassDeclaration cd = toParent2().isClassDeclaration(); cd; cd = cd.baseClass) - { - foreach (b; cd.interfaces) - { - auto v = findVtblIndex(&b.sym.vtbl, cast(int)b.sym.vtbl.length); - if (v >= 0) - return b; - } - } - return null; - } - /**************************************************** * Overload this FuncDeclaration with the new one f. * Return true if successful; i.e. no conflict. diff --git a/gcc/d/dmd/funcsem.d b/gcc/d/dmd/funcsem.d index 84201793c0ef..9e706ee80d9d 100644 --- a/gcc/d/dmd/funcsem.d +++ b/gcc/d/dmd/funcsem.d @@ -18,6 +18,7 @@ import core.stdc.stdio; import dmd.aggregate; import dmd.arraytypes; import dmd.astenums; +import dmd.attrib; import dmd.blockexit; import dmd.gluelayer; import dmd.dcast; @@ -39,13 +40,18 @@ import dmd.globals; import dmd.hdrgen; import dmd.id; import dmd.identifier; +import dmd.importc; import dmd.init; import dmd.location; import dmd.mtype; +import dmd.mustuse; import dmd.objc; +import dmd.opover; +import dmd.pragmasem; import dmd.root.aav; import dmd.common.outbuffer; import dmd.rootobject; +import dmd.root.filename; import dmd.root.string; import dmd.root.stringtable; import dmd.semantic2; @@ -53,9 +59,980 @@ import dmd.semantic3; import dmd.statement_rewrite_walker; import dmd.statement; import dmd.statementsem; +import dmd.target; import dmd.tokens; +import dmd.typesem; import dmd.visitor; +/********************************** + * Main semantic routine for functions. + */ +void funcDeclarationSemantic(Scope* sc, FuncDeclaration funcdecl) +{ + version (none) + { + printf("FuncDeclaration::semantic(sc = %p, this = %p, '%s', linkage = %d)\n", sc, funcdecl, funcdecl.toPrettyChars(), sc.linkage); + if (funcdecl.isFuncLiteralDeclaration()) + printf("\tFuncLiteralDeclaration()\n"); + printf("sc.parent = %s, parent = %s\n", sc.parent.toChars(), funcdecl.parent ? funcdecl.parent.toChars() : ""); + printf("type: %p, %s\n", funcdecl.type, funcdecl.type.toChars()); + } + + if (funcdecl.semanticRun != PASS.initial && funcdecl.isFuncLiteralDeclaration()) + { + /* Member functions that have return types that are + * forward references can have semantic() run more than + * once on them. + * See test\interface2.d, test20 + */ + return; + } + + if (funcdecl.semanticRun >= PASS.semanticdone) + return; + assert(funcdecl.semanticRun <= PASS.semantic); + funcdecl.semanticRun = PASS.semantic; + + if (funcdecl._scope) + { + sc = funcdecl._scope; + funcdecl._scope = null; + } + + if (!sc || funcdecl.errors) + return; + + funcdecl.cppnamespace = sc.namespace; + funcdecl.parent = sc.parent; + Dsymbol parent = funcdecl.toParent(); + + funcdecl.foverrides.setDim(0); // reset in case semantic() is being retried for this function + + funcdecl.storage_class |= sc.stc & ~STC.ref_; + AggregateDeclaration ad = funcdecl.isThis(); + // Don't nest structs b/c of generated methods which should not access the outer scopes. + // https://issues.dlang.org/show_bug.cgi?id=16627 + if (ad && !funcdecl.isGenerated()) + { + funcdecl.storage_class |= ad.storage_class & (STC.TYPECTOR | STC.synchronized_); + ad.makeNested(); + } + if (sc.func) + funcdecl.storage_class |= sc.func.storage_class & STC.disable; + // Remove prefix storage classes silently. + if ((funcdecl.storage_class & STC.TYPECTOR) && !(ad || funcdecl.isNested())) + funcdecl.storage_class &= ~STC.TYPECTOR; + + //printf("function storage_class = x%llx, sc.stc = x%llx, %x\n", storage_class, sc.stc, Declaration.isFinal()); + + if (sc.flags & SCOPE.compile) + funcdecl.skipCodegen = true; + + funcdecl._linkage = sc.linkage; + if (sc.flags & SCOPE.Cfile && funcdecl.isFuncLiteralDeclaration()) + funcdecl._linkage = LINK.d; // so they are uniquely mangled + + if (auto fld = funcdecl.isFuncLiteralDeclaration()) + { + if (fld.treq) + { + Type treq = fld.treq; + assert(treq.nextOf().ty == Tfunction); + if (treq.ty == Tdelegate) + fld.tok = TOK.delegate_; + else if (treq.isPtrToFunction()) + fld.tok = TOK.function_; + else + assert(0); + funcdecl._linkage = treq.nextOf().toTypeFunction().linkage; + } + } + + // evaluate pragma(inline) + if (auto pragmadecl = sc.inlining) + funcdecl.inlining = evalPragmaInline(pragmadecl.loc, sc, pragmadecl.args); + + funcdecl.visibility = sc.visibility; + funcdecl.userAttribDecl = sc.userAttribDecl; + UserAttributeDeclaration.checkGNUABITag(funcdecl, funcdecl._linkage); + checkMustUseReserved(funcdecl); + + if (!funcdecl.originalType) + funcdecl.originalType = funcdecl.type.syntaxCopy(); + + static TypeFunction getFunctionType(FuncDeclaration fd) + { + if (auto tf = fd.type.isTypeFunction()) + return tf; + + if (!fd.type.isTypeError()) + { + .error(fd.loc, "%s `%s` `%s` must be a function instead of `%s`", fd.kind, fd.toPrettyChars, fd.toChars(), fd.type.toChars()); + fd.type = Type.terror; + } + fd.errors = true; + return null; + } + + if (sc.flags & SCOPE.Cfile) + { + /* C11 allows a function to be declared with a typedef, D does not. + */ + if (auto ti = funcdecl.type.isTypeIdentifier()) + { + auto tj = ti.typeSemantic(funcdecl.loc, sc); + if (auto tjf = tj.isTypeFunction()) + { + /* Copy the type instead of just pointing to it, + * as we don't merge function types + */ + auto tjf2 = new TypeFunction(tjf.parameterList, tjf.next, tjf.linkage); + funcdecl.type = tjf2; + funcdecl.originalType = tjf2; + } + } + } + + if (!getFunctionType(funcdecl)) + return; + + if (!funcdecl.type.deco) + { + sc = sc.push(); + sc.stc |= funcdecl.storage_class & (STC.disable | STC.deprecated_); // forward to function type + + TypeFunction tf = funcdecl.type.toTypeFunction(); + if (sc.func) + { + /* If the nesting parent is pure without inference, + * then this function defaults to pure too. + * + * auto foo() pure { + * auto bar() {} // become a weak purity function + * class C { // nested class + * auto baz() {} // become a weak purity function + * } + * + * static auto boo() {} // typed as impure + * // Even though, boo cannot call any impure functions. + * // See also Expression::checkPurity(). + * } + */ + if (tf.purity == PURE.impure && (funcdecl.isNested() || funcdecl.isThis())) + { + FuncDeclaration fd = null; + for (Dsymbol p = funcdecl.toParent2(); p; p = p.toParent2()) + { + if (AggregateDeclaration adx = p.isAggregateDeclaration()) + { + if (adx.isNested()) + continue; + break; + } + if ((fd = p.isFuncDeclaration()) !is null) + break; + } + + /* If the parent's purity is inferred, then this function's purity needs + * to be inferred first. + */ + if (fd && fd.isPureBypassingInference() >= PURE.weak && !funcdecl.isInstantiated()) + { + tf.purity = PURE.fwdref; // default to pure + } + } + } + + if (tf.isref) + sc.stc |= STC.ref_; + if (tf.isScopeQual) + sc.stc |= STC.scope_; + if (tf.isnothrow) + sc.stc |= STC.nothrow_; + if (tf.isnogc) + sc.stc |= STC.nogc; + if (tf.isproperty) + sc.stc |= STC.property; + if (tf.purity == PURE.fwdref) + sc.stc |= STC.pure_; + + if (tf.trust != TRUST.default_) + { + sc.stc &= ~STC.safeGroup; + if (tf.trust == TRUST.safe) + sc.stc |= STC.safe; + else if (tf.trust == TRUST.system) + sc.stc |= STC.system; + else if (tf.trust == TRUST.trusted) + sc.stc |= STC.trusted; + } + + if (funcdecl.isCtorDeclaration()) + { + tf.isctor = true; + Type tret = ad.handleType(); + assert(tret); + tret = tret.addStorageClass(funcdecl.storage_class | sc.stc); + tret = tret.addMod(funcdecl.type.mod); + tf.next = tret; + if (ad.isStructDeclaration()) + sc.stc |= STC.ref_; + } + + // 'return' on a non-static class member function implies 'scope' as well + if (ad && ad.isClassDeclaration() && (tf.isreturn || sc.stc & STC.return_) && !(sc.stc & STC.static_)) + sc.stc |= STC.scope_; + + // If 'this' has no pointers, remove 'scope' as it has no meaning + // Note: this is already covered by semantic of `VarDeclaration` and `TypeFunction`, + // but existing code relies on `hasPointers()` being called here to resolve forward references: + // https://github.com/dlang/dmd/pull/14232#issuecomment-1162906573 + if (sc.stc & STC.scope_ && ad && ad.isStructDeclaration() && !ad.type.hasPointers()) + { + sc.stc &= ~STC.scope_; + tf.isScopeQual = false; + if (tf.isreturnscope) + { + sc.stc &= ~(STC.return_ | STC.returnScope); + tf.isreturn = false; + tf.isreturnscope = false; + } + } + + sc.linkage = funcdecl._linkage; + + if (!tf.isNaked() && !(funcdecl.isThis() || funcdecl.isNested())) + { + import core.bitop : popcnt; + auto mods = MODtoChars(tf.mod); + .error(funcdecl.loc, "%s `%s` without `this` cannot be `%s`", funcdecl.kind, funcdecl.toPrettyChars, mods); + if (tf.next && tf.next.ty != Tvoid && popcnt(tf.mod) == 1) + .errorSupplemental(funcdecl.loc, + "did you mean to use `%s(%s)` as the return type?", mods, tf.next.toChars()); + + tf.mod = 0; // remove qualifiers + } + + /* Apply const, immutable, wild and shared storage class + * to the function type. Do this before type semantic. + */ + auto stc = funcdecl.storage_class; + if (funcdecl.type.isImmutable()) + stc |= STC.immutable_; + if (funcdecl.type.isConst()) + stc |= STC.const_; + if (funcdecl.type.isShared() || funcdecl.storage_class & STC.synchronized_) + stc |= STC.shared_; + if (funcdecl.type.isWild()) + stc |= STC.wild; + funcdecl.type = funcdecl.type.addSTC(stc); + + funcdecl.type = funcdecl.type.typeSemantic(funcdecl.loc, sc); + sc = sc.pop(); + } + + auto f = getFunctionType(funcdecl); + if (!f) + return; // funcdecl's type is not a function + + { + // Merge back function attributes into 'originalType'. + // It's used for mangling, ddoc, and json output. + TypeFunction tfo = funcdecl.originalType.toTypeFunction(); + tfo.mod = f.mod; + tfo.isScopeQual = f.isScopeQual; + tfo.isreturninferred = f.isreturninferred; + tfo.isscopeinferred = f.isscopeinferred; + tfo.isref = f.isref; + tfo.isnothrow = f.isnothrow; + tfo.isnogc = f.isnogc; + tfo.isproperty = f.isproperty; + tfo.purity = f.purity; + tfo.trust = f.trust; + + funcdecl.storage_class &= ~(STC.TYPECTOR | STC.FUNCATTR); + } + + // check pragma(crt_constructor) signature + if (funcdecl.isCrtCtor || funcdecl.isCrtDtor) + { + const idStr = funcdecl.isCrtCtor ? "crt_constructor" : "crt_destructor"; + if (f.nextOf().ty != Tvoid) + .error(funcdecl.loc, "%s `%s` must return `void` for `pragma(%s)`", funcdecl.kind, funcdecl.toPrettyChars, idStr.ptr); + if (funcdecl._linkage != LINK.c && f.parameterList.length != 0) + .error(funcdecl.loc, "%s `%s` must be `extern(C)` for `pragma(%s)` when taking parameters", funcdecl.kind, funcdecl.toPrettyChars, idStr.ptr); + if (funcdecl.isThis()) + .error(funcdecl.loc, "%s `%s` cannot be a non-static member function for `pragma(%s)`", funcdecl.kind, funcdecl.toPrettyChars, idStr.ptr); + } + + if (funcdecl.overnext && funcdecl.isCsymbol()) + { + /* C does not allow function overloading, but it does allow + * redeclarations of the same function. If .overnext points + * to a redeclaration, ok. Error if it is an overload. + */ + auto fnext = funcdecl.overnext.isFuncDeclaration(); + funcDeclarationSemantic(sc, fnext); + auto fn = fnext.type.isTypeFunction(); + if (!fn || !cFuncEquivalence(f, fn)) + { + .error(funcdecl.loc, "%s `%s` redeclaration with different type", funcdecl.kind, funcdecl.toPrettyChars); + //printf("t1: %s\n", f.toChars()); + //printf("t2: %s\n", fn.toChars()); + } + funcdecl.overnext = null; // don't overload the redeclarations + } + + if ((funcdecl.storage_class & STC.auto_) && !f.isref && !funcdecl.inferRetType) + .error(funcdecl.loc, "%s `%s` storage class `auto` has no effect if return type is not inferred", funcdecl.kind, funcdecl.toPrettyChars); + + if (f.isreturn && !funcdecl.needThis() && !funcdecl.isNested()) + { + /* Non-static nested functions have a hidden 'this' pointer to which + * the 'return' applies + */ + if (sc.scopesym && sc.scopesym.isAggregateDeclaration()) + .error(funcdecl.loc, "%s `%s` `static` member has no `this` to which `return` can apply", funcdecl.kind, funcdecl.toPrettyChars); + else + error(funcdecl.loc, "top-level function `%s` has no `this` to which `return` can apply", funcdecl.toChars()); + } + + if (funcdecl.isAbstract() && !funcdecl.isVirtual()) + { + const(char)* sfunc; + if (funcdecl.isStatic()) + sfunc = "static"; + else if (funcdecl.visibility.kind == Visibility.Kind.private_ || funcdecl.visibility.kind == Visibility.Kind.package_) + sfunc = visibilityToChars(funcdecl.visibility.kind); + else + sfunc = "final"; + .error(funcdecl.loc, "%s `%s` `%s` functions cannot be `abstract`", funcdecl.kind, funcdecl.toPrettyChars, sfunc); + } + + if (funcdecl.isOverride() && !funcdecl.isVirtual() && !funcdecl.isFuncLiteralDeclaration()) + { + Visibility.Kind kind = funcdecl.visible().kind; + if ((kind == Visibility.Kind.private_ || kind == Visibility.Kind.package_) && funcdecl.isMember()) + .error(funcdecl.loc, "%s `%s` `%s` method is not virtual and cannot override", funcdecl.kind, funcdecl.toPrettyChars, visibilityToChars(kind)); + else + .error(funcdecl.loc, "%s `%s` cannot override a non-virtual function", funcdecl.kind, funcdecl.toPrettyChars); + } + + if (funcdecl.isAbstract() && funcdecl.isFinalFunc()) + .error(funcdecl.loc, "%s `%s` cannot be both `final` and `abstract`", funcdecl.kind, funcdecl.toPrettyChars); + + if (funcdecl.printf || funcdecl.scanf) + { + checkPrintfScanfSignature(funcdecl, f, sc); + } + + if (auto id = parent.isInterfaceDeclaration()) + { + funcdecl.storage_class |= STC.abstract_; + if (funcdecl.isCtorDeclaration() || funcdecl.isPostBlitDeclaration() || funcdecl.isDtorDeclaration() || funcdecl.isInvariantDeclaration() || funcdecl.isNewDeclaration() || funcdecl.isDelete()) + .error(funcdecl.loc, "%s `%s` constructors, destructors, postblits, invariants, new and delete functions are not allowed in interface `%s`", funcdecl.kind, funcdecl.toPrettyChars, id.toChars()); + if (funcdecl.fbody && funcdecl.isVirtual()) + .error(funcdecl.loc, "%s `%s` function body only allowed in `final` functions in interface `%s`", funcdecl.kind, funcdecl.toPrettyChars, id.toChars()); + } + + if (UnionDeclaration ud = parent.isUnionDeclaration()) + { + if (funcdecl.isPostBlitDeclaration() || funcdecl.isDtorDeclaration() || funcdecl.isInvariantDeclaration()) + .error(funcdecl.loc, "%s `%s` destructors, postblits and invariants are not allowed in union `%s`", funcdecl.kind, funcdecl.toPrettyChars, ud.toChars()); + } + + if (StructDeclaration sd = parent.isStructDeclaration()) + { + if (funcdecl.isCtorDeclaration()) + { + goto Ldone; + } + } + + if (ClassDeclaration cd = parent.isClassDeclaration()) + { + parent = cd = objc.getParent(funcdecl, cd); + + if (funcdecl.isCtorDeclaration()) + { + goto Ldone; + } + + if (funcdecl.storage_class & STC.abstract_) + cd.isabstract = ThreeState.yes; + + // if static function, do not put in vtbl[] + if (!funcdecl.isVirtual()) + { + //printf("\tnot virtual\n"); + goto Ldone; + } + // Suppress further errors if the return type is an error + if (funcdecl.type.nextOf() == Type.terror) + goto Ldone; + + bool may_override = false; + for (size_t i = 0; i < cd.baseclasses.length; i++) + { + BaseClass* b = (*cd.baseclasses)[i]; + ClassDeclaration cbd = b.type.toBasetype().isClassHandle(); + if (!cbd) + continue; + for (size_t j = 0; j < cbd.vtbl.length; j++) + { + FuncDeclaration f2 = cbd.vtbl[j].isFuncDeclaration(); + if (!f2 || f2.ident != funcdecl.ident) + continue; + if (cbd.parent && cbd.parent.isTemplateInstance()) + { + if (!functionSemantic(f2)) + goto Ldone; + } + may_override = true; + } + } + if (may_override && funcdecl.type.nextOf() is null) + { + /* If same name function exists in base class but 'this' is auto return, + * cannot find index of base class's vtbl[] to override. + */ + .error(funcdecl.loc, "%s `%s` return type inference is not supported if may override base class function", funcdecl.kind, funcdecl.toPrettyChars); + } + + /* Find index of existing function in base class's vtbl[] to override + * (the index will be the same as in cd's current vtbl[]) + */ + int vi = cd.baseClass ? findVtblIndex(funcdecl, cd.baseClass.vtbl[]) : -1; + + bool doesoverride = false; + switch (vi) + { + case -1: + Lintro: + /* Didn't find one, so + * This is an 'introducing' function which gets a new + * slot in the vtbl[]. + */ + + // Verify this doesn't override previous final function + if (cd.baseClass) + { + Dsymbol s = cd.baseClass.search(funcdecl.loc, funcdecl.ident); + if (s) + { + if (auto f2 = s.isFuncDeclaration()) + { + f2 = f2.overloadExactMatch(funcdecl.type); + if (f2 && f2.isFinalFunc() && f2.visible().kind != Visibility.Kind.private_) + .error(funcdecl.loc, "%s `%s` cannot override `final` function `%s`", funcdecl.kind, funcdecl.toPrettyChars, f2.toPrettyChars()); + } + } + } + + /* These quirky conditions mimic what happens when virtual + inheritance is implemented by producing a virtual base table + with offsets to each of the virtual bases. + */ + if (target.cpp.splitVBasetable && cd.classKind == ClassKind.cpp && + cd.baseClass && cd.baseClass.vtbl.length) + { + /* if overriding an interface function, then this is not + * introducing and don't put it in the class vtbl[] + */ + funcdecl.interfaceVirtual = overrideInterface(funcdecl); + if (funcdecl.interfaceVirtual) + { + //printf("\tinterface function %s\n", toChars()); + cd.vtblFinal.push(funcdecl); + goto Linterfaces; + } + } + + if (funcdecl.isFinalFunc()) + { + // Don't check here, as it may override an interface function + //if (isOverride()) + // error("is marked as override, but does not override any function"); + cd.vtblFinal.push(funcdecl); + } + else + { + //printf("\tintroducing function %s\n", funcdecl.toChars()); + funcdecl.isIntroducing = true; + if (cd.classKind == ClassKind.cpp && target.cpp.reverseOverloads) + { + /* Overloaded functions with same name are grouped and in reverse order. + * Search for first function of overload group, and insert + * funcdecl into vtbl[] immediately before it. + */ + funcdecl.vtblIndex = cast(int)cd.vtbl.length; + bool found; + foreach (const i, s; cd.vtbl) + { + if (found) + // the rest get shifted forward + ++s.isFuncDeclaration().vtblIndex; + else if (s.ident == funcdecl.ident && s.parent == parent) + { + // found first function of overload group + funcdecl.vtblIndex = cast(int)i; + found = true; + ++s.isFuncDeclaration().vtblIndex; + } + } + cd.vtbl.insert(funcdecl.vtblIndex, funcdecl); + + debug foreach (const i, s; cd.vtbl) + { + // a C++ dtor gets its vtblIndex later (and might even be added twice to the vtbl), + // e.g. when compiling druntime with a debug compiler, namely with core.stdcpp.exception. + if (auto fd = s.isFuncDeclaration()) + assert(fd.vtblIndex == i || + (cd.classKind == ClassKind.cpp && fd.isDtorDeclaration) || + funcdecl.parent.isInterfaceDeclaration); // interface functions can be in multiple vtbls + } + } + else + { + // Append to end of vtbl[] + vi = cast(int)cd.vtbl.length; + cd.vtbl.push(funcdecl); + funcdecl.vtblIndex = vi; + } + } + break; + + case -2: + // can't determine because of forward references + funcdecl.errors = true; + return; + + default: + { + if (vi >= cd.vtbl.length) + { + /* the derived class cd doesn't have its vtbl[] allocated yet. + * https://issues.dlang.org/show_bug.cgi?id=21008 + */ + .error(funcdecl.loc, "%s `%s` circular reference to class `%s`", funcdecl.kind, funcdecl.toPrettyChars, cd.toChars()); + funcdecl.errors = true; + return; + } + FuncDeclaration fdv = cd.baseClass.vtbl[vi].isFuncDeclaration(); + FuncDeclaration fdc = cd.vtbl[vi].isFuncDeclaration(); + // This function is covariant with fdv + + if (fdc == funcdecl) + { + doesoverride = true; + break; + } + + auto vtf = getFunctionType(fdv); + if (vtf.trust > TRUST.system && f.trust == TRUST.system) + .error(funcdecl.loc, "%s `%s` cannot override `@safe` method `%s` with a `@system` attribute", funcdecl.kind, funcdecl.toPrettyChars, + fdv.toPrettyChars); + + if (fdc.toParent() == parent) + { + //printf("vi = %d,\tthis = %p %s %s @ [%s]\n\tfdc = %p %s %s @ [%s]\n\tfdv = %p %s %s @ [%s]\n", + // vi, this, this.toChars(), this.type.toChars(), this.loc.toChars(), + // fdc, fdc .toChars(), fdc .type.toChars(), fdc .loc.toChars(), + // fdv, fdv .toChars(), fdv .type.toChars(), fdv .loc.toChars()); + + // fdc overrides fdv exactly, then this introduces new function. + if (fdc.type.mod == fdv.type.mod && funcdecl.type.mod != fdv.type.mod) + goto Lintro; + } + + if (fdv.isDeprecated && !funcdecl.isDeprecated) + deprecation(funcdecl.loc, "`%s` is overriding the deprecated method `%s`", + funcdecl.toPrettyChars, fdv.toPrettyChars); + + // This function overrides fdv + if (fdv.isFinalFunc()) + .error(funcdecl.loc, "%s `%s` cannot override `final` function `%s`", funcdecl.kind, funcdecl.toPrettyChars, fdv.toPrettyChars()); + + if (!funcdecl.isOverride()) + { + if (fdv.isFuture()) + { + deprecation(funcdecl.loc, "`@__future` base class method `%s` is being overridden by `%s`; rename the latter", fdv.toPrettyChars(), funcdecl.toPrettyChars()); + // Treat 'this' as an introducing function, giving it a separate hierarchy in the vtbl[] + goto Lintro; + } + else + { + // https://issues.dlang.org/show_bug.cgi?id=17349 + error(funcdecl.loc, "cannot implicitly override base class method `%s` with `%s`; add `override` attribute", + fdv.toPrettyChars(), funcdecl.toPrettyChars()); + } + } + doesoverride = true; + if (fdc.toParent() == parent) + { + // If both are mixins, or both are not, then error. + // If either is not, the one that is not overrides the other. + bool thismixin = funcdecl.parent.isClassDeclaration() !is null; + bool fdcmixin = fdc.parent.isClassDeclaration() !is null; + if (thismixin == fdcmixin) + { + .error(funcdecl.loc, "%s `%s` multiple overrides of same function", funcdecl.kind, funcdecl.toPrettyChars); + } + /* + * https://issues.dlang.org/show_bug.cgi?id=711 + * + * If an overriding method is introduced through a mixin, + * we need to update the vtbl so that both methods are + * present. + */ + else if (thismixin) + { + /* if the mixin introduced the overriding method, then reintroduce it + * in the vtbl. The initial entry for the mixined method + * will be updated at the end of the enclosing `if` block + * to point to the current (non-mixined) function. + */ + auto vitmp = cast(int)cd.vtbl.length; + cd.vtbl.push(fdc); + fdc.vtblIndex = vitmp; + } + else if (fdcmixin) + { + /* if the current overriding function is coming from a + * mixined block, then push the current function in the + * vtbl, but keep the previous (non-mixined) function as + * the overriding one. + */ + auto vitmp = cast(int)cd.vtbl.length; + cd.vtbl.push(funcdecl); + funcdecl.vtblIndex = vitmp; + break; + } + else // fdc overrides fdv + { + // this doesn't override any function + break; + } + } + cd.vtbl[vi] = funcdecl; + funcdecl.vtblIndex = vi; + + /* Remember which functions this overrides + */ + funcdecl.foverrides.push(fdv); + + /* This works by whenever this function is called, + * it actually returns tintro, which gets dynamically + * cast to type. But we know that tintro is a base + * of type, so we could optimize it by not doing a + * dynamic cast, but just subtracting the isBaseOf() + * offset if the value is != null. + */ + + if (fdv.tintro) + funcdecl.tintro = fdv.tintro; + else if (!funcdecl.type.equals(fdv.type)) + { + auto tnext = funcdecl.type.nextOf(); + if (auto handle = tnext.isClassHandle()) + { + if (handle.semanticRun < PASS.semanticdone && !handle.isBaseInfoComplete()) + handle.dsymbolSemantic(null); + } + /* Only need to have a tintro if the vptr + * offsets differ + */ + int offset; + if (fdv.type.nextOf().isBaseOf(tnext, &offset)) + { + funcdecl.tintro = fdv.type; + } + } + break; + } + } + + /* Go through all the interface bases. + * If this function is covariant with any members of those interface + * functions, set the tintro. + */ + Linterfaces: + bool foundVtblMatch = false; + + for (ClassDeclaration bcd = cd; !foundVtblMatch && bcd; bcd = bcd.baseClass) + { + foreach (b; bcd.interfaces) + { + vi = findVtblIndex(funcdecl, b.sym.vtbl[]); + switch (vi) + { + case -1: + break; + + case -2: + // can't determine because of forward references + funcdecl.errors = true; + return; + + default: + { + auto fdv = cast(FuncDeclaration)b.sym.vtbl[vi]; + Type ti = null; + + foundVtblMatch = true; + + /* Remember which functions this overrides + */ + funcdecl.foverrides.push(fdv); + + if (fdv.tintro) + ti = fdv.tintro; + else if (!funcdecl.type.equals(fdv.type)) + { + /* Only need to have a tintro if the vptr + * offsets differ + */ + int offset; + if (fdv.type.nextOf().isBaseOf(funcdecl.type.nextOf(), &offset)) + { + ti = fdv.type; + } + } + if (ti) + { + if (funcdecl.tintro) + { + if (!funcdecl.tintro.nextOf().equals(ti.nextOf()) && !funcdecl.tintro.nextOf().isBaseOf(ti.nextOf(), null) && !ti.nextOf().isBaseOf(funcdecl.tintro.nextOf(), null)) + { + .error(funcdecl.loc, "%s `%s` incompatible covariant types `%s` and `%s`", funcdecl.kind, funcdecl.toPrettyChars, funcdecl.tintro.toChars(), ti.toChars()); + } + } + else + { + funcdecl.tintro = ti; + } + } + } + } + } + } + if (foundVtblMatch) + { + goto L2; + } + + if (!doesoverride && funcdecl.isOverride() && (funcdecl.type.nextOf() || !may_override)) + { + BaseClass* bc = null; + Dsymbol s = null; + for (size_t i = 0; i < cd.baseclasses.length; i++) + { + bc = (*cd.baseclasses)[i]; + s = bc.sym.search_correct(funcdecl.ident); + if (s) + break; + } + + if (s) + { + HdrGenState hgs; + OutBuffer buf; + + auto fd = s.isFuncDeclaration(); + functionToBufferFull(cast(TypeFunction)(funcdecl.type), buf, + new Identifier(funcdecl.toPrettyChars()), hgs, null); + const(char)* funcdeclToChars = buf.peekChars(); + + if (fd) + { + OutBuffer buf1; + + if (fd.ident == funcdecl.ident) + hgs.fullQual = true; + + // https://issues.dlang.org/show_bug.cgi?id=23745 + // If the potentially overridden function contains errors, + // inform the user to fix that one first + if (fd.errors) + { + error(funcdecl.loc, "function `%s` does not override any function, did you mean to override `%s`?", + funcdecl.toChars(), fd.toPrettyChars()); + errorSupplemental(fd.loc, "Function `%s` contains errors in its declaration, therefore it cannot be correctly overridden", + fd.toPrettyChars()); + } + else + { + functionToBufferFull(cast(TypeFunction)(fd.type), buf1, + new Identifier(fd.toPrettyChars()), hgs, null); + + error(funcdecl.loc, "function `%s` does not override any function, did you mean to override `%s`?", + funcdeclToChars, buf1.peekChars()); + } + } + else + { + error(funcdecl.loc, "function `%s` does not override any function, did you mean to override %s `%s`?", + funcdeclToChars, s.kind, s.toPrettyChars()); + errorSupplemental(funcdecl.loc, "Functions are the only declarations that may be overridden"); + } + } + else + .error(funcdecl.loc, "%s `%s` does not override any function", funcdecl.kind, funcdecl.toPrettyChars); + } + + L2: + objc.setSelector(funcdecl, sc); + objc.checkLinkage(funcdecl); + objc.addToClassMethodList(funcdecl, cd); + objc.setAsOptional(funcdecl, sc); + + /* Go through all the interface bases. + * Disallow overriding any final functions in the interface(s). + */ + foreach (b; cd.interfaces) + { + if (b.sym) + { + if (auto s = search_function(b.sym, funcdecl.ident)) + { + if (auto f2 = s.isFuncDeclaration()) + { + f2 = f2.overloadExactMatch(funcdecl.type); + if (f2 && f2.isFinalFunc() && f2.visible().kind != Visibility.Kind.private_) + .error(funcdecl.loc, "%s `%s` cannot override `final` function `%s.%s`", funcdecl.kind, funcdecl.toPrettyChars, b.sym.toChars(), f2.toPrettyChars()); + } + } + } + } + + if (funcdecl.isOverride) + { + if (funcdecl.storage_class & STC.disable) + deprecation(funcdecl.loc, + "`%s` cannot be annotated with `@disable` because it is overriding a function in the base class", + funcdecl.toPrettyChars); + + if (funcdecl.isDeprecated && !(funcdecl.foverrides.length && funcdecl.foverrides[0].isDeprecated)) + deprecation(funcdecl.loc, + "`%s` cannot be marked as `deprecated` because it is overriding a function in the base class", + funcdecl.toPrettyChars); + } + + } + else if (funcdecl.isOverride() && !parent.isTemplateInstance()) + .error(funcdecl.loc, "%s `%s` `override` only applies to class member functions", funcdecl.kind, funcdecl.toPrettyChars); + + if (auto ti = parent.isTemplateInstance) + { + objc.setSelector(funcdecl, sc); + objc.setAsOptional(funcdecl, sc); + } + + objc.validateSelector(funcdecl); + objc.validateOptional(funcdecl); + // Reflect this.type to f because it could be changed by findVtblIndex + f = funcdecl.type.toTypeFunction(); + +Ldone: + if (!funcdecl.fbody && !funcdecl.allowsContractWithoutBody()) + .error(funcdecl.loc, "%s `%s` `in` and `out` contracts can only appear without a body when they are virtual interface functions or abstract", funcdecl.kind, funcdecl.toPrettyChars); + + /* Do not allow template instances to add virtual functions + * to a class. + */ + if (funcdecl.isVirtual()) + { + if (auto ti = parent.isTemplateInstance()) + { + // Take care of nested templates + while (1) + { + TemplateInstance ti2 = ti.tempdecl.parent.isTemplateInstance(); + if (!ti2) + break; + ti = ti2; + } + + // If it's a member template + ClassDeclaration cd = ti.tempdecl.isClassMember(); + if (cd) + { + .error(funcdecl.loc, "%s `%s` cannot use template to add virtual function to class `%s`", funcdecl.kind, funcdecl.toPrettyChars, cd.toChars()); + } + } + } + + funcdecl.checkMain(); // Check main() parameters and return type + + /* Purity and safety can be inferred for some functions by examining + * the function body. + */ + if (funcdecl.canInferAttributes(sc)) + funcdecl.initInferAttributes(); + + funcdecl.semanticRun = PASS.semanticdone; + + /* Save scope for possible later use (if we need the + * function internals) + */ + funcdecl._scope = sc.copy(); + funcdecl._scope.setNoFree(); + + __gshared bool printedMain = false; // semantic might run more than once + if (global.params.v.verbose && !printedMain) + { + const(char)* type = funcdecl.isMain() ? "main" : funcdecl.isWinMain() ? "winmain" : funcdecl.isDllMain() ? "dllmain" : cast(const(char)*)null; + Module mod = sc._module; + + if (type && mod) + { + printedMain = true; + auto name = mod.srcfile.toChars(); + auto path = FileName.searchPath(global.path, name, true); + message("entry %-10s\t%s", type, path ? path : name); + } + } + + if (funcdecl.fbody && sc._module.isRoot() && + (funcdecl.isMain() || funcdecl.isWinMain() || funcdecl.isDllMain() || funcdecl.isCMain())) + global.hasMainFunction = true; + + if (funcdecl.fbody && funcdecl.isMain() && sc._module.isRoot()) + { + // check if `_d_cmain` is defined + bool cmainTemplateExists() + { + Dsymbol pscopesym; + auto rootSymbol = sc.search(funcdecl.loc, Id.empty, pscopesym); + if (auto moduleSymbol = rootSymbol.search(funcdecl.loc, Id.object)) + if (moduleSymbol.search(funcdecl.loc, Id.CMain)) + return true; + + return false; + } + + // Only mixin `_d_cmain` if it is defined + if (cmainTemplateExists()) + { + // add `mixin _d_cmain!();` to the declaring module + auto tqual = new TypeIdentifier(funcdecl.loc, Id.CMain); + auto tm = new TemplateMixin(funcdecl.loc, null, tqual, null); + sc._module.members.push(tm); + } + } + + assert(funcdecl.type.ty != Terror || funcdecl.errors); + + // semantic for parameters' UDAs + foreach (i, param; f.parameterList) + { + if (param && param.userAttribDecl) + param.userAttribDecl.dsymbolSemantic(sc); + } +} + + /**************************************************** * Resolve forward reference of function signature - * parameter types, return type, and attributes. @@ -217,3 +1194,176 @@ extern (D) void declareThis(FuncDeclaration fd, Scope* sc) if (ad) fd.objc.selectorParameter = .objc.createSelectorParameter(fd, sc); } + +/**************************************************** + * Check that this function type is properly resolved. + * If not, report "forward reference error" and return true. + */ +extern (D) bool checkForwardRef(FuncDeclaration fd, const ref Loc loc) +{ + if (!functionSemantic(fd)) + return true; + + /* No deco means the functionSemantic() call could not resolve + * forward referenes in the type of this function. + */ + if (!fd.type.deco) + { + bool inSemantic3 = (fd.inferRetType && fd.semanticRun >= PASS.semantic3); + .error(loc, "forward reference to %s`%s`", + (inSemantic3 ? "inferred return type of function " : "").ptr, + fd.toChars()); + return true; + } + return false; +} + +/************************************************* + * Find index of function in vtbl[0..length] that + * this function overrides. + * Prefer an exact match to a covariant one. + * Params: + * fd = function + * vtbl = vtable to use + * Returns: + * -1 didn't find one + * -2 can't determine because of forward references + */ +int findVtblIndex(FuncDeclaration fd, Dsymbol[] vtbl) +{ + //printf("findVtblIndex() %s\n", toChars()); + import dmd.typesem : covariant; + + FuncDeclaration mismatch = null; + StorageClass mismatchstc = 0; + int mismatchvi = -1; + int exactvi = -1; + int bestvi = -1; + for (int vi = 0; vi < cast(int)vtbl.length; vi++) + { + FuncDeclaration fdv = vtbl[vi].isFuncDeclaration(); + if (fdv && fdv.ident == fd.ident) + { + if (fd.type.equals(fdv.type)) // if exact match + { + if (fdv.parent.isClassDeclaration()) + { + if (fdv.isFuture()) + { + bestvi = vi; + continue; // keep looking + } + return vi; // no need to look further + } + + if (exactvi >= 0) + { + .error(fd.loc, "%s `%s` cannot determine overridden function", fd.kind, fd.toPrettyChars); + return exactvi; + } + exactvi = vi; + bestvi = vi; + continue; + } + + StorageClass stc = 0; + const cov = fd.type.covariant(fdv.type, &stc); + //printf("\tbaseclass cov = %d\n", cov); + final switch (cov) + { + case Covariant.distinct: + // types are distinct + break; + + case Covariant.yes: + bestvi = vi; // covariant, but not identical + break; + // keep looking for an exact match + + case Covariant.no: + mismatchvi = vi; + mismatchstc = stc; + mismatch = fdv; // overrides, but is not covariant + break; + // keep looking for an exact match + + case Covariant.fwdref: + return -2; // forward references + } + } + } + if (fd._linkage == LINK.cpp && bestvi != -1) + { + StorageClass stc = 0; + FuncDeclaration fdv = vtbl[bestvi].isFuncDeclaration(); + assert(fdv && fdv.ident == fd.ident); + if (fd.type.covariant(fdv.type, &stc, /*cppCovariant=*/true) == Covariant.no) + { + /* https://issues.dlang.org/show_bug.cgi?id=22351 + * Under D rules, `type` and `fdv.type` are covariant, but under C++ rules, they are not. + * For now, continue to allow D covariant rules to apply when `override` has been used, + * but issue a deprecation warning that this behaviour will change in the future. + * Otherwise, follow the C++ covariant rules, which will create a new vtable entry. + */ + if (fd.isOverride()) + { + /* @@@DEPRECATED_2.110@@@ + * After deprecation period has ended, be sure to remove this entire `LINK.cpp` branch, + * but also the `cppCovariant` parameter from Type.covariant, and update the function + * so that both `LINK.cpp` covariant conditions within are always checked. + */ + .deprecation(fd.loc, "overriding `extern(C++)` function `%s%s` with `const` qualified function `%s%s%s` is deprecated", + fdv.toPrettyChars(), fdv.type.toTypeFunction().parameterList.parametersTypeToChars(), + fd.toPrettyChars(), fd.type.toTypeFunction().parameterList.parametersTypeToChars(), fd.type.modToChars()); + + const char* where = fd.type.isNaked() ? "parameters" : "type"; + deprecationSupplemental(fd.loc, "Either remove `override`, or adjust the `const` qualifiers of the " + ~ "overriding function %s", where); + } + else + { + // Treat as if Covariant.no + mismatchvi = bestvi; + mismatchstc = stc; + mismatch = fdv; + bestvi = -1; + } + } + } + if (bestvi == -1 && mismatch) + { + //type.print(); + //mismatch.type.print(); + //printf("%s %s\n", type.deco, mismatch.type.deco); + //printf("stc = %llx\n", mismatchstc); + if (mismatchstc) + { + // Fix it by modifying the type to add the storage classes + fd.type = fd.type.addStorageClass(mismatchstc); + bestvi = mismatchvi; + } + } + return bestvi; +} + +/********************************* + * If function is a function in a base class, + * return that base class. + * Params: + * fd = function + * Returns: + * base class if overriding, null if not + */ +BaseClass* overrideInterface(FuncDeclaration fd) +{ + for (ClassDeclaration cd = fd.toParent2().isClassDeclaration(); cd; cd = cd.baseClass) + { + foreach (b; cd.interfaces) + { + auto v = findVtblIndex(fd, b.sym.vtbl[]); + if (v >= 0) + return b; + } + } + return null; +} diff --git a/gcc/d/dmd/hdrgen.d b/gcc/d/dmd/hdrgen.d index 030153c91da2..e4cbcc5f0b9a 100644 --- a/gcc/d/dmd/hdrgen.d +++ b/gcc/d/dmd/hdrgen.d @@ -50,6 +50,7 @@ import dmd.root.string; import dmd.statement; import dmd.staticassert; import dmd.tokens; +import dmd.typesem; import dmd.visitor; struct HdrGenState @@ -1552,7 +1553,7 @@ void toCBuffer(Dsymbol s, ref OutBuffer buf, ref HdrGenState hgs) buf.writeByte('}'); buf.writenl(); - if (!hgs.importcHdr) + if (!hgs.importcHdr || !d.ident) return; /* C enums get their members inserted into the symbol table of the enum declaration. diff --git a/gcc/d/dmd/initsem.d b/gcc/d/dmd/initsem.d index 5fe3b9325993..79d7902fc9b4 100644 --- a/gcc/d/dmd/initsem.d +++ b/gcc/d/dmd/initsem.d @@ -30,6 +30,7 @@ import dmd.errors; import dmd.expression; import dmd.expressionsem; import dmd.func; +import dmd.funcsem; import dmd.globals; import dmd.hdrgen; import dmd.id; @@ -59,36 +60,33 @@ Expression toAssocArrayLiteral(ArrayInitializer ai) { //printf("ArrayInitializer::toAssocArrayInitializer(%s)\n", ai.toChars()); //static int i; if (++i == 2) assert(0); - const dim = ai.value.length; - if (!dim) - { - error(ai.loc, "invalid associative array initializer `%s`, use `null` instead", - toChars(ai)); - return ErrorExp.get(); - } + auto no(const char* format, Initializer i) { error(i.loc, format, toChars(i)); return ErrorExp.get(); } - Expression e; - auto keys = new Expressions(dim); + + const dim = ai.value.length; + if (!dim) + return no("invalid associative array initializer `%s`, use `null` instead", ai); + + auto keys = new Expressions(dim); auto values = new Expressions(dim); - for (size_t i = 0; i < dim; i++) + foreach (i, iz; ai.value[]) { - Initializer iz = ai.value[i]; assert(iz); - e = iz.initializerToExpression(); - if (!e) + auto ev = iz.initializerToExpression(); + if (!ev) return no("invalid value `%s` in initializer", iz); - (*values)[i] = e; - e = ai.index[i]; - if (!e) + (*values)[i] = ev; + + auto ei = ai.index[i]; + if (!ei) return no("missing key for value `%s` in initializer", iz); - (*keys)[i] = e; + (*keys)[i] = ei; } - e = new AssocArrayLiteralExp(ai.loc, keys, values); - return e; + return new AssocArrayLiteralExp(ai.loc, keys, values); } /****************************************** @@ -138,8 +136,12 @@ extern(C++) Initializer initializerSemantic(Initializer init, Scope* sc, ref Typ /* This works by replacing the StructInitializer with an ExpInitializer. */ t = t.toBasetype(); - if (t.ty == Tsarray && t.nextOf().toBasetype().ty == Tstruct) - t = t.nextOf().toBasetype(); + if (auto tsa = t.isTypeSArray()) + { + auto ts = tsa.nextOf().toBasetype().isTypeStruct(); + if (ts) + t = ts; + } if (auto ts = t.isTypeStruct()) { StructDeclaration sd = ts.sym; @@ -154,16 +156,17 @@ extern(C++) Initializer initializerSemantic(Initializer init, Scope* sc, ref Typ if (sd.sizeok != Sizeok.done) return err(); - Expression getExp(size_t j, Type fieldType) - { - // Convert initializer to Expression `ex` - auto tm = fieldType.addMod(t.mod); - auto iz = i.value[j].initializerSemantic(sc, tm, needInterpret); - auto ex = iz.initializerToExpression(null, (sc.flags & SCOPE.Cfile) != 0); - if (ex.op != EXP.error) - i.value[j] = iz; - return ex; - } + Expression getExp(size_t j, Type fieldType) + { + // Convert initializer to Expression `ex` + auto tm = fieldType.addMod(t.mod); + auto iz = i.value[j].initializerSemantic(sc, tm, needInterpret); + auto ex = iz.initializerToExpression(null, (sc.flags & SCOPE.Cfile) != 0); + if (ex.op != EXP.error) + i.value[j] = iz; + return ex; + } + auto elements = resolveStructLiteralNamedArgs(sd, t, sc, i.loc, i.field[], &getExp, (size_t j) => i.value[j].loc); if (!elements) return err(); @@ -232,17 +235,19 @@ extern(C++) Initializer initializerSemantic(Initializer init, Scope* sc, ref Typ auto ei = new ExpInitializer(e.loc, e); return ei.initializerSemantic(sc, t, needInterpret); } + case Tpointer: - if (t.nextOf().ty != Tfunction) - break; - goto default; + if (t.nextOf().isTypeFunction()) + goto default; + break; + default: error(i.loc, "cannot use array to initialize `%s`", t.toChars()); return err(); } i.type = t; length = 0; - for (size_t j = 0; j < i.index.length; j++) + for (size_t j = 0; j < i.index.length; j++) // don't replace with foreach; j is modified { Expression idx = i.index[j]; if (idx) @@ -277,9 +282,8 @@ extern(C++) Initializer initializerSemantic(Initializer init, Scope* sc, ref Typ TupleExp te = ei.exp.isTupleExp(); i.index.remove(j); i.value.remove(j); - for (size_t k = 0; k < te.exps.length; ++k) + foreach (k, e; (*te.exps)[]) { - Expression e = (*te.exps)[k]; i.index.insert(j + k, cast(Expression)null); i.value.insert(j + k, new ExpInitializer(e.loc, e)); } @@ -290,7 +294,7 @@ extern(C++) Initializer initializerSemantic(Initializer init, Scope* sc, ref Typ { i.value[j] = val; } - length++; + ++length; if (length == 0) { error(i.loc, "array dimension overflow"); @@ -311,7 +315,7 @@ extern(C++) Initializer initializerSemantic(Initializer init, Scope* sc, ref Typ } else { - uinteger_t edim = tsa.dim.toInteger(); + ulong edim = tsa.dim.toInteger(); if (i.dim > edim) { error(i.loc, "array initializer has %u elements, but array length is %llu", i.dim, edim); @@ -347,7 +351,7 @@ extern(C++) Initializer initializerSemantic(Initializer init, Scope* sc, ref Typ sc = sc.endCTFE(); if (i.exp.op == EXP.error) return err(); - uint olderrors = global.errors; + const olderrors = global.errors; /* ImportC: convert arrays to pointers, functions to pointers to functions */ @@ -1170,7 +1174,7 @@ Initializer inferType(Initializer init, Scope* sc) bool hasOverloads; if (auto f = isFuncAddress(init.exp, &hasOverloads)) { - if (f.checkForwardRef(init.loc)) + if (checkForwardRef(f, init.loc)) { return new ErrorInitializer(); } diff --git a/gcc/d/dmd/mtype.d b/gcc/d/dmd/mtype.d index 276f209d4aa5..c46f5600c809 100644 --- a/gcc/d/dmd/mtype.d +++ b/gcc/d/dmd/mtype.d @@ -52,6 +52,12 @@ enum LOGDEFAULTINIT = 0; // log ::defaultInit() enum SIZE_INVALID = (~cast(uinteger_t)0); // error return from size() functions +static if (__VERSION__ < 2095) +{ + // Fix linker errors when building with older compilers. + // See: https://issues.dlang.org/show_bug.cgi?id=21299 + private alias StringValueType = StringValue!Type; +} /*************************** * Return !=0 if modfrom can be implicitly converted to modto @@ -299,7 +305,7 @@ extern (C++) abstract class Type : ASTNode Type swto; // MODFlags.shared_ | MODFlags.wild Type swcto; // MODFlags.shared_ | MODFlags.wildconst } - private Mcache* mcache; + Mcache* mcache; Type pto; // merged pointer to this type Type rto; // reference to this type @@ -440,7 +446,7 @@ extern (C++) abstract class Type : ASTNode final bool equivalent(Type t) { - return immutableOf().equals(t.immutableOf()); + return immutableOf(this).equals(t.immutableOf()); } // kludge for template.isType() @@ -785,255 +791,6 @@ extern (C++) abstract class Type : ASTNode return t; } - /******************************** - * Convert to 'const'. - */ - final Type constOf() - { - //printf("Type::constOf() %p %s\n", this, toChars()); - if (mod == MODFlags.const_) - return this; - if (mcache && mcache.cto) - { - assert(mcache.cto.mod == MODFlags.const_); - return mcache.cto; - } - Type t = makeConst(); - t = t.merge(); - t.fixTo(this); - //printf("-Type::constOf() %p %s\n", t, t.toChars()); - return t; - } - - /******************************** - * Convert to 'immutable'. - */ - final Type immutableOf() - { - //printf("Type::immutableOf() %p %s\n", this, toChars()); - if (isImmutable()) - return this; - if (mcache && mcache.ito) - { - assert(mcache.ito.isImmutable()); - return mcache.ito; - } - Type t = makeImmutable(); - t = t.merge(); - t.fixTo(this); - //printf("\t%p\n", t); - return t; - } - - /******************************** - * Make type mutable. - */ - final Type mutableOf() - { - //printf("Type::mutableOf() %p, %s\n", this, toChars()); - Type t = this; - if (isImmutable()) - { - getMcache(); - t = mcache.ito; // immutable => naked - assert(!t || (t.isMutable() && !t.isShared())); - } - else if (isConst()) - { - getMcache(); - if (isShared()) - { - if (isWild()) - t = mcache.swcto; // shared wild const -> shared - else - t = mcache.sto; // shared const => shared - } - else - { - if (isWild()) - t = mcache.wcto; // wild const -> naked - else - t = mcache.cto; // const => naked - } - assert(!t || t.isMutable()); - } - else if (isWild()) - { - getMcache(); - if (isShared()) - t = mcache.sto; // shared wild => shared - else - t = mcache.wto; // wild => naked - assert(!t || t.isMutable()); - } - if (!t) - { - t = makeMutable(); - t = t.merge(); - t.fixTo(this); - } - else - t = t.merge(); - assert(t.isMutable()); - return t; - } - - final Type sharedOf() - { - //printf("Type::sharedOf() %p, %s\n", this, toChars()); - if (mod == MODFlags.shared_) - return this; - if (mcache && mcache.sto) - { - assert(mcache.sto.mod == MODFlags.shared_); - return mcache.sto; - } - Type t = makeShared(); - t = t.merge(); - t.fixTo(this); - //printf("\t%p\n", t); - return t; - } - - final Type sharedConstOf() - { - //printf("Type::sharedConstOf() %p, %s\n", this, toChars()); - if (mod == (MODFlags.shared_ | MODFlags.const_)) - return this; - if (mcache && mcache.scto) - { - assert(mcache.scto.mod == (MODFlags.shared_ | MODFlags.const_)); - return mcache.scto; - } - Type t = makeSharedConst(); - t = t.merge(); - t.fixTo(this); - //printf("\t%p\n", t); - return t; - } - - /******************************** - * Make type unshared. - * 0 => 0 - * const => const - * immutable => immutable - * shared => 0 - * shared const => const - * wild => wild - * wild const => wild const - * shared wild => wild - * shared wild const => wild const - */ - final Type unSharedOf() - { - //printf("Type::unSharedOf() %p, %s\n", this, toChars()); - Type t = this; - - if (isShared()) - { - getMcache(); - if (isWild()) - { - if (isConst()) - t = mcache.wcto; // shared wild const => wild const - else - t = mcache.wto; // shared wild => wild - } - else - { - if (isConst()) - t = mcache.cto; // shared const => const - else - t = mcache.sto; // shared => naked - } - assert(!t || !t.isShared()); - } - - if (!t) - { - t = this.nullAttributes(); - t.mod = mod & ~MODFlags.shared_; - t.ctype = ctype; - t = t.merge(); - t.fixTo(this); - } - else - t = t.merge(); - assert(!t.isShared()); - return t; - } - - /******************************** - * Convert to 'wild'. - */ - final Type wildOf() - { - //printf("Type::wildOf() %p %s\n", this, toChars()); - if (mod == MODFlags.wild) - return this; - if (mcache && mcache.wto) - { - assert(mcache.wto.mod == MODFlags.wild); - return mcache.wto; - } - Type t = makeWild(); - t = t.merge(); - t.fixTo(this); - //printf("\t%p %s\n", t, t.toChars()); - return t; - } - - final Type wildConstOf() - { - //printf("Type::wildConstOf() %p %s\n", this, toChars()); - if (mod == MODFlags.wildconst) - return this; - if (mcache && mcache.wcto) - { - assert(mcache.wcto.mod == MODFlags.wildconst); - return mcache.wcto; - } - Type t = makeWildConst(); - t = t.merge(); - t.fixTo(this); - //printf("\t%p %s\n", t, t.toChars()); - return t; - } - - final Type sharedWildOf() - { - //printf("Type::sharedWildOf() %p, %s\n", this, toChars()); - if (mod == (MODFlags.shared_ | MODFlags.wild)) - return this; - if (mcache && mcache.swto) - { - assert(mcache.swto.mod == (MODFlags.shared_ | MODFlags.wild)); - return mcache.swto; - } - Type t = makeSharedWild(); - t = t.merge(); - t.fixTo(this); - //printf("\t%p %s\n", t, t.toChars()); - return t; - } - - final Type sharedWildConstOf() - { - //printf("Type::sharedWildConstOf() %p, %s\n", this, toChars()); - if (mod == (MODFlags.shared_ | MODFlags.wildconst)) - return this; - if (mcache && mcache.swcto) - { - assert(mcache.swcto.mod == (MODFlags.shared_ | MODFlags.wildconst)); - return mcache.swcto; - } - Type t = makeSharedWildConst(); - t = t.merge(); - t.fixTo(this); - //printf("\t%p %s\n", t, t.toChars()); - return t; - } - /********************************** * For our new type 'this', which is type-constructed from t, * fill in the cto, ito, sto, scto, wto shortcuts. @@ -1434,56 +1191,6 @@ extern (C++) abstract class Type : ASTNode return t; } - /************************************ - * Apply MODxxxx bits to existing type. - */ - final Type castMod(MOD mod) - { - Type t; - switch (mod) - { - case 0: - t = unSharedOf().mutableOf(); - break; - - case MODFlags.const_: - t = unSharedOf().constOf(); - break; - - case MODFlags.wild: - t = unSharedOf().wildOf(); - break; - - case MODFlags.wildconst: - t = unSharedOf().wildConstOf(); - break; - - case MODFlags.shared_: - t = mutableOf().sharedOf(); - break; - - case MODFlags.shared_ | MODFlags.const_: - t = sharedConstOf(); - break; - - case MODFlags.shared_ | MODFlags.wild: - t = sharedWildOf(); - break; - - case MODFlags.shared_ | MODFlags.wildconst: - t = sharedWildConstOf(); - break; - - case MODFlags.immutable_: - t = immutableOf(); - break; - - default: - assert(0); - } - return t; - } - /************************************ * Add MODxxxx bits to existing type. * We're adding, not replacing, so adding const to @@ -1506,16 +1213,16 @@ extern (C++) abstract class Type : ASTNode if (isShared()) { if (isWild()) - t = sharedWildConstOf(); + t = this.sharedWildConstOf(); else - t = sharedConstOf(); + t = this.sharedConstOf(); } else { - if (isWild()) - t = wildConstOf(); + if (this.isWild()) + t = this.wildConstOf(); else - t = constOf(); + t = t.constOf(); } break; @@ -1523,63 +1230,63 @@ extern (C++) abstract class Type : ASTNode if (isShared()) { if (isConst()) - t = sharedWildConstOf(); + t = this.sharedWildConstOf(); else - t = sharedWildOf(); + t = this.sharedWildOf(); } else { if (isConst()) - t = wildConstOf(); + t = this.wildConstOf(); else - t = wildOf(); + t = this.wildOf(); } break; case MODFlags.wildconst: if (isShared()) - t = sharedWildConstOf(); + t = this.sharedWildConstOf(); else - t = wildConstOf(); + t = this.wildConstOf(); break; case MODFlags.shared_: if (isWild()) { if (isConst()) - t = sharedWildConstOf(); + t = this.sharedWildConstOf(); else - t = sharedWildOf(); + t = this.sharedWildOf(); } else { if (isConst()) - t = sharedConstOf(); + t = this.sharedConstOf(); else - t = sharedOf(); + t = this.sharedOf(); } break; case MODFlags.shared_ | MODFlags.const_: if (isWild()) - t = sharedWildConstOf(); + t = this.sharedWildConstOf(); else - t = sharedConstOf(); + t = this.sharedConstOf(); break; case MODFlags.shared_ | MODFlags.wild: if (isConst()) - t = sharedWildConstOf(); + t = this.sharedWildConstOf(); else - t = sharedWildOf(); + t = this.sharedWildOf(); break; case MODFlags.shared_ | MODFlags.wildconst: - t = sharedWildConstOf(); + t = this.sharedWildConstOf(); break; case MODFlags.immutable_: - t = immutableOf(); + t = this.immutableOf(); break; default: @@ -1990,7 +1697,7 @@ extern (C++) abstract class Type : ASTNode final Type unqualify(uint m) { - Type t = mutableOf().unSharedOf(); + Type t = this.mutableOf().unSharedOf(); Type tn = ty == Tenum ? null : nextOf(); if (tn && tn.ty != Tfunction) diff --git a/gcc/d/dmd/mtype.h b/gcc/d/dmd/mtype.h index 8b0a1b24ef1b..a7a41c64042f 100644 --- a/gcc/d/dmd/mtype.h +++ b/gcc/d/dmd/mtype.h @@ -142,11 +142,7 @@ public: TY ty; MOD mod; // modifiers MODxxxx char *deco; - -private: void* mcache; - -public: Type *pto; // merged pointer to this type Type *rto; // reference to this type Type *arrayof; // array of this type @@ -257,17 +253,6 @@ public: bool isSharedWild() const { return (mod & (MODshared | MODwild)) == (MODshared | MODwild); } bool isNaked() const { return mod == 0; } Type *nullAttributes() const; - Type *constOf(); - Type *immutableOf(); - Type *mutableOf(); - Type *sharedOf(); - Type *sharedConstOf(); - Type *unSharedOf(); - Type *wildOf(); - Type *wildConstOf(); - Type *sharedWildOf(); - Type *sharedWildConstOf(); - Type *castMod(MOD mod); Type *addMod(MOD mod); virtual Type *addStorageClass(StorageClass stc); Type *pointerTo(); @@ -909,3 +894,14 @@ bool isBaseOf(Type *tthis, Type *t, int *poffset); Type *trySemantic(Type *type, const Loc &loc, Scope *sc); void purityLevel(TypeFunction *type); Type *merge2(Type *type); +Type *constOf(Type *type); +Type *immutableOf(Type *type); +Type *mutableOf(Type *type); +Type *sharedOf(Type *type); +Type *sharedConstOf(Type *type); +Type *unSharedOf(Type *type); +Type *wildOf(Type *type); +Type *wildConstOf(Type *type); +Type *sharedWildOf(Type *type); +Type *sharedWildConstOf(Type *type); +Type *castMod(Type *type, MOD mod); diff --git a/gcc/d/dmd/opover.d b/gcc/d/dmd/opover.d index d596b8487f2a..70eeaff7f47e 100644 --- a/gcc/d/dmd/opover.d +++ b/gcc/d/dmd/opover.d @@ -37,6 +37,7 @@ import dmd.location; import dmd.mtype; import dmd.optimize; import dmd.statement; +import dmd.templatesem; import dmd.tokens; import dmd.typesem; import dmd.visitor; diff --git a/gcc/d/dmd/optimize.d b/gcc/d/dmd/optimize.d index f86abde5c3e2..5c0ef67787c4 100644 --- a/gcc/d/dmd/optimize.d +++ b/gcc/d/dmd/optimize.d @@ -33,6 +33,7 @@ import dmd.printast; import dmd.root.ctfloat; import dmd.sideeffect; import dmd.tokens; +import dmd.typesem; import dmd.visitor; /************************************* @@ -272,7 +273,7 @@ package void setLengthVarIfKnown(VarDeclaration lengthVar, Type type) * Returns: * Constant folded version of `e` */ -Expression optimize(Expression e, int result, bool keepLvalue = false) +extern (C++) Expression optimize(Expression e, int result, bool keepLvalue = false) { //printf("optimize() e: %s result: %d keepLvalue %d\n", e.toChars(), result, keepLvalue); Expression ret = e; diff --git a/gcc/d/dmd/pragmasem.d b/gcc/d/dmd/pragmasem.d new file mode 100644 index 000000000000..b52b5516263d --- /dev/null +++ b/gcc/d/dmd/pragmasem.d @@ -0,0 +1,650 @@ +/** + * Does semantic analysis for pragmas. + * + * Specification: $(LINK2 https://dlang.org/spec/pragma.html, Pragmas) + * + * Copyright: Copyright (C) 1999-2023 by The D Language Foundation, All Rights Reserved + * Authors: $(LINK2 https://www.digitalmars.com, Walter Bright) + * License: $(LINK2 https://www.boost.org/LICENSE_1_0.txt, Boost License 1.0) + * Source: $(LINK2 https://github.com/dlang/dmd/blob/master/src/dmd/pragmasem.d, _pragmasem.d) + * Documentation: https://dlang.org/phobos/dmd_pragmasem.html + * Coverage: https://codecov.io/gh/dlang/dmd/src/master/src/dmd/pragmasem.d + */ + +module dmd.pragmasem; + +import core.stdc.stdio; + +import dmd.astenums; +import dmd.arraytypes; +import dmd.attrib; +import dmd.dinterpret; +import dmd.dscope; +import dmd.dsymbol; +import dmd.errors; +import dmd.expression; +import dmd.expressionsem; +import dmd.globals; +import dmd.location; +import dmd.id; +import dmd.statement; + +/** + * Run semantic on `pragma` declaration. + * + * Params: + * pd = pragma declaration or statement to evaluate + * sc = enclosing scope + */ +void pragmaDeclSemantic(PragmaDeclaration pd, Scope* sc) +{ + import dmd.aggregate; + import dmd.common.outbuffer; + import dmd.dmangle; + import dmd.dmodule; + import dmd.dsymbolsem; + import dmd.identifier; + import dmd.root.rmem; + import dmd.root.utf; + import dmd.target; + import dmd.utils; + + StringExp verifyMangleString(ref Expression e) + { + auto se = semanticString(sc, e, "mangled name"); + if (!se) + return null; + e = se; + if (!se.len) + { + .error(pd.loc, "%s `%s` - zero-length string not allowed for mangled name", pd.kind, pd.toPrettyChars); + return null; + } + if (se.sz != 1) + { + .error(pd.loc, "%s `%s` - mangled name characters can only be of type `char`", pd.kind, pd.toPrettyChars); + return null; + } + version (all) + { + /* Note: D language specification should not have any assumption about backend + * implementation. Ideally pragma(mangle) can accept a string of any content. + * + * Therefore, this validation is compiler implementation specific. + */ + auto slice = se.peekString(); + for (size_t i = 0; i < se.len;) + { + dchar c = slice[i]; + if (c < 0x80) + { + if (c.isValidMangling) + { + ++i; + continue; + } + else + { + .error(pd.loc, "%s `%s` char 0x%02x not allowed in mangled name", pd.kind, pd.toPrettyChars, c); + break; + } + } + if (const msg = utf_decodeChar(slice, i, c)) + { + .error(pd.loc, "%s `%s` %.*s", pd.kind, pd.toPrettyChars, cast(int)msg.length, msg.ptr); + break; + } + if (!isUniAlpha(c)) + { + .error(pd.loc, "%s `%s` char `0x%04x` not allowed in mangled name", pd.kind, pd.toPrettyChars, c); + break; + } + } + } + return se; + } + void declarations() + { + if (!pd.decl) + return; + + Scope* sc2 = pd.newScope(sc); + scope(exit) + if (sc2 != sc) + sc2.pop(); + + foreach (s; (*pd.decl)[]) + { + if (pd.ident == Id.printf || pd.ident == Id.scanf) + { + s.setPragmaPrintf(pd.ident == Id.printf); + s.dsymbolSemantic(sc2); + continue; + } + + s.dsymbolSemantic(sc2); + if (pd.ident != Id.mangle) + continue; + assert(pd.args); + if (auto ad = s.isAggregateDeclaration()) + { + Expression e = (*pd.args)[0]; + sc2 = sc2.startCTFE(); + e = e.expressionSemantic(sc); + e = resolveProperties(sc2, e); + sc2 = sc2.endCTFE(); + AggregateDeclaration agg; + if (auto tc = e.type.isTypeClass()) + agg = tc.sym; + else if (auto ts = e.type.isTypeStruct()) + agg = ts.sym; + ad.pMangleOverride = new MangleOverride; + void setString(ref Expression e) + { + if (auto se = verifyMangleString(e)) + { + const name = (cast(const(char)[])se.peekData()).xarraydup; + ad.pMangleOverride.id = Identifier.idPool(name); + e = se; + } + else + error(e.loc, "must be a string"); + } + if (agg) + { + ad.pMangleOverride.agg = agg; + if (pd.args.length == 2) + { + setString((*pd.args)[1]); + } + else + ad.pMangleOverride.id = agg.ident; + } + else + setString((*pd.args)[0]); + } + else if (auto td = s.isTemplateDeclaration()) + { + .error(pd.loc, "%s `%s` cannot apply to a template declaration", pd.kind, pd.toPrettyChars); + errorSupplemental(pd.loc, "use `template Class(Args...){ pragma(mangle, \"other_name\") class Class {} }`"); + } + else if (auto se = verifyMangleString((*pd.args)[0])) + { + const name = (cast(const(char)[])se.peekData()).xarraydup; + uint cnt = setMangleOverride(s, name); + if (cnt > 1) + .error(pd.loc, "%s `%s` can only apply to a single declaration", pd.kind, pd.toPrettyChars); + } + } + } + + void noDeclarations() + { + if (pd.decl) + { + .error(pd.loc, "%s `%s` is missing a terminating `;`", pd.kind, pd.toPrettyChars); + declarations(); + // do them anyway, to avoid segfaults. + } + } + + // Should be merged with PragmaStatement + //printf("\tpragmaDeclSemantic '%s'\n", pd.toChars()); + if (target.supportsLinkerDirective()) + { + if (pd.ident == Id.linkerDirective) + { + if (!pd.args || pd.args.length != 1) + .error(pd.loc, "%s `%s` one string argument expected for pragma(linkerDirective)", pd.kind, pd.toPrettyChars); + else + { + auto se = semanticString(sc, (*pd.args)[0], "linker directive"); + if (!se) + return noDeclarations(); + (*pd.args)[0] = se; + if (global.params.v.verbose) + message("linkopt %.*s", cast(int)se.len, se.peekString().ptr); + } + return noDeclarations(); + } + } + if (pd.ident == Id.msg) + { + if (!pd.args) + return noDeclarations(); + + if (!pragmaMsgSemantic(pd.loc, sc, pd.args)) + return; + + return noDeclarations(); + } + else if (pd.ident == Id.lib) + { + if (!pd.args || pd.args.length != 1) + .error(pd.loc, "%s `%s` string expected for library name", pd.kind, pd.toPrettyChars); + else + { + auto se = semanticString(sc, (*pd.args)[0], "library name"); + if (!se) + return noDeclarations(); + (*pd.args)[0] = se; + + auto name = se.peekString().xarraydup; + if (global.params.v.verbose) + message("library %s", name.ptr); + if (global.params.moduleDeps.buffer && !global.params.moduleDeps.name) + { + OutBuffer* ob = global.params.moduleDeps.buffer; + Module imod = sc._module; + ob.writestring("depsLib "); + ob.writestring(imod.toPrettyChars()); + ob.writestring(" ("); + escapePath(ob, imod.srcfile.toChars()); + ob.writestring(") : "); + ob.writestring(name); + ob.writenl(); + } + mem.xfree(name.ptr); + } + return noDeclarations(); + } + else if (pd.ident == Id.startaddress) + { + pragmaStartAddressSemantic(pd.loc, sc, pd.args); + return noDeclarations(); + } + else if (pd.ident == Id.Pinline) + { + // this pragma now gets evaluated on demand in function semantic + + return declarations(); + } + else if (pd.ident == Id.mangle) + { + if (!pd.args) + pd.args = new Expressions(); + if (pd.args.length == 0 || pd.args.length > 2) + { + .error(pd.loc, pd.args.length == 0 ? "%s `%s` - string expected for mangled name" + : "%s `%s` expected 1 or 2 arguments", pd.kind, pd.toPrettyChars); + pd.args.setDim(1); + (*pd.args)[0] = ErrorExp.get(); // error recovery + } + return declarations(); + } + else if (pd.ident == Id.crt_constructor || pd.ident == Id.crt_destructor) + { + if (pd.args && pd.args.length != 0) + .error(pd.loc, "%s `%s` takes no argument", pd.kind, pd.toPrettyChars); + else + { + immutable isCtor = pd.ident == Id.crt_constructor; + + static uint recurse(Dsymbol s, bool isCtor) + { + if (auto ad = s.isAttribDeclaration()) + { + uint nestedCount; + auto decls = ad.include(null); + if (decls) + { + for (size_t i = 0; i < decls.length; ++i) + nestedCount += recurse((*decls)[i], isCtor); + } + return nestedCount; + } + else if (auto f = s.isFuncDeclaration()) + { + if (isCtor) + f.isCrtCtor = true; + else + f.isCrtDtor = true; + + return 1; + } + else + return 0; + assert(0); + } + + if (recurse(pd, isCtor) > 1) + .error(pd.loc, "%s `%s` can only apply to a single declaration", pd.kind, pd.toPrettyChars); + } + return declarations(); + } + else if (pd.ident == Id.printf || pd.ident == Id.scanf) + { + if (pd.args && pd.args.length != 0) + .error(pd.loc, "%s `%s` takes no argument", pd.kind, pd.toPrettyChars); + return declarations(); + } + else if (!global.params.ignoreUnsupportedPragmas) + { + error(pd.loc, "unrecognized `pragma(%s)`", pd.ident.toChars()); + return declarations(); + } + + if (!global.params.v.verbose) + return declarations(); + + /* Print unrecognized pragmas + */ + OutBuffer buf; + buf.writestring(pd.ident.toString()); + if (pd.args) + { + const errors_save = global.startGagging(); + for (size_t i = 0; i < pd.args.length; i++) + { + Expression e = (*pd.args)[i]; + sc = sc.startCTFE(); + e = e.expressionSemantic(sc); + e = resolveProperties(sc, e); + sc = sc.endCTFE(); + e = e.ctfeInterpret(); + if (i == 0) + buf.writestring(" ("); + else + buf.writeByte(','); + buf.writestring(e.toChars()); + } + if (pd.args.length) + buf.writeByte(')'); + global.endGagging(errors_save); + } + message("pragma %s", buf.peekChars()); + return declarations(); +} + +/** + * Run semantic on `pragma` statement. + * + * Params: + * ps = pragma statement to evaluate + * sc = enclosing scope + * + * Returns : true if `pragma` is valid, or false if an error was found + */ +bool pragmaStmtSemantic(PragmaStatement ps, Scope* sc) +{ + import dmd.statementsem; + + /* https://dlang.org/spec/statement.html#pragma-statement + */ + // Should be merged with PragmaDeclaration + + //printf("pragmaStmtSemantic() %s\n", ps.toChars()); + //printf("body = %p\n", ps._body); + if (ps.ident == Id.msg) + { + if (!pragmaMsgSemantic(ps.loc, sc, ps.args)) + return false; + } + else if (ps.ident == Id.lib) + { + version (all) + { + /* Should this be allowed? + */ + error(ps.loc, "`pragma(lib)` not allowed as statement"); + return false; + } + else + { + if (!ps.args || ps.args.length != 1) + { + error(ps.loc, "`string` expected for library name"); + return false; + } + else + { + auto se = semanticString(sc, (*ps.args)[0], "library name"); + if (!se) + return false; + + if (global.params.v.verbose) + { + message("library %.*s", cast(int)se.len, se.string); + } + } + } + } + else if (ps.ident == Id.linkerDirective) + { + /* Should this be allowed? + */ + error(ps.loc, "`pragma(linkerDirective)` not allowed as statement"); + return false; + } + else if (ps.ident == Id.startaddress) + { + if (!pragmaStartAddressSemantic(ps.loc, sc, ps.args)) + return false; + } + else if (ps.ident == Id.Pinline) + { + if (auto fd = sc.func) + { + fd.inlining = evalPragmaInline(ps.loc, sc, ps.args); + } + else + { + error(ps.loc, "`pragma(inline)` is not inside a function"); + return false; + } + } + else if (ps.ident == Id.mangle) + { + auto es = ps._body ? ps._body.isExpStatement() : null; + auto de = es ? es.exp.isDeclarationExp() : null; + if (!de) + { + error(ps.loc, "`pragma(mangle)` must be attached to a declaration"); + return false; + } + const se = ps.args && (*ps.args).length == 1 ? semanticString(sc, (*ps.args)[0], "pragma mangle argument") : null; + if (!se) + { + error(ps.loc, "`pragma(mangle)` takes a single argument that must be a string literal"); + return false; + } + const cnt = setMangleOverride(de.declaration, cast(const(char)[])se.peekData()); + if (cnt != 1) + assert(0); + } + else if (!global.params.ignoreUnsupportedPragmas) + { + error(ps.loc, "unrecognized `pragma(%s)`", ps.ident.toChars()); + return false; + } + + if (ps._body) + { + if (ps.ident == Id.msg || ps.ident == Id.startaddress) + { + error(ps.loc, "`pragma(%s)` is missing a terminating `;`", ps.ident.toChars()); + return false; + } + ps._body = ps._body.statementSemantic(sc); + } + return true; +} + +/*************************************** + * Interpret a `pragma(inline, x)` + * + * Params: + * loc = location for error messages + * sc = scope for evaluation of argument + * args = pragma arguments + * Returns: corresponding `PINLINE` state + */ +package PINLINE evalPragmaInline(Loc loc, Scope* sc, Expressions* args) +{ + if (!args || args.length == 0) + return PINLINE.default_; + + if (args && args.length > 1) + { + .error(loc, "one boolean expression expected for `pragma(inline)`, not %llu", cast(ulong) args.length); + args.setDim(1); + (*args)[0] = ErrorExp.get(); + } + + Expression e = (*args)[0]; + if (!e.type) + { + sc = sc.startCTFE(); + e = e.expressionSemantic(sc); + e = resolveProperties(sc, e); + sc = sc.endCTFE(); + e = e.ctfeInterpret(); + e = e.toBoolean(sc); + if (e.isErrorExp()) + .error(loc, "pragma(`inline`, `true` or `false`) expected, not `%s`", (*args)[0].toChars()); + (*args)[0] = e; + } + + const opt = e.toBool(); + if (opt.isEmpty()) + return PINLINE.default_; + else if (opt.get()) + return PINLINE.always; + else + return PINLINE.never; +} + +/** + * Apply pragma mangle to FuncDeclarations and VarDeclarations + * under `s`, poking through attribute declarations such as + * `extern(C)` but not through aggregates or function bodies. + * + * Params: + * s = symbol to apply + * sym = overriding symbol name + */ +private uint setMangleOverride(Dsymbol s, const(char)[] sym) +{ + if (s.isFuncDeclaration() || s.isVarDeclaration()) + { + s.isDeclaration().mangleOverride = sym; + return 1; + } + + if (auto ad = s.isAttribDeclaration()) + { + uint nestedCount = 0; + + ad.include(null).foreachDsymbol( (s) { nestedCount += setMangleOverride(s, sym); } ); + + return nestedCount; + } + return 0; +} + +/*********************************************************** + * Evaluate and print a `pragma(msg, args)` + * + * Params: + * loc = location for error messages + * sc = scope for argument interpretation + * args = expressions to print + * Returns: + * `true` on success + */ +private bool pragmaMsgSemantic(Loc loc, Scope* sc, Expressions* args) +{ + import dmd.tokens; + + if (!args) + return true; + foreach (arg; *args) + { + sc = sc.startCTFE(); + auto e = arg.expressionSemantic(sc); + e = resolveProperties(sc, e); + sc = sc.endCTFE(); + + // pragma(msg) is allowed to contain types as well as expressions + e = ctfeInterpretForPragmaMsg(e); + if (e.op == EXP.error) + { + errorSupplemental(loc, "while evaluating `pragma(msg, %s)`", arg.toChars()); + return false; + } + if (auto se = e.toStringExp()) + { + const slice = se.toUTF8(sc).peekString(); + fprintf(stderr, "%.*s", cast(int)slice.length, slice.ptr); + } + else + fprintf(stderr, "%s", e.toChars()); + } + fprintf(stderr, "\n"); + return true; +} + +/** + * Apply pragma printf/scanf to FuncDeclarations under `s`, + * poking through attribute declarations such as `extern(C)` + * but not through aggregates or function bodies. + * + * Params: + * s = symbol to apply + * printf = `true` for printf, `false` for scanf + */ +private void setPragmaPrintf(Dsymbol s, bool printf) +{ + if (auto fd = s.isFuncDeclaration()) + { + fd.printf = printf; + fd.scanf = !printf; + } + + if (auto ad = s.isAttribDeclaration()) + { + ad.include(null).foreachDsymbol( (s) { setPragmaPrintf(s, printf); } ); + } +} + +/*********************************************************** + * Evaluate `pragma(startAddress, func)` and store the resolved symbol in `args` + * + * Params: + * loc = location for error messages + * sc = scope for argument interpretation + * args = pragma arguments + * Returns: + * `true` on success + */ +private bool pragmaStartAddressSemantic(Loc loc, Scope* sc, Expressions* args) +{ + import dmd.dtemplate; + + if (!args || args.length != 1) + { + .error(loc, "function name expected for start address"); + return false; + } + else + { + /* https://issues.dlang.org/show_bug.cgi?id=11980 + * resolveProperties and ctfeInterpret call are not necessary. + */ + Expression e = (*args)[0]; + sc = sc.startCTFE(); + e = e.expressionSemantic(sc); + // e = resolveProperties(sc, e); + sc = sc.endCTFE(); + + // e = e.ctfeInterpret(); + (*args)[0] = e; + Dsymbol sa = getDsymbol(e); + if (!sa || !sa.isFuncDeclaration()) + { + .error(loc, "function name expected for start address, not `%s`", e.toChars()); + return false; + } + } + return true; +} diff --git a/gcc/d/dmd/scope.h b/gcc/d/dmd/scope.h index 4b157cc9ee7c..f36a14ba0518 100644 --- a/gcc/d/dmd/scope.h +++ b/gcc/d/dmd/scope.h @@ -131,5 +131,5 @@ struct Scope AliasDeclaration *aliasAsg; // if set, then aliasAsg is being assigned a new value, // do not set wasRead for it - Dsymbol *search(const Loc &loc, Identifier *ident, Dsymbol **pscopesym, SearchOptFlags flags = (SearchOptFlags)SearchOpt::all); + Dsymbol *search(const Loc &loc, Identifier *ident, Dsymbol *&pscopesym, SearchOptFlags flags = (SearchOptFlags)SearchOpt::all); }; diff --git a/gcc/d/dmd/semantic2.d b/gcc/d/dmd/semantic2.d index 937e746270ae..b4f91ac7cf04 100644 --- a/gcc/d/dmd/semantic2.d +++ b/gcc/d/dmd/semantic2.d @@ -829,7 +829,8 @@ private void doGNUABITagSemantic(ref Expression e, ref Expression* lastTag) } /** - * Try lower a variable's static Associative Array to a newaa struct. + * Try lower a variable's Associative Array initializer to a newaa struct + * so it can be put in static data. * Params: * vd = Variable to lower * sc = Scope @@ -839,11 +840,20 @@ void lowerStaticAAs(VarDeclaration vd, Scope* sc) if (vd.storage_class & STC.manifest) return; if (auto ei = vd._init.isExpInitializer()) - { - scope v = new StaticAAVisitor(sc); - v.vd = vd; - ei.exp.accept(v); - } + lowerStaticAAs(ei.exp, sc); +} + +/** + * Try lower all Associative Array literals in an expression to a newaa struct + * so it can be put in static data. + * Params: + * e = Expression to traverse + * sc = Scope + */ +void lowerStaticAAs(Expression e, Scope* sc) +{ + scope v = new StaticAAVisitor(sc); + e.accept(v); } /// Visit Associative Array literals and lower them to structs for static initialization @@ -851,7 +861,6 @@ private extern(C++) final class StaticAAVisitor : SemanticTimeTransitiveVisitor { alias visit = SemanticTimeTransitiveVisitor.visit; Scope* sc; - VarDeclaration vd; this(Scope* sc) scope @safe { diff --git a/gcc/d/dmd/sideeffect.d b/gcc/d/dmd/sideeffect.d index 8038770b2914..1d4745afbc19 100644 --- a/gcc/d/dmd/sideeffect.d +++ b/gcc/d/dmd/sideeffect.d @@ -19,6 +19,7 @@ import dmd.expression; import dmd.expressionsem; import dmd.func; import dmd.globals; +import dmd.id; import dmd.identifier; import dmd.init; import dmd.mtype; @@ -270,6 +271,15 @@ bool discardValue(Expression e) break; } case EXP.call: + // https://issues.dlang.org/show_bug.cgi?id=24359 + auto ce = e.isCallExp(); + if (const f = ce.f) + { + if (f.ident == Id.__equals && ce.arguments && ce.arguments.length == 2) + { + return discardValue(new EqualExp(EXP.equal, e.loc, (*ce.arguments)[0], (*ce.arguments)[1])); + } + } return false; case EXP.andAnd: case EXP.orOr: diff --git a/gcc/d/dmd/statementsem.d b/gcc/d/dmd/statementsem.d index 840035c46cf2..a431d5c0922a 100644 --- a/gcc/d/dmd/statementsem.d +++ b/gcc/d/dmd/statementsem.d @@ -16,12 +16,10 @@ module dmd.statementsem; import core.stdc.stdio; import dmd.aggregate; -import dmd.aliasthis; import dmd.arrayop; import dmd.arraytypes; import dmd.astcodegen; import dmd.astenums; -import dmd.attrib; import dmd.blockexit; import dmd.clone; import dmd.cond; @@ -36,9 +34,7 @@ import dmd.dmodule; import dmd.dscope; import dmd.dsymbol; import dmd.dsymbolsem; -import dmd.dtemplate; import dmd.errors; -import dmd.errorsink; import dmd.escape; import dmd.expression; import dmd.expressionsem; @@ -64,7 +60,6 @@ import dmd.root.string; import dmd.semantic2; import dmd.sideeffect; import dmd.statement; -import dmd.staticassert; import dmd.target; import dmd.tokens; import dmd.typesem; @@ -1751,102 +1746,10 @@ Statement statementSemanticVisit(Statement s, Scope* sc) { /* https://dlang.org/spec/statement.html#pragma-statement */ - // Should be merged with PragmaDeclaration - - //printf("PragmaStatement::semantic() %s\n", ps.toChars()); - //printf("body = %p\n", ps._body); - if (ps.ident == Id.msg) - { - if (!pragmaMsgSemantic(ps.loc, sc, ps.args)) - return setError(); - } - else if (ps.ident == Id.lib) - { - version (all) - { - /* Should this be allowed? - */ - error(ps.loc, "`pragma(lib)` not allowed as statement"); - return setError(); - } - else - { - if (!ps.args || ps.args.length != 1) - { - error(ps.loc, "`string` expected for library name"); - return setError(); - } - else - { - auto se = semanticString(sc, (*ps.args)[0], "library name"); - if (!se) - return setError(); - - if (global.params.v.verbose) - { - message("library %.*s", cast(int)se.len, se.string); - } - } - } - } - else if (ps.ident == Id.linkerDirective) - { - /* Should this be allowed? - */ - error(ps.loc, "`pragma(linkerDirective)` not allowed as statement"); - return setError(); - } - else if (ps.ident == Id.startaddress) - { - if (!pragmaStartAddressSemantic(ps.loc, sc, ps.args)) - return setError(); - } - else if (ps.ident == Id.Pinline) - { - if (auto fd = sc.func) - { - fd.inlining = evalPragmaInline(ps.loc, sc, ps.args); - } - else - { - error(ps.loc, "`pragma(inline)` is not inside a function"); - return setError(); - } - } - else if (ps.ident == Id.mangle) - { - auto es = ps._body ? ps._body.isExpStatement() : null; - auto de = es ? es.exp.isDeclarationExp() : null; - if (!de) - { - error(ps.loc, "`pragma(mangle)` must be attached to a declaration"); - return setError(); - } - const se = ps.args && (*ps.args).length == 1 ? semanticString(sc, (*ps.args)[0], "pragma mangle argument") : null; - if (!se) - { - error(ps.loc, "`pragma(mangle)` takes a single argument that must be a string literal"); - return setError(); - } - const cnt = setMangleOverride(de.declaration, cast(const(char)[])se.peekData()); - if (cnt != 1) - assert(0); - } - else if (!global.params.ignoreUnsupportedPragmas) - { - error(ps.loc, "unrecognized `pragma(%s)`", ps.ident.toChars()); + import dmd.pragmasem : pragmaStmtSemantic; + if (!pragmaStmtSemantic(ps, sc)) return setError(); - } - if (ps._body) - { - if (ps.ident == Id.msg || ps.ident == Id.startaddress) - { - error(ps.loc, "`pragma(%s)` is missing a terminating `;`", ps.ident.toChars()); - return setError(); - } - ps._body = ps._body.statementSemantic(sc); - } result = ps._body; } @@ -5010,86 +4913,6 @@ private void debugThrowWalker(Statement s) s.accept(walker); } -/*********************************************************** - * Evaluate and print a `pragma(msg, args)` - * - * Params: - * loc = location for error messages - * sc = scope for argument interpretation - * args = expressions to print - * Returns: - * `true` on success - */ -bool pragmaMsgSemantic(Loc loc, Scope* sc, Expressions* args) -{ - if (!args) - return true; - foreach (arg; *args) - { - sc = sc.startCTFE(); - auto e = arg.expressionSemantic(sc); - e = resolveProperties(sc, e); - sc = sc.endCTFE(); - - // pragma(msg) is allowed to contain types as well as expressions - e = ctfeInterpretForPragmaMsg(e); - if (e.op == EXP.error) - { - errorSupplemental(loc, "while evaluating `pragma(msg, %s)`", arg.toChars()); - return false; - } - if (auto se = e.toStringExp()) - { - const slice = se.toUTF8(sc).peekString(); - fprintf(stderr, "%.*s", cast(int)slice.length, slice.ptr); - } - else - fprintf(stderr, "%s", e.toChars()); - } - fprintf(stderr, "\n"); - return true; -} - -/*********************************************************** - * Evaluate `pragma(startAddress, func)` and store the resolved symbol in `args` - * - * Params: - * loc = location for error messages - * sc = scope for argument interpretation - * args = pragma arguments - * Returns: - * `true` on success - */ -bool pragmaStartAddressSemantic(Loc loc, Scope* sc, Expressions* args) -{ - if (!args || args.length != 1) - { - .error(loc, "function name expected for start address"); - return false; - } - else - { - /* https://issues.dlang.org/show_bug.cgi?id=11980 - * resolveProperties and ctfeInterpret call are not necessary. - */ - Expression e = (*args)[0]; - sc = sc.startCTFE(); - e = e.expressionSemantic(sc); - // e = resolveProperties(sc, e); - sc = sc.endCTFE(); - - // e = e.ctfeInterpret(); - (*args)[0] = e; - Dsymbol sa = getDsymbol(e); - if (!sa || !sa.isFuncDeclaration()) - { - .error(loc, "function name expected for start address, not `%s`", e.toChars()); - return false; - } - } - return true; -} - /************************************ * Check for skipped variable declarations. * Params: diff --git a/gcc/d/dmd/templatesem.d b/gcc/d/dmd/templatesem.d index 1942afe44ae2..0a36838e167d 100644 --- a/gcc/d/dmd/templatesem.d +++ b/gcc/d/dmd/templatesem.d @@ -51,10 +51,160 @@ import dmd.common.outbuffer; import dmd.rootobject; import dmd.semantic2; import dmd.semantic3; +import dmd.templateparamsem; import dmd.tokens; import dmd.typesem; import dmd.visitor; +/************************************ + * Perform semantic analysis on template. + * Params: + * sc = context + * tempdecl = template declaration + */ +void templateDeclarationSemantic(Scope* sc, TemplateDeclaration tempdecl) +{ + enum log = false; + static if (log) + { + printf("TemplateDeclaration.dsymbolSemantic(this = %p, id = '%s')\n", this, tempdecl.ident.toChars()); + printf("sc.stc = %llx\n", sc.stc); + printf("sc.module = %s\n", sc._module.toChars()); + } + if (tempdecl.semanticRun != PASS.initial) + return; // semantic() already run + + if (tempdecl._scope) + { + sc = tempdecl._scope; + tempdecl._scope = null; + } + if (!sc) + return; + + // Remember templates defined in module object that we need to know about + if (sc._module && sc._module.ident == Id.object) + { + if (tempdecl.ident == Id.RTInfo) + Type.rtinfo = tempdecl; + } + + /* Remember Scope for later instantiations, but make + * a copy since attributes can change. + */ + if (!tempdecl._scope) + { + tempdecl._scope = sc.copy(); + tempdecl._scope.setNoFree(); + } + + tempdecl.semanticRun = PASS.semantic; + + tempdecl.parent = sc.parent; + tempdecl.visibility = sc.visibility; + tempdecl.userAttribDecl = sc.userAttribDecl; + tempdecl.cppnamespace = sc.namespace; + tempdecl.isstatic = tempdecl.toParent().isModule() || (tempdecl._scope.stc & STC.static_); + tempdecl.deprecated_ = !!(sc.stc & STC.deprecated_); + + UserAttributeDeclaration.checkGNUABITag(tempdecl, sc.linkage); + + if (!tempdecl.isstatic) + { + if (auto ad = tempdecl.parent.pastMixin().isAggregateDeclaration()) + ad.makeNested(); + } + + // Set up scope for parameters + auto paramsym = new ScopeDsymbol(); + paramsym.parent = tempdecl.parent; + Scope* paramscope = sc.push(paramsym); + paramscope.stc = 0; + + if (global.params.ddoc.doOutput) + { + tempdecl.origParameters = new TemplateParameters(tempdecl.parameters.length); + for (size_t i = 0; i < tempdecl.parameters.length; i++) + { + TemplateParameter tp = (*tempdecl.parameters)[i]; + (*tempdecl.origParameters)[i] = tp.syntaxCopy(); + } + } + + for (size_t i = 0; i < tempdecl.parameters.length; i++) + { + TemplateParameter tp = (*tempdecl.parameters)[i]; + if (!tp.declareParameter(paramscope)) + { + error(tp.loc, "parameter `%s` multiply defined", tp.ident.toChars()); + tempdecl.errors = true; + } + if (!tp.tpsemantic(paramscope, tempdecl.parameters)) + { + tempdecl.errors = true; + } + if (i + 1 != tempdecl.parameters.length && tp.isTemplateTupleParameter()) + { + .error(tempdecl.loc, "%s `%s` template sequence parameter must be the last one", tempdecl.kind, tempdecl.toPrettyChars); + tempdecl.errors = true; + } + } + + /* Calculate TemplateParameter.dependent + */ + TemplateParameters tparams = TemplateParameters(1); + for (size_t i = 0; i < tempdecl.parameters.length; i++) + { + TemplateParameter tp = (*tempdecl.parameters)[i]; + tparams[0] = tp; + + for (size_t j = 0; j < tempdecl.parameters.length; j++) + { + // Skip cases like: X(T : T) + if (i == j) + continue; + + if (TemplateTypeParameter ttp = (*tempdecl.parameters)[j].isTemplateTypeParameter()) + { + if (reliesOnTident(ttp.specType, &tparams)) + tp.dependent = true; + } + else if (TemplateAliasParameter tap = (*tempdecl.parameters)[j].isTemplateAliasParameter()) + { + if (reliesOnTident(tap.specType, &tparams) || + reliesOnTident(isType(tap.specAlias), &tparams)) + { + tp.dependent = true; + } + } + } + } + + paramscope.pop(); + + // Compute again + tempdecl.onemember = null; + if (tempdecl.members) + { + Dsymbol s; + if (Dsymbol.oneMembers(tempdecl.members, s, tempdecl.ident) && s) + { + tempdecl.onemember = s; + s.parent = tempdecl; + } + } + + /* BUG: should check: + * 1. template functions must not introduce virtual functions, as they + * cannot be accomodated in the vtbl[] + * 2. templates cannot introduce non-static data members (i.e. fields) + * as they would change the instance size of the aggregate. + */ + + tempdecl.semanticRun = PASS.semanticdone; +} + + /*************************************** * Given that ti is an instance of this TemplateDeclaration, * deduce the types of the parameters to this, and store @@ -1468,7 +1618,7 @@ Lmatch: sc2.minst = sc.minst; sc2.stc |= fd.storage_class & STC.deprecated_; - fd = td.doHeaderInstantiation(ti, sc2, fd, tthis, argumentList.arguments); + fd = doHeaderInstantiation(td, ti, sc2, fd, tthis, argumentList.arguments); sc2 = sc2.pop(); sc2 = sc2.pop(); @@ -1495,3 +1645,760 @@ Lmatch: //printf("\tmatch %d\n", match); return MATCHpair(matchTiargs, match); } + +/************************************************* + * Limited function template instantiation for using fd.leastAsSpecialized() + */ +private +FuncDeclaration doHeaderInstantiation(TemplateDeclaration td, TemplateInstance ti, Scope* sc2, FuncDeclaration fd, Type tthis, Expressions* fargs) +{ + assert(fd); + version (none) + { + printf("doHeaderInstantiation this = %s\n", toChars()); + } + + // function body and contracts are not need + if (fd.isCtorDeclaration()) + fd = new CtorDeclaration(fd.loc, fd.endloc, fd.storage_class, fd.type.syntaxCopy()); + else + fd = new FuncDeclaration(fd.loc, fd.endloc, fd.ident, fd.storage_class, fd.type.syntaxCopy()); + fd.parent = ti; + + assert(fd.type.ty == Tfunction); + auto tf = fd.type.isTypeFunction(); + tf.fargs = fargs; + + if (tthis) + { + // Match 'tthis' to any TemplateThisParameter's + bool hasttp = false; + foreach (tp; *td.parameters) + { + TemplateThisParameter ttp = tp.isTemplateThisParameter(); + if (ttp) + hasttp = true; + } + if (hasttp) + { + tf = tf.addSTC(ModToStc(tthis.mod)).isTypeFunction(); + assert(!tf.deco); + } + } + + Scope* scx = sc2.push(); + + // Shouldn't run semantic on default arguments and return type. + foreach (ref params; *tf.parameterList.parameters) + params.defaultArg = null; + tf.incomplete = true; + + if (fd.isCtorDeclaration()) + { + // For constructors, emitting return type is necessary for + // isReturnIsolated() in functionResolve. + tf.isctor = true; + + Dsymbol parent = td.toParentDecl(); + Type tret; + AggregateDeclaration ad = parent.isAggregateDeclaration(); + if (!ad || parent.isUnionDeclaration()) + { + tret = Type.tvoid; + } + else + { + tret = ad.handleType(); + assert(tret); + tret = tret.addStorageClass(fd.storage_class | scx.stc); + tret = tret.addMod(tf.mod); + } + tf.next = tret; + if (ad && ad.isStructDeclaration()) + tf.isref = 1; + //printf("tf = %s\n", tf.toChars()); + } + else + tf.next = null; + fd.type = tf; + fd.type = fd.type.addSTC(scx.stc); + fd.type = fd.type.typeSemantic(fd.loc, scx); + scx = scx.pop(); + + if (fd.type.ty != Tfunction) + return null; + + fd.originalType = fd.type; // for mangling + //printf("\t[%s] fd.type = %s, mod = %x, ", loc.toChars(), fd.type.toChars(), fd.type.mod); + //printf("fd.needThis() = %d\n", fd.needThis()); + + return fd; +} + +/************************************************** + * Declare template parameter tp with value o, and install it in the scope sc. + */ +extern (D) RootObject declareParameter(TemplateDeclaration td, Scope* sc, TemplateParameter tp, RootObject o) +{ + //printf("TemplateDeclaration.declareParameter('%s', o = %p)\n", tp.ident.toChars(), o); + Type ta = isType(o); + Expression ea = isExpression(o); + Dsymbol sa = isDsymbol(o); + Tuple va = isTuple(o); + + Declaration d; + VarDeclaration v = null; + + if (ea) + { + if (ea.op == EXP.type) + ta = ea.type; + else if (auto se = ea.isScopeExp()) + sa = se.sds; + else if (auto te = ea.isThisExp()) + sa = te.var; + else if (auto se = ea.isSuperExp()) + sa = se.var; + else if (auto fe = ea.isFuncExp()) + { + if (fe.td) + sa = fe.td; + else + sa = fe.fd; + } + } + + if (ta) + { + //printf("type %s\n", ta.toChars()); + auto ad = new AliasDeclaration(Loc.initial, tp.ident, ta); + ad.storage_class |= STC.templateparameter; + d = ad; + } + else if (sa) + { + //printf("Alias %s %s;\n", sa.ident.toChars(), tp.ident.toChars()); + auto ad = new AliasDeclaration(Loc.initial, tp.ident, sa); + ad.storage_class |= STC.templateparameter; + d = ad; + } + else if (ea) + { + // tdtypes.data[i] always matches ea here + Initializer _init = new ExpInitializer(td.loc, ea); + TemplateValueParameter tvp = tp.isTemplateValueParameter(); + Type t = tvp ? tvp.valType : null; + v = new VarDeclaration(td.loc, t, tp.ident, _init); + v.storage_class = STC.manifest | STC.templateparameter; + d = v; + } + else if (va) + { + //printf("\ttuple\n"); + d = new TupleDeclaration(td.loc, tp.ident, &va.objects); + } + else + { + assert(0); + } + d.storage_class |= STC.templateparameter; + + if (ta) + { + Type t = ta; + // consistent with Type.checkDeprecated() + while (t.ty != Tenum) + { + if (!t.nextOf()) + break; + t = (cast(TypeNext)t).next; + } + if (Dsymbol s = t.toDsymbol(sc)) + { + if (s.isDeprecated()) + d.storage_class |= STC.deprecated_; + } + } + else if (sa) + { + if (sa.isDeprecated()) + d.storage_class |= STC.deprecated_; + } + + if (!sc.insert(d)) + .error(td.loc, "%s `%s` declaration `%s` is already defined", td.kind, td.toPrettyChars, tp.ident.toChars()); + d.dsymbolSemantic(sc); + /* So the caller's o gets updated with the result of semantic() being run on o + */ + if (v) + o = v._init.initializerToExpression(); + return o; +} + +/************************************************* + * Given function arguments, figure out which template function + * to expand, and return matching result. + * Params: + * m = matching result + * dstart = the root of overloaded function templates + * loc = instantiation location + * sc = instantiation scope + * tiargs = initial list of template arguments + * tthis = if !NULL, the 'this' pointer argument + * argumentList= arguments to function + * errorHelper = delegate to send error message to if not null + */ +void functionResolve(ref MatchAccumulator m, Dsymbol dstart, Loc loc, Scope* sc, Objects* tiargs, + Type tthis, ArgumentList argumentList, void delegate(const(char)*) scope errorHelper = null) +{ + version (none) + { + printf("functionResolve() dstart = %s\n", dstart.toChars()); + printf(" tiargs:\n"); + if (tiargs) + { + for (size_t i = 0; i < tiargs.length; i++) + { + RootObject arg = (*tiargs)[i]; + printf("\t%s\n", arg.toChars()); + } + } + printf(" fargs:\n"); + for (size_t i = 0; i < (fargs ? fargs.length : 0); i++) + { + Expression arg = (*fargs)[i]; + printf("\t%s %s\n", arg.type.toChars(), arg.toChars()); + //printf("\tty = %d\n", arg.type.ty); + } + //printf("stc = %llx\n", dstart._scope.stc); + //printf("match:t/f = %d/%d\n", ta_last, m.last); + } + + // results + int property = 0; // 0: uninitialized + // 1: seen @property + // 2: not @property + size_t ov_index = 0; + TemplateDeclaration td_best; + TemplateInstance ti_best; + MATCH ta_last = m.last != MATCH.nomatch ? MATCH.exact : MATCH.nomatch; + Type tthis_best; + + int applyFunction(FuncDeclaration fd) + { + // skip duplicates + if (fd == m.lastf) + return 0; + // explicitly specified tiargs never match to non template function + if (tiargs && tiargs.length > 0) + return 0; + + // constructors need a valid scope in order to detect semantic errors + if (!fd.isCtorDeclaration && + fd.semanticRun < PASS.semanticdone) + { + fd.ungagSpeculative(); + fd.dsymbolSemantic(null); + } + if (fd.semanticRun < PASS.semanticdone) + { + .error(loc, "forward reference to template `%s`", fd.toChars()); + return 1; + } + //printf("fd = %s %s, fargs = %s\n", fd.toChars(), fd.type.toChars(), fargs.toChars()); + auto tf = fd.type.isTypeFunction(); + + int prop = tf.isproperty ? 1 : 2; + if (property == 0) + property = prop; + else if (property != prop) + error(fd.loc, "cannot overload both property and non-property functions"); + + /* For constructors, qualifier check will be opposite direction. + * Qualified constructor always makes qualified object, then will be checked + * that it is implicitly convertible to tthis. + */ + Type tthis_fd = fd.needThis() ? tthis : null; + bool isCtorCall = tthis_fd && fd.isCtorDeclaration(); + if (isCtorCall) + { + //printf("%s tf.mod = x%x tthis_fd.mod = x%x %d\n", tf.toChars(), + // tf.mod, tthis_fd.mod, fd.isReturnIsolated()); + if (MODimplicitConv(tf.mod, tthis_fd.mod) || + tf.isWild() && tf.isShared() == tthis_fd.isShared() || + fd.isReturnIsolated()) + { + /* && tf.isShared() == tthis_fd.isShared()*/ + // Uniquely constructed object can ignore shared qualifier. + // TODO: Is this appropriate? + tthis_fd = null; + } + else + return 0; // MATCH.nomatch + } + /* Fix Issue 17970: + If a struct is declared as shared the dtor is automatically + considered to be shared, but when the struct is instantiated + the instance is no longer considered to be shared when the + function call matching is done. The fix makes it so that if a + struct declaration is shared, when the destructor is called, + the instantiated struct is also considered shared. + */ + if (auto dt = fd.isDtorDeclaration()) + { + auto dtmod = dt.type.toTypeFunction(); + auto shared_dtor = dtmod.mod & MODFlags.shared_; + auto shared_this = tthis_fd !is null ? + tthis_fd.mod & MODFlags.shared_ : 0; + if (shared_dtor && !shared_this) + tthis_fd = dtmod; + else if (shared_this && !shared_dtor && tthis_fd !is null) + tf.mod = tthis_fd.mod; + } + const(char)* failMessage; + MATCH mfa = tf.callMatch(tthis_fd, argumentList, 0, errorHelper, sc); + //printf("test1: mfa = %d\n", mfa); + if (failMessage) + errorHelper(failMessage); + if (mfa == MATCH.nomatch) + return 0; + + int firstIsBetter() + { + td_best = null; + ti_best = null; + ta_last = MATCH.exact; + m.last = mfa; + m.lastf = fd; + tthis_best = tthis_fd; + ov_index = 0; + m.count = 1; + return 0; + } + + if (mfa > m.last) return firstIsBetter(); + if (mfa < m.last) return 0; + + /* See if one of the matches overrides the other. + */ + assert(m.lastf); + if (m.lastf.overrides(fd)) return 0; + if (fd.overrides(m.lastf)) return firstIsBetter(); + + /* Try to disambiguate using template-style partial ordering rules. + * In essence, if f() and g() are ambiguous, if f() can call g(), + * but g() cannot call f(), then pick f(). + * This is because f() is "more specialized." + */ + { + MATCH c1 = FuncDeclaration.leastAsSpecialized(fd, m.lastf, argumentList.names); + MATCH c2 = FuncDeclaration.leastAsSpecialized(m.lastf, fd, argumentList.names); + //printf("c1 = %d, c2 = %d\n", c1, c2); + if (c1 > c2) return firstIsBetter(); + if (c1 < c2) return 0; + } + + /* The 'overrides' check above does covariant checking only + * for virtual member functions. It should do it for all functions, + * but in order to not risk breaking code we put it after + * the 'leastAsSpecialized' check. + * In the future try moving it before. + * I.e. a not-the-same-but-covariant match is preferred, + * as it is more restrictive. + */ + if (!m.lastf.type.equals(fd.type)) + { + //printf("cov: %d %d\n", m.lastf.type.covariant(fd.type), fd.type.covariant(m.lastf.type)); + const lastCovariant = m.lastf.type.covariant(fd.type); + const firstCovariant = fd.type.covariant(m.lastf.type); + + if (lastCovariant == Covariant.yes || lastCovariant == Covariant.no) + { + if (firstCovariant != Covariant.yes && firstCovariant != Covariant.no) + { + return 0; + } + } + else if (firstCovariant == Covariant.yes || firstCovariant == Covariant.no) + { + return firstIsBetter(); + } + } + + /* If the two functions are the same function, like: + * int foo(int); + * int foo(int x) { ... } + * then pick the one with the body. + * + * If none has a body then don't care because the same + * real function would be linked to the decl (e.g from object file) + */ + if (tf.equals(m.lastf.type) && + fd.storage_class == m.lastf.storage_class && + fd.parent == m.lastf.parent && + fd.visibility == m.lastf.visibility && + fd._linkage == m.lastf._linkage) + { + if (fd.fbody && !m.lastf.fbody) + return firstIsBetter(); + if (!fd.fbody) + return 0; + } + + // https://issues.dlang.org/show_bug.cgi?id=14450 + // Prefer exact qualified constructor for the creating object type + if (isCtorCall && tf.mod != m.lastf.type.mod) + { + if (tthis.mod == tf.mod) return firstIsBetter(); + if (tthis.mod == m.lastf.type.mod) return 0; + } + + m.nextf = fd; + m.count++; + return 0; + } + + int applyTemplate(TemplateDeclaration td) + { + //printf("applyTemplate(): td = %s\n", td.toChars()); + if (td == td_best) // skip duplicates + return 0; + + if (!sc) + sc = td._scope; // workaround for Type.aliasthisOf + + if (td.semanticRun == PASS.initial && td._scope) + { + // Try to fix forward reference. Ungag errors while doing so. + td.ungagSpeculative(); + td.dsymbolSemantic(td._scope); + } + if (td.semanticRun == PASS.initial) + { + .error(loc, "forward reference to template `%s`", td.toChars()); + Lerror: + m.lastf = null; + m.count = 0; + m.last = MATCH.nomatch; + return 1; + } + //printf("td = %s\n", td.toChars()); + + if (argumentList.hasNames) + { + .error(loc, "named arguments with Implicit Function Template Instantiation are not supported yet"); + goto Lerror; + } + auto f = td.onemember ? td.onemember.isFuncDeclaration() : null; + if (!f) + { + if (!tiargs) + tiargs = new Objects(); + auto ti = new TemplateInstance(loc, td, tiargs); + Objects dedtypes = Objects(td.parameters.length); + assert(td.semanticRun != PASS.initial); + MATCH mta = matchWithInstance(sc, td, ti, dedtypes, argumentList, 0); + //printf("matchWithInstance = %d\n", mta); + if (mta == MATCH.nomatch || mta < ta_last) // no match or less match + return 0; + + ti.templateInstanceSemantic(sc, argumentList); + if (!ti.inst) // if template failed to expand + return 0; + + Dsymbol s = ti.inst.toAlias(); + FuncDeclaration fd; + if (auto tdx = s.isTemplateDeclaration()) + { + Objects dedtypesX; // empty tiargs + + // https://issues.dlang.org/show_bug.cgi?id=11553 + // Check for recursive instantiation of tdx. + for (TemplatePrevious* p = tdx.previous; p; p = p.prev) + { + if (arrayObjectMatch(*p.dedargs, dedtypesX)) + { + //printf("recursive, no match p.sc=%p %p %s\n", p.sc, this, this.toChars()); + /* It must be a subscope of p.sc, other scope chains are not recursive + * instantiations. + */ + for (Scope* scx = sc; scx; scx = scx.enclosing) + { + if (scx == p.sc) + { + error(loc, "recursive template expansion while looking for `%s.%s`", ti.toChars(), tdx.toChars()); + goto Lerror; + } + } + } + /* BUG: should also check for ref param differences + */ + } + + TemplatePrevious pr; + pr.prev = tdx.previous; + pr.sc = sc; + pr.dedargs = &dedtypesX; + tdx.previous = ≺ // add this to threaded list + + fd = resolveFuncCall(loc, sc, s, null, tthis, argumentList, FuncResolveFlag.quiet); + + tdx.previous = pr.prev; // unlink from threaded list + } + else if (s.isFuncDeclaration()) + { + fd = resolveFuncCall(loc, sc, s, null, tthis, argumentList, FuncResolveFlag.quiet); + } + else + goto Lerror; + + if (!fd) + return 0; + + if (fd.type.ty != Tfunction) + { + m.lastf = fd; // to propagate "error match" + m.count = 1; + m.last = MATCH.nomatch; + return 1; + } + + Type tthis_fd = fd.needThis() && !fd.isCtorDeclaration() ? tthis : null; + + auto tf = fd.type.isTypeFunction(); + MATCH mfa = tf.callMatch(tthis_fd, argumentList, 0, null, sc); + if (mfa < m.last) + return 0; + + if (mta < ta_last) goto Ltd_best2; + if (mta > ta_last) goto Ltd2; + + if (mfa < m.last) goto Ltd_best2; + if (mfa > m.last) goto Ltd2; + + // td_best and td are ambiguous + //printf("Lambig2\n"); + m.nextf = fd; + m.count++; + return 0; + + Ltd_best2: + return 0; + + Ltd2: + // td is the new best match + assert(td._scope); + td_best = td; + ti_best = null; + property = 0; // (backward compatibility) + ta_last = mta; + m.last = mfa; + m.lastf = fd; + tthis_best = tthis_fd; + ov_index = 0; + m.nextf = null; + m.count = 1; + return 0; + } + + //printf("td = %s\n", td.toChars()); + for (size_t ovi = 0; f; f = f.overnext0, ovi++) + { + if (f.type.ty != Tfunction || f.errors) + goto Lerror; + + /* This is a 'dummy' instance to evaluate constraint properly. + */ + auto ti = new TemplateInstance(loc, td, tiargs); + ti.parent = td.parent; // Maybe calculating valid 'enclosing' is unnecessary. + + auto fd = f; + MATCHpair x = td.deduceFunctionTemplateMatch(ti, sc, fd, tthis, argumentList); + MATCH mta = x.mta; + MATCH mfa = x.mfa; + //printf("match:t/f = %d/%d\n", mta, mfa); + if (!fd || mfa == MATCH.nomatch) + continue; + + Type tthis_fd = fd.needThis() ? tthis : null; + + bool isCtorCall = tthis_fd && fd.isCtorDeclaration(); + if (isCtorCall) + { + // Constructor call requires additional check. + auto tf = fd.type.isTypeFunction(); + assert(tf.next); + if (MODimplicitConv(tf.mod, tthis_fd.mod) || + tf.isWild() && tf.isShared() == tthis_fd.isShared() || + fd.isReturnIsolated()) + { + tthis_fd = null; + } + else + continue; // MATCH.nomatch + + // need to check here whether the constructor is the member of a struct + // declaration that defines a copy constructor. This is already checked + // in the semantic of CtorDeclaration, however, when matching functions, + // the template instance is not expanded. + // https://issues.dlang.org/show_bug.cgi?id=21613 + auto ad = fd.isThis(); + auto sd = ad.isStructDeclaration(); + if (checkHasBothRvalueAndCpCtor(sd, fd.isCtorDeclaration(), ti)) + continue; + } + + if (mta < ta_last) goto Ltd_best; + if (mta > ta_last) goto Ltd; + + if (mfa < m.last) goto Ltd_best; + if (mfa > m.last) goto Ltd; + + if (td_best) + { + // Disambiguate by picking the most specialized TemplateDeclaration + MATCH c1 = leastAsSpecialized(sc, td, td_best, argumentList); + MATCH c2 = leastAsSpecialized(sc, td_best, td, argumentList); + //printf("1: c1 = %d, c2 = %d\n", c1, c2); + if (c1 > c2) goto Ltd; + if (c1 < c2) goto Ltd_best; + } + assert(fd && m.lastf); + { + // Disambiguate by tf.callMatch + auto tf1 = fd.type.isTypeFunction(); + auto tf2 = m.lastf.type.isTypeFunction(); + MATCH c1 = tf1.callMatch(tthis_fd, argumentList, 0, null, sc); + MATCH c2 = tf2.callMatch(tthis_best, argumentList, 0, null, sc); + //printf("2: c1 = %d, c2 = %d\n", c1, c2); + if (c1 > c2) goto Ltd; + if (c1 < c2) goto Ltd_best; + } + { + // Disambiguate by picking the most specialized FunctionDeclaration + MATCH c1 = FuncDeclaration.leastAsSpecialized(fd, m.lastf, argumentList.names); + MATCH c2 = FuncDeclaration.leastAsSpecialized(m.lastf, fd, argumentList.names); + //printf("3: c1 = %d, c2 = %d\n", c1, c2); + if (c1 > c2) goto Ltd; + if (c1 < c2) goto Ltd_best; + } + + // https://issues.dlang.org/show_bug.cgi?id=14450 + // Prefer exact qualified constructor for the creating object type + if (isCtorCall && fd.type.mod != m.lastf.type.mod) + { + if (tthis.mod == fd.type.mod) goto Ltd; + if (tthis.mod == m.lastf.type.mod) goto Ltd_best; + } + + m.nextf = fd; + m.count++; + continue; + + Ltd_best: // td_best is the best match so far + //printf("Ltd_best\n"); + continue; + + Ltd: // td is the new best match + //printf("Ltd\n"); + assert(td._scope); + td_best = td; + ti_best = ti; + property = 0; // (backward compatibility) + ta_last = mta; + m.last = mfa; + m.lastf = fd; + tthis_best = tthis_fd; + ov_index = ovi; + m.nextf = null; + m.count = 1; + continue; + } + return 0; + } + + auto td = dstart.isTemplateDeclaration(); + if (td && td.funcroot) + dstart = td.funcroot; + overloadApply(dstart, (Dsymbol s) + { + if (s.errors) + return 0; + if (auto fd = s.isFuncDeclaration()) + return applyFunction(fd); + if (auto td = s.isTemplateDeclaration()) + return applyTemplate(td); + return 0; + }, sc); + + //printf("td_best = %p, m.lastf = %p\n", td_best, m.lastf); + if (td_best && ti_best && m.count == 1) + { + // Matches to template function + assert(td_best.onemember && td_best.onemember.isFuncDeclaration()); + /* The best match is td_best with arguments tdargs. + * Now instantiate the template. + */ + assert(td_best._scope); + if (!sc) + sc = td_best._scope; // workaround for Type.aliasthisOf + + auto ti = new TemplateInstance(loc, td_best, ti_best.tiargs); + ti.templateInstanceSemantic(sc, argumentList); + + m.lastf = ti.toAlias().isFuncDeclaration(); + if (!m.lastf) + goto Lnomatch; + if (ti.errors) + { + Lerror: + m.count = 1; + assert(m.lastf); + m.last = MATCH.nomatch; + return; + } + + // look forward instantiated overload function + // Dsymbol.oneMembers is alredy called in TemplateInstance.semantic. + // it has filled overnext0d + while (ov_index--) + { + m.lastf = m.lastf.overnext0; + assert(m.lastf); + } + + tthis_best = m.lastf.needThis() && !m.lastf.isCtorDeclaration() ? tthis : null; + + if (m.lastf.type.ty == Terror) + goto Lerror; + auto tf = m.lastf.type.isTypeFunction(); + if (!tf.callMatch(tthis_best, argumentList, 0, null, sc)) + goto Lnomatch; + + /* As https://issues.dlang.org/show_bug.cgi?id=3682 shows, + * a template instance can be matched while instantiating + * that same template. Thus, the function type can be incomplete. Complete it. + * + * https://issues.dlang.org/show_bug.cgi?id=9208 + * For auto function, completion should be deferred to the end of + * its semantic3. Should not complete it in here. + */ + if (tf.next && !m.lastf.inferRetType) + { + m.lastf.type = tf.typeSemantic(loc, sc); + } + } + else if (m.lastf) + { + // Matches to non template function, + // or found matches were ambiguous. + assert(m.count >= 1); + } + else + { + Lnomatch: + m.count = 0; + m.lastf = null; + m.last = MATCH.nomatch; + } +} diff --git a/gcc/d/dmd/typesem.d b/gcc/d/dmd/typesem.d index 6721fa6544a7..b1ca92da4cb8 100644 --- a/gcc/d/dmd/typesem.d +++ b/gcc/d/dmd/typesem.d @@ -41,6 +41,7 @@ import dmd.errorsink; import dmd.expression; import dmd.expressionsem; import dmd.func; +import dmd.funcsem; import dmd.globals; import dmd.hdrgen; import dmd.id; @@ -3742,12 +3743,12 @@ void resolve(Type mt, const ref Loc loc, Scope* sc, out Expression pe, out Type // f might be a unittest declaration which is incomplete when compiled // without -unittest. That causes a segfault in checkForwardRef, see // https://issues.dlang.org/show_bug.cgi?id=20626 - if ((!f.isUnitTestDeclaration() || global.params.useUnitTests) && f.checkForwardRef(loc)) + if ((!f.isUnitTestDeclaration() || global.params.useUnitTests) && checkForwardRef(f, loc)) goto Lerr; } if (auto f = isFuncAddress(mt.exp)) { - if (f.checkForwardRef(loc)) + if (checkForwardRef(f, loc)) goto Lerr; } @@ -6105,6 +6106,305 @@ extern(C++) bool isBaseOf(Type tthis, Type t, int* poffset) return false; } +/******************************** + * Convert to 'const'. + */ +extern(C++) Type constOf(Type type) +{ + //printf("Type::constOf() %p %s\n", type, type.toChars()); + if (type.mod == MODFlags.const_) + return type; + if (type.mcache && type.mcache.cto) + { + assert(type.mcache.cto.mod == MODFlags.const_); + return type.mcache.cto; + } + Type t = type.makeConst(); + t = t.merge(); + t.fixTo(type); + //printf("-Type::constOf() %p %s\n", t, t.toChars()); + return t; +} + +/******************************** + * Convert to 'immutable'. + */ +extern(C++) Type immutableOf(Type type) +{ + //printf("Type::immutableOf() %p %s\n", this, toChars()); + if (type.isImmutable()) + return type; + if (type.mcache && type.mcache.ito) + { + assert(type.mcache.ito.isImmutable()); + return type.mcache.ito; + } + Type t = type.makeImmutable(); + t = t.merge(); + t.fixTo(type); + //printf("\t%p\n", t); + return t; +} + +/******************************** + * Make type mutable. + */ +extern(C++) Type mutableOf(Type type) +{ + //printf("Type::mutableOf() %p, %s\n", type, type.toChars()); + Type t = type; + if (type.isImmutable()) + { + type.getMcache(); + t = type.mcache.ito; // immutable => naked + assert(!t || (t.isMutable() && !t.isShared())); + } + else if (type.isConst()) + { + type.getMcache(); + if (type.isShared()) + { + if (type.isWild()) + t = type.mcache.swcto; // shared wild const -> shared + else + t = type.mcache.sto; // shared const => shared + } + else + { + if (type.isWild()) + t = type.mcache.wcto; // wild const -> naked + else + t = type.mcache.cto; // const => naked + } + assert(!t || t.isMutable()); + } + else if (type.isWild()) + { + type.getMcache(); + if (type.isShared()) + t = type.mcache.sto; // shared wild => shared + else + t = type.mcache.wto; // wild => naked + assert(!t || t.isMutable()); + } + if (!t) + { + t = type.makeMutable(); + t = t.merge(); + t.fixTo(type); + } + else + t = t.merge(); + assert(t.isMutable()); + return t; +} + +extern(C++) Type sharedOf(Type type) +{ + //printf("Type::sharedOf() %p, %s\n", type, type.toChars()); + if (type.mod == MODFlags.shared_) + return type; + if (type.mcache && type.mcache.sto) + { + assert(type.mcache.sto.mod == MODFlags.shared_); + return type.mcache.sto; + } + Type t = type.makeShared(); + t = t.merge(); + t.fixTo(type); + //printf("\t%p\n", t); + return t; +} + +extern(C++) Type sharedConstOf(Type type) +{ + //printf("Type::sharedConstOf() %p, %s\n", type, type.toChars()); + if (type.mod == (MODFlags.shared_ | MODFlags.const_)) + return type; + if (type.mcache && type.mcache.scto) + { + assert(type.mcache.scto.mod == (MODFlags.shared_ | MODFlags.const_)); + return type.mcache.scto; + } + Type t = type.makeSharedConst(); + t = t.merge(); + t.fixTo(type); + //printf("\t%p\n", t); + return t; +} + +/******************************** + * Make type unshared. + * 0 => 0 + * const => const + * immutable => immutable + * shared => 0 + * shared const => const + * wild => wild + * wild const => wild const + * shared wild => wild + * shared wild const => wild const + */ +extern(C++) Type unSharedOf(Type type) +{ + //printf("Type::unSharedOf() %p, %s\n", type, type.toChars()); + Type t = type; + + if (type.isShared()) + { + type.getMcache(); + if (type.isWild()) + { + if (type.isConst()) + t = type.mcache.wcto; // shared wild const => wild const + else + t = type.mcache.wto; // shared wild => wild + } + else + { + if (type.isConst()) + t = type.mcache.cto; // shared const => const + else + t = type.mcache.sto; // shared => naked + } + assert(!t || !t.isShared()); + } + + if (!t) + { + t = type.nullAttributes(); + t.mod = type.mod & ~MODFlags.shared_; + t.ctype = type.ctype; + t = t.merge(); + t.fixTo(type); + } + else + t = t.merge(); + assert(!t.isShared()); + return t; +} + +/******************************** + * Convert to 'wild'. + */ +extern(C++) Type wildOf(Type type) +{ + //printf("Type::wildOf() %p %s\n", type, type.toChars()); + if (type.mod == MODFlags.wild) + return type; + if (type.mcache && type.mcache.wto) + { + assert(type.mcache.wto.mod == MODFlags.wild); + return type.mcache.wto; + } + Type t = type.makeWild(); + t = t.merge(); + t.fixTo(type); + //printf("\t%p %s\n", t, t.toChars()); + return t; +} + +extern(C++) Type wildConstOf(Type type) +{ + //printf("Type::wildConstOf() %p %s\n", type, type.toChars()); + if (type.mod == MODFlags.wildconst) + return type; + if (type.mcache && type.mcache.wcto) + { + assert(type.mcache.wcto.mod == MODFlags.wildconst); + return type.mcache.wcto; + } + Type t = type.makeWildConst(); + t = t.merge(); + t.fixTo(type); + //printf("\t%p %s\n", t, t.toChars()); + return t; +} + +extern(C++) Type sharedWildOf(Type type) +{ + //printf("Type::sharedWildOf() %p, %s\n", type, type.toChars()); + if (type.mod == (MODFlags.shared_ | MODFlags.wild)) + return type; + if (type.mcache && type.mcache.swto) + { + assert(type.mcache.swto.mod == (MODFlags.shared_ | MODFlags.wild)); + return type.mcache.swto; + } + Type t = type.makeSharedWild(); + t = t.merge(); + t.fixTo(type); + //printf("\t%p %s\n", t, t.toChars()); + return t; +} + +extern(C++) Type sharedWildConstOf(Type type) +{ + //printf("Type::sharedWildConstOf() %p, %s\n", type, type.toChars()); + if (type.mod == (MODFlags.shared_ | MODFlags.wildconst)) + return type; + if (type.mcache && type.mcache.swcto) + { + assert(type.mcache.swcto.mod == (MODFlags.shared_ | MODFlags.wildconst)); + return type.mcache.swcto; + } + Type t = type.makeSharedWildConst(); + t = t.merge(); + t.fixTo(type); + //printf("\t%p %s\n", t, t.toChars()); + return t; +} + +/************************************ + * Apply MODxxxx bits to existing type. + */ +extern(C++) Type castMod(Type type, MOD mod) +{ + Type t; + switch (mod) + { + case 0: + t = type.unSharedOf().mutableOf(); + break; + + case MODFlags.const_: + t = type.unSharedOf().constOf(); + break; + + case MODFlags.wild: + t = type.unSharedOf().wildOf(); + break; + + case MODFlags.wildconst: + t = type.unSharedOf().wildConstOf(); + break; + + case MODFlags.shared_: + t = type.mutableOf().sharedOf(); + break; + + case MODFlags.shared_ | MODFlags.const_: + t = type.sharedConstOf(); + break; + + case MODFlags.shared_ | MODFlags.wild: + t = type.sharedWildOf(); + break; + + case MODFlags.shared_ | MODFlags.wildconst: + t = type.sharedWildConstOf(); + break; + + case MODFlags.immutable_: + t = type.immutableOf(); + break; + + default: + assert(0); + } + return t; +} + /******************************* Private *****************************************/ private: diff --git a/gcc/d/dmd/utils.d b/gcc/d/dmd/utils.d index 75ee78cdd2e5..72d80367bbe9 100644 --- a/gcc/d/dmd/utils.d +++ b/gcc/d/dmd/utils.d @@ -299,3 +299,44 @@ bool parseDigits(T)(ref T val, const(char)[] p, const T max = T.max) assert(i.parseDigits("420", 500) && i == 420); assert(!i.parseDigits("420", 400)); } + +/** + * Cast a `ubyte[]` to an array of larger integers as if we are on a big endian architecture + * Params: + * data = array with big endian data + * size = 1 for ubyte[], 2 for ushort[], 4 for uint[], 8 for ulong[] + * Returns: copy of `data`, with bytes shuffled if compiled for `version(LittleEndian)` + */ +ubyte[] arrayCastBigEndian(const ubyte[] data, size_t size) +{ + ubyte[] impl(T)() + { + auto result = new T[](data.length / T.sizeof); + foreach (i; 0 .. result.length) + { + result[i] = 0; + foreach (j; 0 .. T.sizeof) + { + result[i] |= T(data[i * T.sizeof + j]) << ((T.sizeof - 1 - j) * 8); + } + } + return cast(ubyte[]) result; + } + switch (size) + { + case 1: return data.dup; + case 2: return impl!ushort; + case 4: return impl!uint; + case 8: return impl!ulong; + default: assert(0); + } +} + +unittest +{ + ubyte[] data = [0xAA, 0xBB, 0xCC, 0xDD, 0xEE, 0xFF, 0x11, 0x22]; + assert(cast(ulong[]) arrayCastBigEndian(data, 8) == [0xAABBCCDDEEFF1122]); + assert(cast(uint[]) arrayCastBigEndian(data, 4) == [0xAABBCCDD, 0xEEFF1122]); + assert(cast(ushort[]) arrayCastBigEndian(data, 2) == [0xAABB, 0xCCDD, 0xEEFF, 0x1122]); + assert(cast(ubyte[]) arrayCastBigEndian(data, 1) == data); +} diff --git a/gcc/d/expr.cc b/gcc/d/expr.cc index 0a85a55b397b..a05058834afa 100644 --- a/gcc/d/expr.cc +++ b/gcc/d/expr.cc @@ -1178,7 +1178,7 @@ public: { libcall = LIBCALL_AAGETY; ptr = build_address (build_expr (e->e1)); - tinfo = build_typeinfo (e, tb1->unSharedOf ()->mutableOf ()); + tinfo = build_typeinfo (e, mutableOf (unSharedOf (tb1))); } else { @@ -2170,7 +2170,7 @@ public: { /* Generate a slice for non-zero initialized aggregates, otherwise create an empty array. */ - gcc_assert (e->type == Type::tvoid->arrayOf ()->constOf ()); + gcc_assert (e->type == constOf (Type::tvoid->arrayOf ())); tree type = build_ctype (e->type); tree length = size_int (sd->dsym->structsize); @@ -2709,17 +2709,16 @@ public: void visit (AssocArrayLiteralExp *e) final override { - if (e->lowering != NULL) + if (this->constp_ && e->lowering != NULL) { /* When an associative array literal gets lowered, it's converted into a struct literal suitable for static initialization. */ - gcc_assert (this->constp_); this->result_ = build_expr (e->lowering, this->constp_, true); return ; } /* Want the mutable type for typeinfo reference. */ - Type *tb = e->type->toBasetype ()->mutableOf (); + Type *tb = mutableOf (e->type->toBasetype ()); /* Handle empty assoc array literals. */ TypeAArray *ta = tb->isTypeAArray (); diff --git a/gcc/d/runtime.cc b/gcc/d/runtime.cc index 8a47ac119662..9d11e7e132a2 100644 --- a/gcc/d/runtime.cc +++ b/gcc/d/runtime.cc @@ -150,11 +150,11 @@ get_libcall_type (d_libcall_type type) break; case LCT_CONST_TYPEINFO: - libcall_types[type] = Type::dtypeinfo->type->constOf (); + libcall_types[type] = constOf (Type::dtypeinfo->type); break; case LCT_CONST_CLASSINFO: - libcall_types[type] = Type::typeinfoclass->type->constOf (); + libcall_types[type] = constOf (Type::typeinfoclass->type); break; case LCT_ARRAY_VOID: @@ -202,7 +202,7 @@ get_libcall_type (d_libcall_type type) break; case LCT_IMMUTABLE_CHARPTR: - libcall_types[type] = Type::tchar->pointerTo ()->immutableOf (); + libcall_types[type] = immutableOf (Type::tchar->pointerTo ()); break; default: diff --git a/gcc/d/typeinfo.cc b/gcc/d/typeinfo.cc index 1600ca92bd4e..3dbda55ad2b1 100644 --- a/gcc/d/typeinfo.cc +++ b/gcc/d/typeinfo.cc @@ -577,7 +577,7 @@ public: void visit (TypeInfoConstDeclaration *d) final override { - Type *tm = d->tinfo->mutableOf (); + Type *tm = mutableOf (d->tinfo); tm = merge2 (tm); /* The vtable for TypeInfo_Const. */ @@ -594,7 +594,7 @@ public: void visit (TypeInfoInvariantDeclaration *d) final override { - Type *tm = d->tinfo->mutableOf (); + Type *tm = mutableOf (d->tinfo); tm = merge2 (tm); /* The vtable for TypeInfo_Invariant. */ @@ -611,7 +611,7 @@ public: void visit (TypeInfoSharedDeclaration *d) final override { - Type *tm = d->tinfo->unSharedOf (); + Type *tm = unSharedOf (d->tinfo); tm = merge2 (tm); /* The vtable for TypeInfo_Shared. */ @@ -628,7 +628,7 @@ public: void visit (TypeInfoWildDeclaration *d) final override { - Type *tm = d->tinfo->mutableOf (); + Type *tm = mutableOf (d->tinfo); tm = merge2 (tm); /* The vtable for TypeInfo_Inout. */ diff --git a/gcc/d/types.cc b/gcc/d/types.cc index ca574fd46dfc..4e14b158bea5 100644 --- a/gcc/d/types.cc +++ b/gcc/d/types.cc @@ -1329,7 +1329,7 @@ build_ctype (Type *t) t->accept (&v); else { - Type *tb = t->castMod (0); + Type *tb = castMod (t, 0); if (!tb->ctype) tb->accept (&v); t->ctype = insert_type_modifiers (tb->ctype, t->mod); diff --git a/gcc/testsuite/gdc.test/compilable/ddoc4162.d b/gcc/testsuite/gdc.test/compilable/ddoc4162.d index dd2447580d1f..f609fc9d043d 100644 --- a/gcc/testsuite/gdc.test/compilable/ddoc4162.d +++ b/gcc/testsuite/gdc.test/compilable/ddoc4162.d @@ -1,4 +1,4 @@ -// PERMUTE_ARGS: +// PERMUTE_ARGS: // REQUIRED_ARGS: -D -Dd${RESULTS_DIR}/compilable -o- // POST_SCRIPT: compilable/extra-files/ddocAny-postscript.sh diff --git a/gcc/testsuite/gdc.test/compilable/ddoc5446.d b/gcc/testsuite/gdc.test/compilable/ddoc5446.d index 29cb8c9cefd7..2da477f67017 100644 --- a/gcc/testsuite/gdc.test/compilable/ddoc5446.d +++ b/gcc/testsuite/gdc.test/compilable/ddoc5446.d @@ -1,4 +1,4 @@ -// PERMUTE_ARGS: +// PERMUTE_ARGS: // REQUIRED_ARGS: -D -Dd${RESULTS_DIR}/compilable -o- // EXTRA_FILES: ddoc5446a.d ddoc5446b.d // POST_SCRIPT: compilable/extra-files/ddocAny-postscript.sh diff --git a/gcc/testsuite/gdc.test/compilable/ddoc7795.d b/gcc/testsuite/gdc.test/compilable/ddoc7795.d index 2a6ba02787ef..9ad774071095 100644 --- a/gcc/testsuite/gdc.test/compilable/ddoc7795.d +++ b/gcc/testsuite/gdc.test/compilable/ddoc7795.d @@ -1,4 +1,4 @@ -// PERMUTE_ARGS: +// PERMUTE_ARGS: // REQUIRED_ARGS: -D -Dd${RESULTS_DIR}/compilable -o- // POST_SCRIPT: compilable/extra-files/ddocAny-postscript.sh diff --git a/gcc/testsuite/gdc.test/compilable/ddoc12.d b/gcc/testsuite/gdc.test/compilable/ddoc_bom_UTF8.d similarity index 100% rename from gcc/testsuite/gdc.test/compilable/ddoc12.d rename to gcc/testsuite/gdc.test/compilable/ddoc_bom_UTF8.d diff --git a/gcc/testsuite/gdc.test/compilable/test24338.d b/gcc/testsuite/gdc.test/compilable/test24338.d new file mode 100644 index 000000000000..467b8bd71cb8 --- /dev/null +++ b/gcc/testsuite/gdc.test/compilable/test24338.d @@ -0,0 +1,10 @@ +// https://issues.dlang.org/show_bug.cgi?id=24338 + +enum Foo: char[4] +{ + elem = "test" +} + +immutable a = [Foo.elem]; +immutable b = [Foo.elem]; +immutable c = a ~ b; diff --git a/gcc/testsuite/gdc.test/fail_compilation/discard_value.d b/gcc/testsuite/gdc.test/fail_compilation/discard_value.d new file mode 100644 index 000000000000..7fe30a687065 --- /dev/null +++ b/gcc/testsuite/gdc.test/fail_compilation/discard_value.d @@ -0,0 +1,34 @@ +/* +TEST_OUTPUT: +--- +fail_compilation/discard_value.d(24): Error: the result of the equality expression `3 is 3` is discarded +fail_compilation/discard_value.d(25): Error: the result of the equality expression `null !is null` is discarded +fail_compilation/discard_value.d(26): Error: the result of the equality expression `v == 0` is discarded +fail_compilation/discard_value.d(27): Error: the result of the equality expression `v == 0` is discarded +fail_compilation/discard_value.d(28): Error: `!__equals("", "")` has no effect +fail_compilation/discard_value.d(29): Error: the result of the equality expression `"" == ""` is discarded +fail_compilation/discard_value.d(30): Error: the result of the equality expression `fun().i == 4` is discarded +fail_compilation/discard_value.d(30): note that `fun().i` may have a side effect +fail_compilation/discard_value.d(33): Error: the result of the equality expression `slice == slice[0..0]` is discarded +--- +*/ + +struct S { int i; } + +S fun() { return S(42); } + +int v; + +void main() +{ + 3 is 3; + null !is null; + true && v == 0; + true || v == 0; + "" != ""; + "" == ""; // https://issues.dlang.org/show_bug.cgi?id=24359 + fun().i == 4; // https://issues.dlang.org/show_bug.cgi?id=12390 + + int[] slice = [0, 1]; + slice == slice[0 .. 0]; +} diff --git a/gcc/testsuite/gdc.test/fail_compilation/fail12390.d b/gcc/testsuite/gdc.test/fail_compilation/fail12390.d deleted file mode 100644 index 5c852a1ac917..000000000000 --- a/gcc/testsuite/gdc.test/fail_compilation/fail12390.d +++ /dev/null @@ -1,16 +0,0 @@ -/* -TEST_OUTPUT: ---- -fail_compilation/fail12390.d(15): Error: the result of the equality expression `fun().i == 4` is discarded -fail_compilation/fail12390.d(15): note that `fun().i` may have a side effect ---- -*/ - -struct S { int i; } - -S fun() { return S(42); } - -void main() -{ - fun().i == 4; -} diff --git a/gcc/testsuite/gdc.test/fail_compilation/gag4269a.d b/gcc/testsuite/gdc.test/fail_compilation/gag4269a.d index 3ab4db778679..85a146c14ad4 100644 --- a/gcc/testsuite/gdc.test/fail_compilation/gag4269a.d +++ b/gcc/testsuite/gdc.test/fail_compilation/gag4269a.d @@ -1,4 +1,4 @@ -// REQUIRED_ARGS: -c -o- +// REQUIRED_ARGS: -c -o- /* TEST_OUTPUT: --- diff --git a/gcc/testsuite/gdc.test/fail_compilation/gag4269b.d b/gcc/testsuite/gdc.test/fail_compilation/gag4269b.d index 718fa942ef23..e680721b213a 100644 --- a/gcc/testsuite/gdc.test/fail_compilation/gag4269b.d +++ b/gcc/testsuite/gdc.test/fail_compilation/gag4269b.d @@ -1,4 +1,4 @@ -// REQUIRED_ARGS: -c -o- +// REQUIRED_ARGS: -c -o- /* TEST_OUTPUT: --- diff --git a/gcc/testsuite/gdc.test/fail_compilation/gag4269c.d b/gcc/testsuite/gdc.test/fail_compilation/gag4269c.d index 1a9383148cd0..1fa1567cde84 100644 --- a/gcc/testsuite/gdc.test/fail_compilation/gag4269c.d +++ b/gcc/testsuite/gdc.test/fail_compilation/gag4269c.d @@ -1,4 +1,4 @@ -// REQUIRED_ARGS: -c -o- +// REQUIRED_ARGS: -c -o- /* TEST_OUTPUT: --- diff --git a/gcc/testsuite/gdc.test/fail_compilation/gag4269d.d b/gcc/testsuite/gdc.test/fail_compilation/gag4269d.d index bdfabaecc9e7..3154ea580fc3 100644 --- a/gcc/testsuite/gdc.test/fail_compilation/gag4269d.d +++ b/gcc/testsuite/gdc.test/fail_compilation/gag4269d.d @@ -1,4 +1,4 @@ -// REQUIRED_ARGS: -c -o- +// REQUIRED_ARGS: -c -o- /* TEST_OUTPUT: --- diff --git a/gcc/testsuite/gdc.test/fail_compilation/gag4269e.d b/gcc/testsuite/gdc.test/fail_compilation/gag4269e.d index d6eed626b874..4a5757cdd7d2 100644 --- a/gcc/testsuite/gdc.test/fail_compilation/gag4269e.d +++ b/gcc/testsuite/gdc.test/fail_compilation/gag4269e.d @@ -1,4 +1,4 @@ -// REQUIRED_ARGS: -c -o- +// REQUIRED_ARGS: -c -o- /* TEST_OUTPUT: --- diff --git a/gcc/testsuite/gdc.test/fail_compilation/gag4269f.d b/gcc/testsuite/gdc.test/fail_compilation/gag4269f.d index b571059eb453..db781e9879c2 100644 --- a/gcc/testsuite/gdc.test/fail_compilation/gag4269f.d +++ b/gcc/testsuite/gdc.test/fail_compilation/gag4269f.d @@ -1,4 +1,4 @@ -// REQUIRED_ARGS: -c -o- +// REQUIRED_ARGS: -c -o- /* TEST_OUTPUT: --- diff --git a/gcc/testsuite/gdc.test/fail_compilation/gag4269g.d b/gcc/testsuite/gdc.test/fail_compilation/gag4269g.d index 348207e0d5e5..4799fa13c1f7 100644 --- a/gcc/testsuite/gdc.test/fail_compilation/gag4269g.d +++ b/gcc/testsuite/gdc.test/fail_compilation/gag4269g.d @@ -1,4 +1,4 @@ -// REQUIRED_ARGS: -c -o- +// REQUIRED_ARGS: -c -o- /* TEST_OUTPUT: --- diff --git a/gcc/testsuite/gdc.test/fail_compilation/hexstring.d b/gcc/testsuite/gdc.test/fail_compilation/hexstring.d index caca3b3e97e7..95b07e763fff 100644 --- a/gcc/testsuite/gdc.test/fail_compilation/hexstring.d +++ b/gcc/testsuite/gdc.test/fail_compilation/hexstring.d @@ -2,8 +2,6 @@ TEST_OUTPUT: --- fail_compilation/hexstring.d(29): Error: cannot implicitly convert expression `"123F"` of type `string` to `immutable(ubyte[])` -fail_compilation/hexstring.d(30): Error: cannot implicitly convert expression `x"123F"c` of type `string` to `immutable(ubyte[])` -fail_compilation/hexstring.d(31): Error: cannot implicitly convert expression `x"123F"` of type `string` to `immutable(ubyte[])` fail_compilation/hexstring.d(33): Error: hex string length 1 must be a multiple of 2 to cast to `immutable(ushort[])` fail_compilation/hexstring.d(34): Error: hex string length 3 must be a multiple of 4 to cast to `immutable(uint[])` fail_compilation/hexstring.d(35): Error: hex string length 5 must be a multiple of 8 to cast to `immutable(ulong[])` @@ -13,6 +11,8 @@ fail_compilation/hexstring.d(37): Error: array cast from `string` to `immutable( fail_compilation/hexstring.d(38): Error: array cast from `string` to `immutable(ushort[])` is not supported at compile time fail_compilation/hexstring.d(39): Error: array cast from `string` to `immutable(uint[])` is not supported at compile time fail_compilation/hexstring.d(39): perhaps remove postfix `c` from hex string +fail_compilation/hexstring.d(40): Error: hex string with `dstring` type needs to be multiple of 4 bytes, not 5 +fail_compilation/hexstring.d(41): Error: cannot implicitly convert expression `x"44332211"d` of type `dstring` to `immutable(float[])` fail_compilation/hexstring.d(28): Error: cannot implicitly convert expression `x"123F"` of type `string` to `ubyte[]` --- */ @@ -33,7 +33,9 @@ immutable ubyte[] f4 = cast(string) x"123F"; immutable ushort[] f5 = cast(immutable ushort[]) x"11"; immutable uint[] f6 = cast(immutable uint[]) x"112233"; immutable ulong[] f7 = cast(immutable ulong[]) x"1122334455"; -immutable ulong[] f8 = cast(immutable ulong[]) x"1122334455"w; +immutable ulong[] f8 = cast(immutable ulong[]) x"11223344"w; immutable uint[] f9 = cast(immutable uint[]) "ABCD"; immutable ushort[] f10 = cast(immutable ushort[]) (x"1122" ~ ""); immutable uint[] f11 = cast(immutable uint[]) x"AABBCCDD"c; +immutable uint[] f12 = x"1122334455"d; +immutable float[] f13 = x"11223344"d; diff --git a/gcc/testsuite/gdc.test/fail_compilation/ice10599.d b/gcc/testsuite/gdc.test/fail_compilation/ice10599.d index 6e9649c486b3..378894db4683 100644 --- a/gcc/testsuite/gdc.test/fail_compilation/ice10599.d +++ b/gcc/testsuite/gdc.test/fail_compilation/ice10599.d @@ -1,4 +1,4 @@ -// https://issues.dlang.org/show_bug.cgi?id=10599 +// https://issues.dlang.org/show_bug.cgi?id=10599 // ICE(interpret.c) /* TEST_OUTPUT: diff --git a/gcc/testsuite/gdc.test/fail_compilation/test24365.d b/gcc/testsuite/gdc.test/fail_compilation/test24365.d new file mode 100644 index 000000000000..9ec1e2ac3a97 --- /dev/null +++ b/gcc/testsuite/gdc.test/fail_compilation/test24365.d @@ -0,0 +1,20 @@ +// https://issues.dlang.org/show_bug.cgi?id=243645 + +/* +TEST_OUTPUT: +--- +fail_compilation/test24365.d(16): Error: `f` cannot be interpreted at compile time, because it has no available source code +fail_compilation/test24365.d(14): compile time context created here +fail_compilation/test24365.d(19): while evaluating: `static assert(r == 2)` +--- +*/ + +void main() +{ + enum r = () { + void f(); + f(); + return 2; + }(); + static assert(r == 2); +} diff --git a/gcc/testsuite/gdc.test/runnable/helloUTF8.d b/gcc/testsuite/gdc.test/runnable/helloUTF8.d deleted file mode 100644 index aed66134f097..000000000000 --- a/gcc/testsuite/gdc.test/runnable/helloUTF8.d +++ /dev/null @@ -1,16 +0,0 @@ -/* -PERMUTE_ARGS: -RUN_OUTPUT: ---- -hello world ---- -*/ - -extern(C) int printf(const char *, ...); - -int main(char[][] args) -{ - printf("hello world\n"); - - return 0; -} diff --git a/gcc/testsuite/gdc.test/runnable/literal.d b/gcc/testsuite/gdc.test/runnable/literal.d index 69971240d948..27b5543b6fce 100644 --- a/gcc/testsuite/gdc.test/runnable/literal.d +++ b/gcc/testsuite/gdc.test/runnable/literal.d @@ -260,6 +260,19 @@ void testHexstring() // Test printing StringExp with size 8 enum toStr(immutable ulong[] v) = v.stringof; static assert(toStr!y == `x"88776655443322119900FFEEDDCCBBAA"`); + + // Hex string postfixes + // https://issues.dlang.org/show_bug.cgi?id=24363 + wstring wStr = x"AA BB CC DD"w; + immutable int[] dStr = x"AA BB CC DD"d; + assert(wStr[0] == 0xAABB); + assert(wStr[1] == 0xCCDD); + assert(dStr[0] == 0xAABBCCDD); + + // Test sliceCmpStringWithArray with size 8 + static immutable ulong[] z0 = cast(immutable ulong[]) x"1111 1111 1111 1111 0000 000F 0000 0000"; + static immutable ulong[] z1 = [0x1111_1111_1111_1111, 0x0000_000E_0000_0000]; + static assert(z0 !is z1); } /***************************************************/ diff --git a/gcc/testsuite/gdc.test/runnable/staticaa.d b/gcc/testsuite/gdc.test/runnable/staticaa.d index 606b70e908a3..e5b25d1f66aa 100644 --- a/gcc/testsuite/gdc.test/runnable/staticaa.d +++ b/gcc/testsuite/gdc.test/runnable/staticaa.d @@ -154,6 +154,17 @@ void testLocalStatic() @trusted ///////////////////////////////////////////// +// https://issues.dlang.org/show_bug.cgi?id=24311 +enum E : int[int] { x = [123: 456] } + +void testEnumInit() +{ + E e = E.init; + assert(e[123] == 456); +} + +///////////////////////////////////////////// + void main() { testSimple(); @@ -163,4 +174,5 @@ void main() testClassInit(); testImmutable(); testLocalStatic(); + testEnumInit(); } diff --git a/gcc/testsuite/gdc.test/runnable/xtestenum.d b/gcc/testsuite/gdc.test/runnable/xtestenum.d index ce77782b88cd..4a4edd100898 100644 --- a/gcc/testsuite/gdc.test/runnable/xtestenum.d +++ b/gcc/testsuite/gdc.test/runnable/xtestenum.d @@ -155,6 +155,19 @@ class C7379 } } +/***********************************/ +// https://issues.dlang.org/show_bug.cgi?id=23515 + +enum Easing : void function() +{ + identity1 = (){}, +} + +void test23515() +{ + Easing.identity1(); +} + /***********************************/ int main() @@ -166,6 +179,7 @@ int main() test5(); test6(); test7(); + test23515(); printf("Success\n"); return 0; diff --git a/libphobos/libdruntime/MERGE b/libphobos/libdruntime/MERGE index 9217c654225b..57ac2dc69e75 100644 --- a/libphobos/libdruntime/MERGE +++ b/libphobos/libdruntime/MERGE @@ -1,4 +1,4 @@ -e7709452775d374c1e2dfb67566668ada3dec5fc +a6f10836997d0b5526c8c363d781b4029c77f09f The first line of this file holds the git revision number of the last merge done from the dlang/dmd repository. diff --git a/libphobos/libdruntime/core/atomic.d b/libphobos/libdruntime/core/atomic.d index ff7f7abf0c29..899e0b054ba1 100644 --- a/libphobos/libdruntime/core/atomic.d +++ b/libphobos/libdruntime/core/atomic.d @@ -88,14 +88,7 @@ enum MemoryOrder T atomicLoad(MemoryOrder ms = MemoryOrder.seq, T)(auto ref return scope const T val) pure nothrow @nogc @trusted if (!is(T == shared U, U) && !is(T == shared inout U, U) && !is(T == shared const U, U)) { - static if (__traits(isFloating, T)) - { - alias IntTy = IntForFloat!T; - IntTy r = core.internal.atomic.atomicLoad!ms(cast(IntTy*)&val); - return *cast(T*)&r; - } - else - return core.internal.atomic.atomicLoad!ms(cast(T*)&val); + return core.internal.atomic.atomicLoad!ms(cast(T*)&val); } /// Ditto @@ -137,13 +130,7 @@ void atomicStore(MemoryOrder ms = MemoryOrder.seq, T, V)(ref T val, V newval) pu // resolve implicit conversions T arg = newval; - static if (__traits(isFloating, T)) - { - alias IntTy = IntForFloat!T; - core.internal.atomic.atomicStore!ms(cast(IntTy*)&val, *cast(IntTy*)&arg); - } - else - core.internal.atomic.atomicStore!ms(&val, arg); + core.internal.atomic.atomicStore!ms(&val, arg); } /// Ditto @@ -246,14 +233,7 @@ in (atomicPtrIsProperlyAligned(here), "Argument `here` is not properly aligned") // resolve implicit conversions T arg = exchangeWith; - static if (__traits(isFloating, T)) - { - alias IntTy = IntForFloat!T; - IntTy r = core.internal.atomic.atomicExchange!ms(cast(IntTy*)here, *cast(IntTy*)&arg); - return *cast(shared(T)*)&r; - } - else - return core.internal.atomic.atomicExchange!ms(here, arg); + return core.internal.atomic.atomicExchange!ms(here, arg); } /// Ditto @@ -314,14 +294,7 @@ template cas(MemoryOrder succ = MemoryOrder.seq, MemoryOrder fail = MemoryOrder. const T arg1 = ifThis; T arg2 = writeThis; - static if (__traits(isFloating, T)) - { - alias IntTy = IntForFloat!T; - return atomicCompareExchangeStrongNoResult!(succ, fail)( - cast(IntTy*)here, *cast(IntTy*)&arg1, *cast(IntTy*)&arg2); - } - else - return atomicCompareExchangeStrongNoResult!(succ, fail)(here, arg1, arg2); + return atomicCompareExchangeStrongNoResult!(succ, fail)(here, arg1, arg2); } /// Compare-and-set for shared value type @@ -364,14 +337,7 @@ template cas(MemoryOrder succ = MemoryOrder.seq, MemoryOrder fail = MemoryOrder. // resolve implicit conversions T arg1 = writeThis; - static if (__traits(isFloating, T)) - { - alias IntTy = IntForFloat!T; - return atomicCompareExchangeStrong!(succ, fail)( - cast(IntTy*)here, cast(IntTy*)ifThis, *cast(IntTy*)&writeThis); - } - else - return atomicCompareExchangeStrong!(succ, fail)(here, ifThis, writeThis); + return atomicCompareExchangeStrong!(succ, fail)(here, ifThis, writeThis); } /// Compare and exchange for mixed-`shared`ness types diff --git a/libphobos/libdruntime/core/demangle.d b/libphobos/libdruntime/core/demangle.d index f11315914d37..5a6ad6f5cf5e 100644 --- a/libphobos/libdruntime/core/demangle.d +++ b/libphobos/libdruntime/core/demangle.d @@ -79,6 +79,17 @@ pure @safe: AddType addType = AddType.yes; bool mute = false; Hooks hooks; + bool hasErrors = false; + + /// Called when encountering an error / unrecognized mangle. + /// + /// Currently, errors simply make `demangle` return + /// the input string, but the `msg` string can be used for debugging. + /// As a future enhancement, error handlers can be supplied through `Hooks` + void error(string msg = "error") + { + hasErrors = true; + } ////////////////////////////////////////////////////////////////////////// // Type Testing and Conversion @@ -93,7 +104,7 @@ pure @safe: } - static bool isDigit( char val ) + static bool isDigit( char val ) nothrow { return '0' <= val && '9' >= val; } @@ -107,7 +118,7 @@ pure @safe: } - static ubyte ascii2hex( char val ) + static ubyte ascii2hex( out bool errStatus, char val ) nothrow { if (val >= 'a' && val <= 'f') return cast(ubyte)(val - 'a' + 10); @@ -115,13 +126,15 @@ pure @safe: return cast(ubyte)(val - 'A' + 10); if (val >= '0' && val <= '9') return cast(ubyte)(val - '0'); - error(); + + errStatus = true; + return 0; } - char[] shift(scope const(char)[] val) return scope + BufSlice shift(scope const BufSlice val) return scope { if (mute) - return null; + return dst.bslice_empty; return dst.shift(val); } @@ -138,7 +151,12 @@ pure @safe: put(val[]); } - void put(scope const(char)[] val) return scope + void put(scope BufSlice val) return scope + { + put(val.getSlice); + } + + void put(scope const(char)[] val) return scope nothrow { if (mute) return; @@ -173,11 +191,14 @@ pure @safe: } - void silent( void delegate() pure @safe dg ) + void silent( out bool err_status, void delegate(out bool err_status) pure @safe nothrow dg ) nothrow { debug(trace) printf( "silent+\n" ); debug(trace) scope(success) printf( "silent-\n" ); - auto n = dst.length; dg(); dst.len = n; + auto n = dst.length; + dg(err_status); + if(!err_status) + dst.len = n; } @@ -205,41 +226,43 @@ pure @safe: } - void test( char val ) + bool test( char val ) nothrow { - if ( val != front ) - error(); + return val == front; } - - void popFront() + void popFront() nothrow { if ( pos++ >= buf.length ) - error(); + assert(false); } - void popFront(int i) + void popFront(int i) nothrow { while (i--) popFront(); } - void match( char val ) + bool match( char val ) nothrow { - test( val ); - popFront(); + if (!test(val)) + return false; + else + { + popFront(); + return true; + } } - - void match( const(char)[] val ) + bool match( const(char)[] val ) nothrow { foreach (char e; val ) - { - test( e ); - popFront(); - } + if (!match( e )) + return false; + + return true; } @@ -249,7 +272,7 @@ pure @safe: popFront(); } - bool isSymbolNameFront() + bool isSymbolNameFront(out bool errStatus) nothrow { char val = front; if ( isDigit( val ) || val == '_' ) @@ -259,21 +282,28 @@ pure @safe: // check the back reference encoding after 'Q' val = peekBackref(); + if (val == 0) + { + // invalid back reference + errStatus = true; + return false; + } + return isDigit( val ); // identifier ref } // return the first character at the back reference - char peekBackref() + char peekBackref() nothrow { assert( front == 'Q' ); auto n = decodeBackref!1(); if (!n || n > pos) - error("invalid back reference"); + return 0; // invalid back reference return buf[pos - n]; } - size_t decodeBackref(size_t peekAt = 0)() + size_t decodeBackref(size_t peekAt = 0)() nothrow { enum base = 26; size_t n = 0; @@ -292,7 +322,8 @@ pure @safe: if (t < 'A' || t > 'Z') { if (t < 'a' || t > 'z') - error("invalid back reference"); + return 0; // invalid back reference + n = base * n + t - 'a'; return n; } @@ -328,16 +359,15 @@ pure @safe: } - size_t decodeNumber() scope + size_t decodeNumber(out bool errStatus) scope nothrow { debug(trace) printf( "decodeNumber+\n" ); debug(trace) scope(success) printf( "decodeNumber-\n" ); - return decodeNumber( sliceNumber() ); + return decodeNumber( errStatus, sliceNumber() ); } - - size_t decodeNumber( scope const(char)[] num ) scope + size_t decodeNumber( out bool errStatus, scope const(char)[] num ) scope nothrow { debug(trace) printf( "decodeNumber+\n" ); debug(trace) scope(success) printf( "decodeNumber-\n" ); @@ -352,13 +382,15 @@ pure @safe: val = mulu(val, 10, overflow); val = addu(val, c - '0', overflow); if (overflow) - error(); + { + errStatus = true; + return 0; + } } return val; } - - void parseReal() scope + void parseReal(out bool errStatus) scope nothrow { debug(trace) printf( "parseReal+\n" ); debug(trace) scope(success) printf( "parseReal-\n" ); @@ -367,9 +399,15 @@ pure @safe: size_t tlen = 0; real val = void; + void onError() + { + errStatus = true; + } + if ( 'I' == front ) { - match( "INF" ); + if (!match("INF")) + return onError(); put( "real.infinity" ); return; } @@ -378,13 +416,15 @@ pure @safe: popFront(); if ( 'I' == front ) { - match( "INF" ); + if (!match("INF")) + return onError(); put( "-real.infinity" ); return; } if ( 'A' == front ) { - match( "AN" ); + if (!match("AN")) + return onError(); put( "real.nan" ); return; } @@ -393,18 +433,23 @@ pure @safe: tbuf[tlen++] = '0'; tbuf[tlen++] = 'X'; - if ( !isHexDigit( front ) ) - error( "Expected hex digit" ); + errStatus = !isHexDigit( front ); + if (errStatus) + return; // Expected hex digit + tbuf[tlen++] = front; tbuf[tlen++] = '.'; popFront(); while ( isHexDigit( front ) ) { + if (tlen >= tbuf.length) + return onError(); // Too many hex float digits tbuf[tlen++] = front; popFront(); } - match( 'P' ); + if (!match('P')) + return onError(); tbuf[tlen++] = 'p'; if ( 'N' == front ) { @@ -449,14 +494,23 @@ pure @safe: Namechar Namechar Namechars */ - void parseLName() scope + void parseLName(out string errMsg) scope nothrow { debug(trace) printf( "parseLName+\n" ); debug(trace) scope(success) printf( "parseLName-\n" ); static if (__traits(hasMember, Hooks, "parseLName")) - if (hooks.parseLName(this)) + { + auto r = hooks.parseLName(errMsg, this); + if (errMsg !is null) return; + if (r) return; + } + + void error(string msg) + { + errMsg = msg; + } if ( front == 'Q' ) { @@ -464,31 +518,39 @@ pure @safe: auto refPos = pos; popFront(); size_t n = decodeBackref(); - if ( !n || n > refPos ) - error( "Invalid LName back reference" ); + if (!n || n > refPos) + return error("Invalid LName back reference"); + if ( !mute ) { auto savePos = pos; scope(exit) pos = savePos; pos = refPos - n; - parseLName(); + parseLName(errMsg); } return; } - auto n = decodeNumber(); + + bool err_flag; + auto n = decodeNumber(err_flag); + if (err_flag) + return error("Number overflow"); + if ( n == 0 ) { put( "__anonymous" ); return; } if ( n > buf.length || n > buf.length - pos ) - error( "LName must be at least 1 character" ); + return error("LName must be at least 1 character"); + if ( '_' != front && !isAlpha( front ) ) - error( "Invalid character in LName" ); + return error("Invalid character in LName"); + foreach (char e; buf[pos + 1 .. pos + n] ) { if ( '_' != e && !isAlpha( e ) && !isDigit( e ) ) - error( "Invalid character in LName" ); + return error("Invalid character in LName"); } put( buf[pos .. pos + n] ); @@ -671,7 +733,7 @@ pure @safe: TypeTuple: B Number Arguments */ - char[] parseType() return scope + BufSlice parseType() return scope nothrow { static immutable string[23] primitives = [ "char", // a @@ -700,30 +762,45 @@ pure @safe: ]; static if (__traits(hasMember, Hooks, "parseType")) - if (auto n = hooks.parseType(this, null)) - return n; + { + auto n = hooks.parseType(this, null); + if (this.hasErrors) + return dst.bslice_empty; + else + if (n !is null) + return BufSlice(n, 0, n.length); + } debug(trace) printf( "parseType+\n" ); debug(trace) scope(success) printf( "parseType-\n" ); auto beg = dst.length; auto t = front; - char[] parseBackrefType(scope char[] delegate() pure @safe parseDg) pure @safe + BufSlice parseBackrefType(scope BufSlice delegate() pure @safe nothrow parseDg) pure @safe nothrow { if (pos == brp) - error("recursive back reference"); + { + this.error("recursive back reference"); + return dst.bslice_empty; + } + auto refPos = pos; popFront(); auto n = decodeBackref(); if (n == 0 || n > pos) - error("invalid back reference"); + { + this.error("invalid back reference"); + return dst.bslice_empty; + } + if ( mute ) - return null; + return dst.bslice_empty; auto savePos = pos; auto saveBrp = brp; scope(success) { pos = savePos; brp = saveBrp; } pos = refPos - n; brp = refPos; + auto ret = parseDg(); return ret; } @@ -731,7 +808,8 @@ pure @safe: switch ( t ) { case 'Q': // Type back reference - return parseBackrefType(() => parseType()); + auto r = parseBackrefType(() => parseType()); + return r; case 'O': // Shared (O Type) popFront(); put( "shared(" ); @@ -773,6 +851,7 @@ pure @safe: return dst[beg .. $]; default: error(); + return dst.bslice_empty; } case 'A': // TypeArray (A Type) popFront(); @@ -791,6 +870,8 @@ pure @safe: popFront(); // skip t1 auto tx = parseType(); + if (this.hasErrors) + return dst.bslice_empty; parseType(); put( '[' ); shift(tx); @@ -802,21 +883,46 @@ pure @safe: put( '*' ); return dst[beg .. $]; case 'F': case 'U': case 'W': case 'V': case 'R': // TypeFunction - return parseTypeFunction(); + bool errStatus; + auto r = parseTypeFunction(errStatus); + if (errStatus) + { + error(); + return dst.bslice_empty; + } + return r; case 'C': // TypeClass (C LName) case 'S': // TypeStruct (S LName) case 'E': // TypeEnum (E LName) case 'T': // TypeTypedef (T LName) popFront(); - parseQualifiedName(); + bool errStatus; + parseQualifiedName(errStatus); + if (errStatus) + return dst.bslice_empty; return dst[beg .. $]; case 'D': // TypeDelegate (D TypeFunction) popFront(); auto modifiers = parseModifier(); if ( front == 'Q' ) - parseBackrefType(() => parseTypeFunction(IsDelegate.yes)); + { + bool errStatus; + auto r = parseBackrefType(() => parseTypeFunction(errStatus, IsDelegate.yes)); + if (errStatus) + { + error(); + return dst.bslice_empty; + } + return r; + } else - parseTypeFunction(IsDelegate.yes); + { + bool errStatus; + parseTypeFunction(errStatus, IsDelegate.yes); + if (this.hasErrors || errStatus) + return dst.bslice_empty; + } + if (modifiers) { // write modifiers behind the function arguments @@ -866,10 +972,12 @@ pure @safe: put( "ucent" ); return dst[beg .. $]; default: - error(); + error("unknown type"); + return dst.bslice_empty; } } - error(); + error("unknown type"); + return dst.bslice_empty; } } @@ -945,7 +1053,7 @@ pure @safe: Y // variadic T t...) style Z // not variadic */ - void parseCallConvention() + void parseCallConvention(out bool errStatus) nothrow { // CallConvention switch ( front ) @@ -966,7 +1074,7 @@ pure @safe: put( "extern (C++) " ); break; default: - error(); + errStatus = true; } } @@ -1004,7 +1112,7 @@ pure @safe: } } - ushort parseFuncAttr() + ushort parseFuncAttr(out bool errStatus) nothrow { // FuncAttrs ushort result; @@ -1081,13 +1189,14 @@ pure @safe: result |= FuncAttributes.Live; continue; default: - error(); + errStatus = true; + return 0; } } return result; } - void parseFuncArguments() scope + void parseFuncArguments(out bool errStatus) scope nothrow { // Arguments for ( size_t n = 0; true; n++ ) @@ -1179,6 +1288,7 @@ pure @safe: else pos--; } + switch ( front ) { case 'I': // in (I Type) @@ -1215,19 +1325,26 @@ pure @safe: TypeFunction: CallConvention FuncAttrs Arguments ArgClose Type */ - char[] parseTypeFunction(IsDelegate isdg = IsDelegate.no) return scope + BufSlice parseTypeFunction(out bool errStatus, IsDelegate isdg = IsDelegate.no) return scope nothrow { debug(trace) printf( "parseTypeFunction+\n" ); debug(trace) scope(success) printf( "parseTypeFunction-\n" ); auto beg = dst.length; - parseCallConvention(); - auto attributes = parseFuncAttr(); + parseCallConvention(errStatus); + if (errStatus) + return dst.bslice_empty; + + auto attributes = parseFuncAttr(errStatus); + if (errStatus) + return dst.bslice_empty; auto argbeg = dst.length; put(IsDelegate.yes == isdg ? "delegate" : "function"); put( '(' ); - parseFuncArguments(); + parseFuncArguments(errStatus); + if (errStatus) + return dst.bslice_empty; put( ')' ); if (attributes) { @@ -1245,6 +1362,8 @@ pure @safe: { auto retbeg = dst.length; parseType(); + if (this.hasErrors) + return dst.bslice_empty; put(' '); shift(dst[argbeg .. retbeg]); } @@ -1297,11 +1416,22 @@ pure @safe: E F */ - void parseValue(scope char[] name = null, char type = '\0' ) scope + + void parseValue(out bool errStatus) scope nothrow + { + parseValue(errStatus, dst.bslice_empty); + } + + void parseValue(out bool errStatus, scope BufSlice name, char type = '\0' ) scope nothrow { debug(trace) printf( "parseValue+\n" ); debug(trace) scope(success) printf( "parseValue-\n" ); + void onError() + { + errStatus = true; + } + // printf( "*** %c\n", front ); switch ( front ) { @@ -1311,39 +1441,55 @@ pure @safe: return; case 'i': popFront(); - if ( '0' > front || '9' < front ) - error( "Number expected" ); + if ('0' > front || '9' < front) + return onError(); // Number expected goto case; case '0': .. case '9': - parseIntegerValue( name, type ); + parseIntegerValue( errStatus, name, type ); return; case 'N': popFront(); put( '-' ); - parseIntegerValue( name, type ); + parseIntegerValue( errStatus, name, type ); return; case 'e': popFront(); - parseReal(); + parseReal(errStatus); return; case 'c': popFront(); - parseReal(); + parseReal(errStatus); + if (errStatus) + return; put( '+' ); - match( 'c' ); - parseReal(); + if (!match('c')) + return onError(); + parseReal(errStatus); + if (errStatus) + return; put( 'i' ); return; case 'a': case 'w': case 'd': char t = front; popFront(); - auto n = decodeNumber(); - match( '_' ); + auto n = decodeNumber(errStatus); + if (errStatus) + return; + if (!match('_')) + return onError(); put( '"' ); foreach (i; 0..n) { - auto a = ascii2hex( front ); popFront(); - auto b = ascii2hex( front ); popFront(); + auto a = ascii2hex( errStatus, front ); + if (errStatus) + return; + popFront(); + + auto b = ascii2hex( errStatus, front ); + if (errStatus) + return; + popFront(); + auto v = cast(char)((a << 4) | b); if (' ' <= v && v <= '~') // ASCII printable { @@ -1373,11 +1519,15 @@ pure @safe: // An array literal. Value is repeated Number times. popFront(); put( '[' ); - auto n = decodeNumber(); + auto n = decodeNumber(errStatus); + if (errStatus) + return; foreach ( i; 0 .. n ) { putComma(i); - parseValue(); + parseValue(errStatus); + if (errStatus) + return; } put( ']' ); return; @@ -1387,13 +1537,19 @@ pure @safe: // An associative array literal. Value is repeated 2*Number times. popFront(); put( '[' ); - auto n = decodeNumber(); + auto n = decodeNumber(errStatus); + if (errStatus) + return; foreach ( i; 0 .. n ) { putComma(i); - parseValue(); + parseValue(errStatus); + if (errStatus) + return; put(':'); - parseValue(); + parseValue(errStatus); + if (errStatus) + return; } put( ']' ); return; @@ -1404,11 +1560,15 @@ pure @safe: if ( name.length ) put( name ); put( '(' ); - auto n = decodeNumber(); + auto n = decodeNumber(errStatus); + if (errStatus) + return; foreach ( i; 0 .. n ) { putComma(i); - parseValue(); + parseValue(errStatus); + if (errStatus) + return; } put( ')' ); return; @@ -1417,14 +1577,15 @@ pure @safe: // A function literal symbol popFront(); parseMangledName(false, 1); + if (this.hasErrors) + errStatus = true; return; default: - error(); + errStatus = true; } } - - void parseIntegerValue( scope char[] name = null, char type = '\0' ) scope + void parseIntegerValue( out bool errStatus, scope BufSlice name, char type = '\0' ) scope nothrow { debug(trace) printf( "parseIntegerValue+\n" ); debug(trace) scope(success) printf( "parseIntegerValue-\n" ); @@ -1436,7 +1597,9 @@ pure @safe: case 'w': // dchar { auto val = sliceNumber(); - auto num = decodeNumber( val ); + auto num = decodeNumber( errStatus, val ); + if (errStatus) + return; switch ( num ) { @@ -1498,7 +1661,10 @@ pure @safe: } } case 'b': // bool - put( decodeNumber() ? "true" : "false" ); + auto d = decodeNumber(errStatus); + if (errStatus) + return; + put( d ? "true" : "false" ); return; case 'h', 't', 'k': // ubyte, ushort, uint put( sliceNumber() ); @@ -1534,7 +1700,7 @@ pure @safe: S Number_opt QualifiedName X ExternallyMangledName */ - void parseTemplateArgs() scope + void parseTemplateArgs(out bool errStatus) scope nothrow { debug(trace) printf( "parseTemplateArgs+\n" ); debug(trace) scope(success) printf( "parseTemplateArgs-\n" ); @@ -1551,6 +1717,11 @@ pure @safe: popFront(); putComma(n); parseType(); + if (this.hasErrors) + { + errStatus = true; + return; + } continue; case 'V': popFront(); @@ -1561,9 +1732,22 @@ pure @safe: // decrement len and let put/append do its thing. char t = front; // peek at type for parseValue if ( t == 'Q' ) + { t = peekBackref(); - char[] name; silent( delegate void() { name = parseType(); } ); - parseValue( name, t ); + if (t == 0) + { + // invalid back reference + errStatus = true; + return; + } + } + BufSlice name = dst.bslice_empty; + silent( errStatus, delegate void(out bool e_flg) nothrow { name = parseType(); } ); + if (errStatus) + return; + parseValue( errStatus, name, t ); + if (errStatus) + return; continue; case 'S': popFront(); @@ -1574,13 +1758,12 @@ pure @safe: auto l = dst.length; auto p = pos; auto b = brp; - try - { - debug(trace) printf( "may be mangled name arg\n" ); - parseMangledNameArg(); + + debug(trace) printf( "may be mangled name arg\n" ); + + if (parseMangledNameArg()) continue; - } - catch ( ParseException e ) + else { dst.len = l; pos = p; @@ -1592,34 +1775,46 @@ pure @safe: { // ambiguity: length followed by qualified name (starting with number) // try all possible pairs of numbers - auto qlen = decodeNumber() / 10; // last digit needed for QualifiedName + auto qlen = decodeNumber(errStatus); + if (errStatus) + return; + + qlen /= 10; // last digit needed for QualifiedName pos--; auto l = dst.length; auto p = pos; auto b = brp; while ( qlen > 0 ) { - try + errStatus = false; + parseQualifiedName(errStatus); + + if (!errStatus) { - parseQualifiedName(); if ( pos == p + qlen ) continue L_nextArg; } - catch ( ParseException e ) - { - } + qlen /= 10; // retry with one digit less pos = --p; dst.len = l; brp = b; } } - parseQualifiedName(); + + parseQualifiedName(errStatus); + if (errStatus) + return; continue; case 'X': popFront(); putComma(n); - parseLName(); + { + string errMsg; + parseLName(errMsg); + if (errMsg) + return; + } continue; default: return; @@ -1628,79 +1823,127 @@ pure @safe: } - bool mayBeMangledNameArg() + bool mayBeMangledNameArg() nothrow { debug(trace) printf( "mayBeMangledNameArg+\n" ); debug(trace) scope(success) printf( "mayBeMangledNameArg-\n" ); + bool errStatus; auto p = pos; scope(exit) pos = p; + if ( isDigit( buf[pos] ) ) { - auto n = decodeNumber(); - return n >= 4 && + auto n = decodeNumber(errStatus); + + return !errStatus && n >= 4 && pos < buf.length && '_' == buf[pos++] && pos < buf.length && 'D' == buf[pos++] && isDigit( buf[pos] ); } else { - return pos < buf.length && '_' == buf[pos++] && + const isSNF = isSymbolNameFront(errStatus); + + return !errStatus && + pos < buf.length && '_' == buf[pos++] && pos < buf.length && 'D' == buf[pos++] && - isSymbolNameFront(); + isSNF; } } - - void parseMangledNameArg() + bool parseMangledNameArg() nothrow { debug(trace) printf( "parseMangledNameArg+\n" ); debug(trace) scope(success) printf( "parseMangledNameArg-\n" ); size_t n = 0; if ( isDigit( front ) ) - n = decodeNumber(); - parseMangledName( false, n ); - } + { + bool errStatus; + n = decodeNumber(errStatus); + if (errStatus) + { + error(); + return false; + } + } + parseMangledName(false, n); + return !this.hasErrors; + } /* TemplateInstanceName: Number __T LName TemplateArgs Z */ - void parseTemplateInstanceName(bool hasNumber) scope + void parseTemplateInstanceName(out bool errStatus, bool hasNumber) scope nothrow { debug(trace) printf( "parseTemplateInstanceName+\n" ); debug(trace) scope(success) printf( "parseTemplateInstanceName-\n" ); auto sav = pos; auto saveBrp = brp; - scope(failure) + + void onError() { + errStatus = true; pos = sav; brp = saveBrp; } - auto n = hasNumber ? decodeNumber() : 0; + + size_t n = 0; + if (hasNumber) + { + n = decodeNumber(errStatus); + if (errStatus) + return onError(); + } + auto beg = pos; - match( "__T" ); - parseLName(); + errStatus = !match( "__T" ); + if (errStatus) + return onError(); + + { + string errMsg; + parseLName(errMsg); + if (errMsg !is null) + return onError(); + } + put( "!(" ); - parseTemplateArgs(); - match( 'Z' ); + + parseTemplateArgs(errStatus); + if (errStatus) + return onError(); + + if (!match('Z')) + return onError(); + if ( hasNumber && pos - beg != n ) - error( "Template name length mismatch" ); + { + // Template name length mismatch + return onError(); + } + put( ')' ); } - bool mayBeTemplateInstanceName() scope + bool mayBeTemplateInstanceName() scope nothrow { debug(trace) printf( "mayBeTemplateInstanceName+\n" ); debug(trace) scope(success) printf( "mayBeTemplateInstanceName-\n" ); auto p = pos; scope(exit) pos = p; - auto n = decodeNumber(); + + bool errStatus; + auto n = decodeNumber(errStatus); + if (errStatus) + return false; + return n >= 5 && pos < buf.length && '_' == buf[pos++] && pos < buf.length && '_' == buf[pos++] && @@ -1713,7 +1956,7 @@ pure @safe: LName TemplateInstanceName */ - void parseSymbolName() scope + void parseSymbolName(out bool errStatus) scope nothrow { debug(trace) printf( "parseSymbolName+\n" ); debug(trace) scope(success) printf( "parseSymbolName-\n" ); @@ -1724,7 +1967,7 @@ pure @safe: { case '_': // no length encoding for templates for new mangling - parseTemplateInstanceName(false); + parseTemplateInstanceName(errStatus, false); return; case '0': .. case '9': @@ -1732,13 +1975,11 @@ pure @safe: { auto t = dst.length; - try - { - debug(trace) printf( "may be template instance name\n" ); - parseTemplateInstanceName(true); + debug(trace) printf( "may be template instance name\n" ); + parseTemplateInstanceName(errStatus, true); + if (!errStatus) return; - } - catch ( ParseException e ) + else { debug(trace) printf( "not a template instance name\n" ); dst.len = t; @@ -1746,64 +1987,71 @@ pure @safe: } goto case; case 'Q': - parseLName(); + string errMsg; + parseLName(errMsg); + errStatus = errMsg !is null; return; default: - error(); + errStatus = true; } } // parse optional function arguments as part of a symbol name, i.e without return type // if keepAttr, the calling convention and function attributes are not discarded, but returned - char[] parseFunctionTypeNoReturn( bool keepAttr = false ) return scope + BufSlice parseFunctionTypeNoReturn( bool keepAttr = false ) return scope nothrow { // try to demangle a function, in case we are pointing to some function local auto prevpos = pos; auto prevlen = dst.length; auto prevbrp = brp; - try + if ( 'M' == front ) { - if ( 'M' == front ) + // do not emit "needs this" + popFront(); + auto modifiers = parseModifier(); + while (auto str = typeCtors.toStringConsume(modifiers)) { - // do not emit "needs this" - popFront(); - auto modifiers = parseModifier(); - while (auto str = typeCtors.toStringConsume(modifiers)) - { - put(str); - put(' '); - } + put(str); + put(' '); } - if ( isCallConvention( front ) ) + } + if ( isCallConvention( front ) ) + { + BufSlice attr = dst.bslice_empty; + // we don't want calling convention and attributes in the qualified name + bool errStatus; + parseCallConvention(errStatus); + if (!errStatus) { - char[] attr; - // we don't want calling convention and attributes in the qualified name - parseCallConvention(); - auto attributes = parseFuncAttr(); - if (keepAttr) { - while (auto str = funcAttrs.toStringConsume(attributes)) - { - put(str); - put(' '); + auto attributes = parseFuncAttr(errStatus); + if (!errStatus) + { + if (keepAttr) { + while (auto str = funcAttrs.toStringConsume(attributes)) + { + put(str); + put(' '); + } + attr = dst[prevlen .. $]; } - attr = dst[prevlen .. $]; - } - put( '(' ); - parseFuncArguments(); - put( ')' ); - return attr; + put( '(' ); + parseFuncArguments(errStatus); + if (errStatus) + return dst.bslice_empty; + put( ')' ); + return attr; + } } - } - catch ( ParseException ) - { + // not part of a qualified name, so back up pos = prevpos; dst.len = prevlen; brp = prevbrp; } - return null; + + return dst.bslice_empty; } /* @@ -1811,22 +2059,30 @@ pure @safe: SymbolName SymbolName QualifiedName */ - char[] parseQualifiedName() return scope + void parseQualifiedName(out bool errStatus) return scope nothrow { debug(trace) printf( "parseQualifiedName+\n" ); debug(trace) scope(success) printf( "parseQualifiedName-\n" ); - size_t beg = dst.length; + size_t n = 0; + bool is_sym_name_front; do { if ( n++ ) put( '.' ); - parseSymbolName(); + + parseSymbolName(errStatus); + if (errStatus) + return; + parseFunctionTypeNoReturn(); - } while ( isSymbolNameFront() ); - return dst[beg .. $]; + is_sym_name_front = isSymbolNameFront(errStatus); + if (errStatus) + return; + + } while ( is_sym_name_front ); } @@ -1835,32 +2091,44 @@ pure @safe: _D QualifiedName Type _D QualifiedName M Type */ - void parseMangledName( bool displayType, size_t n = 0 ) scope + void parseMangledName(bool displayType, size_t n = 0 ) scope nothrow { debug(trace) printf( "parseMangledName+\n" ); debug(trace) scope(success) printf( "parseMangledName-\n" ); - char[] name = null; + BufSlice name = dst.bslice_empty; auto end = pos + n; eat( '_' ); - match( 'D' ); + if (!match('D')) + return error(); + do { size_t beg = dst.length; size_t nameEnd = dst.length; - char[] attr; + BufSlice attr = dst.bslice_empty; + bool is_sym_name_front; + do { - if ( attr ) + if ( attr.length ) dst.remove(attr); // dump attributes of parent symbols if (beg != dst.length) put( '.' ); - parseSymbolName(); + + bool errStatus; + parseSymbolName(errStatus); + if (errStatus) + return error(); + nameEnd = dst.length; attr = parseFunctionTypeNoReturn( displayType ); - } while ( isSymbolNameFront() ); + is_sym_name_front = isSymbolNameFront(errStatus); + if (errStatus) + return error(); + } while (is_sym_name_front); if ( displayType ) { @@ -1875,6 +2143,9 @@ pure @safe: auto lastlen = dst.length; auto type = parseType(); + if (this.hasErrors) + return; + if ( displayType ) { if ( type.length ) @@ -1905,45 +2176,28 @@ pure @safe: } while ( true ); } - void parseMangledName() + void parseMangledName() nothrow { - parseMangledName( AddType.yes == addType ); + parseMangledName(AddType.yes == addType); } - char[] doDemangle(alias FUNC)() return scope + char[] doDemangle(alias FUNC)() return scope nothrow { while ( true ) { - try - { - debug(info) printf( "demangle(%.*s)\n", cast(int) buf.length, buf.ptr ); - FUNC(); - return dst[0 .. $]; - } - catch ( OverflowException e ) + debug(info) printf( "demangle(%.*s)\n", cast(int) buf.length, buf.ptr ); + + FUNC(); + if (!this.hasErrors) { - debug(trace) printf( "overflow... restarting\n" ); - auto a = Buffer.minSize; - auto b = 2 * dst.dst.length; - auto newsz = a < b ? b : a; - debug(info) printf( "growing dst to %lu bytes\n", newsz ); - dst.dst.length = newsz; - pos = dst.len = brp = 0; - continue; + return dst[0 .. $].getSlice; } - catch ( ParseException e ) + else { - debug(info) - { - auto msg = e.toString(); - printf( "error: %.*s\n", cast(int) msg.length, msg.ptr ); - } + debug(info) printf( "error" ); + return dst.copyInput(buf); } - catch ( Exception e ) - { - assert( false ); // no other exceptions thrown - } } } @@ -2058,8 +2312,13 @@ char[] reencodeMangled(return scope const(char)[] mangled) nothrow pure @safe } } - bool parseLName(scope ref Remangle d) scope @trusted + bool parseLName(out string errMsg, scope ref Remangle d) scope @trusted nothrow { + bool error(string msg) + { + errMsg = msg; + return false; + } flushPosition(d); auto reslen = result.length; @@ -2073,19 +2332,25 @@ char[] reencodeMangled(return scope const(char)[] mangled) nothrow pure @safe d.popFront(); size_t n = d.decodeBackref(); if (!n || n > refpos) - error("invalid back reference"); + return error("invalid back reference"); auto savepos = d.pos; scope(exit) d.pos = savepos; size_t srcpos = refpos - n; - auto idlen = d.decodeNumber(); + bool errStatus; + auto idlen = d.decodeNumber(errStatus); + if (errStatus) + return error("invalid number"); + if (d.pos + idlen > d.buf.length) - error("invalid back reference"); + return error("invalid back reference"); + auto id = d.buf[d.pos .. d.pos + idlen]; auto pid = id in idpos; if (!pid) - error("invalid back reference"); + return error("invalid back reference"); + npos = positionInResult(*pid); } encodeBackref(reslen - npos); @@ -2094,9 +2359,14 @@ char[] reencodeMangled(return scope const(char)[] mangled) nothrow pure @safe } else { - auto n = d.decodeNumber(); + bool errStatus; + auto n = d.decodeNumber(errStatus); + if (errStatus) + return error("invalid number"); + if (!n || n > d.buf.length || n > d.buf.length - d.pos) - error("LName too shot or too long"); + return error("LName too short or too long"); + auto id = d.buf[d.pos .. d.pos + n]; d.pos += n; if (auto pid = id in idpos) @@ -2117,8 +2387,9 @@ char[] reencodeMangled(return scope const(char)[] mangled) nothrow pure @safe return true; } - char[] parseType( ref Remangle d, char[] name = null ) return scope + char[] parseType(ref Remangle d, char[] name) return scope nothrow { + bool errStatus; if (d.front != 'Q') return null; @@ -2128,7 +2399,10 @@ char[] reencodeMangled(return scope const(char)[] mangled) nothrow pure @safe d.popFront(); auto n = d.decodeBackref(); if (n == 0 || n > refPos) - error("invalid back reference"); + { + d.error("invalid back reference"); + return null; + } size_t npos = positionInResult(refPos - n); size_t reslen = result.length; @@ -2159,18 +2433,18 @@ char[] reencodeMangled(return scope const(char)[] mangled) nothrow pure @safe auto d = Demangle!(PrependHooks)(mangled, null); d.hooks = PrependHooks(); d.mute = true; // no demangled output - try - { - d.parseMangledName(); - if (d.hooks.lastpos < d.pos) - d.hooks.result ~= d.buf[d.hooks.lastpos .. d.pos]; - return d.hooks.result; - } - catch (Exception) + + bool errStatus; + d.parseMangledName(errStatus); + if (d.hasErrors) { - // overflow exception cannot occur + // error cannot occur return mangled.dup; } + + if (d.hooks.lastpos < d.pos) + d.hooks.result ~= d.buf[d.hooks.lastpos .. d.pos]; + return d.hooks.result; } /** @@ -2511,6 +2785,9 @@ else ["_D3foo3FooQiMNgFNlNfZv", "inout scope @safe void foo.Foo.foo()"], ["_D3foo3Foo4foorMNgFNjNfZv", "inout return @safe void foo.Foo.foor()"], ["_D3foo3Foo3rabMNgFNlNjNfZv", "inout scope return @safe void foo.Foo.rab()"], + + // Hex float digit overflow + ["_D3foo__T1fVdeFA3D0FBFB72A3C33FFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFF", "_D3foo__T1fVdeFA3D0FBFB72A3C33FFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFF"], ]; @@ -2834,51 +3111,6 @@ private char[] demangleCXX(return scope const(char)[] buf, CXX_DEMANGLER __cxa_d return dst; } -/** - * Error handling through Exceptions - * - * The following types / functions are only used in this module, - * hence why the functions are `@trusted`. - * To make things `@nogc`, default-initialized instances are thrown. - */ -private class ParseException : Exception -{ - public this(string msg) @safe pure nothrow - { - super(msg); - } -} - -/// Ditto -private class OverflowException : Exception -{ - public this(string msg) @safe pure nothrow - { - super(msg); - } -} - -/// Ditto -private noreturn error(string msg = "Invalid symbol") @trusted pure -{ - version (DigitalMars) pragma(inline, false); // tame dmd inliner - - //throw new ParseException( msg ); - debug(info) printf( "error: %.*s\n", cast(int) msg.length, msg.ptr ); - throw __ctfe ? new ParseException(msg) - : cast(ParseException) __traits(initSymbol, ParseException).ptr; -} - -/// Ditto -private noreturn overflow(string msg = "Buffer overflow") @trusted pure -{ - version (DigitalMars) pragma(inline, false); // tame dmd inliner - - //throw new OverflowException( msg ); - debug(info) printf( "overflow: %.*s\n", cast(int) msg.length, msg.ptr ); - throw cast(OverflowException) __traits(initSymbol, OverflowException).ptr; -} - private struct Buffer { enum size_t minSize = 4000; @@ -2895,23 +3127,17 @@ private struct Buffer return this.len; } - public inout(char)[] opSlice (size_t from, size_t to) - inout return scope @safe pure nothrow @nogc + public BufSlice opSlice (size_t from, size_t to) + return scope @safe pure nothrow @nogc { - assert(from <= to); - assert(to <= len); - return this.dst[from .. to]; + return bslice(from, to); } - static bool contains(scope const(char)[] a, scope const(char)[] b) @trusted + static bool contains(scope const(char)[] a, scope const BufSlice b) @safe nothrow { - if (a.length && b.length) - { - auto bend = b.ptr + b.length; - auto aend = a.ptr + a.length; - return a.ptr <= b.ptr && bend <= aend; - } - return false; + return + b.from < a.length && + b.to <= a.length; } char[] copyInput(scope const(char)[] buf) @@ -2924,46 +3150,62 @@ private struct Buffer return r; } + private void checkAndStretchBuf(size_t len_to_add) scope nothrow + { + const required = len + len_to_add; + + if (required > dst.length) + dst.length = dst.length + len_to_add; + } + // move val to the end of the dst buffer - char[] shift(scope const(char)[] val) return scope + BufSlice shift(scope const BufSlice val) return scope nothrow { version (DigitalMars) pragma(inline, false); // tame dmd inliner if (val.length) { - assert( contains( dst[0 .. len], val ) ); - debug(info) printf( "shifting (%.*s)\n", cast(int) val.length, val.ptr ); + const ptrdiff_t s = val.from; + const size_t f = len; - if (len + val.length > dst.length) - overflow(); - size_t v = &val[0] - &dst[0]; - dst[len .. len + val.length] = val[]; - for (size_t p = v; p < len; p++) + assert(contains( dst[0 .. len], val ), + "\ndst=\""~dst[0 .. len]~"\"\n"~ + "val=\""~val.getSlice~"\"\n" + ); + + checkAndStretchBuf(val.length); + + // store value temporary over len index + dst[len .. len + val.length] = val.getSlice(); + + // shift all chars including temporary saved above + // if buf was allocated above it will be leave for further usage + for (size_t p = s; p < f; p++) dst[p] = dst[p + val.length]; - return dst[len - val.length .. len]; + return bslice(len - val.length, len); } - return null; + + return bslice_empty; } // remove val from dst buffer - void remove(scope const(char)[] val) scope + void remove(scope BufSlice val) scope nothrow { version (DigitalMars) pragma(inline, false); // tame dmd inliner if ( val.length ) { assert( contains( dst[0 .. len], val ) ); - debug(info) printf( "removing (%.*s)\n", cast(int) val.length, val.ptr ); - size_t v = &val[0] - &dst[0]; + assert( len >= val.length && len <= dst.length ); len -= val.length; - for (size_t p = v; p < len; p++) + for (size_t p = val.from; p < len; p++) dst[p] = dst[p + val.length]; } } - char[] append(scope const(char)[] val) return scope + void append(scope const(char)[] val) scope nothrow { version (DigitalMars) pragma(inline, false); // tame dmd inliner @@ -2971,25 +3213,71 @@ private struct Buffer { if ( !dst.length ) dst.length = minSize; - assert( !contains( dst[0 .. len], val ) ); + debug(info) printf( "appending (%.*s)\n", cast(int) val.length, val.ptr ); - if ( dst.length - len >= val.length && &dst[len] == &val[0] ) - { - // data is already in place - auto t = dst[len .. len + val.length]; - len += val.length; - return t; - } - if ( dst.length - len >= val.length ) - { + checkAndStretchBuf(val.length); + + // data is already not in place? + if ( &dst[len] != &val[0] ) dst[len .. len + val.length] = val[]; - auto t = dst[len .. len + val.length]; - len += val.length; - return t; - } - overflow(); + + len += val.length; + } + } + + @nogc: + + private scope bslice(size_t from, size_t to) nothrow + { + return BufSlice(dst, from, to); + } + + private static scope bslice_empty() nothrow + { + return BufSlice.init; + } +} + +private struct BufSlice +{ + char[] buf; + size_t from; + size_t to; + + @safe: + pure: + nothrow: + + @disable this(); + + this(return scope char[] buf) scope nothrow @nogc + { + this(buf, 0, 0); + } + + this(return scope char[] buf, size_t from, size_t to, bool lastArgIsLen = false) scope nothrow @nogc + { + this.buf = buf; + this.from = from; + + if (lastArgIsLen) + this.to = from + to; + else + this.to = to; + } + + invariant() + { + if (buf is null) + { + assert(from == 0); + assert(to == 0); } - return null; + + assert(from <= to); } + + auto getSlice() inout nothrow scope { return buf[from .. to]; } + size_t length() const scope { return to - from; } } diff --git a/libphobos/libdruntime/core/internal/atomic.d b/libphobos/libdruntime/core/internal/atomic.d index 3fd5d4a595dd..03d1c017c07d 100644 --- a/libphobos/libdruntime/core/internal/atomic.d +++ b/libphobos/libdruntime/core/internal/atomic.d @@ -54,7 +54,17 @@ version (DigitalMars) inout(T) atomicLoad(MemoryOrder order = MemoryOrder.seq, T)(inout(T)* src) pure nothrow @nogc @trusted if (CanCAS!T) { - static assert(order != MemoryOrder.rel, "invalid MemoryOrder for atomicLoad()"); + static assert(order != MemoryOrder.rel && order != MemoryOrder.acq_rel, + "invalid MemoryOrder for atomicLoad()"); + + // We place some storage on the stack, + // get a pointer to that (which is also stored on the stack) + // and then store the result of the load into the storage. + // Finally returning it. + // Anything other than this is calling convention specific, + // and that is very fail heavy. + size_t[2] storage = void; + size_t* resultValuePtr = cast(size_t*)&storage[0]; static if (T.sizeof == size_t.sizeof * 2) { @@ -62,107 +72,87 @@ version (DigitalMars) { asm pure nothrow @nogc @trusted { + push EBX; // call preserved push EDI; - push EBX; + mov EBX, 0; mov ECX, 0; mov EAX, 0; mov EDX, 0; + mov EDI, src; lock; cmpxchg8b [EDI]; - pop EBX; + + lea EBX, resultValuePtr; + mov EBX, [EBX]; + mov [EBX], EAX; + mov [EBX + size_t.sizeof], EDX; + pop EDI; + pop EBX; } } else version (D_InlineAsm_X86_64) { - version (Windows) + asm pure nothrow @nogc @trusted { - static if (RegisterReturn!T) - { - enum SrcPtr = SizedReg!CX; - enum RetPtr = null; - } - else - { - enum SrcPtr = SizedReg!DX; - enum RetPtr = SizedReg!CX; - } + push RBX; // call preserved - mixin (simpleFormat(q{ - asm pure nothrow @nogc @trusted - { - naked; - push RBX; - mov R8, %0; - ?1 mov R9, %1; - mov RBX, 0; - mov RCX, 0; - mov RAX, 0; - mov RDX, 0; - lock; cmpxchg16b [R8]; - ?1 mov [R9], RAX; - ?1 mov 8[R9], RDX; - pop RBX; - ret; - } - }, [SrcPtr, RetPtr])); - } - else - { - asm pure nothrow @nogc @trusted - { - naked; - push RBX; - mov RBX, 0; - mov RCX, 0; - mov RAX, 0; - mov RDX, 0; - lock; cmpxchg16b [RDI]; - pop RBX; - ret; - } + mov RBX, 0; + mov RCX, 0; + mov RAX, 0; + mov RDX, 0; + + mov R8, src; + lock; cmpxchg16b [R8]; + + lea RBX, resultValuePtr; + mov RBX, [RBX]; + mov [RBX], RAX; + mov [RBX + size_t.sizeof], RDX; + + pop RBX; } } + else + static assert(0, "Operation not supported"); + + return *cast(inout(T)*)resultValuePtr; } else static if (needsLoadBarrier!order) { version (D_InlineAsm_X86) { - enum SrcReg = SizedReg!CX; - enum ZeroReg = SizedReg!(DX, T); - enum ResReg = SizedReg!(AX, T); - - mixin (simpleFormat(q{ - asm pure nothrow @nogc @trusted - { - mov %1, 0; - mov %2, 0; - mov %0, src; - lock; cmpxchg [%0], %1; - } - }, [SrcReg, ZeroReg, ResReg])); } else version (D_InlineAsm_X86_64) { - version (Windows) - enum SrcReg = SizedReg!CX; - else - enum SrcReg = SizedReg!DI; - enum ZeroReg = SizedReg!(DX, T); - enum ResReg = SizedReg!(AX, T); - - mixin (simpleFormat(q{ - asm pure nothrow @nogc @trusted - { - naked; - mov %1, 0; - mov %2, 0; - lock; cmpxchg [%0], %1; - ret; - } - }, [SrcReg, ZeroReg, ResReg])); } + else + static assert(0, "Operation not supported"); + + enum SrcReg = SizedReg!CX; + enum ZeroReg = SizedReg!(DX, T); + enum ResReg = SizedReg!(AX, T); + enum TemporaryReg = SizedReg!(BX); + + mixin (simpleFormat(q{ + asm pure nothrow @nogc @trusted + { + push %3; // call preserved + + mov %1, 0; + mov %2, 0; + mov %0, src; + lock; cmpxchg [%0], %1; + lea %3, resultValuePtr; + mov %3, [%3]; + mov [%3], %2; + + pop %3; + } + }, [SrcReg, ZeroReg, ResReg, TemporaryReg])); + + return *cast(inout(T)*)resultValuePtr; } else return *src; @@ -171,7 +161,8 @@ version (DigitalMars) void atomicStore(MemoryOrder order = MemoryOrder.seq, T)(T* dest, T value) pure nothrow @nogc @trusted if (CanCAS!T) { - static assert(order != MemoryOrder.acq, "Invalid MemoryOrder for atomicStore()"); + static assert(order != MemoryOrder.acq && order != MemoryOrder.acq_rel, + "Invalid MemoryOrder for atomicStore()"); static if (T.sizeof == size_t.sizeof * 2) { @@ -293,48 +284,38 @@ version (DigitalMars) T atomicExchange(MemoryOrder order = MemoryOrder.seq, bool result = true, T)(T* dest, T value) pure nothrow @nogc @trusted if (CanCAS!T) { + static assert(order != MemoryOrder.acq, "Invalid MemoryOrder for atomicExchange()"); + // We place some storage on the stack, + // this storage and cast it to appropriete type. + // This is calling convention agnostic. + size_t storage = void; + version (D_InlineAsm_X86) { - static assert(T.sizeof <= 4, "64bit atomicExchange not supported on 32bit target." ); - - enum DestReg = SizedReg!CX; - enum ValReg = SizedReg!(AX, T); - - mixin (simpleFormat(q{ - asm pure nothrow @nogc @trusted - { - mov %1, value; - mov %0, dest; - xchg [%0], %1; - } - }, [DestReg, ValReg])); + static assert(T.sizeof <= 4, "64bit atomicExchange not supported on 32bit target."); } else version (D_InlineAsm_X86_64) { - version (Windows) - { - enum DestReg = SizedReg!DX; - enum ValReg = SizedReg!(CX, T); - } - else + } + else + static assert(0, "Operation not supported"); + + enum DestReg = SizedReg!CX; + enum ValReg = SizedReg!(AX, T); + + mixin (simpleFormat(q{ + asm pure nothrow @nogc @trusted { - enum DestReg = SizedReg!SI; - enum ValReg = SizedReg!(DI, T); + mov %1, value; + mov %0, dest; + lock; xchg [%0], %1; + + lea %0, storage; + mov [%0], %1; } - enum ResReg = result ? SizedReg!(AX, T) : null; + }, [DestReg, ValReg])); - mixin (simpleFormat(q{ - asm pure nothrow @nogc @trusted - { - naked; - xchg [%0], %1; - ?2 mov %2, %1; - ret; - } - }, [DestReg, ValReg, ResReg])); - } - else - static assert (false, "Unsupported architecture."); + return *cast(T*)&storage; } alias atomicCompareExchangeWeak = atomicCompareExchangeStrong; @@ -342,142 +323,102 @@ version (DigitalMars) bool atomicCompareExchangeStrong(MemoryOrder succ = MemoryOrder.seq, MemoryOrder fail = MemoryOrder.seq, T)(T* dest, T* compare, T value) pure nothrow @nogc @trusted if (CanCAS!T) { - version (D_InlineAsm_X86) + static assert(fail != MemoryOrder.rel && fail != MemoryOrder.acq_rel, + "Invalid fail MemoryOrder for atomicCompareExchangeStrong()"); + static assert (succ >= fail, "The first MemoryOrder argument for atomicCompareExchangeStrong() cannot be weaker than the second argument"); + bool success; + + static if (T.sizeof == size_t.sizeof * 2) { - static if (T.sizeof <= 4) - { - enum DestAddr = SizedReg!CX; - enum CmpAddr = SizedReg!DI; - enum Val = SizedReg!(DX, T); - enum Cmp = SizedReg!(AX, T); + // some values simply cannot be loa'd here, so we'll use an intermediary pointer that we can move instead + T* valuePointer = &value; - mixin (simpleFormat(q{ - asm pure nothrow @nogc @trusted - { - push %1; - mov %2, value; - mov %1, compare; - mov %3, [%1]; - mov %0, dest; - lock; cmpxchg [%0], %2; - mov [%1], %3; - setz AL; - pop %1; - } - }, [DestAddr, CmpAddr, Val, Cmp])); - } - else static if (T.sizeof == 8) + version (D_InlineAsm_X86) { asm pure nothrow @nogc @trusted { + push EBX; // call preserved push EDI; - push EBX; - lea EDI, value; + + mov EDI, valuePointer; // value mov EBX, [EDI]; - mov ECX, 4[EDI]; - mov EDI, compare; + mov ECX, [EDI + size_t.sizeof]; + mov EDI, compare; // [compare] mov EAX, [EDI]; - mov EDX, 4[EDI]; + mov EDX, [EDI + size_t.sizeof]; + mov EDI, dest; lock; cmpxchg8b [EDI]; + + setz success; mov EDI, compare; mov [EDI], EAX; - mov 4[EDI], EDX; - setz AL; - pop EBX; + mov [EDI + size_t.sizeof], EDX; + pop EDI; + pop EBX; } } - else - static assert(T.sizeof <= 8, "128bit atomicCompareExchangeStrong not supported on 32bit target." ); - } - else version (D_InlineAsm_X86_64) - { - static if (T.sizeof <= 8) + else version (D_InlineAsm_X86_64) { - version (Windows) - { - enum DestAddr = SizedReg!R8; - enum CmpAddr = SizedReg!DX; - enum Val = SizedReg!(CX, T); - } - else + asm pure nothrow @nogc @trusted { - enum DestAddr = SizedReg!DX; - enum CmpAddr = SizedReg!SI; - enum Val = SizedReg!(DI, T); - } - enum Res = SizedReg!(AX, T); + push RBX; // call preserved - mixin (simpleFormat(q{ - asm pure nothrow @nogc @trusted - { - naked; - mov %3, [%1]; - lock; cmpxchg [%0], %2; - jne compare_fail; - mov AL, 1; - ret; - compare_fail: - mov [%1], %3; - xor AL, AL; - ret; - } - }, [DestAddr, CmpAddr, Val, Res])); + mov R8, valuePointer; // value + mov RBX, [R8]; + mov RCX, [R8 + size_t.sizeof]; + mov R8, compare; // [compare] + mov RAX, [R8]; + mov RDX, [R8 + size_t.sizeof]; + + mov R8, dest; + lock; cmpxchg16b [R8]; + + setz success; + mov R8, compare; + mov [R8], RAX; + mov [R8 + size_t.sizeof], RDX; + + pop RBX; + } } else + static assert(0, "Operation not supported"); + } + else + { + version (D_InlineAsm_X86) { - version (Windows) - { - asm pure nothrow @nogc @trusted - { - naked; - push RBX; - mov R9, RDX; - mov RAX, [RDX]; - mov RDX, 8[RDX]; - mov RBX, [RCX]; - mov RCX, 8[RCX]; - lock; cmpxchg16b [R8]; - pop RBX; - jne compare_fail; - mov AL, 1; - ret; - compare_fail: - mov [R9], RAX; - mov 8[R9], RDX; - xor AL, AL; - ret; - } - } - else + } + else version (D_InlineAsm_X86_64) + { + } + else + static assert(0, "Operation not supported"); + + enum SrcReg = SizedReg!CX; + enum ValueReg = SizedReg!(DX, T); + enum CompareReg = SizedReg!(AX, T); + + mixin (simpleFormat(q{ + asm pure nothrow @nogc @trusted { - asm pure nothrow @nogc @trusted - { - naked; - push RBX; - mov R8, RCX; - mov R9, RDX; - mov RAX, [RDX]; - mov RDX, 8[RDX]; - mov RBX, RDI; - mov RCX, RSI; - lock; cmpxchg16b [R8]; - pop RBX; - jne compare_fail; - mov AL, 1; - ret; - compare_fail: - mov [R9], RAX; - mov 8[R9], RDX; - xor AL, AL; - ret; - } + mov %1, value; + mov %0, compare; + mov %2, [%0]; + + mov %0, dest; + lock; cmpxchg [%0], %1; + + setz success; + mov %0, compare; + mov [%0], %2; } - } + }, [SrcReg, ValueReg, CompareReg])); } - else - static assert (false, "Unsupported architecture."); + + return success; } alias atomicCompareExchangeWeakNoResult = atomicCompareExchangeStrongNoResult; @@ -485,114 +426,94 @@ version (DigitalMars) bool atomicCompareExchangeStrongNoResult(MemoryOrder succ = MemoryOrder.seq, MemoryOrder fail = MemoryOrder.seq, T)(T* dest, const T compare, T value) pure nothrow @nogc @trusted if (CanCAS!T) { - version (D_InlineAsm_X86) + static assert(fail != MemoryOrder.rel && fail != MemoryOrder.acq_rel, + "Invalid fail MemoryOrder for atomicCompareExchangeStrongNoResult()"); + static assert (succ >= fail, "The first MemoryOrder argument for atomicCompareExchangeStrongNoResult() cannot be weaker than the second argument"); + bool success; + + static if (T.sizeof == size_t.sizeof * 2) { - static if (T.sizeof <= 4) - { - enum DestAddr = SizedReg!CX; - enum Cmp = SizedReg!(AX, T); - enum Val = SizedReg!(DX, T); + // some values simply cannot be loa'd here, so we'll use an intermediary pointer that we can move instead + T* valuePointer = &value; + const(T)* comparePointer = &compare; - mixin (simpleFormat(q{ - asm pure nothrow @nogc @trusted - { - mov %2, value; - mov %1, compare; - mov %0, dest; - lock; cmpxchg [%0], %2; - setz AL; - } - }, [DestAddr, Cmp, Val])); - } - else static if (T.sizeof == 8) + version (D_InlineAsm_X86) { asm pure nothrow @nogc @trusted { + push EBX; // call preserved push EDI; - push EBX; - lea EDI, value; + + mov EDI, valuePointer; // value mov EBX, [EDI]; - mov ECX, 4[EDI]; - lea EDI, compare; + mov ECX, [EDI + size_t.sizeof]; + mov EDI, comparePointer; // compare mov EAX, [EDI]; - mov EDX, 4[EDI]; + mov EDX, [EDI + size_t.sizeof]; + mov EDI, dest; lock; cmpxchg8b [EDI]; - setz AL; - pop EBX; + + setz success; + pop EDI; + pop EBX; } } - else - static assert(T.sizeof <= 8, "128bit atomicCompareExchangeStrong not supported on 32bit target." ); - } - else version (D_InlineAsm_X86_64) - { - static if (T.sizeof <= 8) + else version (D_InlineAsm_X86_64) { - version (Windows) - { - enum DestAddr = SizedReg!R8; - enum Cmp = SizedReg!(DX, T); - enum Val = SizedReg!(CX, T); - } - else + asm pure nothrow @nogc @trusted { - enum DestAddr = SizedReg!DX; - enum Cmp = SizedReg!(SI, T); - enum Val = SizedReg!(DI, T); - } - enum AXReg = SizedReg!(AX, T); + push RBX; // call preserved - mixin (simpleFormat(q{ - asm pure nothrow @nogc @trusted - { - naked; - mov %3, %1; - lock; cmpxchg [%0], %2; - setz AL; - ret; - } - }, [DestAddr, Cmp, Val, AXReg])); + mov R8, valuePointer; // value + mov RBX, [R8]; + mov RCX, [R8 + size_t.sizeof]; + mov R8, comparePointer; // compare + mov RAX, [R8]; + mov RDX, [R8 + size_t.sizeof]; + + mov R8, dest; + lock; cmpxchg16b [R8]; + + setz success; + + pop RBX; + } } else + static assert(0, "Operation not supported"); + } + else + { + version (D_InlineAsm_X86) { - version (Windows) - { - asm pure nothrow @nogc @trusted - { - naked; - push RBX; - mov RAX, [RDX]; - mov RDX, 8[RDX]; - mov RBX, [RCX]; - mov RCX, 8[RCX]; - lock; cmpxchg16b [R8]; - setz AL; - pop RBX; - ret; - } - } - else + } + else version (D_InlineAsm_X86_64) + { + } + else + static assert(0, "Operation not supported"); + + enum SrcReg = SizedReg!CX; + enum ValueReg = SizedReg!(DX, T); + enum CompareReg = SizedReg!(AX, T); + + mixin (simpleFormat(q{ + asm pure nothrow @nogc @trusted { - asm pure nothrow @nogc @trusted - { - naked; - push RBX; - mov RAX, RDX; - mov RDX, RCX; - mov RBX, RDI; - mov RCX, RSI; - lock; cmpxchg16b [R8]; - setz AL; - pop RBX; - ret; - } + mov %1, value; + mov %2, compare; + + mov %0, dest; + lock; cmpxchg [%0], %1; + + setz success; } - } + }, [SrcReg, ValueReg, CompareReg])); } - else - static assert (false, "Unsupported architecture."); + + return success; } void atomicFence(MemoryOrder order = MemoryOrder.seq)() pure nothrow @nogc @trusted @@ -688,57 +609,40 @@ else version (GNU) import gcc.builtins; import gcc.config; - // Targets where MemoryOrder.acq_rel is sufficiently cheaper than using - // MemoryOrder.seq, used when the MemoryOrder requested is not valid for - // a given atomic operation. - version (IA64) - private enum PreferAcquireRelease = true; - else version (PPC) - private enum PreferAcquireRelease = true; - else version (PPC64) - private enum PreferAcquireRelease = true; - else - private enum PreferAcquireRelease = false; - enum IsAtomicLockFree(T) = __atomic_is_lock_free(T.sizeof, null); inout(T) atomicLoad(MemoryOrder order = MemoryOrder.seq, T)(inout(T)* src) pure nothrow @nogc @trusted if (CanCAS!T) { - // MemoryOrder.rel and MemoryOrder.acq_rel are not valid for load. - static assert(order != MemoryOrder.rel, "invalid MemoryOrder for atomicLoad()"); - - static if (order == MemoryOrder.acq_rel) - enum smodel = PreferAcquireRelease ? MemoryOrder.acq : MemoryOrder.seq; - else - enum smodel = order; + static assert(order != MemoryOrder.rel && order != MemoryOrder.acq_rel, + "invalid MemoryOrder for atomicLoad()"); static if (GNU_Have_Atomics || GNU_Have_LibAtomic) { static if (T.sizeof == ubyte.sizeof) { - ubyte value = __atomic_load_1(cast(shared)src, smodel); + ubyte value = __atomic_load_1(cast(shared)src, order); return *cast(typeof(return)*)&value; } else static if (T.sizeof == ushort.sizeof) { - ushort value = __atomic_load_2(cast(shared)src, smodel); + ushort value = __atomic_load_2(cast(shared)src, order); return *cast(typeof(return)*)&value; } else static if (T.sizeof == uint.sizeof) { - uint value = __atomic_load_4(cast(shared)src, smodel); + uint value = __atomic_load_4(cast(shared)src, order); return *cast(typeof(return)*)&value; } else static if (T.sizeof == ulong.sizeof && GNU_Have_64Bit_Atomics) { - ulong value = __atomic_load_8(cast(shared)src, smodel); + ulong value = __atomic_load_8(cast(shared)src, order); return *cast(typeof(return)*)&value; } else static if (GNU_Have_LibAtomic) { T value; - __atomic_load(T.sizeof, cast(shared)src, &value, smodel); + __atomic_load(T.sizeof, cast(shared)src, cast(void*)&value, order); return *cast(typeof(return)*)&value; } else @@ -755,26 +659,21 @@ else version (GNU) void atomicStore(MemoryOrder order = MemoryOrder.seq, T)(T* dest, T value) pure nothrow @nogc @trusted if (CanCAS!T) { - // MemoryOrder.acq and MemoryOrder.acq_rel are not valid for store. - static assert(order != MemoryOrder.acq, "Invalid MemoryOrder for atomicStore()"); - - static if (order == MemoryOrder.acq_rel) - enum smodel = PreferAcquireRelease ? MemoryOrder.rel : MemoryOrder.seq; - else - enum smodel = order; + static assert(order != MemoryOrder.acq && order != MemoryOrder.acq_rel, + "Invalid MemoryOrder for atomicStore()"); static if (GNU_Have_Atomics || GNU_Have_LibAtomic) { static if (T.sizeof == ubyte.sizeof) - __atomic_store_1(cast(shared)dest, *cast(ubyte*)&value, smodel); + __atomic_store_1(cast(shared)dest, *cast(ubyte*)&value, order); else static if (T.sizeof == ushort.sizeof) - __atomic_store_2(cast(shared)dest, *cast(ushort*)&value, smodel); + __atomic_store_2(cast(shared)dest, *cast(ushort*)&value, order); else static if (T.sizeof == uint.sizeof) - __atomic_store_4(cast(shared)dest, *cast(uint*)&value, smodel); + __atomic_store_4(cast(shared)dest, *cast(uint*)&value, order); else static if (T.sizeof == ulong.sizeof && GNU_Have_64Bit_Atomics) - __atomic_store_8(cast(shared)dest, *cast(ulong*)&value, smodel); + __atomic_store_8(cast(shared)dest, *cast(ulong*)&value, order); else static if (GNU_Have_LibAtomic) - __atomic_store(T.sizeof, cast(shared)dest, cast(void*)&value, smodel); + __atomic_store(T.sizeof, cast(shared)dest, cast(void*)&value, order); else static assert(0, "Invalid template type specified."); } @@ -843,40 +742,36 @@ else version (GNU) } T atomicExchange(MemoryOrder order = MemoryOrder.seq, bool result = true, T)(T* dest, T value) pure nothrow @nogc @trusted - if (is(T : ulong) || is(T == class) || is(T == interface) || is(T U : U*)) + if (CanCAS!T) { + static assert(order != MemoryOrder.acq, "Invalid MemoryOrder for atomicExchange()"); + static if (GNU_Have_Atomics || GNU_Have_LibAtomic) { - // MemoryOrder.acq is not valid for exchange. - static if (order == MemoryOrder.acq) - enum smodel = PreferAcquireRelease ? MemoryOrder.acq_rel : MemoryOrder.seq; - else - enum smodel = order; - static if (T.sizeof == byte.sizeof) { - ubyte res = __atomic_exchange_1(cast(shared)dest, *cast(ubyte*)&value, smodel); + ubyte res = __atomic_exchange_1(cast(shared)dest, *cast(ubyte*)&value, order); return *cast(typeof(return)*)&res; } else static if (T.sizeof == short.sizeof) { - ushort res = __atomic_exchange_2(cast(shared)dest, *cast(ushort*)&value, smodel); + ushort res = __atomic_exchange_2(cast(shared)dest, *cast(ushort*)&value, order); return *cast(typeof(return)*)&res; } else static if (T.sizeof == int.sizeof) { - uint res = __atomic_exchange_4(cast(shared)dest, *cast(uint*)&value, smodel); + uint res = __atomic_exchange_4(cast(shared)dest, *cast(uint*)&value, order); return *cast(typeof(return)*)&res; } else static if (T.sizeof == long.sizeof && GNU_Have_64Bit_Atomics) { - ulong res = __atomic_exchange_8(cast(shared)dest, *cast(ulong*)&value, smodel); + ulong res = __atomic_exchange_8(cast(shared)dest, *cast(ulong*)&value, order); return *cast(typeof(return)*)&res; } else static if (GNU_Have_LibAtomic) { T res = void; - __atomic_exchange(T.sizeof, cast(shared)dest, cast(void*)&value, &res, smodel); + __atomic_exchange(T.sizeof, cast(shared)dest, cast(void*)&value, &res, order); return res; } else @@ -920,46 +815,29 @@ else version (GNU) private bool atomicCompareExchangeImpl(MemoryOrder succ = MemoryOrder.seq, MemoryOrder fail = MemoryOrder.seq, bool weak, T)(T* dest, T* compare, T value) pure nothrow @nogc @trusted if (CanCAS!T) { + static assert(fail != MemoryOrder.rel && fail != MemoryOrder.acq_rel, + "Invalid fail MemoryOrder for atomicCompareExchange()"); + static assert (succ >= fail, "The first MemoryOrder argument for atomicCompareExchange() cannot be weaker than the second argument"); + bool res = void; static if (GNU_Have_Atomics || GNU_Have_LibAtomic) { - static if (fail == MemoryOrder.rel || fail == MemoryOrder.acq_rel) - { - // MemoryOrder.rel and MemoryOrder.acq_rel are not valid failure models. - enum smodel = (succ != MemoryOrder.seq && PreferAcquireRelease) - ? MemoryOrder.acq_rel : MemoryOrder.seq; - enum fmodel = (succ != MemoryOrder.seq && PreferAcquireRelease) - ? MemoryOrder.raw : MemoryOrder.seq; - } - else static if (fail > succ) - { - // Failure memory model cannot be stronger than success. - enum smodel = (fail != MemoryOrder.seq && PreferAcquireRelease) - ? MemoryOrder.acq_rel : MemoryOrder.seq; - enum fmodel = fail; - } - else - { - enum smodel = succ; - enum fmodel = fail; - } - static if (T.sizeof == byte.sizeof) res = __atomic_compare_exchange_1(cast(shared)dest, compare, *cast(ubyte*)&value, - weak, smodel, fmodel); + weak, succ, fail); else static if (T.sizeof == short.sizeof) res = __atomic_compare_exchange_2(cast(shared)dest, compare, *cast(ushort*)&value, - weak, smodel, fmodel); + weak, succ, fail); else static if (T.sizeof == int.sizeof) res = __atomic_compare_exchange_4(cast(shared)dest, compare, *cast(uint*)&value, - weak, smodel, fmodel); + weak, succ, fail); else static if (T.sizeof == long.sizeof && GNU_Have_64Bit_Atomics) res = __atomic_compare_exchange_8(cast(shared)dest, compare, *cast(ulong*)&value, - weak, smodel, fmodel); + weak, succ, fail); else static if (GNU_Have_LibAtomic) res = __atomic_compare_exchange(T.sizeof, cast(shared)dest, compare, cast(void*)&value, - smodel, fmodel); + succ, fail); else static assert(0, "Invalid template type specified."); } @@ -1122,10 +1000,10 @@ version (Windows) enum RegisterReturn(T) = is(T : U[], U) || is(T : R delegate(A), R, A...); } -enum CanCAS(T) = is(T : ulong) || +enum CanCAS(T) = (__traits(isScalar, T) && // check to see if it is some kind of basic type like an integer/float/pointer + T.sizeof <= size_t.sizeof * 2) || // make sure if it is, that it is no more than 2 words is(T == class) || is(T == interface) || - is(T : U*, U) || is(T : U[], U) || is(T : R delegate(A), R, A...) || (is(T == struct) && __traits(isPOD, T) && diff --git a/libphobos/libdruntime/core/internal/traits.d b/libphobos/libdruntime/core/internal/traits.d index 966839f176ac..0b2eb1f21a71 100644 --- a/libphobos/libdruntime/core/internal/traits.d +++ b/libphobos/libdruntime/core/internal/traits.d @@ -38,7 +38,7 @@ template Unqual(T : const U, U) template BaseElemOf(T) { - static if (is(T == E[N], E, size_t N)) + static if (is(OriginalType!T == E[N], E, size_t N)) alias BaseElemOf = BaseElemOf!E; else alias BaseElemOf = T; @@ -51,6 +51,8 @@ unittest static assert(is(BaseElemOf!(int[1][2]) == int)); static assert(is(BaseElemOf!(int[1][]) == int[1][])); static assert(is(BaseElemOf!(int[][1]) == int[])); + static enum E : int[2]{ test = [0, 1] } + static assert(is(BaseElemOf!(E) == int)); } // [For internal use] diff --git a/libphobos/libdruntime/core/stdc/stdatomic.d b/libphobos/libdruntime/core/stdc/stdatomic.d index ae17e040da7f..72e037f7e929 100644 --- a/libphobos/libdruntime/core/stdc/stdatomic.d +++ b/libphobos/libdruntime/core/stdc/stdatomic.d @@ -7,6 +7,8 @@ * * $(NOTE The D shared type qualifier is the closest to the _Atomic type qualifier from C. It may be changed from shared in the future.) * + * $(NOTE Fail memory order is currently ignored due to limitations with internal implementation of atomics.) + * * Copyright: Copyright Richard (Rikki) Andrew Cattermole 2023. * License: $(LINK2 http://www.boost.org/LICENSE_1_0.txt, Boost License 1.0) * Authors: Richard (Rikki) Andrew cattermole @@ -101,7 +103,7 @@ version (DigitalMars) alias atomic_fetch_and_explicit = atomic_fetch_and_explicit_impl; /// } } -else version(GNU) +else { alias atomic_flag_clear = atomic_flag_clear_impl; /// alias atomic_flag_clear_explicit = atomic_flag_clear_explicit_impl; /// @@ -169,6 +171,7 @@ void atomic_flag_clear_explicit_impl()(atomic_flag* obj, memory_order order) break; case memory_order.memory_order_acquire: + case memory_order.memory_order_acq_rel: // Ideally this would error at compile time but alas it is not an intrinsic. // Note: this is not a valid memory order for this operation. atomicStore!(memory_order.memory_order_seq_cst)(&obj.b, false); @@ -178,10 +181,6 @@ void atomic_flag_clear_explicit_impl()(atomic_flag* obj, memory_order order) atomicStore!(memory_order.memory_order_release)(&obj.b, false); break; - case memory_order.memory_order_acq_rel: - atomicStore!(memory_order.memory_order_acq_rel)(&obj.b, false); - break; - case memory_order.memory_order_seq_cst: atomicStore(&obj.b, false); break; @@ -197,7 +196,7 @@ bool atomic_flag_test_and_set_impl()(atomic_flag* obj) } /// -unittest +@trusted unittest { atomic_flag flag; assert(!atomic_flag_test_and_set_impl(&flag)); @@ -216,7 +215,9 @@ bool atomic_flag_test_and_set_explicit_impl()(atomic_flag* obj, memory_order ord return atomicExchange!(memory_order.memory_order_relaxed)(&obj.b, true); case memory_order.memory_order_acquire: - return atomicExchange!(memory_order.memory_order_acquire)(&obj.b, true); + // Ideally this would error at compile time but alas it is not an intrinsic. + // Note: this is not a valid memory order for this operation. + return atomicExchange!(memory_order.memory_order_seq_cst)(&obj.b, true); case memory_order.memory_order_release: return atomicExchange!(memory_order.memory_order_release)(&obj.b, true); @@ -230,7 +231,7 @@ bool atomic_flag_test_and_set_explicit_impl()(atomic_flag* obj, memory_order ord } /// -unittest +@trusted unittest { atomic_flag flag; assert(!atomic_flag_test_and_set_explicit_impl(&flag, memory_order.memory_order_seq_cst)); @@ -253,6 +254,9 @@ unittest { shared int val; atomic_init(val, 2); + + shared float valF; + atomic_init(valF, 3.2); } /// No-op function, doesn't apply to D @@ -269,7 +273,7 @@ void atomic_signal_fence_impl()(memory_order order) final switch (order) { case memory_order.memory_order_relaxed: - atomicSignalFence!(memory_order.memory_order_relaxed); + // This is a no-op operation for relaxed memory orders. break; case memory_order.memory_order_acquire: @@ -303,7 +307,7 @@ void atomic_thread_fence_impl()(memory_order order) final switch (order) { case memory_order.memory_order_relaxed: - atomicFence!(memory_order.memory_order_relaxed); + // This is a no-op operation for relaxed memory orders. break; case memory_order.memory_order_acquire: @@ -413,14 +417,17 @@ pragma(inline, true) void atomic_store_impl(A, C)(shared(A)* obj, C desired) @trusted { assert(obj !is null); - atomicStore(obj, cast(A)desired); + atomicStore(cast(A*)obj, cast(A)desired); } /// -unittest +@trusted unittest { shared(int) obj; atomic_store_impl(&obj, 3); + + shared(float) objF; + atomic_store_impl(&objF, 3.21); } /// @@ -432,34 +439,34 @@ void atomic_store_explicit_impl(A, C)(shared(A)* obj, C desired, memory_order or final switch (order) { case memory_order.memory_order_relaxed: - atomicStore!(memory_order.memory_order_relaxed)(obj, cast(A)desired); + atomicStore!(memory_order.memory_order_relaxed)(cast(A*)obj, cast(A)desired); break; case memory_order.memory_order_acquire: + case memory_order.memory_order_acq_rel: // Ideally this would error at compile time but alas it is not an intrinsic. // Note: this is not a valid memory order for this operation. - atomicStore!(memory_order.memory_order_release)(obj, cast(A)desired); + atomicStore!(memory_order.memory_order_release)(cast(A*)obj, cast(A)desired); break; case memory_order.memory_order_release: - atomicStore!(memory_order.memory_order_release)(obj, cast(A)desired); - break; - - case memory_order.memory_order_acq_rel: - atomicStore!(memory_order.memory_order_acq_rel)(obj, cast(A)desired); + atomicStore!(memory_order.memory_order_release)(cast(A*)obj, cast(A)desired); break; case memory_order.memory_order_seq_cst: - atomicStore!(memory_order.memory_order_seq_cst)(obj, cast(A)desired); + atomicStore!(memory_order.memory_order_seq_cst)(cast(A*)obj, cast(A)desired); break; } } /// -unittest +@trusted unittest { shared(int) obj; atomic_store_explicit_impl(&obj, 3, memory_order.memory_order_seq_cst); + + shared(float) objF; + atomic_store_explicit_impl(&objF, 3.21, memory_order.memory_order_seq_cst); } /// @@ -467,14 +474,24 @@ pragma(inline, true) A atomic_load_impl(A)(const shared(A)* obj) @trusted { assert(obj !is null); - return atomicLoad(cast(shared(A)*)obj); + return atomicLoad(cast(A*)obj); } /// -unittest +@trusted unittest { shared(int) obj = 3; assert(atomic_load_impl(&obj) == 3); + + shared(float) objF = 3.5; + assert(atomic_load_impl(&objF) > 3); + + static struct S2 + { + size_t[2] values; + } + align(S2.sizeof) shared(S2) objS2 = {[1, 2]}; + assert(atomic_load_impl(&objS2).values == [1, 2]); } /// @@ -486,29 +503,30 @@ A atomic_load_explicit_impl(A)(const shared(A)* obj, memory_order order) @truste final switch (order) { case memory_order.memory_order_relaxed: - return atomicLoad!(memory_order.memory_order_relaxed)(obj); + return atomicLoad!(memory_order.memory_order_relaxed)(cast(A*)obj); case memory_order.memory_order_acquire: - return atomicLoad!(memory_order.memory_order_acquire)(obj); + return atomicLoad!(memory_order.memory_order_acquire)(cast(A*)obj); case memory_order.memory_order_release: + case memory_order.memory_order_acq_rel: // Ideally this would error at compile time but alas it is not an intrinsic. // Note: this is not a valid memory order for this operation. - return atomicLoad!(memory_order.memory_order_acquire)(obj); - - case memory_order.memory_order_acq_rel: - return atomicLoad!(memory_order.memory_order_acq_rel)(obj); + return atomicLoad!(memory_order.memory_order_acquire)(cast(A*)obj); case memory_order.memory_order_seq_cst: - return atomicLoad!(memory_order.memory_order_seq_cst)(obj); + return atomicLoad!(memory_order.memory_order_seq_cst)(cast(A*)obj); } } /// -unittest +@trusted unittest { shared(int) obj = 3; assert(atomic_load_explicit_impl(&obj, memory_order.memory_order_seq_cst) == 3); + + shared(float) objF = 3.5; + assert(atomic_load_explicit_impl(&objF, memory_order.memory_order_seq_cst) > 3); } /// @@ -516,14 +534,17 @@ pragma(inline, true) A atomic_exchange_impl(A, C)(shared(A)* obj, C desired) @trusted { assert(obj !is null); - return atomicExchange(cast(shared(A)*)obj, cast(A)desired); + return atomicExchange(cast(A*)obj, cast(A)desired); } /// -unittest +@trusted unittest { shared(int) obj = 3; assert(atomic_exchange_impl(&obj, 2) == 3); + + shared(float) objF = 3; + assert(atomic_exchange_impl(&objF, 2.1) > 2.5); } /// @@ -535,270 +556,215 @@ A atomic_exchange_explicit_impl(A, C)(shared(A)* obj, C desired, memory_order or final switch (order) { case memory_order.memory_order_relaxed: - return atomicExchange!(memory_order.memory_order_relaxed)(obj, cast(A)desired); + return atomicExchange!(memory_order.memory_order_relaxed)(cast(A*)obj, cast(A)desired); case memory_order.memory_order_acquire: - return atomicExchange!(memory_order.memory_order_acquire)(obj, cast(A)desired); + // Ideally this would error at compile time but alas it is not an intrinsic. + // Note: this is not a valid memory order for this operation. + return atomicExchange!(memory_order.memory_order_seq_cst)(cast(A*)obj, cast(A)desired); case memory_order.memory_order_release: - return atomicExchange!(memory_order.memory_order_release)(obj, cast(A)desired); + return atomicExchange!(memory_order.memory_order_release)(cast(A*)obj, cast(A)desired); case memory_order.memory_order_acq_rel: - return atomicExchange!(memory_order.memory_order_acq_rel)(obj, cast(A)desired); + return atomicExchange!(memory_order.memory_order_acq_rel)(cast(A*)obj, cast(A)desired); case memory_order.memory_order_seq_cst: - return atomicExchange!(memory_order.memory_order_seq_cst)(obj, cast(A)desired); + return atomicExchange!(memory_order.memory_order_seq_cst)(cast(A*)obj, cast(A)desired); } } /// -unittest +@trusted unittest { shared(int) obj = 3; assert(atomic_exchange_explicit_impl(&obj, 2, memory_order.memory_order_seq_cst) == 3); + + shared(float) objF = 1.5; + assert(atomic_exchange_explicit_impl(&objF, 2.1, memory_order.memory_order_seq_cst) < 2); } /// pragma(inline, true) -bool atomic_compare_exchange_strong_impl(A, C)(shared(A)* obj, A* expected, C desired) @trusted +bool atomic_compare_exchange_strong_impl(A, B, C)(shared(A)* obj, B* expected, C desired) @trusted { - return atomicCompareExchangeStrong(cast(A*)obj, expected, cast(A)desired); + static assert(is(shared(B) : A), "Both expected and object must be the same type"); + return atomicCompareExchangeStrong(cast(B*)obj, expected, cast(B)desired); } /// -unittest +@trusted unittest { shared(int) obj = 3; int expected = 3; assert(atomic_compare_exchange_strong_impl(&obj, &expected, 2)); } +/// +@trusted unittest +{ + shared(float) obj = 3; + float expected = 3; + assert(atomic_compare_exchange_strong_impl(&obj, &expected, 2.1)); +} + /// pragma(inline, true) -bool atomic_compare_exchange_weak_impl(A, C)(shared(A)* obj, A* expected, C desired) @trusted +bool atomic_compare_exchange_weak_impl(A, B, C)(shared(A)* obj, B* expected, C desired) @trusted { - return atomicCompareExchangeStrong(cast(A*)obj, expected, cast(A)desired); + static assert(is(shared(B) : A), "Both expected and object must be the same type"); + return atomicCompareExchangeWeak(cast(B*)obj, expected, cast(B)desired); } /// -unittest +@trusted unittest { shared(int) obj = 3; int expected = 3; static assert(__traits(compiles, {atomic_compare_exchange_weak_impl(&obj, &expected, 2);})); } +/// +@trusted unittest +{ + shared(float) obj = 3; + float expected = 3; + static assert(__traits(compiles, {atomic_compare_exchange_weak_impl(&obj, &expected, 2.1);})); +} + /// pragma(inline, true) -bool atomic_compare_exchange_strong_explicit_impl(A, C)(shared(A)* obj, A* expected, C desired, memory_order succ, memory_order fail) @trusted +bool atomic_compare_exchange_strong_explicit_impl(A, B, C)(shared(A)* obj, B* expected, C desired, memory_order succ, memory_order fail) @trusted { + static assert(is(shared(B) : A), "Both expected and object must be the same type"); assert(obj !is null); - // We use these giant switch inside switch statements - // because as of 2023 they are capable of being for the most part inlined by gdc & ldc when using literal arguments for memory_order. + // NOTE: To not have to deal with all invalid cases, the failure model is ignored for now. final switch(succ) { case memory_order.memory_order_relaxed: - final switch(fail) - { - case memory_order.memory_order_relaxed: - return atomicCompareExchangeStrong!(memory_order.memory_order_relaxed, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acquire: - return atomicCompareExchangeStrong!(memory_order.memory_order_relaxed, memory_order.memory_order_acquire)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_release: - return atomicCompareExchangeStrong!(memory_order.memory_order_relaxed, memory_order.memory_order_release)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acq_rel: - return atomicCompareExchangeStrong!(memory_order.memory_order_relaxed, memory_order.memory_order_acq_rel)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_seq_cst: - return atomicCompareExchangeStrong!(memory_order.memory_order_relaxed, memory_order.memory_order_seq_cst)(cast(A*)obj, expected, cast(A)desired); - } + return atomicCompareExchangeStrong!(memory_order.memory_order_relaxed, memory_order.memory_order_relaxed)(cast(B*)obj, expected, cast(B)desired); case memory_order.memory_order_acquire: - final switch(fail) - { - case memory_order.memory_order_relaxed: - return atomicCompareExchangeStrong!(memory_order.memory_order_acquire, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acquire: - return atomicCompareExchangeStrong!(memory_order.memory_order_acquire, memory_order.memory_order_acquire)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_release: - return atomicCompareExchangeStrong!(memory_order.memory_order_acquire, memory_order.memory_order_release)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acq_rel: - return atomicCompareExchangeStrong!(memory_order.memory_order_acquire, memory_order.memory_order_acq_rel)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_seq_cst: - return atomicCompareExchangeStrong!(memory_order.memory_order_acquire, memory_order.memory_order_seq_cst)(cast(A*)obj, expected, cast(A)desired); - } + return atomicCompareExchangeStrong!(memory_order.memory_order_acquire, memory_order.memory_order_relaxed)(cast(B*)obj, expected, cast(B)desired); case memory_order.memory_order_release: - final switch(fail) - { - case memory_order.memory_order_relaxed: - return atomicCompareExchangeStrong!(memory_order.memory_order_release, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acquire: - return atomicCompareExchangeStrong!(memory_order.memory_order_release, memory_order.memory_order_acquire)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_release: - return atomicCompareExchangeStrong!(memory_order.memory_order_release, memory_order.memory_order_release)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acq_rel: - return atomicCompareExchangeStrong!(memory_order.memory_order_release, memory_order.memory_order_acq_rel)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_seq_cst: - return atomicCompareExchangeStrong!(memory_order.memory_order_release, memory_order.memory_order_seq_cst)(cast(A*)obj, expected, cast(A)desired); - } + return atomicCompareExchangeStrong!(memory_order.memory_order_release, memory_order.memory_order_relaxed)(cast(B*)obj, expected, cast(B)desired); case memory_order.memory_order_acq_rel: - final switch(fail) - { - case memory_order.memory_order_relaxed: - return atomicCompareExchangeStrong!(memory_order.memory_order_acq_rel, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acquire: - return atomicCompareExchangeStrong!(memory_order.memory_order_acq_rel, memory_order.memory_order_acquire)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_release: - return atomicCompareExchangeStrong!(memory_order.memory_order_acq_rel, memory_order.memory_order_release)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acq_rel: - return atomicCompareExchangeStrong!(memory_order.memory_order_acq_rel, memory_order.memory_order_acq_rel)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_seq_cst: - return atomicCompareExchangeStrong!(memory_order.memory_order_acq_rel, memory_order.memory_order_seq_cst)(cast(A*)obj, expected, cast(A)desired); - } + return atomicCompareExchangeStrong!(memory_order.memory_order_acq_rel, memory_order.memory_order_relaxed)(cast(B*)obj, expected, cast(B)desired); case memory_order.memory_order_seq_cst: - final switch(fail) - { - case memory_order.memory_order_relaxed: - return atomicCompareExchangeStrong!(memory_order.memory_order_seq_cst, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acquire: - return atomicCompareExchangeStrong!(memory_order.memory_order_seq_cst, memory_order.memory_order_acquire)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_release: - return atomicCompareExchangeStrong!(memory_order.memory_order_seq_cst, memory_order.memory_order_release)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acq_rel: - return atomicCompareExchangeStrong!(memory_order.memory_order_seq_cst, memory_order.memory_order_acq_rel)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_seq_cst: - return atomicCompareExchangeStrong!(memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst)(cast(A*)obj, expected, cast(A)desired); - } + return atomicCompareExchangeStrong!(memory_order.memory_order_seq_cst, memory_order.memory_order_relaxed)(cast(B*)obj, expected, cast(B)desired); } } /// -unittest +@trusted unittest { shared(int) obj = 3; int expected = 3; assert(atomic_compare_exchange_strong_explicit_impl(&obj, &expected, 2, memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst)); } +/// +@trusted unittest +{ + align(size_t[2].sizeof) shared(size_t[2]) obj = [3, 4]; + size_t[2] expected = [3, 4]; + size_t[2] toSwap = [1, 2]; + assert(atomic_compare_exchange_strong_explicit_impl(&obj, &expected, toSwap, memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst)); +} + +/// +@trusted unittest +{ + shared(float) obj = 3; + float expected = 3; + assert(atomic_compare_exchange_strong_explicit_impl(&obj, &expected, 2.1, memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst)); +} + /// pragma(inline, true) -bool atomic_compare_exchange_weak_explicit_impl(A, C)(shared(A)* obj, A* expected, C desired, memory_order succ, memory_order fail) @trusted +bool atomic_compare_exchange_weak_explicit_impl(A, B, C)(shared(A)* obj, B* expected, C desired, memory_order succ, memory_order fail) @trusted { + static assert(is(shared(B) : A), "Both expected and object must be the same type"); assert(obj !is null); - // We use these giant switch inside switch statements - // because as of 2023 they are capable of being for the most part inlined by gdc & ldc when using literal arguments for memory_order. + // NOTE: To not have to deal with all invalid cases, the failure model is ignored for now. final switch(succ) { case memory_order.memory_order_relaxed: - final switch(fail) - { - case memory_order.memory_order_relaxed: - return atomicCompareExchangeWeak!(memory_order.memory_order_relaxed, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acquire: - return atomicCompareExchangeWeak!(memory_order.memory_order_relaxed, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_release: - return atomicCompareExchangeWeak!(memory_order.memory_order_relaxed, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acq_rel: - return atomicCompareExchangeWeak!(memory_order.memory_order_relaxed, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_seq_cst: - return atomicCompareExchangeWeak!(memory_order.memory_order_relaxed, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - } + return atomicCompareExchangeWeak!(memory_order.memory_order_relaxed, memory_order.memory_order_relaxed)(cast(B*)obj, expected, cast(B)desired); case memory_order.memory_order_acquire: - final switch(fail) - { - case memory_order.memory_order_relaxed: - return atomicCompareExchangeWeak!(memory_order.memory_order_acquire, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acquire: - return atomicCompareExchangeWeak!(memory_order.memory_order_acquire, memory_order.memory_order_acquire)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_release: - return atomicCompareExchangeWeak!(memory_order.memory_order_acquire, memory_order.memory_order_release)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acq_rel: - return atomicCompareExchangeWeak!(memory_order.memory_order_acquire, memory_order.memory_order_acq_rel)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_seq_cst: - return atomicCompareExchangeWeak!(memory_order.memory_order_acquire, memory_order.memory_order_seq_cst)(cast(A*)obj, expected, cast(A)desired); - } + return atomicCompareExchangeWeak!(memory_order.memory_order_acquire, memory_order.memory_order_relaxed)(cast(B*)obj, expected, cast(B)desired); case memory_order.memory_order_release: - final switch(fail) - { - case memory_order.memory_order_relaxed: - return atomicCompareExchangeWeak!(memory_order.memory_order_release, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acquire: - return atomicCompareExchangeWeak!(memory_order.memory_order_release, memory_order.memory_order_acquire)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_release: - return atomicCompareExchangeWeak!(memory_order.memory_order_release, memory_order.memory_order_release)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acq_rel: - return atomicCompareExchangeWeak!(memory_order.memory_order_release, memory_order.memory_order_acq_rel)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_seq_cst: - return atomicCompareExchangeWeak!(memory_order.memory_order_release, memory_order.memory_order_seq_cst)(cast(A*)obj, expected, cast(A)desired); - } + return atomicCompareExchangeWeak!(memory_order.memory_order_release, memory_order.memory_order_relaxed)(cast(B*)obj, expected, cast(B)desired); case memory_order.memory_order_acq_rel: - final switch(fail) - { - case memory_order.memory_order_relaxed: - return atomicCompareExchangeWeak!(memory_order.memory_order_acq_rel, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acquire: - return atomicCompareExchangeWeak!(memory_order.memory_order_acq_rel, memory_order.memory_order_acquire)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_release: - return atomicCompareExchangeWeak!(memory_order.memory_order_acq_rel, memory_order.memory_order_release)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acq_rel: - return atomicCompareExchangeWeak!(memory_order.memory_order_acq_rel, memory_order.memory_order_acq_rel)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_seq_cst: - return atomicCompareExchangeWeak!(memory_order.memory_order_acq_rel, memory_order.memory_order_seq_cst)(cast(A*)obj, expected, cast(A)desired); - } + return atomicCompareExchangeWeak!(memory_order.memory_order_acq_rel, memory_order.memory_order_relaxed)(cast(B*)obj, expected, cast(B)desired); case memory_order.memory_order_seq_cst: - final switch(fail) - { - case memory_order.memory_order_relaxed: - return atomicCompareExchangeWeak!(memory_order.memory_order_seq_cst, memory_order.memory_order_relaxed)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acquire: - return atomicCompareExchangeWeak!(memory_order.memory_order_seq_cst, memory_order.memory_order_acquire)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_release: - return atomicCompareExchangeWeak!(memory_order.memory_order_seq_cst, memory_order.memory_order_release)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_acq_rel: - return atomicCompareExchangeWeak!(memory_order.memory_order_seq_cst, memory_order.memory_order_acq_rel)(cast(A*)obj, expected, cast(A)desired); - case memory_order.memory_order_seq_cst: - return atomicCompareExchangeWeak!(memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst)(cast(A*)obj, expected, cast(A)desired); - } + return atomicCompareExchangeWeak!(memory_order.memory_order_seq_cst, memory_order.memory_order_relaxed)(cast(B*)obj, expected, cast(B)desired); } } /// -unittest +@trusted unittest { shared(int) obj = 3; int expected = 3; atomic_compare_exchange_weak_explicit_impl(&obj, &expected, 2, memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst); } +/// +@trusted unittest +{ + align(size_t[2].sizeof) shared(size_t[2]) obj = [3, 4]; + size_t[2] expected = [3, 4]; + size_t[2] toSwap = [1, 2]; + assert(atomic_compare_exchange_weak_explicit_impl(&obj, &expected, toSwap, memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst)); +} + +/// +@trusted unittest +{ + shared(float) obj = 3; + float expected = 3; + atomic_compare_exchange_weak_explicit_impl(&obj, &expected, 2, memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst); +} + /// pragma(inline, true) A atomic_fetch_add_impl(A, M)(shared(A)* obj, M arg) @trusted { assert(obj !is null); - return atomicFetchAdd(cast(A*)obj, arg); + return atomic_fetch_op!(memory_order.memory_order_seq_cst, "+=")(cast(A*)obj, arg); } /// -unittest +@trusted unittest { shared(int) val; atomic_fetch_add_impl(&val, 3); assert(atomic_load_impl(&val) == 3); + + shared(float) valF = 0.5; + atomic_fetch_add_impl(&valF, 3); + assert(atomic_load_impl(&valF) > 3); } pragma(inline, true) A atomic_fetch_sub_impl(A, M)(shared(A)* obj, M arg) @trusted { assert(obj !is null); - return atomicFetchSub(cast(A*)obj, arg); + return atomic_fetch_op!(memory_order.memory_order_seq_cst, "-=")(cast(A*)obj, arg); } /// -unittest +@trusted unittest { shared(int) val = 3; atomic_fetch_sub_impl(&val, 3); assert(atomic_load_impl(&val) == 0); + + shared(float) valF = 3; + atomic_fetch_sub_impl(&valF, 1); + assert(atomic_load_impl(&valF) < 3); } /// @@ -810,24 +776,28 @@ A atomic_fetch_add_explicit_impl(A, M)(shared(A)* obj, M arg, memory_order order final switch(order) { case memory_order.memory_order_relaxed: - return atomicFetchAdd!(memory_order.memory_order_relaxed)(cast(A*)obj, arg); + return atomic_fetch_op!(memory_order.memory_order_relaxed, "+=")(cast(A*)obj, arg); case memory_order.memory_order_acquire: - return atomicFetchAdd!(memory_order.memory_order_acquire)(cast(A*)obj, arg); + return atomic_fetch_op!(memory_order.memory_order_acquire, "+=")(cast(A*)obj, arg); case memory_order.memory_order_release: - return atomicFetchAdd!(memory_order.memory_order_release)(cast(A*)obj, arg); + return atomic_fetch_op!(memory_order.memory_order_release, "+=")(cast(A*)obj, arg); case memory_order.memory_order_acq_rel: - return atomicFetchAdd!(memory_order.memory_order_acq_rel)(cast(A*)obj, arg); + return atomic_fetch_op!(memory_order.memory_order_acq_rel, "+=")(cast(A*)obj, arg); case memory_order.memory_order_seq_cst: - return atomicFetchAdd!(memory_order.memory_order_seq_cst)(cast(A*)obj, arg); + return atomic_fetch_op!(memory_order.memory_order_seq_cst, "+=")(cast(A*)obj, arg); } } /// -unittest +@trusted unittest { shared(int) val; atomic_fetch_add_explicit_impl(&val, 3, memory_order.memory_order_seq_cst); assert(atomic_load_impl(&val) == 3); + + shared(float) valF = 3; + atomic_fetch_add_explicit_impl(&valF, 3, memory_order.memory_order_seq_cst); + assert(atomic_load_impl(&valF) > 3); } /// @@ -839,24 +809,28 @@ A atomic_fetch_sub_explicit_impl(A, M)(shared(A)* obj, M arg, memory_order order final switch(order) { case memory_order.memory_order_relaxed: - return atomicFetchSub!(memory_order.memory_order_relaxed)(cast(A*)obj, arg); + return atomic_fetch_op!(memory_order.memory_order_relaxed, "-=")(cast(A*)obj, arg); case memory_order.memory_order_acquire: - return atomicFetchSub!(memory_order.memory_order_acquire)(cast(A*)obj, arg); + return atomic_fetch_op!(memory_order.memory_order_acquire, "-=")(cast(A*)obj, arg); case memory_order.memory_order_release: - return atomicFetchSub!(memory_order.memory_order_release)(cast(A*)obj, arg); + return atomic_fetch_op!(memory_order.memory_order_release, "-=")(cast(A*)obj, arg); case memory_order.memory_order_acq_rel: - return atomicFetchSub!(memory_order.memory_order_acq_rel)(cast(A*)obj, arg); + return atomic_fetch_op!(memory_order.memory_order_acq_rel, "-=")(cast(A*)obj, arg); case memory_order.memory_order_seq_cst: - return atomicFetchSub!(memory_order.memory_order_seq_cst)(cast(A*)obj, arg); + return atomic_fetch_op!(memory_order.memory_order_seq_cst, "-=")(cast(A*)obj, arg); } } /// -unittest +@trusted unittest { shared(int) val = 3; atomic_fetch_sub_explicit_impl(&val, 3, memory_order.memory_order_seq_cst); assert(atomic_load_impl(&val) == 0); + + shared(float) valF = 4; + atomic_fetch_sub_explicit_impl(&valF, 3, memory_order.memory_order_seq_cst); + assert(atomic_load_impl(&valF) < 4); } /// @@ -864,21 +838,11 @@ pragma(inline, true) A atomic_fetch_or_impl(A, M)(shared(A)* obj, M arg) @trusted { assert(obj !is null); - - // copied from atomicOp - - A set, get = atomicLoad(cast(A*)obj); - - do - { - set = get | arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst)(cast(A*)obj, &get, cast(A)set)); - - return get; + return atomic_fetch_op!(memory_order.memory_order_seq_cst, "|=")(cast(A*)obj, arg); } /// -unittest +@trusted unittest { shared(int) val = 5; atomic_fetch_or_impl(&val, 3); @@ -891,56 +855,23 @@ A atomic_fetch_or_explicit_impl(A, M)(shared(A)* obj, M arg, memory_order order) { assert(obj !is null); - A set, get; - final switch(order) { case memory_order.memory_order_relaxed: - get = atomicLoad!(memory_order.memory_order_relaxed)(cast(A*)obj); - do - { - set = get | arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_relaxed, memory_order.memory_order_relaxed)(cast(A*)obj, &get, cast(A)set)); - break; - + return atomic_fetch_op!(memory_order.memory_order_relaxed, "|=")(cast(A*)obj, arg); case memory_order.memory_order_acquire: - get = atomicLoad!(memory_order.memory_order_acquire)(cast(A*)obj); - do - { - set = get | arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_acquire, memory_order.memory_order_acquire)(cast(A*)obj, &get, cast(A)set)); - break; - + return atomic_fetch_op!(memory_order.memory_order_acquire, "|=")(cast(A*)obj, arg); case memory_order.memory_order_release: - get = atomicLoad!(memory_order.memory_order_relaxed)(cast(A*)obj); - do - { - set = get | arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_release, memory_order.memory_order_release)(cast(A*)obj, &get, cast(A)set)); - break; - + return atomic_fetch_op!(memory_order.memory_order_release, "|=")(cast(A*)obj, arg); case memory_order.memory_order_acq_rel: - get = atomicLoad!(memory_order.memory_order_acq_rel)(cast(A*)obj); - do - { - set = get | arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_acq_rel, memory_order.memory_order_acq_rel)(cast(A*)obj, &get, cast(A)set)); - break; - + return atomic_fetch_op!(memory_order.memory_order_acq_rel, "|=")(cast(A*)obj, arg); case memory_order.memory_order_seq_cst: - get = atomicLoad!(memory_order.memory_order_relaxed)(cast(A*)obj); - do - { - set = get | arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst)(cast(A*)obj, &get, cast(A)set)); - break; + return atomic_fetch_op!(memory_order.memory_order_seq_cst, "|=")(cast(A*)obj, arg); } - - return get; } /// -unittest +@trusted unittest { shared(int) val = 5; atomic_fetch_or_explicit_impl(&val, 3, memory_order.memory_order_seq_cst); @@ -952,21 +883,11 @@ pragma(inline, true) A atomic_fetch_xor_impl(A, M)(shared(A)* obj, M arg) @trusted { assert(obj !is null); - - // copied from atomicOp - - A set, get = atomicLoad(cast(A*)obj); - - do - { - set = get ^ arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst)(cast(A*)obj, &get, cast(A)set)); - - return get; + return atomic_fetch_op!(memory_order.memory_order_seq_cst, "^=")(cast(A*)obj, arg); } /// -unittest +@trusted unittest { shared(int) val = 5; atomic_fetch_xor_impl(&val, 3); @@ -979,56 +900,23 @@ A atomic_fetch_xor_explicit_impl(A, M)(shared(A)* obj, M arg, memory_order order { assert(obj !is null); - A set, get; - final switch(order) { case memory_order.memory_order_relaxed: - get = atomicLoad!(memory_order.memory_order_relaxed)(cast(A*)obj); - do - { - set = get ^ arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_relaxed, memory_order.memory_order_relaxed)(cast(A*)obj, &get, cast(A)set)); - break; - + return atomic_fetch_op!(memory_order.memory_order_relaxed, "^=")(cast(A*)obj, arg); case memory_order.memory_order_acquire: - get = atomicLoad!(memory_order.memory_order_acquire)(cast(A*)obj); - do - { - set = get ^ arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_acquire, memory_order.memory_order_acquire)(cast(A*)obj, &get, cast(A)set)); - break; - + return atomic_fetch_op!(memory_order.memory_order_acquire, "^=")(cast(A*)obj, arg); case memory_order.memory_order_release: - get = atomicLoad!(memory_order.memory_order_relaxed)(cast(A*)obj); - do - { - set = get ^ arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_release, memory_order.memory_order_release)(cast(A*)obj, &get, cast(A)set)); - break; - + return atomic_fetch_op!(memory_order.memory_order_release, "^=")(cast(A*)obj, arg); case memory_order.memory_order_acq_rel: - get = atomicLoad!(memory_order.memory_order_acq_rel)(cast(A*)obj); - do - { - set = get ^ arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_acq_rel, memory_order.memory_order_acq_rel)(cast(A*)obj, &get, cast(A)set)); - break; - + return atomic_fetch_op!(memory_order.memory_order_acq_rel, "^=")(cast(A*)obj, arg); case memory_order.memory_order_seq_cst: - get = atomicLoad!(memory_order.memory_order_relaxed)(cast(A*)obj); - do - { - set = get ^ arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst)(cast(A*)obj, &get, cast(A)set)); - break; + return atomic_fetch_op!(memory_order.memory_order_seq_cst, "^=")(cast(A*)obj, arg); } - - return get; } /// -unittest +@trusted unittest { shared(int) val = 5; atomic_fetch_xor_explicit_impl(&val, 3, memory_order.memory_order_seq_cst); @@ -1040,21 +928,11 @@ pragma(inline, true) A atomic_fetch_and_impl(A, M)(shared(A)* obj, M arg) @trusted { assert(obj !is null); - - // copied from atomicOp - - A set, get = atomicLoad(cast(A*)obj); - - do - { - set = get & arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst)(cast(A*)obj, &get, cast(A)set)); - - return get; + return atomic_fetch_op!(memory_order.memory_order_seq_cst, "&=")(cast(A*)obj, arg); } /// -unittest +@trusted unittest { shared(int) val = 5; atomic_fetch_and_impl(&val, 3); @@ -1067,52 +945,19 @@ A atomic_fetch_and_explicit_impl(A, M)(shared(A)* obj, M arg, memory_order order { assert(obj !is null); - A set, get; - final switch(order) { case memory_order.memory_order_relaxed: - get = atomicLoad!(memory_order.memory_order_relaxed)(cast(A*)obj); - do - { - set = get & arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_relaxed, memory_order.memory_order_relaxed)(cast(A*)obj, &get, cast(A)set)); - break; - + return atomic_fetch_op!(memory_order.memory_order_relaxed, "&=")(cast(A*)obj, arg); case memory_order.memory_order_acquire: - get = atomicLoad!(memory_order.memory_order_acquire)(cast(A*)obj); - do - { - set = get & arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_acquire, memory_order.memory_order_acquire)(cast(A*)obj, &get, cast(A)set)); - break; - + return atomic_fetch_op!(memory_order.memory_order_acquire, "&=")(cast(A*)obj, arg); case memory_order.memory_order_release: - get = atomicLoad!(memory_order.memory_order_relaxed)(cast(A*)obj); - do - { - set = get & arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_release, memory_order.memory_order_release)(cast(A*)obj, &get, cast(A)set)); - break; - + return atomic_fetch_op!(memory_order.memory_order_release, "&=")(cast(A*)obj, arg); case memory_order.memory_order_acq_rel: - get = atomicLoad!(memory_order.memory_order_acq_rel)(cast(A*)obj); - do - { - set = get & arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_acq_rel, memory_order.memory_order_acq_rel)(cast(A*)obj, &get, cast(A)set)); - break; - + return atomic_fetch_op!(memory_order.memory_order_acq_rel, "&=")(cast(A*)obj, arg); case memory_order.memory_order_seq_cst: - get = atomicLoad!(memory_order.memory_order_relaxed)(cast(A*)obj); - do - { - set = get & arg; - } while (!atomicCompareExchangeWeak!(memory_order.memory_order_seq_cst, memory_order.memory_order_seq_cst)(cast(A*)obj, &get, cast(A)set)); - break; + return atomic_fetch_op!(memory_order.memory_order_seq_cst, "&=")(cast(A*)obj, arg); } - - return get; } /// @@ -1122,3 +967,33 @@ unittest atomic_fetch_and_explicit_impl(&val, 3, memory_order.memory_order_seq_cst); assert(atomic_load_impl(&val) == 1); } + +private: + +pragma(inline, true) +A atomic_fetch_op(memory_order order, string op, A, M)(A* obj, M arg) @trusted +{ + static if (is(A : ulong) && (op == "+=" || op == "-=")) + { + // these cannot handle floats + static if (op == "+=") + { + return atomicFetchAdd!order(obj, arg); + } + else static if (op == "-=") + { + return atomicFetchSub!order(obj, arg); + } + } + else + { + // copied from core.atomic + A set, get = atomicLoad!(MemoryOrder.raw, A)(obj); + do + { + set = get; + mixin("set " ~ op ~ " arg;"); // will error if op (which is not exposed to user) is invalid + } while (!atomicCompareExchangeWeak!(order, MemoryOrder.raw)(obj, &get, set)); + return get; // unlike core.atomic we return the prior value, not the new one. + } +} diff --git a/libphobos/libdruntime/core/thread/fiber.d b/libphobos/libdruntime/core/thread/fiber.d index 8bbd6e15c4e6..50253b095128 100644 --- a/libphobos/libdruntime/core/thread/fiber.d +++ b/libphobos/libdruntime/core/thread/fiber.d @@ -1066,13 +1066,11 @@ private: { m_pmem = valloc( sz ); } - else static if ( __traits( compiles, malloc ) ) - { - m_pmem = malloc( sz ); - } else { - m_pmem = null; + import core.stdc.stdlib : malloc; + + m_pmem = malloc( sz ); } if ( !m_pmem ) @@ -1116,11 +1114,8 @@ private: // Free this fiber's stack. // final void freeStack() nothrow @nogc - in - { - assert( m_pmem && m_ctxt ); - } - do + in(m_pmem) + in(m_ctxt) { // NOTE: m_ctxt is guaranteed to be alive because it is held in the // global context list. @@ -1140,11 +1135,7 @@ private: { munmap( m_pmem, m_size ); } - else static if ( __traits( compiles, valloc ) ) - { - free( m_pmem ); - } - else static if ( __traits( compiles, malloc ) ) + else { free( m_pmem ); } diff --git a/libphobos/src/MERGE b/libphobos/src/MERGE index 1d41231db9dd..8b81f80e5295 100644 --- a/libphobos/src/MERGE +++ b/libphobos/src/MERGE @@ -1,4 +1,4 @@ -6d6e0b9b9fb5e882c7296f719baf829feb4939a3 +31dedd7daa38004229cb4e49a03ac7a6e0f723dd The first line of this file holds the git revision number of the last merge done from the dlang/phobos repository. diff --git a/libphobos/src/std/algorithm/searching.d b/libphobos/src/std/algorithm/searching.d index 4526aa22bc02..465723c16edd 100644 --- a/libphobos/src/std/algorithm/searching.d +++ b/libphobos/src/std/algorithm/searching.d @@ -5053,7 +5053,8 @@ if (isInputRange!Range) _input = input; _sentinel = sentinel; _openRight = openRight; - static if (isInputRange!Sentinel) + static if (isInputRange!Sentinel + && is(immutable ElementEncodingType!Sentinel == immutable ElementEncodingType!Range)) { _matchStarted = predSatisfied(); _done = _input.empty || _sentinel.empty || openRight && _matchStarted; @@ -5120,7 +5121,8 @@ if (isInputRange!Range) assert(!empty, "Can not popFront of an empty Until"); if (!_openRight) { - static if (isInputRange!Sentinel) + static if (isInputRange!Sentinel + && is(immutable ElementEncodingType!Sentinel == immutable ElementEncodingType!Range)) { _input.popFront(); _done = _input.empty || _sentinel.empty; @@ -5237,6 +5239,7 @@ pure @safe unittest assert(equal(r.save, "foo")); } } + // https://issues.dlang.org/show_bug.cgi?id=14543 pure @safe unittest { @@ -5267,3 +5270,10 @@ pure @safe unittest assert("one two three".until!((a,b)=>a.toUpper == b)("TWO", No.openRight).equal("one two")); } +// https://issues.dlang.org/show_bug.cgi?id=24342 +pure @safe unittest +{ + import std.algorithm.comparison : equal; + assert(["A", "BC", "D"].until("BC", No.openRight).equal(["A", "BC"])); + assert([[1], [2, 3], [4]].until([2, 3], No.openRight).equal([[1], [2, 3]])); +} -- GitLab