Bug 589199 - Parse and emit bytecode for global lexicals. (r=efaust)

This commit is contained in:
Shu-yu Guo 2015-10-06 14:00:29 -07:00
Родитель aedb453377
Коммит 2c1ffa9a18
20 изменённых файлов: 254 добавлений и 266 удалений

Просмотреть файл

@ -640,7 +640,6 @@ ModuleBuilder::processExport(frontend::ParseNode* pn)
case PNK_VAR:
case PNK_CONST:
case PNK_GLOBALCONST:
case PNK_LET: {
MOZ_ASSERT(kid->isArity(PN_LIST));
for (ParseNode* var = kid->pn_head; var; var = var->pn_next) {

Просмотреть файл

@ -2166,7 +2166,6 @@ ASTSerializer::declaration(ParseNode* pn, MutableHandleValue dst)
{
MOZ_ASSERT(pn->isKind(PNK_FUNCTION) ||
pn->isKind(PNK_VAR) ||
pn->isKind(PNK_GLOBALCONST) ||
pn->isKind(PNK_LET) ||
pn->isKind(PNK_CONST));
@ -2175,7 +2174,6 @@ ASTSerializer::declaration(ParseNode* pn, MutableHandleValue dst)
return function(pn, AST_FUNC_DECL, dst);
case PNK_VAR:
case PNK_GLOBALCONST:
return variableDeclaration(pn, false, dst);
default:
@ -2188,7 +2186,7 @@ bool
ASTSerializer::variableDeclaration(ParseNode* pn, bool lexical, MutableHandleValue dst)
{
MOZ_ASSERT_IF(lexical, pn->isKind(PNK_LET) || pn->isKind(PNK_CONST));
MOZ_ASSERT_IF(!lexical, pn->isKind(PNK_VAR) || pn->isKind(PNK_GLOBALCONST));
MOZ_ASSERT_IF(!lexical, pn->isKind(PNK_VAR));
VarDeclKind kind = VARDECL_ERR;
// Treat both the toplevel const binding (secretly var-like) and the lexical const
@ -2345,9 +2343,8 @@ ASTSerializer::exportDeclaration(ParseNode* pn, MutableHandleValue dst)
case PNK_VAR:
case PNK_CONST:
case PNK_GLOBALCONST:
case PNK_LET:
if (!variableDeclaration(kid, (kind == PNK_LET || kind == PNK_CONST), &decl))
if (!variableDeclaration(kid, kind != PNK_VAR, &decl))
return false;
break;
@ -2494,7 +2491,7 @@ ASTSerializer::forInit(ParseNode* pn, MutableHandleValue dst)
return true;
}
return (pn->isKind(PNK_VAR) || pn->isKind(PNK_GLOBALCONST))
return (pn->isKind(PNK_VAR))
? variableDeclaration(pn, false, dst)
: expression(pn, dst);
}
@ -2544,7 +2541,6 @@ ASTSerializer::statement(ParseNode* pn, MutableHandleValue dst)
switch (pn->getKind()) {
case PNK_FUNCTION:
case PNK_VAR:
case PNK_GLOBALCONST:
return declaration(pn, dst);
case PNK_LETBLOCK:

Просмотреть файл

@ -76,6 +76,7 @@ class MOZ_STACK_CLASS BytecodeCompiler
bool insideNonGlobalEval = false);
bool isEvalCompilationUnit();
bool isNonGlobalEvalCompilationUnit();
bool isNonSyntacticCompilationUnit();
bool createParseContext(Maybe<ParseContext<FullParseHandler>>& parseContext,
SharedContext& globalsc, uint32_t blockScopeDepth = 0);
bool saveCallerFun(HandleScript evalCaller, ParseContext<FullParseHandler>& parseContext);
@ -280,7 +281,7 @@ BytecodeCompiler::createEmitter(SharedContext* sharedContext, HandleScript evalC
bool
BytecodeCompiler::isEvalCompilationUnit()
{
return enclosingStaticScope && enclosingStaticScope->is<StaticEvalObject>();
return enclosingStaticScope->is<StaticEvalObject>();
}
bool
@ -290,6 +291,12 @@ BytecodeCompiler::isNonGlobalEvalCompilationUnit()
enclosingStaticScope->as<StaticEvalObject>().enclosingScopeForStaticScopeIter();
}
bool
BytecodeCompiler::isNonSyntacticCompilationUnit()
{
return enclosingStaticScope->is<StaticNonSyntacticScopeObjects>();
}
bool
BytecodeCompiler::createParseContext(Maybe<ParseContext<FullParseHandler>>& parseContext,
SharedContext& globalsc, uint32_t blockScopeDepth)

Просмотреть файл

@ -823,7 +823,7 @@ BytecodeEmitter::computeLocalOffset(Handle<StaticBlockObject*> blockObj)
if (StmtInfoBCE* stmt = innermostScopeStmt()) {
Rooted<NestedScopeObject*> outer(cx, stmt->staticScope);
for (; outer; outer = outer->enclosingNestedScope()) {
if (outer->is<StaticBlockObject>()) {
if (outer->is<StaticBlockObject>() && !IsStaticGlobalLexicalScope(outer)) {
StaticBlockObject& outerBlock = outer->as<StaticBlockObject>();
localOffset = outerBlock.localOffset() + outerBlock.numVariables();
break;
@ -1354,15 +1354,15 @@ BytecodeEmitter::emitVarIncDec(ParseNode* pn)
bool
BytecodeEmitter::atBodyLevel() const
{
// 'eval' scripts are always under an invisible lexical scope, but
// since it is not syntactic, it should still be considered at body
// level.
if (sc->staticScope() && sc->staticScope()->is<StaticEvalObject>()) {
// 'eval' and non-syntactic scripts are always under an invisible lexical
// scope, but since it is not syntactic, it should still be considered at
// body level.
if (sc->staticScope()->is<StaticEvalObject>()) {
bool bl = !innermostStmt()->enclosing;
MOZ_ASSERT_IF(bl, innermostStmt()->type == StmtType::BLOCK);
MOZ_ASSERT_IF(bl, innermostStmt()->staticScope
->as<StaticBlockObject>()
.maybeEnclosingEval() == sc->staticScope());
.enclosingStaticScope() == sc->staticScope());
return bl;
}
return !innermostStmt() || sc->isModuleBox();
@ -1429,7 +1429,6 @@ BytecodeEmitter::isAliasedName(BytecodeEmitter* bceOfDef, ParseNode* pn)
*/
return script->formalIsAliased(pn->pn_scopecoord.slot());
case Definition::VAR:
case Definition::GLOBALCONST:
MOZ_ASSERT_IF(sc->allLocalsAliased(), script->localIsAliased(pn->pn_scopecoord.slot()));
return script->localIsAliased(pn->pn_scopecoord.slot());
case Definition::PLACEHOLDER:
@ -1643,14 +1642,13 @@ BytecodeEmitter::tryConvertFreeName(ParseNode* pn)
JSOp op;
switch (pn->getOp()) {
case JSOP_GETNAME: op = JSOP_GETGNAME; break;
case JSOP_SETNAME: op = strictifySetNameOp(JSOP_SETGNAME); break;
case JSOP_SETCONST:
// Not supported.
return false;
case JSOP_GETNAME: op = JSOP_GETGNAME; break;
case JSOP_SETNAME: op = strictifySetNameOp(JSOP_SETGNAME); break;
default: MOZ_CRASH("gname");
}
pn->setOp(op);
MOZ_ASSERT_IF(op == JSOP_INITGLEXICAL,
IsStaticGlobalLexicalScope(blockScopeOfDef(pn->resolve())));
return true;
}
@ -1704,7 +1702,6 @@ BytecodeEmitter::bindNameToSlotHelper(ParseNode* pn)
// Throw an error on attempts to mutate const-declared bindings.
switch (op) {
case JSOP_GETNAME:
case JSOP_SETCONST:
break;
default:
if (pn->isConst()) {
@ -1789,7 +1786,6 @@ BytecodeEmitter::bindNameToSlotHelper(ParseNode* pn)
break;
case Definition::VAR:
case Definition::GLOBALCONST:
case Definition::CONST:
case Definition::LET:
switch (op) {
@ -1798,8 +1794,6 @@ BytecodeEmitter::bindNameToSlotHelper(ParseNode* pn)
case JSOP_SETNAME:
case JSOP_STRICTSETNAME:
op = JSOP_SETLOCAL; break;
case JSOP_SETCONST:
op = JSOP_SETLOCAL; break;
default: MOZ_CRASH("local");
}
break;
@ -2163,7 +2157,6 @@ BytecodeEmitter::checkSideEffects(ParseNode* pn, bool* answer)
case PNK_VAR:
case PNK_CONST:
case PNK_LET:
case PNK_GLOBALCONST:
MOZ_ASSERT(pn->isArity(PN_LIST));
*answer = true;
return true;
@ -3001,8 +2994,7 @@ BytecodeEmitter::enterBlockScope(StmtInfoBCE* stmtInfo, ObjectBox* objbox, JSOp
{
// This is so terrible. The eval body-level lexical scope needs to be
// emitted in the prologue so DEFFUN can pick up the right scope chain.
bool isEvalBodyLexicalScope = sc->staticScope() &&
sc->staticScope()->is<StaticEvalObject>() &&
bool isEvalBodyLexicalScope = sc->staticScope()->is<StaticEvalObject>() &&
!innermostStmt();
if (isEvalBodyLexicalScope) {
MOZ_ASSERT(code().length() == 0);
@ -3704,7 +3696,7 @@ BytecodeEmitter::emitDestructuringLHS(ParseNode* target, VarEmitOption emitOptio
case JSOP_STRICTSETNAME:
case JSOP_SETGNAME:
case JSOP_STRICTSETGNAME:
case JSOP_SETCONST: {
case JSOP_INITGLEXICAL: {
// This is like ordinary assignment, but with one difference.
//
// In `a = b`, we first determine a binding for `a` (using
@ -3719,7 +3711,9 @@ BytecodeEmitter::emitDestructuringLHS(ParseNode* target, VarEmitOption emitOptio
if (!makeAtomIndex(target->pn_atom, &atomIndex))
return false;
if (!target->isOp(JSOP_SETCONST)) {
// INITGLEXICAL always initializes a binding on the global
// lexical scope and does not need a BINDGNAME.
if (!target->isOp(JSOP_INITGLEXICAL)) {
bool global = target->isOp(JSOP_SETGNAME) || target->isOp(JSOP_STRICTSETGNAME);
JSOp bindOp = global ? JSOP_BINDGNAME : JSOP_BINDNAME;
if (!emitIndex32(bindOp, atomIndex))
@ -4341,7 +4335,7 @@ BytecodeEmitter::emitVariables(ParseNode* pn, VarEmitOption emitOption, bool isL
if (!emitTree(pn3))
return false;
emittingForInit = oldEmittingForInit;
} else if (op == JSOP_INITLEXICAL || isLetExpr) {
} else if (op == JSOP_INITLEXICAL || op == JSOP_INITGLEXICAL || isLetExpr) {
// 'let' bindings cannot be used before they are
// initialized. JSOP_INITLEXICAL distinguishes the binding site.
MOZ_ASSERT(emitOption != DefineVars);
@ -7382,13 +7376,6 @@ BytecodeEmitter::emitDefaultsAndDestructuring(ParseNode* pn)
bool
BytecodeEmitter::emitLexicalInitialization(ParseNode* pn, JSOp globalDefOp)
{
/*
* This function is significantly more complicated than it needs to be.
* In fact, it shouldn't exist at all. This should all be a
* JSOP_INITLEXIAL. Unfortunately, toplevel lexicals are broken, and
* are emitted as vars :(. As such, we have to do these ministrations to
* to make sure that all works properly.
*/
MOZ_ASSERT(pn->isKind(PNK_NAME));
if (!bindNameToSlot(pn))
@ -7398,14 +7385,6 @@ BytecodeEmitter::emitLexicalInitialization(ParseNode* pn, JSOp globalDefOp)
if (!maybeEmitVarDecl(globalDefOp, pn, &atomIndex))
return false;
if (pn->getOp() != JSOP_INITLEXICAL) {
bool global = IsGlobalOp(pn->getOp());
if (!emitIndex32(global ? JSOP_BINDGNAME : JSOP_BINDNAME, atomIndex))
return false;
if (!emit1(JSOP_SWAP))
return false;
}
if (!pn->pn_scopecoord.isFree()) {
if (!emitVarOp(pn, pn->getOp()))
return false;
@ -7509,7 +7488,7 @@ BytecodeEmitter::emitClass(ParseNode* pn)
ParseNode* outerName = names->outerBinding();
if (outerName) {
if (!emitLexicalInitialization(outerName, JSOP_DEFVAR))
if (!emitLexicalInitialization(outerName, JSOP_DEFLET))
return false;
// Only class statements make outer bindings, and they do not leave
// themselves on the stack.
@ -7675,7 +7654,6 @@ BytecodeEmitter::emitTree(ParseNode* pn)
break;
case PNK_VAR:
case PNK_GLOBALCONST:
if (!emitVariables(pn, InitializeVars))
return false;
break;

Просмотреть файл

@ -75,7 +75,7 @@ ContainsHoistedDeclaration(ExclusiveContext* cx, ParseNode* node, bool* result)
// Non-global lexical declarations are block-scoped (ergo not hoistable).
// (Global lexical declarations, in addition to being irrelevant here as
// ContainsHoistedDeclaration is only used on the arms of an |if|
// statement, are handled by PNK_GLOBALCONST and PNK_VAR.)
// statement, are handled by PNK_VAR.)
case PNK_LET:
case PNK_CONST:
MOZ_ASSERT(node->isArity(PN_LIST));
@ -417,10 +417,6 @@ ContainsHoistedDeclaration(ExclusiveContext* cx, ParseNode* node, bool* result)
MOZ_CRASH("ContainsHoistedDeclaration should have indicated false on "
"some parent node without recurring to test this node");
case PNK_GLOBALCONST:
MOZ_CRASH("ContainsHoistedDeclaration is only called on nested nodes where "
"globalconst nodes should never have been generated");
case PNK_LIMIT: // invalid sentinel value
MOZ_CRASH("unexpected PNK_LIMIT in node");
}
@ -1837,7 +1833,6 @@ Fold(ExclusiveContext* cx, ParseNode** pnp, Parser<FullParseHandler>& parser, bo
case PNK_TEMPLATE_STRING_LIST:
case PNK_VAR:
case PNK_CONST:
case PNK_GLOBALCONST:
case PNK_LET:
case PNK_ARGSBODY:
case PNK_CALLSITEOBJ:

Просмотреть файл

@ -720,6 +720,7 @@ class FullParseHandler
}
inline bool finishInitializerAssignment(ParseNode* pn, ParseNode* init, JSOp op);
inline void setLexicalDeclarationOp(ParseNode* pn, JSOp op);
void setBeginPosition(ParseNode* pn, ParseNode* oth) {
setBeginPosition(pn, oth->pn_pos.begin);
@ -752,8 +753,7 @@ class FullParseHandler
return new_<ListNode>(kind, op, TokenPos(begin, begin + 1));
}
ParseNode* newDeclarationList(ParseNodeKind kind, JSOp op = JSOP_NOP) {
MOZ_ASSERT(kind == PNK_VAR || kind == PNK_CONST || kind == PNK_LET ||
kind == PNK_GLOBALCONST);
MOZ_ASSERT(kind == PNK_VAR || kind == PNK_CONST || kind == PNK_LET);
return new_<ListNode>(kind, op, pos());
}
@ -763,8 +763,7 @@ class FullParseHandler
return new_<ListNode>(kind, op, kid);
}
ParseNode* newDeclarationList(ParseNodeKind kind, ParseNode* kid, JSOp op = JSOP_NOP) {
MOZ_ASSERT(kind == PNK_VAR || kind == PNK_CONST || kind == PNK_LET ||
kind == PNK_GLOBALCONST);
MOZ_ASSERT(kind == PNK_VAR || kind == PNK_CONST || kind == PNK_LET);
return new_<ListNode>(kind, op, kid);
}
@ -993,12 +992,8 @@ FullParseHandler::finishInitializerAssignment(ParseNode* pn, ParseNode* init, JS
pn->pn_expr = init;
}
if (op == JSOP_INITLEXICAL)
pn->setOp(op);
else if (pn->pn_dflags & PND_BOUND)
if (pn->pn_dflags & PND_BOUND)
pn->setOp(JSOP_SETLOCAL);
else if (op == JSOP_DEFCONST)
pn->setOp(JSOP_SETCONST);
else
pn->setOp(JSOP_SETNAME);
@ -1009,6 +1004,19 @@ FullParseHandler::finishInitializerAssignment(ParseNode* pn, ParseNode* init, JS
return true;
}
inline void
FullParseHandler::setLexicalDeclarationOp(ParseNode* pn, JSOp op)
{
if (op == JSOP_DEFLET || op == JSOP_DEFCONST) {
// Subtlety here. Lexical definitions that are PND_BOUND but whose
// scope coordinates are free are global lexicals. They cannot use
// scope coordinate lookup because we rely on being able to clone
// scripts to run on multiple globals. However, they always go on the
// global lexical scope, so in that sense they are bound.
pn->setOp(pn->pn_scopecoord.isFree() ? JSOP_INITGLEXICAL : JSOP_INITLEXICAL);
}
}
inline ParseNode*
FullParseHandler::makeAssignment(ParseNode* pn, ParseNode* rhs)
{

Просмотреть файл

@ -682,7 +682,6 @@ class NameResolver
case PNK_VAR:
case PNK_CONST:
case PNK_LET:
case PNK_GLOBALCONST:
MOZ_ASSERT(cur->isArity(PN_LIST));
for (ParseNode* element = cur->pn_head; element; element = element->pn_next) {
if (!resolve(element, prefix))

Просмотреть файл

@ -497,7 +497,6 @@ PushNodeChildren(ParseNode* pn, NodeStack* stack)
case PNK_CALLSITEOBJ:
case PNK_VAR:
case PNK_CONST:
case PNK_GLOBALCONST:
case PNK_LET:
case PNK_CATCHLIST:
case PNK_STATEMENTLIST:
@ -656,7 +655,6 @@ Definition::kindString(Kind kind)
"",
js_var_str,
js_const_str,
js_const_str,
js_let_str,
"argument",
js_function_str,

Просмотреть файл

@ -131,7 +131,6 @@ class PackedScopeCoordinate
F(CONTINUE) \
F(VAR) \
F(CONST) \
F(GLOBALCONST) \
F(WITH) \
F(RETURN) \
F(NEW) \
@ -1571,7 +1570,6 @@ struct Definition : public ParseNode
enum Kind {
MISSING = 0,
VAR,
GLOBALCONST,
CONST,
LET,
ARG,
@ -1601,8 +1599,6 @@ struct Definition : public ParseNode
return IMPORT;
if (isLexical())
return isConst() ? CONST : LET;
if (isConst())
return GLOBALCONST;
return VAR;
}
};

Просмотреть файл

@ -241,7 +241,6 @@ ParseContext<FullParseHandler>::define(TokenStream& ts,
return false;
break;
case Definition::GLOBALCONST:
case Definition::VAR:
if (!sc->isGlobalContext()) {
dn->setOp((js_CodeSpec[dn->getOp()].format & JOF_SET) ? JSOP_SETLOCAL : JSOP_GETLOCAL);
@ -262,7 +261,8 @@ ParseContext<FullParseHandler>::define(TokenStream& ts,
case Definition::LET:
case Definition::CONST:
dn->setOp(JSOP_INITLEXICAL);
// See FullParseHandler::setLexicalDeclarationOp.
dn->setOp(dn->pn_scopecoord.isFree() ? JSOP_INITGLEXICAL : JSOP_INITLEXICAL);
dn->pn_dflags |= (PND_LEXICAL | PND_BOUND);
if (atModuleLevel())
dn->pn_dflags |= PND_CLOSED;
@ -394,7 +394,6 @@ AppendPackedBindings(const ParseContext<ParseHandler>* pc, const DeclVector& vec
kind = Binding::VARIABLE;
break;
case Definition::CONST:
case Definition::GLOBALCONST:
kind = Binding::CONSTANT;
break;
case Definition::ARG:
@ -780,8 +779,9 @@ Parser<ParseHandler>::parse()
* an object lock before it finishes generating bytecode into a script
* protected from the GC by a root or a stack frame reference.
*/
Rooted<ScopeObject*> staticLexical(context, &context->global()->lexicalScope().staticBlock());
Directives directives(options().strictOption);
GlobalSharedContext globalsc(context, /* staticScope = */ nullptr, directives,
GlobalSharedContext globalsc(context, staticLexical, directives,
options().extraWarningsOption);
ParseContext<ParseHandler> globalpc(this, /* parent = */ nullptr, ParseHandler::null(),
&globalsc, /* newDirectives = */ nullptr,
@ -1316,17 +1316,17 @@ struct BindData
: kind_(Uninitialized), nameNode_(ParseHandler::null()), letData_(cx)
{}
void initLexical(VarContext varContext, StaticBlockObject* blockObj, unsigned overflow,
bool isConst = false)
void initLexical(VarContext varContext, JSOp op, StaticBlockObject* blockObj,
unsigned overflow)
{
init(LexicalBinding, JSOP_INITLEXICAL, isConst);
init(LexicalBinding, op, op == JSOP_DEFCONST);
letData_.varContext = varContext;
letData_.blockObj = blockObj;
letData_.overflow = overflow;
}
void initVarOrGlobalConst(JSOp op) {
init(VarBinding, op, op == JSOP_DEFCONST);
void initVar(JSOp op) {
init(VarBinding, op, false);
}
void initDestructuring(JSOp op) {
@ -1365,7 +1365,7 @@ struct BindData
case LexicalBinding:
return Parser<ParseHandler>::bindLexical(this, name, parser);
case VarBinding:
return Parser<ParseHandler>::bindVarOrGlobalConst(this, name, parser);
return Parser<ParseHandler>::bindVar(this, name, parser);
case DestructuringBinding:
return Parser<ParseHandler>::bindDestructuringArg(this, name, parser);
default:
@ -2084,8 +2084,7 @@ Parser<FullParseHandler>::checkFunctionDefinition(HandlePropertyName funName,
MOZ_ASSERT(!dn->isUsed());
MOZ_ASSERT(dn->isDefn());
bool throwRedeclarationError = dn->kind() == Definition::GLOBALCONST ||
dn->kind() == Definition::CONST ||
bool throwRedeclarationError = dn->kind() == Definition::CONST ||
dn->kind() == Definition::LET;
if (options().extraWarningsOption || throwRedeclarationError) {
JSAutoByteString name;
@ -2317,10 +2316,7 @@ Parser<SyntaxParseHandler>::checkFunctionDefinition(HandlePropertyName funName,
* function (thereby avoiding JSOP_DEFFUN and dynamic name lookup).
*/
if (DefinitionNode dn = pc->decls().lookupFirst(funName)) {
if (dn == Definition::GLOBALCONST ||
dn == Definition::CONST ||
dn == Definition::LET)
{
if (dn == Definition::CONST || dn == Definition::LET) {
JSAutoByteString name;
if (!AtomToPrintableString(context, funName, &name) ||
!report(ParseError, false, null(), JSMSG_REDECLARED_VAR,
@ -3267,32 +3263,38 @@ Parser<FullParseHandler>::bindLexical(BindData<FullParseHandler>* data,
ExclusiveContext* cx = parser->context;
Rooted<StaticBlockObject*> blockObj(cx, data->letData().blockObj);
unsigned index;
uint32_t index;
if (blockObj) {
index = blockObj->numVariables();
if (index >= StaticBlockObject::LOCAL_INDEX_LIMIT) {
parser->report(ParseError, false, pn, data->letData().overflow);
return false;
// Leave the scope coordinate free on global lexicals.
//
// For block-level lets, assign block-local index to pn->pn_scopecoord
// right away. The emitter will adjust the node's slot based on its
// stack depth model -- and, for global and eval code,
// js::frontend::CompileScript will adjust the slot again to include
// script->nfixed and body-level lets.
//
// XXXshu: I should like to optimize global lexicals, but we rely on
// being able to clone JSScripts to run on multiple globals and to be
// able to parse scripts off-thread in a different compartment.
if (!blockObj->isGlobal()) {
index = blockObj->numVariables();
if (index >= StaticBlockObject::LOCAL_INDEX_LIMIT) {
parser->report(ParseError, false, pn, data->letData().overflow);
return false;
}
if (!pn->pn_scopecoord.setSlot(parser->tokenStream, index))
return false;
}
} else {
// If we don't have a block object, we are parsing a body-level let,
// in which case we use a bogus index. See comment block below in
// setting the pn_scopecoord for explanation on how it gets adjusted.
} else if (!pc->sc->isGlobalContext()) {
// If we don't have a block object and are parsing a function
// body-level let, use a bogus index. It is adjusted when creating the
// function's Bindings. See ParseContext::generateFunctionBindings and
// AppendPackedBindings.
index = 0;
if (!pn->pn_scopecoord.setSlot(parser->tokenStream, index))
return false;
}
// For block-level lets, assign block-local index to pn->pn_scopecoord
// right away. The emitter will adjust the node's slot based on its
// stack depth model -- and, for global and eval code,
// js::frontend::CompileScript will adjust the slot again to include
// script->nfixed and body-level lets.
//
// For body-level lets, the index is bogus at this point and is adjusted
// when creating Bindings. See ParseContext::generateBindings and
// AppendPackedBindings.
if (!pn->pn_scopecoord.setSlot(parser->tokenStream, index))
return false;
Definition::Kind bindingKind;
if (pn->isImport())
bindingKind = Definition::IMPORT;
@ -3315,24 +3317,26 @@ Parser<FullParseHandler>::bindLexical(BindData<FullParseHandler>* data,
}
if (blockObj) {
bool redeclared;
RootedId id(cx, NameToId(name));
RootedShape shape(cx, StaticBlockObject::addVar(cx, blockObj, id,
data->isConst(), index, &redeclared));
if (!shape) {
if (redeclared) {
// The only way to be redeclared without a previous definition is if we're in a
// comma separated list in a DontHoistVars block, so a let block of for header. In
// that case, we must be redeclaring the same type of definition as we're trying to
// make.
Definition::Kind dnKind = dn ? dn->kind() : bindingKind;
parser->reportRedeclaration(pn, dnKind, name);
if (!blockObj->isGlobal()) {
bool redeclared;
RootedId id(cx, NameToId(name));
RootedShape shape(cx, StaticBlockObject::addVar(cx, blockObj, id,
data->isConst(), index, &redeclared));
if (!shape) {
if (redeclared) {
// The only way to be redeclared without a previous definition is if we're in a
// comma separated list in a DontHoistVars block, so a let block of for header. In
// that case, we must be redeclaring the same type of definition as we're trying to
// make.
Definition::Kind dnKind = dn ? dn->kind() : bindingKind;
parser->reportRedeclaration(pn, dnKind, name);
}
return false;
}
return false;
}
/* Store pn in the static block object. */
blockObj->setDefinitionParseNode(index, reinterpret_cast<Definition*>(pn));
/* Store pn in the static block object. */
blockObj->setDefinitionParseNode(index, reinterpret_cast<Definition*>(pn));
}
} else {
// Body-level lets are hoisted and need to have been defined via
// pc->define above.
@ -3491,13 +3495,12 @@ OuterLet(ParseContext<ParseHandler>* pc, StmtInfoPC* stmt, HandleAtom atom)
template <typename ParseHandler>
/* static */ bool
Parser<ParseHandler>::bindVarOrGlobalConst(BindData<ParseHandler>* data,
HandlePropertyName name, Parser<ParseHandler>* parser)
Parser<ParseHandler>::bindVar(BindData<ParseHandler>* data,
HandlePropertyName name, Parser<ParseHandler>* parser)
{
ExclusiveContext* cx = parser->context;
ParseContext<ParseHandler>* pc = parser->pc;
Node pn = data->nameNode();
bool isConstDecl = data->op() == JSOP_DEFCONST;
/* Default best op for pn is JSOP_GETNAME; we'll try to improve below. */
parser->handler.setOp(pn, JSOP_GETNAME);
@ -3530,10 +3533,8 @@ Parser<ParseHandler>::bindVarOrGlobalConst(BindData<ParseHandler>* data,
DefinitionList::Range defs = pc->decls().lookupMulti(name);
MOZ_ASSERT_IF(stmt, !defs.empty());
if (defs.empty()) {
return pc->define(parser->tokenStream, name, pn,
isConstDecl ? Definition::GLOBALCONST : Definition::VAR);
}
if (defs.empty())
return pc->define(parser->tokenStream, name, pn, Definition::VAR);
/*
* There was a previous declaration with the same name. The standard
@ -3548,19 +3549,12 @@ Parser<ParseHandler>::bindVarOrGlobalConst(BindData<ParseHandler>* data,
JSAutoByteString bytes;
if (!AtomToPrintableString(cx, name, &bytes))
return false;
if (isConstDecl) {
parser->report(ParseError, false, pn, JSMSG_REDECLARED_PARAM, bytes.ptr());
return false;
}
if (!parser->report(ParseExtraWarning, false, pn, JSMSG_VAR_HIDES_ARG, bytes.ptr()))
return false;
} else {
bool inCatchBody = (stmt && stmt->type == StmtType::CATCH);
bool error = (isConstDecl ||
dn_kind == Definition::IMPORT ||
bool error = (dn_kind == Definition::IMPORT ||
dn_kind == Definition::CONST ||
dn_kind == Definition::GLOBALCONST ||
(dn_kind == Definition::LET &&
(!inCatchBody || OuterLet(pc, stmt, name))));
@ -3681,12 +3675,10 @@ Parser<FullParseHandler>::bindInitialized(BindData<FullParseHandler>* data, Pars
* Select the appropriate name-setting opcode, respecting eager selection
* done by the data->bind function.
*/
if (data->op() == JSOP_INITLEXICAL)
pn->setOp(JSOP_INITLEXICAL);
if (data->op() == JSOP_DEFLET || data->op() == JSOP_DEFCONST)
pn->setOp(pn->pn_scopecoord.isFree() ? JSOP_INITGLEXICAL : JSOP_INITLEXICAL);
else if (pn->pn_dflags & PND_BOUND)
pn->setOp(JSOP_SETLOCAL);
else if (data->op() == JSOP_DEFCONST)
pn->setOp(JSOP_SETCONST);
else
pn->setOp(JSOP_SETNAME);
@ -4012,6 +4004,9 @@ Parser<ParseHandler>::deprecatedLetBlock(YieldHandling yieldHandling)
RootedStaticBlockObject blockObj(context, StaticBlockObject::create(context));
if (!blockObj)
return null();
// Initialize the enclosing scope manually for the call to |variables|
// below.
blockObj->initEnclosingScopeFromParser(pc->innermostStaticScope());
uint32_t begin = pos().begin;
@ -4106,14 +4101,7 @@ Parser<ParseHandler>::variables(YieldHandling yieldHandling,
ForInitLocation location,
bool* psimple, StaticBlockObject* blockObj, VarContext varContext)
{
/*
* The four options here are:
* - PNK_VAR: We're parsing var declarations.
* - PNK_CONST: We're parsing const declarations.
* - PNK_GLOBALCONST: We're parsing const declarations at toplevel (see bug 589119).
* - PNK_LET: We are parsing a let declaration.
*/
MOZ_ASSERT(kind == PNK_VAR || kind == PNK_CONST || kind == PNK_LET || kind == PNK_GLOBALCONST);
MOZ_ASSERT(kind == PNK_VAR || kind == PNK_CONST || kind == PNK_LET);
/*
* The simple flag is set if the declaration has the form 'var x', with
@ -4121,28 +4109,23 @@ Parser<ParseHandler>::variables(YieldHandling yieldHandling,
*/
MOZ_ASSERT_IF(psimple, *psimple);
JSOp op = JSOP_NOP;
if (kind == PNK_VAR)
op = JSOP_DEFVAR;
else if (kind == PNK_GLOBALCONST)
op = JSOP_DEFCONST;
JSOp op;
switch (kind) {
case PNK_VAR: op = JSOP_DEFVAR; break;
case PNK_CONST: op = JSOP_DEFCONST; break;
case PNK_LET: op = JSOP_DEFLET; break;
default: MOZ_CRASH("unknown variable kind");
}
Node pn = handler.newDeclarationList(kind, op);
if (!pn)
return null();
/*
* SpiderMonkey const is really "write once per initialization evaluation"
* var, whereas let is block scoped. ES-Harmony wants block-scoped const so
* this code will change soon.
*/
BindData<ParseHandler> data(context);
if (kind == PNK_VAR || kind == PNK_GLOBALCONST) {
data.initVarOrGlobalConst(op);
} else {
data.initLexical(varContext, blockObj, JSMSG_TOO_MANY_LOCALS,
/* isConst = */ kind == PNK_CONST);
}
if (kind == PNK_VAR)
data.initVar(op);
else
data.initLexical(varContext, op, blockObj, JSMSG_TOO_MANY_LOCALS);
bool first = true;
Node pn2;
@ -4228,7 +4211,7 @@ Parser<ParseHandler>::variables(YieldHandling yieldHandling,
}
RootedPropertyName name(context, tokenStream.currentName());
pn2 = newBindingNode(name, kind == PNK_VAR || kind == PNK_GLOBALCONST, varContext);
pn2 = newBindingNode(name, kind == PNK_VAR, varContext);
if (!pn2)
return null();
if (data.isConst())
@ -4309,6 +4292,7 @@ Parser<ParseHandler>::variables(YieldHandling yieldHandling,
}
}
handler.setLexicalDeclarationOp(pn2, data.op());
handler.setEndPosition(pn, pn2);
} while (false);
@ -4348,14 +4332,9 @@ Parser<FullParseHandler>::checkAndPrepareLexical(bool isConst, const TokenPos& e
MOZ_ASSERT(pc->atBodyLevel());
/*
* When bug 589199 is fixed, let variables will be stored in
* the slots of a new scope chain object, encountered just
* before the global object in the overall chain. This extra
* object is present in the scope chain for all code in that
* global, including self-hosted code. But self-hosted code
* must be usable against *any* global object, including ones
* with other let variables -- variables possibly placed in
* conflicting slots. Forbid top-level let declarations to
* Self-hosted code must be usable against *any* global object,
* including ones with other let variables -- variables possibly
* placed in conflicting slots. Forbid top-level let declarations to
* prevent such conflicts from ever occurring.
*/
bool isGlobal = !pc->sc->isFunctionBox() && stmt == pc->innermostScopeStmt();
@ -4409,8 +4388,12 @@ Parser<FullParseHandler>::checkAndPrepareLexical(bool isConst, const TokenPos& e
static StaticBlockObject*
CurrentLexicalStaticBlock(ParseContext<FullParseHandler>* pc)
{
return !pc->innermostStmt() ? nullptr :
&pc->innermostStmt()->staticScope->as<StaticBlockObject>();
if (pc->innermostStaticScope()->is<StaticBlockObject>())
return &pc->innermostStaticScope()->as<StaticBlockObject>();
MOZ_ASSERT(pc->atBodyLevel() &&
(!pc->sc->isGlobalContext() ||
HasNonSyntacticStaticScopeChain(pc->innermostStaticScope())));
return nullptr;
}
template <>
@ -4418,16 +4401,12 @@ ParseNode*
Parser<FullParseHandler>::makeInitializedLexicalBinding(HandlePropertyName name, bool isConst,
const TokenPos& pos)
{
// Handle the silliness of global and body level lexical decls.
BindData<FullParseHandler> data(context);
if (pc->atGlobalLevel()) {
data.initVarOrGlobalConst(isConst ? JSOP_DEFCONST : JSOP_DEFVAR);
} else {
if (!checkAndPrepareLexical(isConst, pos))
return null();
data.initLexical(HoistVars, CurrentLexicalStaticBlock(pc), JSMSG_TOO_MANY_LOCALS, isConst);
}
ParseNode* dn = newBindingNode(name, pc->atGlobalLevel());
if (!checkAndPrepareLexical(isConst, pos))
return null();
data.initLexical(HoistVars, isConst ? JSOP_DEFCONST : JSOP_DEFLET,
CurrentLexicalStaticBlock(pc), JSMSG_TOO_MANY_LOCALS);
ParseNode* dn = newBindingNode(name, false);
if (!dn)
return null();
handler.setPosition(dn, pos);
@ -4457,16 +4436,8 @@ Parser<FullParseHandler>::lexicalDeclaration(YieldHandling yieldHandling, bool i
* requires that uninitialized lets throw ReferenceError on use.
*
* See 8.1.1.1.6 and the note in 13.2.1.
*
* FIXME global-level lets are still considered vars until
* other bugs are fixed.
*/
ParseNodeKind kind = PNK_LET;
if (pc->atGlobalLevel())
kind = isConst ? PNK_GLOBALCONST : PNK_VAR;
else if (isConst)
kind = PNK_CONST;
ParseNodeKind kind = isConst ? PNK_CONST : PNK_LET;
ParseNode* pn = variables(yieldHandling, kind, NotInForInit,
nullptr, CurrentLexicalStaticBlock(pc), HoistVars);
if (!pn)
@ -4532,7 +4503,7 @@ Parser<FullParseHandler>::newBoundImportForCurrentName()
importNode->pn_dflags |= PND_CONST | PND_IMPORT;
BindData<FullParseHandler> data(context);
data.initLexical(HoistVars, nullptr, JSMSG_TOO_MANY_LOCALS);
data.initLexical(HoistVars, JSOP_DEFLET, nullptr, JSMSG_TOO_MANY_LOCALS);
handler.setPosition(importNode, pos());
if (!bindUninitialized(&data, importNode))
return null();
@ -5271,6 +5242,9 @@ Parser<FullParseHandler>::forStatement(YieldHandling yieldHandling)
blockObj = StaticBlockObject::create(context);
if (!blockObj)
return null();
// Initialize the enclosing scope manually for the call to
// |variables| below.
blockObj->initEnclosingScopeFromParser(pc->innermostStaticScope());
pn1 = variables(yieldHandling, constDecl ? PNK_CONST : PNK_LET, InForInit,
nullptr, blockObj, DontHoistVars);
} else {
@ -5287,7 +5261,7 @@ Parser<FullParseHandler>::forStatement(YieldHandling yieldHandling)
}
MOZ_ASSERT_IF(isForDecl, pn1->isArity(PN_LIST));
MOZ_ASSERT(!!blockObj == (isForDecl && pn1->isOp(JSOP_NOP)));
MOZ_ASSERT(!!blockObj == (isForDecl && (pn1->isOp(JSOP_DEFLET) || pn1->isOp(JSOP_DEFCONST))));
// All forms of for-loop (for(;;), for-in, for-of) generate an implicit
// block to store any lexical variables declared by the loop-head. We
@ -6298,7 +6272,7 @@ Parser<ParseHandler>::tryStatement(YieldHandling yieldHandling)
* scoped, not a property of a new Object instance. This is
* an intentional change that anticipates ECMA Ed. 4.
*/
data.initLexical(HoistVars,
data.initLexical(HoistVars, JSOP_DEFLET,
&stmtInfo->staticScope->template as<StaticBlockObject>(),
JSMSG_TOO_MANY_CATCH_VARS);
MOZ_ASSERT(data.letData().blockObj);
@ -7798,7 +7772,7 @@ Parser<FullParseHandler>::legacyComprehensionTail(ParseNode* bodyExpr, unsigned
MOZ_ASSERT(pc->innermostScopeStmt() &&
pc->innermostScopeStmt()->staticScope == pn->pn_objbox->object);
data.initLexical(HoistVars,
data.initLexical(HoistVars, JSOP_DEFLET,
&pc->innermostScopeStmt()->staticScope->as<StaticBlockObject>(),
JSMSG_ARRAY_INIT_TOO_BIG);
@ -7916,7 +7890,7 @@ Parser<FullParseHandler>::legacyComprehensionTail(ParseNode* bodyExpr, unsigned
* These are lets to tell the bytecode emitter to emit initialization
* code for the temporal dead zone.
*/
ParseNode* lets = handler.newList(PNK_LET, pn3);
ParseNode* lets = handler.newDeclarationList(PNK_LET, pn3, JSOP_DEFLET);
if (!lets)
return null();
lets->pn_xflags |= PNX_POPVAR;
@ -8227,10 +8201,15 @@ Parser<ParseHandler>::comprehensionFor(GeneratorKind comprehensionKind)
AutoPushStmtInfoPC stmtInfo(*this, StmtType::BLOCK);
BindData<ParseHandler> data(context);
RootedStaticBlockObject blockObj(context, StaticBlockObject::create(context));
if (!blockObj)
return null();
data.initLexical(DontHoistVars, blockObj, JSMSG_TOO_MANY_LOCALS);
// Initialize the enclosing scope manually for the call to |bind|
// below, which is before the call to |pushLetScope|.
blockObj->initEnclosingScopeFromParser(pc->innermostStaticScope());
data.initLexical(DontHoistVars, JSOP_DEFLET, blockObj, JSMSG_TOO_MANY_LOCALS);
Node decls = handler.newList(PNK_LET, lhs);
if (!decls)
return null();

Просмотреть файл

@ -301,15 +301,15 @@ struct MOZ_STACK_CLASS ParseContext : public GenericParseContext
// if (cond) { function f3() { if (cond) { function f4() { } } } }
//
bool atBodyLevel() {
// 'eval' scripts are always under an invisible lexical scope, but
// since it is not syntactic, it should still be considered at body
// level.
if (sc->staticScope() && sc->staticScope()->is<StaticEvalObject>()) {
// 'eval' and non-syntactic scripts are always under an invisible
// lexical scope, but since it is not syntactic, it should still be
// considered at body level.
if (sc->staticScope()->is<StaticEvalObject>()) {
bool bl = !innermostStmt()->enclosing;
MOZ_ASSERT_IF(bl, innermostStmt()->type == StmtType::BLOCK);
MOZ_ASSERT_IF(bl, innermostStmt()->staticScope
->template as<StaticBlockObject>()
.maybeEnclosingEval() == sc->staticScope());
.enclosingStaticScope() == sc->staticScope());
return bl;
}
return !innermostStmt();
@ -578,9 +578,11 @@ class Parser : private JS::AutoGCRooter, public StrictModeGetter
bool maybeParseDirective(Node list, Node pn, bool* cont);
// Parse the body of an eval. It is distinguished from global scripts in
// that in ES6, per 18.2.1.1 steps 9 and 10, all eval scripts are executed
// under a fresh lexical scope.
// Parse the body of an eval.
//
// Eval scripts are distinguished from global scripts in that in ES6, per
// 18.2.1.1 steps 9 and 10, all eval scripts are executed under a fresh
// lexical scope.
Node evalBody();
// Parse a module.
@ -850,8 +852,8 @@ class Parser : private JS::AutoGCRooter, public StrictModeGetter
HandlePropertyName name, Parser<ParseHandler>* parser);
static bool
bindVarOrGlobalConst(BindData<ParseHandler>* data,
HandlePropertyName name, Parser<ParseHandler>* parser);
bindVar(BindData<ParseHandler>* data,
HandlePropertyName name, Parser<ParseHandler>* parser);
static Node null() { return ParseHandler::null(); }

Просмотреть файл

@ -349,6 +349,7 @@ class SyntaxParseHandler
}
bool finishInitializerAssignment(Node pn, Node init, JSOp op) { return true; }
void setLexicalDeclarationOp(Node pn, JSOp op) {}
void setBeginPosition(Node pn, Node oth) {}
void setBeginPosition(Node pn, uint32_t begin) {}
@ -371,8 +372,7 @@ class SyntaxParseHandler
return NodeGeneric;
}
Node newDeclarationList(ParseNodeKind kind, JSOp op = JSOP_NOP) {
MOZ_ASSERT(kind == PNK_VAR || kind == PNK_CONST || kind == PNK_LET ||
kind == PNK_GLOBALCONST);
MOZ_ASSERT(kind == PNK_VAR || kind == PNK_CONST || kind == PNK_LET);
return kind == PNK_VAR ? NodeHoistableDeclaration : NodeGeneric;
}
Node newList(ParseNodeKind kind, Node kid, JSOp op = JSOP_NOP) {
@ -380,8 +380,7 @@ class SyntaxParseHandler
return NodeGeneric;
}
Node newDeclarationList(ParseNodeKind kind, Node kid, JSOp op = JSOP_NOP) {
MOZ_ASSERT(kind == PNK_VAR || kind == PNK_CONST || kind == PNK_LET ||
kind == PNK_GLOBALCONST);
MOZ_ASSERT(kind == PNK_VAR || kind == PNK_CONST || kind == PNK_LET);
return kind == PNK_VAR ? NodeHoistableDeclaration : NodeGeneric;
}

Просмотреть файл

@ -1,11 +1,5 @@
function qualified_tests(prefix) {
let scope = evalReturningScope(prefix + "let x = 1");
assertEq(scope.x, 1);
scope = evalReturningScope(prefix + "var x = 1");
assertEq(scope.x, 1);
scope = evalReturningScope(prefix + "const x = 1");
let scope = evalReturningScope(prefix + "var x = 1");
assertEq(scope.x, 1);
}

Просмотреть файл

@ -3470,20 +3470,28 @@ IsFunctionCloneable(HandleFunction fun)
// If a function was compiled to be lexically nested inside some other
// script, we cannot clone it without breaking the compiler's assumptions.
if (JSObject* scope = fun->nonLazyScript()->enclosingStaticScope()) {
// If the script already deals with a non-syntactic scope, we can clone
// it.
if (scope->is<StaticNonSyntacticScopeObjects>())
return true;
// If the script is directly under the global scope, we can clone it.
if (IsStaticGlobalLexicalScope(scope))
return true;
// If the script is an indirect eval that is immediately scoped under
// the global, we can clone it.
// 'eval' and non-syntactic scopes are always scoped immediately under
// a non-extensible lexical scope.
if (scope->is<StaticBlockObject>()) {
if (StaticEvalObject* staticEval = scope->as<StaticBlockObject>().maybeEnclosingEval())
return !staticEval->isDirect();
StaticBlockObject& block = scope->as<StaticBlockObject>();
if (block.needsClone())
return false;
JSObject* enclosing = block.enclosingStaticScope();
// If the script is an indirect eval that is immediately scoped
// under the global, we can clone it.
if (enclosing->is<StaticEvalObject>())
return !enclosing->as<StaticEvalObject>().isDirect();
// If the script already deals with a non-syntactic scope, we can
// clone it.
if (enclosing->is<StaticNonSyntacticScopeObjects>())
return true;
}
// Any other enclosing static scope (e.g., function, block) cannot be

Просмотреть файл

@ -590,8 +590,9 @@ js::XDRInterpretedFunction(XDRState<mode>* xdr, HandleObject enclosingScope, Han
gc::AllocKind allocKind = gc::AllocKind::FUNCTION;
if (uint16_t(flagsword) & JSFunction::EXTENDED)
allocKind = gc::AllocKind::FUNCTION_EXTENDED;
RootedObject globalLexical(cx, &cx->global()->lexicalScope());
fun = NewFunctionWithProto(cx, nullptr, 0, JSFunction::INTERPRETED,
/* enclosingDynamicScope = */ nullptr, nullptr, proto,
globalLexical, nullptr, proto,
allocKind, TenuredObject);
if (!fun)
return false;

Просмотреть файл

@ -990,10 +990,14 @@ js::XDRScript(XDRState<mode>* xdr, HandleObject enclosingScopeArg, HandleScript
uint32_t enclosingStaticScopeIndex = 0;
if (mode == XDR_ENCODE) {
NestedScopeObject& scope = (*objp)->as<NestedScopeObject>();
if (NestedScopeObject* enclosing = scope.enclosingNestedScope())
enclosingStaticScopeIndex = FindScopeObjectIndex(script, *enclosing);
else
if (NestedScopeObject* enclosing = scope.enclosingNestedScope()) {
if (IsStaticGlobalLexicalScope(enclosing))
enclosingStaticScopeIndex = UINT32_MAX;
else
enclosingStaticScopeIndex = FindScopeObjectIndex(script, *enclosing);
} else {
enclosingStaticScopeIndex = UINT32_MAX;
}
}
if (!xdr->codeUint32(&enclosingStaticScopeIndex))
return false;
@ -1056,8 +1060,12 @@ js::XDRScript(XDRState<mode>* xdr, HandleObject enclosingScopeArg, HandleScript
MOZ_ASSERT_IF(ssi.done() || ssi.type() != StaticScopeIter<NoGC>::Function, !fun);
funEnclosingScopeIndex = UINT32_MAX;
} else if (ssi.type() == StaticScopeIter<NoGC>::Block) {
funEnclosingScopeIndex = FindScopeObjectIndex(script, ssi.block());
MOZ_ASSERT(funEnclosingScopeIndex < i);
if (ssi.block().isGlobal()) {
funEnclosingScopeIndex = UINT32_MAX;
} else {
funEnclosingScopeIndex = FindScopeObjectIndex(script, ssi.block());
MOZ_ASSERT(funEnclosingScopeIndex < i);
}
} else {
funEnclosingScopeIndex = FindScopeObjectIndex(script, ssi.staticWith());
MOZ_ASSERT(funEnclosingScopeIndex < i);
@ -3295,10 +3303,16 @@ js::detail::CopyScript(JSContext* cx, HandleObject scriptStaticScope, HandleScri
Rooted<NestedScopeObject*> innerBlock(cx, &obj->as<NestedScopeObject>());
RootedObject enclosingScope(cx);
if (NestedScopeObject* enclosingBlock = innerBlock->enclosingNestedScope())
enclosingScope = objects[FindScopeObjectIndex(src, *enclosingBlock)];
else
if (NestedScopeObject* enclosingBlock = innerBlock->enclosingNestedScope()) {
if (IsStaticGlobalLexicalScope(enclosingBlock)) {
MOZ_ASSERT(IsStaticGlobalLexicalScope(scriptStaticScope));
enclosingScope = scriptStaticScope;
} else {
enclosingScope = objects[FindScopeObjectIndex(src, *enclosingBlock)];
}
} else {
enclosingScope = scriptStaticScope;
}
clone = CloneNestedScopeObject(cx, enclosingScope, innerBlock);
} else if (obj->is<JSFunction>()) {

Просмотреть файл

@ -14,6 +14,8 @@
#include "jsiter.h"
#include "jspubtd.h"
#include "frontend/ParseNode.h"
#include "vm/Stack.h"
namespace js {

Просмотреть файл

@ -214,15 +214,9 @@
* Stack: v1, v2 => v1, v2, v1, v2
*/ \
macro(JSOP_DUP2, 13, "dup2", NULL, 1, 2, 4, JOF_BYTE) \
/*
* Defines a readonly property on the frame's current variables-object (the
* scope object on the scope chain designated to receive new variables).
* Category: Variables and Scopes
* Type: Variables
* Operands: uint32_t nameIndex
* Stack: val => val
*/ \
macro(JSOP_SETCONST, 14, "setconst", NULL, 5, 1, 1, JOF_ATOM|JOF_NAME|JOF_SET) \
\
macro(JSOP_UNUSED14, 14, "unused14", NULL, 1, 0, 0, JOF_BYTE) \
\
/*
* Pops the top two values 'lval' and 'rval' from the stack, then pushes
* the result of the operation applied to the two operands, converting
@ -1295,14 +1289,10 @@
* Stack: =>
*/ \
macro(JSOP_DEFFUN, 127,"deffun", NULL, 5, 0, 0, JOF_OBJECT) \
/*
* Defines the new binding on the frame's current variables-object (the
* scope object on the scope chain designated to receive new variables) with
* 'READONLY' attribute. The binding is *not* JSPROP_PERMANENT. See bug
* 1019181 for the reason.
/* Defines the new constant binding on global lexical scope.
*
* This is used for global scripts and also in some cases for function
* scripts where use of dynamic scoping inhibits optimization.
* Throws if a binding with the same name already exists on the scope, or
* if a var binding with the same name exists on the global.
* Category: Variables and Scopes
* Type: Variables
* Operands: uint32_t nameIndex
@ -1313,6 +1303,9 @@
* Defines the new binding on the frame's current variables-object (the
* scope object on the scope chain designated to receive new variables).
*
* Throws if the current variables-object is the global object and a
* binding with the same name exists on the global lexical scope.
*
* This is used for global scripts and also in some cases for function
* scripts where use of dynamic scoping inhibits optimization.
* Category: Variables and Scopes
@ -1655,8 +1648,27 @@
*/ \
macro(JSOP_REGEXP, 160,"regexp", NULL, 5, 0, 1, JOF_REGEXP) \
\
macro(JSOP_UNUSED161, 161,"unused161", NULL, 1, 0, 0, JOF_BYTE) \
macro(JSOP_UNUSED162, 162,"unused162", NULL, 1, 0, 0, JOF_BYTE) \
/*
* Initializes an uninitialized global lexical binding with the top of
* stack value.
* Category: Variables and Scopes
* Type: Free Variables
* Operands: uint32_t nameIndex
* Stack: val => val
*/ \
macro(JSOP_INITGLEXICAL, 161,"initglexical", NULL, 5, 1, 1, JOF_ATOM|JOF_NAME|JOF_SET|JOF_GNAME) \
\
/* Defines the new mutable binding on global lexical scope.
*
* Throws if a binding with the same name already exists on the scope, or
* if a var binding with the same name exists on the global.
* Category: Variables and Scopes
* Type: Variables
* Operands: uint32_t nameIndex
* Stack: =>
*/ \
macro(JSOP_DEFLET, 162,"deflet", NULL, 5, 0, 0, JOF_ATOM) \
\
macro(JSOP_UNUSED163, 163,"unused163", NULL, 1, 0, 0, JOF_BYTE) \
macro(JSOP_UNUSED164, 164,"unused164", NULL, 1, 0, 0, JOF_BYTE) \
macro(JSOP_UNUSED165, 165,"unused165", NULL, 1, 0, 0, JOF_BYTE) \

Просмотреть файл

@ -1038,11 +1038,13 @@ js::XDRStaticBlockObject(XDRState<mode>* xdr, HandleObject enclosingScope,
Rooted<StaticBlockObject*> obj(cx);
uint32_t count = 0, offset = 0;
uint8_t extensible = 0;
if (mode == XDR_ENCODE) {
obj = objp;
count = obj->numVariables();
offset = obj->localOffset();
extensible = obj->isExtensible() ? 1 : 0;
}
if (mode == XDR_DECODE) {
@ -1057,6 +1059,8 @@ js::XDRStaticBlockObject(XDRState<mode>* xdr, HandleObject enclosingScope,
return false;
if (!xdr->codeUint32(&offset))
return false;
if (!xdr->codeUint8(&extensible))
return false;
/*
* XDR the block object's properties. We know that there are 'count'
@ -1090,6 +1094,11 @@ js::XDRStaticBlockObject(XDRState<mode>* xdr, HandleObject enclosingScope,
bool aliased = !!(propFlags >> 1);
obj->setAliased(i, aliased);
}
if (!extensible) {
if (!obj->makeNonExtensible(cx))
return false;
}
} else {
Rooted<ShapeVector> shapes(cx, ShapeVector(cx));
if (!shapes.growBy(count))

Просмотреть файл

@ -661,14 +661,6 @@ class StaticBlockObject : public BlockObject
*/
inline StaticBlockObject* enclosingBlock() const;
StaticEvalObject* maybeEnclosingEval() const {
if (JSObject* enclosing = enclosingStaticScope()) {
if (enclosing->is<StaticEvalObject>())
return &enclosing->as<StaticEvalObject>();
}
return nullptr;
}
uint32_t localOffset() {
return getReservedSlot(LOCAL_OFFSET_SLOT).toPrivateUint32();
}