/* Cycript - Optimizing JavaScript Compiler/Runtime
- * Copyright (C) 2009-2013 Jay Freeman (saurik)
+ * Copyright (C) 2009-2014 Jay Freeman (saurik)
*/
-/* GNU General Public License, Version 3 {{{ */
+/* GNU Affero General Public License, Version 3 {{{ */
/*
- * Cycript is free software: you can redistribute it and/or modify
- * it under the terms of the GNU General Public License as published
- * by the Free Software Foundation, either version 3 of the License,
- * or (at your option) any later version.
- *
- * Cycript is distributed in the hope that it will be useful, but
- * WITHOUT ANY WARRANTY; without even the implied warranty of
+ * This program is free software: you can redistribute it and/or modify
+ * it under the terms of the GNU Affero General Public License as published by
+ * the Free Software Foundation, either version 3 of the License, or
+ * (at your option) any later version.
+
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
- * GNU General Public License for more details.
- *
- * You should have received a copy of the GNU General Public License
- * along with Cycript. If not, see <http://www.gnu.org/licenses/>.
+ * GNU Affero General Public License for more details.
+
+ * You should have received a copy of the GNU Affero General Public License
+ * along with this program. If not, see <http://www.gnu.org/licenses/>.
**/
/* }}} */
CYExpression *CYAdd::Replace(CYContext &context) {
CYInfix::Replace(context);
- CYExpression *lhp(lhs_->Primitive(context));
- CYExpression *rhp(rhs_->Primitive(context));
-
- CYString *lhs(dynamic_cast<CYString *>(lhp));
- CYString *rhs(dynamic_cast<CYString *>(rhp));
+ CYString *lhs(dynamic_cast<CYString *>(lhs_));
+ CYString *rhs(dynamic_cast<CYString *>(rhs_));
if (lhs != NULL || rhs != NULL) {
if (lhs == NULL) {
- lhs = lhp->String(context);
+ lhs = lhs_->String(context);
if (lhs == NULL)
return this;
} else if (rhs == NULL) {
- rhs = rhp->String(context);
+ rhs = rhs_->String(context);
if (rhs == NULL)
return this;
}
return lhs->Concat(context, rhs);
}
- if (CYNumber *lhn = lhp->Number(context))
- if (CYNumber *rhn = rhp->Number(context))
+ if (CYNumber *lhn = lhs_->Number(context))
+ if (CYNumber *rhn = rhs_->Number(context))
return $D(lhn->Value() + rhn->Value());
return this;
}
CYExpression *CYCompound::Replace(CYContext &context) {
- context.ReplaceAll(expressions_);
- if (expressions_ == NULL)
- return NULL;
+ if (next_ == NULL)
+ return expression_;
+
+ context.Replace(expression_);
+ context.Replace(next_);
+
+ if (CYCompound *compound = dynamic_cast<CYCompound *>(expression_)) {
+ expression_ = compound->expression_;
+ compound->expression_ = compound->next_;
+ compound->next_ = next_;
+ next_ = compound;
+ }
+
return this;
}
CYExpression *CYCompound::Primitive(CYContext &context) {
- CYExpression *expression(expressions_);
- if (expression == NULL)
+ CYExpression *expression(expression_);
+ if (expression == NULL || next_ != NULL)
return NULL;
- while (expression->next_ != NULL)
- expression = expression->next_;
return expression->Primitive(context);
}
}
CYCompound *CYDeclarations::Compound(CYContext &context) { $T(NULL)
- CYCompound *compound(next_->Compound(context) ?: $ CYCompound());
+ CYCompound *compound(next_->Compound(context));
if (CYAssignment *assignment = declaration_->Assignment(context))
- compound->AddPrev(assignment);
+ compound = $ CYCompound(assignment, compound);
return compound;
}
CYStatement *CYExpress::Replace(CYContext &context) {
while (CYExpress *express = dynamic_cast<CYExpress *>(next_)) {
- CYCompound *compound(dynamic_cast<CYCompound *>(express->expression_));
- if (compound == NULL)
- compound = $ CYCompound(express->expression_);
- compound->AddPrev(expression_);
- expression_ = compound;
+ expression_ = $ CYCompound(expression_, express->expression_);
SetNext(express->next_);
}
return $ CYIf(test_, CYComprehension::Replace(context, statement));
}
+CYStatement *CYImport::Replace(CYContext &context) {
+ return $ CYVar($L1($L(module_->part_->Word(), $C1($V("require"), module_->Replace(context, "/")))));
+}
+
CYExpression *CYIndirect::Replace(CYContext &context) {
return $M(rhs_, $S("$cyi"));
}
return $E($ CYCall(CYNonLocalize(context, $ CYFunctionExpression(NULL, declarations_->Parameter(context), code_)), declarations_->Argument(context)));
}
+CYString *CYModule::Replace(CYContext &context, const char *separator) const {
+ if (next_ == NULL)
+ return $ CYString(part_);
+ return $ CYString($pool.strcat(next_->Replace(context, separator)->Value(), separator, part_->Word(), NULL));
+}
+
CYExpression *CYMultiply::Replace(CYContext &context) {
CYInfix::Replace(context);
- CYExpression *lhp(lhs_->Primitive(context));
- CYExpression *rhp(rhs_->Primitive(context));
-
- if (CYNumber *lhn = lhp->Number(context))
- if (CYNumber *rhn = rhp->Number(context))
+ if (CYNumber *lhn = lhs_->Number(context))
+ if (CYNumber *rhn = rhs_->Number(context))
return $D(lhn->Value() * rhn->Value());
return this;
return $E($ CYAssign($V(typed_->identifier_), typed_->Replace(context)));
}
+CYExpression *CYTypeError::Replace(CYContext &context) {
+ _assert(false);
+ return NULL;
+}
+
CYExpression *CYTypeModifier::Replace(CYContext &context, CYExpression *type) { $T(type)
return Replace_(context, type);
}
return next_->Replace(context, $ CYCall($ CYDirectMember(type, $ CYString("functionWith")), parameters_->Argument(context)));
}
+CYExpression *CYTypeLong::Replace(CYContext &context) {
+ return $ CYCall($ CYDirectMember(specifier_->Replace(context), $ CYString("long")));
+}
+
CYExpression *CYTypePointerTo::Replace_(CYContext &context, CYExpression *type) {
return next_->Replace(context, $ CYCall($ CYDirectMember(type, $ CYString("pointerTo"))));
}
+CYExpression *CYTypeShort::Replace(CYContext &context) {
+ return $ CYCall($ CYDirectMember(specifier_->Replace(context), $ CYString("short")));
+}
+
+CYExpression *CYTypeSigned::Replace(CYContext &context) {
+ return $ CYCall($ CYDirectMember(specifier_->Replace(context), $ CYString("signed")));
+}
+
+CYExpression *CYTypeUnsigned::Replace(CYContext &context) {
+ return $ CYCall($ CYDirectMember(specifier_->Replace(context), $ CYString("unsigned")));
+}
+
+CYExpression *CYTypeVariable::Replace(CYContext &context) {
+ return $V(name_);
+}
+
+CYExpression *CYTypeVoid::Replace(CYContext &context) {
+ return $N1($V("Type"), $ CYString("v"));
+}
+
CYExpression *CYTypeVolatile::Replace_(CYContext &context, CYExpression *type) {
return next_->Replace(context, $ CYCall($ CYDirectMember(type, $ CYString("volatile"))));
}
CYExpression *CYTypedIdentifier::Replace(CYContext &context) {
- return modifier_->Replace(context, type_);
+ return modifier_->Replace(context, specifier_->Replace(context));
}
CYArgument *CYTypedParameter::Argument(CYContext &context) { $T(NULL)
}
CYExpression *CYTypedParameter::TypeSignature(CYContext &context, CYExpression *prefix) { $T(prefix)
- return next_->TypeSignature(context, $ CYAdd(prefix, typed_->type_->Replace(context)));
+ return next_->TypeSignature(context, $ CYAdd(prefix, typed_->Replace(context)));
}
CYStatement *CYVar::Replace(CYContext &context) {
declarations_->Replace(context);
- return $E(declarations_->Compound(context));
+ if (CYCompound *compound = declarations_->Compound(context))
+ return $E(compound);
+ return $ CYEmpty();
}
CYExpression *CYVariable::Replace(CYContext &context) {