# HG changeset patch # User lindquist # Date 1191462176 -7200 # Node ID 788401029ecf220dd9a9de7949e3578a366655dd # Parent c05ef76f1c20ee17fcaa7f0de35e47c17977ab5e [svn r23] * Updated to DMD 1.021 diff -r c05ef76f1c20 -r 788401029ecf dmd/attrib.c --- a/dmd/attrib.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/attrib.c Thu Oct 04 03:42:56 2007 +0200 @@ -192,6 +192,28 @@ } } +int AttribDeclaration::cvMember(unsigned char *p) +{ + unsigned i; + int nwritten = 0; + int n; + Array *d = include(NULL, NULL); + + if (d) + { + for (i = 0; i < d->dim; i++) + { Dsymbol *s; + + s = (Dsymbol *)d->data[i]; + n = s->cvMember(p); + if (p) + p += n; + nwritten += n; + } + } + return nwritten; +} + int AttribDeclaration::hasPointers() { Array *d = include(NULL, NULL); diff -r c05ef76f1c20 -r 788401029ecf dmd/attrib.h --- a/dmd/attrib.h Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/attrib.h Thu Oct 04 03:42:56 2007 +0200 @@ -51,6 +51,7 @@ AttribDeclaration *isAttribDeclaration() { return this; } void toObjFile(); // compile to .obj file + int cvMember(unsigned char *p); }; struct StorageClassDeclaration: AttribDeclaration diff -r c05ef76f1c20 -r 788401029ecf dmd/cast.c --- a/dmd/cast.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/cast.c Thu Oct 04 03:42:56 2007 +0200 @@ -658,77 +658,85 @@ Expression *StringExp::castTo(Scope *sc, Type *t) { + /* This follows copy-on-write; any changes to 'this' + * will result in a copy. + * The this->string member is considered immutable. + */ StringExp *se; Type *tb; - int unique; + int copied = 0; //printf("StringExp::castTo(t = %s), '%s' committed = %d\n", t->toChars(), toChars(), committed); - if (!committed && t->ty == Tpointer && t->next->ty == Tvoid) + if (!committed && t->ty == Tpointer && t->nextOf()->ty == Tvoid) { error("cannot convert string literal to void*"); } + se = this; + if (!committed) + { se = (StringExp *)copy(); + se->committed = 1; + copied = 1; + } + + if (type == t) + { + return se; + } + tb = t->toBasetype(); //printf("\ttype = %s\n", type->toChars()); if (tb->ty == Tdelegate && type->toBasetype()->ty != Tdelegate) return Expression::castTo(sc, t); - se = this; - unique = 0; - if (!committed) + Type *typeb = type->toBasetype(); + if (typeb == tb) { - // Copy when committing the type - void *s; - - s = (unsigned char *)mem.malloc((len + 1) * sz); - memcpy(s, string, (len + 1) * sz); - se = new StringExp(loc, s, len); - se->type = type; - se->sz = sz; - se->committed = 0; - unique = 1; // this is the only instance - } - se->type = type->toBasetype(); - if (tb == se->type) - { se->type = t; - se->committed = 1; + if (!copied) + { se = (StringExp *)copy(); + copied = 1; + } + se->type = t; return se; } if (tb->ty != Tsarray && tb->ty != Tarray && tb->ty != Tpointer) - { se->committed = 1; - goto Lcast; - } - if (se->type->ty != Tsarray && se->type->ty != Tarray && se->type->ty != Tpointer) - { se->committed = 1; + { if (!copied) + { se = (StringExp *)copy(); + copied = 1; + } goto Lcast; } - - if (se->committed == 1) - { - if (se->type->next->size() == tb->next->size()) - { se->type = t; - return se; + if (typeb->ty != Tsarray && typeb->ty != Tarray && typeb->ty != Tpointer) + { if (!copied) + { se = (StringExp *)copy(); + copied = 1; } goto Lcast; } - se->committed = 1; + if (typeb->nextOf()->size() == tb->nextOf()->size()) + { + if (!copied) + { se = (StringExp *)copy(); + copied = 1; + } + if (tb->ty == Tsarray) + goto L2; // handle possible change in static array dimension + se->type = t; + return se; + } - int tfty; - int ttty; - char *p; - size_t u; - unsigned c; - size_t newlen; + if (committed) + goto Lcast; #define X(tf,tt) ((tf) * 256 + (tt)) { OutBuffer buffer; - newlen = 0; - tfty = se->type->next->toBasetype()->ty; - ttty = tb->next->toBasetype()->ty; + size_t newlen = 0; + int tfty = typeb->nextOf()->toBasetype()->ty; + int ttty = tb->nextOf()->toBasetype()->ty; switch (X(tfty, ttty)) { case X(Tchar, Tchar): @@ -737,9 +745,9 @@ break; case X(Tchar, Twchar): - for (u = 0; u < len;) - { - p = utf_decodeChar((unsigned char *)se->string, len, &u, &c); + for (size_t u = 0; u < len;) + { unsigned c; + char *p = utf_decodeChar((unsigned char *)se->string, len, &u, &c); if (p) error("%s", p); else @@ -750,9 +758,9 @@ goto L1; case X(Tchar, Tdchar): - for (u = 0; u < len;) - { - p = utf_decodeChar((unsigned char *)se->string, len, &u, &c); + for (size_t u = 0; u < len;) + { unsigned c; + char *p = utf_decodeChar((unsigned char *)se->string, len, &u, &c); if (p) error("%s", p); buffer.write4(c); @@ -762,9 +770,9 @@ goto L1; case X(Twchar,Tchar): - for (u = 0; u < len;) - { - p = utf_decodeWchar((unsigned short *)se->string, len, &u, &c); + for (size_t u = 0; u < len;) + { unsigned c; + char *p = utf_decodeWchar((unsigned short *)se->string, len, &u, &c); if (p) error("%s", p); else @@ -775,9 +783,9 @@ goto L1; case X(Twchar,Tdchar): - for (u = 0; u < len;) - { - p = utf_decodeWchar((unsigned short *)se->string, len, &u, &c); + for (size_t u = 0; u < len;) + { unsigned c; + char *p = utf_decodeWchar((unsigned short *)se->string, len, &u, &c); if (p) error("%s", p); buffer.write4(c); @@ -787,9 +795,9 @@ goto L1; case X(Tdchar,Tchar): - for (u = 0; u < len; u++) + for (size_t u = 0; u < len; u++) { - c = ((unsigned *)se->string)[u]; + unsigned c = ((unsigned *)se->string)[u]; if (!utf_isValidDchar(c)) error("invalid UCS-32 char \\U%08x", c); else @@ -801,9 +809,9 @@ goto L1; case X(Tdchar,Twchar): - for (u = 0; u < len; u++) + for (size_t u = 0; u < len; u++) { - c = ((unsigned *)se->string)[u]; + unsigned c = ((unsigned *)se->string)[u]; if (!utf_isValidDchar(c)) error("invalid UCS-32 char \\U%08x", c); else @@ -815,22 +823,23 @@ goto L1; L1: - if (!unique) - se = new StringExp(loc, NULL, 0); + if (!copied) + { se = (StringExp *)copy(); + copied = 1; + } se->string = buffer.extractData(); se->len = newlen; - se->sz = tb->next->size(); + se->sz = tb->nextOf()->size(); break; default: - if (se->type->next->size() == tb->next->size()) - { se->type = t; - return se; - } + assert(typeb->nextOf()->size() != tb->nextOf()->size()); goto Lcast; } } #undef X +L2: + assert(copied); // See if need to truncate or extend the literal if (tb->ty == Tsarray) @@ -842,28 +851,18 @@ // Changing dimensions if (dim2 != se->len) { + // Copy when changing the string literal unsigned newsz = se->sz; + void *s; + int d; - if (unique && dim2 < se->len) - { se->len = dim2; - // Add terminating 0 - memset((unsigned char *)se->string + dim2 * newsz, 0, newsz); - } - else - { - // Copy when changing the string literal - void *s; - int d; - - d = (dim2 < se->len) ? dim2 : se->len; - s = (unsigned char *)mem.malloc((dim2 + 1) * newsz); - memcpy(s, se->string, d * newsz); - // Extend with 0, add terminating 0 - memset((char *)s + d * newsz, 0, (dim2 + 1 - d) * newsz); - se = new StringExp(loc, s, dim2); - se->committed = 1; // it now has a firm type - se->sz = newsz; - } + d = (dim2 < se->len) ? dim2 : se->len; + s = (unsigned char *)mem.malloc((dim2 + 1) * newsz); + memcpy(s, se->string, d * newsz); + // Extend with 0, add terminating 0 + memset((char *)s + d * newsz, 0, (dim2 + 1 - d) * newsz); + se->string = s; + se->len = dim2; } } se->type = t; @@ -871,7 +870,7 @@ Lcast: Expression *e = new CastExp(loc, se, t); - e->type = t; + e->type = t; // so semantic() won't be run on e return e; } diff -r c05ef76f1c20 -r 788401029ecf dmd/constfold.c --- a/dmd/constfold.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/constfold.c Thu Oct 04 03:42:56 2007 +0200 @@ -668,7 +668,35 @@ assert(op == TOKequal || op == TOKnotequal); - if (e1->op == TOKstring && e2->op == TOKstring) + if (e1->op == TOKnull) + { + if (e2->op == TOKnull) + cmp = 1; + else if (e2->op == TOKstring) + { StringExp *es2 = (StringExp *)e2; + cmp = (0 == es2->len); + } + else if (e2->op == TOKarrayliteral) + { ArrayLiteralExp *es2 = (ArrayLiteralExp *)e2; + cmp = !es2->elements || (0 == es2->elements->dim); + } + else + return EXP_CANT_INTERPRET; + } + else if (e2->op == TOKnull) + { + if (e1->op == TOKstring) + { StringExp *es1 = (StringExp *)e1; + cmp = (0 == es1->len); + } + else if (e1->op == TOKarrayliteral) + { ArrayLiteralExp *es1 = (ArrayLiteralExp *)e1; + cmp = !es1->elements || (0 == es1->elements->dim); + } + else + return EXP_CANT_INTERPRET; + } + else if (e1->op == TOKstring && e2->op == TOKstring) { StringExp *es1 = (StringExp *)e1; StringExp *es2 = (StringExp *)e2; @@ -792,7 +820,11 @@ Loc loc = e1->loc; int cmp; - if (e1->op == TOKsymoff && e2->op == TOKsymoff) + if (e1->op == TOKnull && e2->op == TOKnull) + { + cmp = 1; + } + else if (e1->op == TOKsymoff && e2->op == TOKsymoff) { SymOffExp *es1 = (SymOffExp *)e1; SymOffExp *es2 = (SymOffExp *)e2; @@ -1051,7 +1083,7 @@ } else { - error("cannot cast %s to %s", e1->type->toChars(), type->toChars()); + error(loc, "cannot cast %s to %s", e1->type->toChars(), type->toChars()); e = new IntegerExp(loc, 0, type); } return e; @@ -1245,11 +1277,11 @@ //printf("Cat(e1 = %s, e2 = %s)\n", e1->toChars(), e2->toChars()); - if (e1->op == TOKnull && e2->op == TOKint64) + if (e1->op == TOKnull && (e2->op == TOKint64 || e2->op == TOKstructliteral)) { e = e2; goto L2; } - else if (e1->op == TOKint64 && e2->op == TOKnull) + else if ((e1->op == TOKint64 || e1->op == TOKstructliteral) && e2->op == TOKnull) { e = e1; L2: Type *tn = e->type->toBasetype(); @@ -1381,7 +1413,7 @@ e->type = type; } else if (e1->op == TOKarrayliteral && - e1->type->toBasetype()->next->equals(e2->type)) + e1->type->toBasetype()->nextOf()->equals(e2->type)) { ArrayLiteralExp *es1 = (ArrayLiteralExp *)e1; @@ -1398,7 +1430,7 @@ e->type = type; } else if (e2->op == TOKarrayliteral && - e2->type->toBasetype()->next->equals(e1->type)) + e2->type->toBasetype()->nextOf()->equals(e1->type)) { ArrayLiteralExp *es2 = (ArrayLiteralExp *)e2; @@ -1425,7 +1457,7 @@ t = e2->type; L1: Type *tb = t->toBasetype(); - if (tb->ty == Tarray && tb->next->equals(e->type)) + if (tb->ty == Tarray && tb->nextOf()->equals(e->type)) { Expressions *expressions = new Expressions(); expressions->push(e); e = new ArrayLiteralExp(loc, expressions); diff -r c05ef76f1c20 -r 788401029ecf dmd/declaration.c --- a/dmd/declaration.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/declaration.c Thu Oct 04 03:42:56 2007 +0200 @@ -771,7 +771,12 @@ //printf("Providing default initializer for '%s'\n", toChars()); if (type->ty == Tstruct && ((TypeStruct *)type)->sym->zeroInit == 1) - { + { /* If a struct is all zeros, as a special case + * set it's initializer to the integer 0. + * In AssignExp::toElem(), we check for this and issue + * a memset() to initialize the struct. + * Must do same check in interpreter. + */ Expression *e = new IntegerExp(loc, 0, Type::tint32); Expression *e1; e1 = new VarExp(loc, this); @@ -801,11 +806,12 @@ if (init) { ArrayInitializer *ai = init->isArrayInitializer(); - if (ai && type->toBasetype()->ty == Taarray) + if (ai && tb->ty == Taarray) { init = ai->toAssocArrayInitializer(); } + StructInitializer *si = init->isStructInitializer(); ExpInitializer *ei = init->isExpInitializer(); // See if we can allocate on the stack @@ -898,16 +904,25 @@ * Ignore failure. */ - if (ei && !global.errors && !inferred) + if (!global.errors && !inferred) { unsigned errors = global.errors; global.gag++; //printf("+gag\n"); - Expression *e = ei->exp->syntaxCopy(); + Expression *e; + Initializer *i2 = init; inuse++; - e = e->semantic(sc); + if (ei) + { + e = ei->exp->syntaxCopy(); + e = e->semantic(sc); + e = e->implicitCastTo(sc, type); + } + else if (si || ai) + { i2 = init->syntaxCopy(); + i2 = i2->semantic(sc, type); + } inuse--; - e = e->implicitCastTo(sc, type); global.gag--; //printf("-gag\n"); if (errors != global.errors) // if errors happened @@ -915,7 +930,7 @@ if (global.gag == 0) global.errors = errors; // act as if nothing happened } - else + else if (ei) { e = e->optimize(WANTvalue | WANTinterpret); if (e->op == TOKint64 || e->op == TOKstring) @@ -923,6 +938,8 @@ ei->exp = e; // no errors, keep result } } + else + init = i2; // no errors, keep result } } } diff -r c05ef76f1c20 -r 788401029ecf dmd/dsymbol.c --- a/dmd/dsymbol.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/dsymbol.c Thu Oct 04 03:42:56 2007 +0200 @@ -775,6 +775,43 @@ } +/******************************************* + * Look for member of the form: + * const(MemberInfo)[] getMembers(string); + * Returns NULL if not found + */ + +#if V2 +FuncDeclaration *ScopeDsymbol::findGetMembers() +{ + Dsymbol *s = search_function(this, Id::getmembers); + FuncDeclaration *fdx = s ? s->isFuncDeclaration() : NULL; + +#if 0 // Finish + static TypeFunction *tfgetmembers; + + if (!tfgetmembers) + { + Scope sc; + Arguments *arguments = new Arguments; + Arguments *arg = new Argument(STCin, Type::tchar->constOf()->arrayOf(), NULL, NULL); + arguments->push(arg); + + Type *tret = NULL; + tfgetmembers = new TypeFunction(arguments, tret, 0, LINKd); + tfgetmembers = (TypeFunction *)tfgetmembers->semantic(0, &sc); + } + if (fdx) + fdx = fdx->overloadExactMatch(tfgetmembers); +#endif + if (fdx && fdx->isVirtual()) + fdx = NULL; + + return fdx; +} +#endif + + /****************************** WithScopeSymbol ******************************/ WithScopeSymbol::WithScopeSymbol(WithStatement *withstate) diff -r c05ef76f1c20 -r 788401029ecf dmd/expression.c --- a/dmd/expression.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/expression.c Thu Oct 04 03:42:56 2007 +0200 @@ -619,9 +619,11 @@ for (size_t i = 0; i < arguments->dim; i++) { Expression *arg = (Expression *)arguments->data[i]; - if (i) - buf->writeByte(','); - expToCBuffer(buf, hgs, arg, PREC_assign); + if (arg) + { if (i) + buf->writeByte(','); + expToCBuffer(buf, hgs, arg, PREC_assign); + } } } } @@ -3979,9 +3981,9 @@ /************************************************************/ -IftypeExp::IftypeExp(Loc loc, Type *targ, Identifier *id, enum TOK tok, +IsExp::IsExp(Loc loc, Type *targ, Identifier *id, enum TOK tok, Type *tspec, enum TOK tok2) - : Expression(loc, TOKis, sizeof(IftypeExp)) + : Expression(loc, TOKis, sizeof(IsExp)) { this->targ = targ; this->id = id; @@ -3990,9 +3992,9 @@ this->tok2 = tok2; } -Expression *IftypeExp::syntaxCopy() -{ - return new IftypeExp(loc, +Expression *IsExp::syntaxCopy() +{ + return new IsExp(loc, targ->syntaxCopy(), id, tok, @@ -4000,10 +4002,10 @@ tok2); } -Expression *IftypeExp::semantic(Scope *sc) +Expression *IsExp::semantic(Scope *sc) { Type *tded; - //printf("IftypeExp::semantic()\n"); + //printf("IsExp::semantic()\n"); if (id && !(sc->flags & SCOPEstaticif)) error("can only declare type aliases within static if conditionals"); @@ -4201,11 +4203,15 @@ return new IntegerExp(0); } -void IftypeExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +void IsExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("is("); targ->toCBuffer(buf, id, hgs); - if (tspec) + if (tok2 != TOKreserved) + { + buf->printf(" %s %s", Token::toChars(tok), Token::toChars(tok2)); + } + else if (tspec) { if (tok == TOKcolon) buf->writestring(" : "); @@ -4213,6 +4219,17 @@ buf->writestring(" == "); tspec->toCBuffer(buf, NULL, hgs); } +#if V2 + if (parameters) + { // First parameter is already output, so start with second + for (int i = 1; i < parameters->dim; i++) + { + buf->writeByte(','); + TemplateParameter *tp = (TemplateParameter *)parameters->data[i]; + tp->toCBuffer(buf, hgs); + } + } +#endif buf->writeByte(')'); } @@ -5308,7 +5325,7 @@ int istemp; #if LOGSEMANTIC - printf("CallExp::semantic('%s')\n", toChars()); + printf("CallExp::semantic() %s\n", toChars()); #endif if (type) return this; // semantic() already run @@ -5443,6 +5460,9 @@ ad = ((TypeStruct *)t1)->sym; if (search_function(ad, Id::call)) goto L1; // overload of opCall, therefore it's a call + + if (e1->op != TOKtype) + error("%s %s does not overload ()", ad->kind(), ad->toChars()); /* It's a struct literal */ Expression *e = new StructLiteralExp(loc, (StructDeclaration *)ad, arguments); diff -r c05ef76f1c20 -r 788401029ecf dmd/expression.h --- a/dmd/expression.h Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/expression.h Thu Oct 04 03:42:56 2007 +0200 @@ -70,6 +70,8 @@ void argExpTypesToCBuffer(OutBuffer *buf, Expressions *arguments, HdrGenState *hgs); void argsToCBuffer(OutBuffer *buf, Expressions *arguments, HdrGenState *hgs); void expandTuples(Expressions *exps); +FuncDeclaration *hasThis(Scope *sc); +Expression *fromConstInitializer(int result, Expression *e); struct Expression : Object { @@ -622,7 +624,7 @@ elem *toElem(IRState *irs); }; -struct IftypeExp : Expression +struct IsExp : Expression { /* is(targ id tok tspec) * is(targ id == tok2) @@ -633,7 +635,7 @@ Type *tspec; // can be NULL enum TOK tok2; // 'struct', 'union', 'typedef', etc. - IftypeExp(Loc loc, Type *targ, Identifier *id, enum TOK tok, Type *tspec, enum TOK tok2); + IsExp(Loc loc, Type *targ, Identifier *id, enum TOK tok, Type *tspec, enum TOK tok2); Expression *syntaxCopy(); Expression *semantic(Scope *sc); void toCBuffer(OutBuffer *buf, HdrGenState *hgs); diff -r c05ef76f1c20 -r 788401029ecf dmd/func.c --- a/dmd/func.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/func.c Thu Oct 04 03:42:56 2007 +0200 @@ -255,7 +255,7 @@ if (!isVirtual()) { //printf("\tnot virtual\n"); - return; + goto Ldone; } // Find index of existing function in vtbl[] to override @@ -405,8 +405,8 @@ #if 0 if (offset) ti = fdv->type; - else if (type->next->ty == Tclass) - { ClassDeclaration *cdn = ((TypeClass *)type->next)->sym; + else if (type->nextOf()->ty == Tclass) + { ClassDeclaration *cdn = ((TypeClass *)type->nextOf())->sym; if (cdn && cdn->sizeok != 1) ti = fdv->type; } @@ -480,8 +480,8 @@ { Argument *arg0 = Argument::getNth(f->parameters, 0); if (arg0->type->ty != Tarray || - arg0->type->next->ty != Tarray || - arg0->type->next->next->ty != Tchar || + arg0->type->nextOf()->ty != Tarray || + arg0->type->nextOf()->nextOf()->ty != Tchar || arg0->storageClass & (STCout | STCref | STClazy)) goto Lmainerr; break; @@ -526,6 +526,7 @@ } } +Ldone: /* Save scope for possible later use (if we need the * function internals) */ @@ -2185,7 +2186,8 @@ /********************************* StaticCtorDeclaration ****************************/ StaticCtorDeclaration::StaticCtorDeclaration(Loc loc, Loc endloc) - : FuncDeclaration(loc, endloc, Id::staticCtor, STCstatic, NULL) + : FuncDeclaration(loc, endloc, + Identifier::generateId("_staticCtor"), STCstatic, NULL) { } @@ -2257,7 +2259,8 @@ /********************************* StaticDtorDeclaration ****************************/ StaticDtorDeclaration::StaticDtorDeclaration(Loc loc, Loc endloc) - : FuncDeclaration(loc, endloc, Id::staticDtor, STCstatic, NULL) + : FuncDeclaration(loc, endloc, + Identifier::generateId("_staticDtor"), STCstatic, NULL) { } diff -r c05ef76f1c20 -r 788401029ecf dmd/id.c --- a/dmd/id.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/id.c Thu Oct 04 03:42:56 2007 +0200 @@ -12,8 +12,6 @@ Identifier *Id::dtor; Identifier *Id::classInvariant; Identifier *Id::unitTest; -Identifier *Id::staticCtor; -Identifier *Id::staticDtor; Identifier *Id::init; Identifier *Id::size; Identifier *Id::__sizeof; @@ -187,8 +185,6 @@ dtor = Lexer::idPool("_dtor"); classInvariant = Lexer::idPool("__invariant"); unitTest = Lexer::idPool("_unitTest"); - staticCtor = Lexer::idPool("_staticCtor"); - staticDtor = Lexer::idPool("_staticDtor"); init = Lexer::idPool("init"); size = Lexer::idPool("size"); __sizeof = Lexer::idPool("sizeof"); diff -r c05ef76f1c20 -r 788401029ecf dmd/id.h --- a/dmd/id.h Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/id.h Thu Oct 04 03:42:56 2007 +0200 @@ -14,8 +14,6 @@ static Identifier *dtor; static Identifier *classInvariant; static Identifier *unitTest; - static Identifier *staticCtor; - static Identifier *staticDtor; static Identifier *init; static Identifier *size; static Identifier *__sizeof; diff -r c05ef76f1c20 -r 788401029ecf dmd/identifier.c --- a/dmd/identifier.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/identifier.c Thu Oct 04 03:42:56 2007 +0200 @@ -53,14 +53,20 @@ else if (this == Id::dtor) p = "~this"; else if (this == Id::classInvariant) p = "invariant"; else if (this == Id::unitTest) p = "unittest"; - else if (this == Id::staticCtor) p = "static this"; - else if (this == Id::staticDtor) p = "static ~this"; else if (this == Id::dollar) p = "$"; else if (this == Id::withSym) p = "with"; else if (this == Id::result) p = "result"; else if (this == Id::returnLabel) p = "return"; else - p = toChars(); + { p = toChars(); + if (*p == '_') + { + if (memcmp(p, "_staticCtor", 11) == 0) + p = "static this"; + else if (memcmp(p, "_staticDtor", 11) == 0) + p = "static ~this"; + } + } return p; } diff -r c05ef76f1c20 -r 788401029ecf dmd/idgen.c --- a/dmd/idgen.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/idgen.c Thu Oct 04 03:42:56 2007 +0200 @@ -38,8 +38,6 @@ { "dtor", "_dtor" }, { "classInvariant", "__invariant" }, { "unitTest", "_unitTest" }, - { "staticCtor", "_staticCtor" }, - { "staticDtor", "_staticDtor" }, { "init" }, { "size" }, { "__sizeof", "sizeof" }, diff -r c05ef76f1c20 -r 788401029ecf dmd/init.c --- a/dmd/init.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/init.c Thu Oct 04 03:42:56 2007 +0200 @@ -235,9 +235,43 @@ } +/*************************************** + * This works by transforming a struct initializer into + * a struct literal. In the future, the two should be the + * same thing. + */ Expression *StructInitializer::toExpression() -{ - return NULL; // cannot do it +{ Expression *e; + + //printf("StructInitializer::toExpression() %s\n", toChars()); + if (!ad) // if fwd referenced + { + return NULL; + } + StructDeclaration *sd = ad->isStructDeclaration(); + if (!sd) + return NULL; + Expressions *elements = new Expressions(); + for (size_t i = 0; i < value.dim; i++) + { + if (field.data[i]) + goto Lno; + Initializer *iz = (Initializer *)value.data[i]; + if (!iz) + goto Lno; + Expression *ex = iz->toExpression(); + if (!ex) + goto Lno; + elements->push(ex); + } + e = new StructLiteralExp(loc, sd, elements); + e->type = sd->type; + return e; + +Lno: + delete elements; + //error(loc, "struct initializers as expressions are not allowed"); + return NULL; } diff -r c05ef76f1c20 -r 788401029ecf dmd/init.h --- a/dmd/init.h Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/init.h Thu Oct 04 03:42:56 2007 +0200 @@ -23,6 +23,7 @@ struct dt_t; struct AggregateDeclaration; struct VoidInitializer; +struct StructInitializer; struct ArrayInitializer; struct ExpInitializer; struct StructInitializer; @@ -47,9 +48,9 @@ virtual dt_t *toDt(); virtual VoidInitializer *isVoidInitializer() { return NULL; } + virtual StructInitializer *isStructInitializer() { return NULL; } virtual ArrayInitializer *isArrayInitializer() { return NULL; } virtual ExpInitializer *isExpInitializer() { return NULL; } - virtual StructInitializer *isStructInitializer() { return NULL; } }; struct VoidInitializer : Initializer @@ -84,7 +85,7 @@ dt_t *toDt(); - virtual StructInitializer *isStructInitializer() { return this; } + StructInitializer *isStructInitializer() { return this; } }; struct ArrayInitializer : Initializer diff -r c05ef76f1c20 -r 788401029ecf dmd/interpret.c --- a/dmd/interpret.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/interpret.c Thu Oct 04 03:42:56 2007 +0200 @@ -77,6 +77,7 @@ return NULL; } + //printf("test2 %d, %p\n", semanticRun, scope); if (semanticRun == 0 && scope) { semantic3(scope); @@ -276,7 +277,7 @@ Expression *e = exp->interpret(istate); if (e == EXP_CANT_INTERPRET) { - //printf("cannot interpret %s\n", exp->toChars()); + //printf("-ExpStatement::interpret(): %p\n", e); return EXP_CANT_INTERPRET; } } @@ -364,20 +365,13 @@ //if (e == EXP_CANT_INTERPRET) printf("cannot interpret\n"); if (e != EXP_CANT_INTERPRET) { - if (!e->isConst()) - { - e = EXP_CANT_INTERPRET; - } + if (e->isBool(TRUE)) + e = ifbody ? ifbody->interpret(istate) : NULL; + else if (e->isBool(FALSE)) + e = elsebody ? elsebody->interpret(istate) : NULL; else { - if (e->isBool(TRUE)) - e = ifbody ? ifbody->interpret(istate) : NULL; - else if (e->isBool(FALSE)) - e = elsebody ? elsebody->interpret(istate) : NULL; - else - { - e = EXP_CANT_INTERPRET; - } + e = EXP_CANT_INTERPRET; } } return e; @@ -957,7 +951,7 @@ { if (v->isConst() && v->init) { e = v->init->toExpression(); - if (!e->type) + if (e && !e->type) e->type = v->type; } else @@ -994,7 +988,7 @@ #if LOG printf("DeclarationExp::interpret() %s\n", toChars()); #endif - Expression *e = EXP_CANT_INTERPRET; + Expression *e; VarDeclaration *v = declaration->isVarDeclaration(); if (v) { @@ -1015,6 +1009,19 @@ e->type = v->type; } } + else if (declaration->isAttribDeclaration() || + declaration->isTemplateMixin() || + declaration->isTupleDeclaration()) + { // These can be made to work, too lazy now + e = EXP_CANT_INTERPRET; + } + else + { // Others should not contain executable code, so are trivial to evaluate + e = NULL; + } +#if LOG + printf("-DeclarationExp::interpret(): %p\n", e); +#endif return e; } @@ -1084,7 +1091,7 @@ if (!expsx) { expsx = new Expressions(); expsx->setDim(elements->dim); - for (size_t j = 0; j < i; j++) + for (size_t j = 0; j < elements->dim; j++) { expsx->data[j] = elements->data[j]; } @@ -1342,6 +1349,7 @@ if (e1 == EXP_CANT_INTERPRET) goto Lcant; if (e1->isConst() != 1 && + e1->op != TOKnull && e1->op != TOKstring && e1->op != TOKarrayliteral && e1->op != TOKstructliteral) @@ -1351,6 +1359,7 @@ if (e2 == EXP_CANT_INTERPRET) goto Lcant; if (e2->isConst() != 1 && + e2->op != TOKnull && e2->op != TOKstring && e2->op != TOKarrayliteral && e2->op != TOKstructliteral) @@ -1420,7 +1429,14 @@ if (fp) e2 = (*fp)(v->type, ev, e2); else + { /* Look for special case of struct being initialized with 0. + */ + if (v->type->toBasetype()->ty == Tstruct && e2->op == TOKint64) + { + e2 = v->type->defaultInit(); + } e2 = Cast(v->type, v->type, e2); + } if (e2 != EXP_CANT_INTERPRET) { if (!v->isParameter()) @@ -1453,9 +1469,15 @@ { error("variable %s is used before initialization", v->toChars()); return e; } - if (v->value->op != TOKstructliteral) + Expression *vie = v->value; + if (vie->op == TOKvar) + { + Declaration *d = ((VarExp *)vie)->var; + vie = getVarExp(e1->loc, istate, d); + } + if (vie->op != TOKstructliteral) return EXP_CANT_INTERPRET; - StructLiteralExp *se = (StructLiteralExp *)v->value; + StructLiteralExp *se = (StructLiteralExp *)vie; int fieldi = se->getFieldIndex(type, soe->offset); if (fieldi == -1) return EXP_CANT_INTERPRET; @@ -1843,6 +1865,10 @@ { e = ArrayLength(type, e1); } + else if (e1->op == TOKnull) + { + e = new IntegerExp(loc, 0, type); + } else goto Lcant; return e; diff -r c05ef76f1c20 -r 788401029ecf dmd/lexer.c --- a/dmd/lexer.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/lexer.c Thu Oct 04 03:42:56 2007 +0200 @@ -459,7 +459,7 @@ if (!p || !*p) goto Linvalid; - if (isdigit(*p)) + if (*p >= '0' && *p <= '9') // beware of isdigit() on signed chars goto Linvalid; len = strlen(p); @@ -568,6 +568,23 @@ t->value = hexStringConstant(t); return; +#if V2 + case 'q': + if (p[1] == '"') + { + p++; + t->value = delimitedStringConstant(t); + return; + } + else if (p[1] == '{') + { + p++; + t->value = tokenStringConstant(t); + return; + } + else + goto case_ident; +#endif case '"': t->value = escapeStringConstant(t,0); @@ -598,7 +615,11 @@ case 'a': case 'b': case 'c': case 'd': case 'e': case 'f': case 'g': case 'h': case 'i': case 'j': case 'k': case 'm': case 'n': case 'o': +#if V2 + case 'p': /*case 'q': case 'r':*/ case 's': case 't': +#else case 'p': case 'q': /*case 'r':*/ case 's': case 't': +#endif case 'u': case 'v': case 'w': /*case 'x':*/ case 'y': case 'z': case 'A': case 'B': case 'C': case 'D': case 'E': @@ -1431,6 +1452,223 @@ } } + +#if V2 +/************************************** + * Lex delimited strings: + * q"(foo(xxx))" // "foo(xxx)" + * q"[foo(]" // "foo(" + * q"/foo]/" // "foo]" + * q"HERE + * foo + * HERE" // "foo\n" + * Input: + * p is on the " + */ + +TOK Lexer::delimitedStringConstant(Token *t) +{ unsigned c; + Loc start = loc; + unsigned delimleft = 0; + unsigned delimright = 0; + unsigned nest = 1; + unsigned nestcount; + Identifier *hereid = NULL; + unsigned blankrol = 0; + unsigned startline = 0; + + p++; + stringbuffer.reset(); + while (1) + { + c = *p++; + //printf("c = '%c'\n", c); + switch (c) + { + case '\n': + Lnextline: +printf("Lnextline\n"); + loc.linnum++; + startline = 1; + if (blankrol) + { blankrol = 0; + continue; + } + if (hereid) + { + stringbuffer.writeUTF8(c); + continue; + } + break; + + case '\r': + if (*p == '\n') + continue; // ignore + c = '\n'; // treat EndOfLine as \n character + goto Lnextline; + + case 0: + case 0x1A: + goto Lerror; + + default: + if (c & 0x80) + { p--; + c = decodeUTF(); + p++; + if (c == PS || c == LS) + goto Lnextline; + } + break; + } + if (delimleft == 0) + { delimleft = c; + nest = 1; + nestcount = 1; + if (c == '(') + delimright = ')'; + else if (c == '{') + delimright = '}'; + else if (c == '[') + delimright = ']'; + else if (c == '<') + delimright = '>'; + else if (isalpha(c) || c == '_' || (c >= 0x80 && isUniAlpha(c))) + { // Start of identifier; must be a heredoc + Token t; + p--; + scan(&t); // read in heredoc identifier + if (t.value != TOKidentifier) + { error("identifier expected for heredoc, not %s", t.toChars()); + delimright = c; + } + else + { hereid = t.ident; +printf("hereid = '%s'\n", hereid->toChars()); + blankrol = 1; + } + nest = 0; + } + else + { delimright = c; + nest = 0; + } + } + else + { + if (blankrol) + { error("heredoc rest of line should be blank"); + blankrol = 0; + continue; + } + if (nest == 1) + { + if (c == delimleft) + nestcount++; + else if (c == delimright) + { nestcount--; + if (nestcount == 0) + goto Ldone; + } + } + else if (c == delimright) + goto Ldone; + if (startline && isalpha(c)) + { Token t; + unsigned char *psave = p; + p--; + scan(&t); // read in possible heredoc identifier +printf("endid = '%s'\n", t.ident->toChars()); + if (t.value == TOKidentifier && t.ident->equals(hereid)) + { /* should check that rest of line is blank + */ +printf("done\n"); + goto Ldone; + } + p = psave; + } + stringbuffer.writeUTF8(c); + startline = 0; + } + } + +Ldone: + if (*p == '"') + p++; + else + error("delimited string must end in %c\"", delimright); + t->len = stringbuffer.offset; + stringbuffer.writeByte(0); + t->ustring = (unsigned char *)mem.malloc(stringbuffer.offset); + memcpy(t->ustring, stringbuffer.data, stringbuffer.offset); + stringPostfix(t); + return TOKstring; + +Lerror: + error("unterminated string constant starting at %s", start.toChars()); + t->ustring = (unsigned char *)""; + t->len = 0; + t->postfix = 0; + return TOKstring; +} + +/************************************** + * Lex delimited strings: + * q{ foo(xxx) } // " foo(xxx) " + * q{foo(} // "foo(" + * q{{foo}"}"} // "{foo}"}"" + * Input: + * p is on the q + */ + +TOK Lexer::tokenStringConstant(Token *t) +{ + unsigned nest = 1; + Loc start = loc; + unsigned char *pstart = ++p; + + while (1) + { Token tok; + + scan(&tok); + switch (tok.value) + { + case TOKlcurly: + nest++; + continue; + + case TOKrcurly: + if (--nest == 0) + goto Ldone; + continue; + + case TOKeof: + goto Lerror; + + default: + continue; + } + } + +Ldone: + t->len = p - 1 - pstart; + t->ustring = (unsigned char *)mem.malloc(t->len + 1); + memcpy(t->ustring, pstart, t->len); + t->ustring[t->len] = 0; + stringPostfix(t); + return TOKstring; + +Lerror: + error("unterminated token string constant starting at %s", start.toChars()); + t->ustring = (unsigned char *)""; + t->len = 0; + t->postfix = 0; + return TOKstring; +} + +#endif + + /************************************** */ @@ -2641,6 +2879,9 @@ // Added after 1.0 { "ref", TOKref }, { "macro", TOKmacro }, +#if V2 + { "__traits", TOKtraits }, +#endif }; int Token::isKeyword() diff -r c05ef76f1c20 -r 788401029ecf dmd/lexer.h --- a/dmd/lexer.h Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/lexer.h Thu Oct 04 03:42:56 2007 +0200 @@ -150,6 +150,9 @@ // Added after 1.0 TOKref, TOKmacro, +#if V2 + TOKtraits, +#endif TOKMAX }; @@ -266,6 +269,10 @@ unsigned escapeSequence(); TOK wysiwygStringConstant(Token *t, int tc); TOK hexStringConstant(Token *t); +#if V2 + TOK delimitedStringConstant(Token *t); + TOK tokenStringConstant(Token *t); +#endif TOK escapeStringConstant(Token *t, int wide); TOK charConstant(Token *t, int wide); void stringPostfix(Token *t); diff -r c05ef76f1c20 -r 788401029ecf dmd/mars.c --- a/dmd/mars.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/mars.c Thu Oct 04 03:42:56 2007 +0200 @@ -68,7 +68,7 @@ copyright = "Copyright (c) 1999-2007 by Digital Mars and Tomas Lindquist Olsen"; written = "written by Walter Bright and Tomas Lindquist Olsen"; llvmdc_version = "0.0.1"; - version = "v1.020"; + version = "v1.021"; global.structalign = 8; memset(¶ms, 0, sizeof(Param)); @@ -282,6 +282,9 @@ global.params.optimizeLevel = 2; global.params.runtimeImppath = 0; + global.params.defaultlibname = "phobos"; + global.params.debuglibname = global.params.defaultlibname; + // Predefine version identifiers #if IN_LLVM VersionCondition::addPredefinedGlobalIdent("LLVM"); @@ -474,7 +477,7 @@ { global.params.runtimeImppath = p+2; } - else if (memcmp(p + 1, "debug", 5) == 0) + else if (memcmp(p + 1, "debug", 5) == 0 && p[6] != 'l') { // Parse: // -debug @@ -545,6 +548,14 @@ { global.params.linkswitches->push(p + 2); } + else if (memcmp(p + 1, "defaultlib=", 11) == 0) + { + global.params.defaultlibname = p + 1 + 11; + } + else if (memcmp(p + 1, "debuglib=", 9) == 0) + { + global.params.debuglibname = p + 1 + 9; + } else if (strcmp(p + 1, "run") == 0) { global.params.run = 1; global.params.runargs_length = ((i >= argcstart) ? argc : argcstart) - i - 1; diff -r c05ef76f1c20 -r 788401029ecf dmd/mars.h --- a/dmd/mars.h Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/mars.h Thu Oct 04 03:42:56 2007 +0200 @@ -94,6 +94,11 @@ bool dump_source; + char *defaultlibname; // default library for non-debug builds + char *debuglibname; // default library for debug builds + + char *xmlname; // filename for XML output + // Hidden debug switches char debuga; char debugb; diff -r c05ef76f1c20 -r 788401029ecf dmd/parse.c --- a/dmd/parse.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/parse.c Thu Oct 04 03:42:56 2007 +0200 @@ -3940,7 +3940,7 @@ { error("(type identifier : specialization) expected following is"); goto Lerr; } - e = new IftypeExp(loc, targ, ident, tok, tspec, tok2); + e = new IsExp(loc, targ, ident, tok, tspec, tok2); break; } diff -r c05ef76f1c20 -r 788401029ecf dmd/statement.c --- a/dmd/statement.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/statement.c Thu Oct 04 03:42:56 2007 +0200 @@ -894,6 +894,7 @@ sc->noctor--; condition = condition->semantic(sc); condition = resolveProperties(sc, condition); + condition = condition->optimize(WANTvalue); condition = condition->checkToBoolean(); @@ -979,6 +980,7 @@ sc->noctor++; condition = condition->semantic(sc); condition = resolveProperties(sc, condition); + condition = condition->optimize(WANTvalue); condition = condition->checkToBoolean(); if (increment) increment = increment->semantic(sc); @@ -1090,7 +1092,8 @@ { Arguments *args = Argument::arraySyntaxCopy(arguments); Expression *exp = aggr->syntaxCopy(); - ForeachStatement *s = new ForeachStatement(loc, op, args, exp, body->syntaxCopy()); + ForeachStatement *s = new ForeachStatement(loc, op, args, exp, + body ? body->syntaxCopy() : NULL); return s; } @@ -1255,7 +1258,7 @@ /* Look for special case of parsing char types out of char type * array. */ - tn = tab->next->toBasetype(); + tn = tab->nextOf()->toBasetype(); if (tn->ty == Tchar || tn->ty == Twchar || tn->ty == Tdchar) { Argument *arg; @@ -1311,9 +1314,6 @@ error("foreach: %s is not an array of %s", tab->toChars(), value->type->toChars()); } - if (value->storage_class & STCout && value->type->toBasetype()->ty == Tbit) - error("foreach: value cannot be out and type bit"); - if (key && ((key->type->ty != Tint32 && key->type->ty != Tuns32) || (global.params.is64bit && @@ -1356,7 +1356,7 @@ Identifier *id; Type *tret; - tret = func->type->next; + tret = func->type->nextOf(); // Need a variable to hold value from any return statements in body. if (!sc->func->vresult && tret && tret != Type::tvoid) @@ -1430,8 +1430,8 @@ error("foreach: index must be type %s, not %s", taa->index->toChars(), arg->type->toChars()); arg = (Argument *)arguments->data[1]; } - if (!arg->type->equals(taa->next)) - error("foreach: value must be type %s, not %s", taa->next->toChars(), arg->type->toChars()); + if (!arg->type->equals(taa->nextOf())) + error("foreach: value must be type %s, not %s", taa->nextOf()->toChars(), arg->type->toChars()); /* Call: * _aaApply(aggr, keysize, flde) @@ -1982,7 +1982,7 @@ // If it's not an array, cast it to one if (condition->type->ty != Tarray) { - condition = condition->implicitCastTo(sc, condition->type->next->arrayOf()); + condition = condition->implicitCastTo(sc, condition->type->nextOf()->arrayOf()); } } else @@ -2122,6 +2122,7 @@ Statement *CaseStatement::semantic(Scope *sc) { SwitchStatement *sw = sc->sw; + //printf("CaseStatement::semantic() %s\n", toChars()); exp = exp->semantic(sc); if (sw) { int i; @@ -2390,9 +2391,9 @@ } } - Type *tret = fd->type->next; + Type *tret = fd->type->nextOf(); if (fd->tintro) - tret = fd->tintro->next; + tret = fd->tintro->nextOf(); Type *tbret = NULL; if (tret) @@ -2452,18 +2453,18 @@ } else if (fd->inferRetType) { - if (fd->type->next) + if (fd->type->nextOf()) { - if (!exp->type->equals(fd->type->next)) + if (!exp->type->equals(fd->type->nextOf())) error("mismatched function return type inference of %s and %s", - exp->type->toChars(), fd->type->next->toChars()); + exp->type->toChars(), fd->type->nextOf()->toChars()); } else { fd->type->next = exp->type; fd->type = fd->type->semantic(loc, sc); if (!fd->tintro) - { tret = fd->type->next; + { tret = fd->type->nextOf(); tbret = tret->toBasetype(); } } @@ -2475,11 +2476,11 @@ } else if (fd->inferRetType) { - if (fd->type->next) + if (fd->type->nextOf()) { - if (fd->type->next->ty != Tvoid) + if (fd->type->nextOf()->ty != Tvoid) error("mismatched function return type inference of void and %s", - fd->type->next->toChars()); + fd->type->nextOf()->toChars()); } else { @@ -2510,7 +2511,7 @@ sc->fes->cases.push(this); s = new ReturnStatement(0, new IntegerExp(sc->fes->cases.dim + 1)); } - else if (fd->type->next->toBasetype() == Type::tvoid) + else if (fd->type->nextOf()->toBasetype() == Type::tvoid) { Statement *s1; Statement *s2; diff -r c05ef76f1c20 -r 788401029ecf dmd/staticassert.c --- a/dmd/staticassert.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/staticassert.c Thu Oct 04 03:42:56 2007 +0200 @@ -49,6 +49,7 @@ { Expression *e; + //printf("StaticAssert::semantic2() %s\n", toChars()); e = exp->semantic(sc); e = e->optimize(WANTvalue | WANTinterpret); if (e->isBool(FALSE)) diff -r c05ef76f1c20 -r 788401029ecf dmd/template.c --- a/dmd/template.c Thu Oct 04 01:47:53 2007 +0200 +++ b/dmd/template.c Thu Oct 04 03:42:56 2007 +0200 @@ -1232,7 +1232,7 @@ return (MATCH) implicitConvTo(at); } else if (ty == Tsarray && at->ty == Tarray && - next->equals(at->nextOf())) + nextOf()->equals(at->nextOf())) { goto Lexact; } @@ -3278,7 +3278,6 @@ else if (ea) { sinteger_t v; real_t r; - unsigned char *p; if (ea->op == TOKvar) { @@ -3298,6 +3297,8 @@ continue; } #if 1 + /* Use deco that matches what it would be for a function parameter + */ buf.writestring(ea->type->deco); #else // Use type of parameter, not type of argument