Commit b615dfa5 authored by Daniel Clifford's avatar Daniel Clifford Committed by Commit Bot

[torque] Implement methods and constructors for structs and classes

With the changes in this patch,	it is now possible to add methods to
both Torque's class and struct types. As a special case, "constructor"
methods are used to initialize the values of classes and structs when
they are constructed.

The functionality in this patch	includes:

- The refactoring of class- and struct-handling code to share field
  and method declaration code between both.

- Addition of the "%Allocate" intrinsic that allocates raw bytes to be
  allocated from the V8 GC's NewSpace heap as the basis for freshly
  created, initialized class objects.

- An implementation of a CallMethodExpression AST node that enables
  calling methods and constructors, including special handling of
  passing through the "this" pointer for method calls on structs by
  reference. The syntax for struct construction using "{}" remains as
  before, but now calls the struct's matching constructor rather than
  implicitly initializing the struct fields with the initialization
  arguments. A new syntax for allocation classes is introduced: "new
  ClassName{constructor_param1, constructor_param1, ...}", which
  de-sugars to an %Allocate call followed by a call to the matching
  constructor.

- class	constructors can use the "super" keyword to initialize	their
  super class.

- If classes and struct do not have a constructor, Torque creates a
  default constructor for them based on their field declarations,
  where each field's initial value is assigned to a same-typed
  parameter to the the default constructor. The default constructor's
  parameters are in field-declaration order, and for derived classes,
  the default constructor automatically uses a "super" initialization
  call to initialize inherited fields.

- Class field declarations now automatically create ".field" and
  ".field=" operators that create CSA-compatible object accessors.

- Addition of a no-argument constructor for JSArrays that creates an
  empty, PACKED_SMI_ELEMENTS JSArray using the machinery added
  elsewhere in this patch.

Bug: v8:7793
Change-Id: I31ce5f4b444656ab999555d780aeeba605666bfa
Reviewed-on: https://chromium-review.googlesource.com/c/1392192
Commit-Queue: Daniel Clifford <danno@chromium.org>
Reviewed-by: 's avatarTobias Tebbi <tebbi@chromium.org>
Cr-Commit-Position: refs/heads/master@{#58860}
parent d5f321cb
......@@ -58,6 +58,11 @@ type Map extends HeapObject generates 'TNode<Map>';
extern operator '.map' macro LoadMap(HeapObject): Map;
extern transitioning operator '.map=' macro StoreMap(HeapObject, Map);
// This intrinsic should never be called from Torque code. It's used internally
// by the 'new' operator and only declared here because it's simpler than
// building the definition from C++.
intrinsic %Allocate<Class: type>(size: intptr): Class;
type FixedArrayBase extends HeapObject generates 'TNode<FixedArrayBase>';
type FixedArray extends FixedArrayBase generates 'TNode<FixedArray>';
type FixedDoubleArray extends FixedArrayBase
......@@ -79,6 +84,15 @@ class JSArgumentsObjectWithLength extends JSObject {
}
class JSArray extends JSObject {
constructor(implicit context: Context)() {
super(
GetFastPackedSmiElementsJSArrayMap(), kEmptyFixedArray,
kEmptyFixedArray);
this.length = 0;
}
IsEmpty(): bool {
return this.length == 0;
}
length: Number;
}
......@@ -139,6 +153,8 @@ const OBJECT_FUNCTION_INDEX: constexpr NativeContextSlot
generates 'Context::OBJECT_FUNCTION_INDEX';
const ITERATOR_RESULT_MAP_INDEX: constexpr NativeContextSlot
generates 'Context::ITERATOR_RESULT_MAP_INDEX';
const JS_ARRAY_PACKED_SMI_ELEMENTS_MAP_INDEX: constexpr NativeContextSlot
generates 'Context::JS_ARRAY_PACKED_SMI_ELEMENTS_MAP_INDEX';
extern operator '[]' macro LoadContextElement(
NativeContext, NativeContextSlot): Object;
extern operator '[]=' macro StoreContextElement(
......@@ -466,8 +482,11 @@ extern operator '==' macro Float64Equal(float64, float64): bool;
extern operator '!=' macro Float64NotEqual(float64, float64): bool;
extern operator '>' macro Float64GreaterThan(float64, float64): bool;
extern operator '==' macro BranchIfNumberEqual(Number, Number): never
extern macro BranchIfNumberEqual(Number, Number): never
labels Taken, NotTaken;
operator '==' macro IsNumberEqual(a: Number, b: Number): bool {
return (BranchIfNumberEqual(a, b)) ? true : false;
}
extern operator '!=' macro BranchIfNumberNotEqual(Number, Number): never
labels Taken, NotTaken;
extern operator '<' macro BranchIfNumberLessThan(Number, Number): never
......@@ -1160,6 +1179,11 @@ macro GetObjectFunction(implicit context: Context)(): JSFunction {
LoadNativeContext(context)[OBJECT_FUNCTION_INDEX]);
}
macro GetFastPackedSmiElementsJSArrayMap(implicit context: Context)(): Map {
return UnsafeCast<Map>(
LoadNativeContext(context)[JS_ARRAY_PACKED_SMI_ELEMENTS_MAP_INDEX]);
}
extern transitioning macro Call(Context, Callable, Object): Object;
extern transitioning macro Call(Context, Callable, Object, Object): Object;
extern transitioning macro Call(
......
......@@ -19,6 +19,7 @@ namespace torque {
#define AST_EXPRESSION_NODE_KIND_LIST(V) \
V(CallExpression) \
V(CallMethodExpression) \
V(LoadObjectFieldExpression) \
V(StoreObjectFieldExpression) \
V(IntrinsicCallExpression) \
......@@ -33,6 +34,7 @@ namespace torque {
V(ElementAccessExpression) \
V(AssignmentExpression) \
V(IncrementDecrementExpression) \
V(NewExpression) \
V(AssumeTypeImpossibleExpression) \
V(StatementExpression) \
V(TryLabelExpression)
......@@ -190,6 +192,8 @@ class Ast {
std::vector<std::unique_ptr<AstNode>> nodes_;
};
static const char* const kThisParameterName = "this";
struct IdentifierExpression : LocationExpression {
DEFINE_AST_NODE_LEAF_BOILERPLATE(IdentifierExpression)
IdentifierExpression(SourcePosition pos,
......@@ -202,6 +206,7 @@ struct IdentifierExpression : LocationExpression {
IdentifierExpression(SourcePosition pos, std::string name,
std::vector<TypeExpression*> args = {})
: IdentifierExpression(pos, {}, std::move(name), std::move(args)) {}
bool IsThis() const { return name == kThisParameterName; }
std::vector<std::string> namespace_qualification;
std::string name;
std::vector<TypeExpression*> generic_arguments;
......@@ -246,6 +251,23 @@ struct IntrinsicCallExpression : Expression {
std::vector<Expression*> arguments;
};
struct CallMethodExpression : Expression {
DEFINE_AST_NODE_LEAF_BOILERPLATE(CallMethodExpression)
CallMethodExpression(SourcePosition pos, Expression* target,
IdentifierExpression* method,
std::vector<Expression*> arguments,
std::vector<std::string> labels)
: Expression(kKind, pos),
target(target),
method(method),
arguments(std::move(arguments)),
labels(std::move(labels)) {}
Expression* target;
IdentifierExpression* method;
std::vector<Expression*> arguments;
std::vector<std::string> labels;
};
struct CallExpression : Expression {
DEFINE_AST_NODE_LEAF_BOILERPLATE(CallExpression)
CallExpression(SourcePosition pos, IdentifierExpression* callee,
......@@ -378,6 +400,15 @@ struct AssumeTypeImpossibleExpression : Expression {
Expression* expression;
};
struct NewExpression : Expression {
DEFINE_AST_NODE_LEAF_BOILERPLATE(NewExpression)
NewExpression(SourcePosition pos, TypeExpression* type,
std::vector<Expression*> parameters)
: Expression(kKind, pos), type(type), parameters(parameters) {}
TypeExpression* type;
std::vector<Expression*> parameters;
};
struct ParameterList {
std::vector<std::string> names;
std::vector<TypeExpression*> types;
......@@ -851,11 +882,14 @@ struct ExternConstDeclaration : Declaration {
struct StructDeclaration : Declaration {
DEFINE_AST_NODE_LEAF_BOILERPLATE(StructDeclaration)
StructDeclaration(SourcePosition pos, std::string name,
std::vector<Declaration*> methods,
std::vector<NameAndTypeExpression> fields)
: Declaration(kKind, pos),
name(std::move(name)),
methods(std::move(methods)),
fields(std::move(fields)) {}
std::string name;
std::vector<Declaration*> methods;
std::vector<NameAndTypeExpression> fields;
};
......@@ -864,17 +898,20 @@ struct ClassDeclaration : Declaration {
ClassDeclaration(SourcePosition pos, std::string name, bool transient,
base::Optional<std::string> extends,
base::Optional<std::string> generates,
std::vector<Declaration*> methods,
std::vector<ClassFieldExpression> fields)
: Declaration(kKind, pos),
name(std::move(name)),
transient(transient),
extends(std::move(extends)),
generates(std::move(generates)),
methods(std::move(methods)),
fields(std::move(fields)) {}
std::string name;
bool transient;
base::Optional<std::string> extends;
base::Optional<std::string> generates;
std::vector<Declaration*> methods;
std::vector<ClassFieldExpression> fields;
};
......
......@@ -234,6 +234,9 @@ void CSAGenerator::EmitInstruction(const CallIntrinsicInstruction& instruction,
s << "%FromConstexpr does not support return type " << *return_type;
ReportError(s.str());
}
} else if (instruction.intrinsic->ExternalName() == "%Allocate") {
out_ << "ca_.UncheckedCast<" << return_type->GetGeneratedTNodeTypeName()
<< ">(CodeStubAssembler(state_).Allocate";
} else {
ReportError("no built in intrinsic with name " +
instruction.intrinsic->ExternalName());
......@@ -241,6 +244,7 @@ void CSAGenerator::EmitInstruction(const CallIntrinsicInstruction& instruction,
out_ << "(";
PrintCommaSeparatedList(out_, args);
if (instruction.intrinsic->ExternalName() == "%Allocate") out_ << ")";
if (return_type->IsStructType()) {
out_ << ").Flatten();\n";
} else {
......@@ -683,8 +687,13 @@ void CSAGenerator::EmitInstruction(
stack->Push(value);
const Field& field =
instruction.class_type->LookupField(instruction.field_name);
out_ << " CodeStubAssembler(state_).StoreObjectField(" + object + ", " +
std::to_string(field.offset) + ", " + value + ");\n";
if (field.offset == 0) {
out_ << " CodeStubAssembler(state_).StoreMap(" + object + ", " + value +
");\n";
} else {
out_ << " CodeStubAssembler(state_).StoreObjectField(" + object + ", " +
std::to_string(field.offset) + ", " + value + ");\n";
}
}
// static
......
......@@ -44,6 +44,7 @@ class Declarable {
enum Kind {
kNamespace,
kMacro,
kMethod,
kBuiltin,
kRuntimeFunction,
kIntrinsic,
......@@ -54,7 +55,8 @@ class Declarable {
};
Kind kind() const { return kind_; }
bool IsNamespace() const { return kind() == kNamespace; }
bool IsMacro() const { return kind() == kMacro; }
bool IsMacro() const { return kind() == kMacro || kind() == kMethod; }
bool IsMethod() const { return kind() == kMethod; }
bool IsIntrinsic() const { return kind() == kIntrinsic; }
bool IsBuiltin() const { return kind() == kBuiltin; }
bool IsRuntimeFunction() const { return kind() == kRuntimeFunction; }
......@@ -65,7 +67,8 @@ class Declarable {
bool IsValue() const { return IsExternConstant() || IsNamespaceConstant(); }
bool IsScope() const { return IsNamespace() || IsCallable(); }
bool IsCallable() const {
return IsMacro() || IsBuiltin() || IsRuntimeFunction() || IsIntrinsic();
return IsMacro() || IsBuiltin() || IsRuntimeFunction() || IsIntrinsic() ||
IsMethod();
}
virtual const char* type_name() const { return "<<unknown>>"; }
Scope* ParentScope() const { return parent_scope_; }
......@@ -250,7 +253,8 @@ class Callable : public Scope {
bool IsTransitioning() const { return transitioning_; }
base::Optional<Statement*> body() const { return body_; }
bool IsExternal() const { return !body_.has_value(); }
bool ShouldBeInlined() const { return false; }
virtual bool ShouldBeInlined() const { return false; }
bool IsConstructor() const { return readable_name_ == kConstructMethodName; }
protected:
Callable(Declarable::Kind kind, std::string external_name,
......@@ -284,22 +288,51 @@ class Macro : public Callable {
return external_assembler_name_;
}
private:
friend class Declarations;
Macro(std::string external_name, std::string readable_name,
std::string external_assembler_name, const Signature& signature,
bool transitioning, base::Optional<Statement*> body)
: Callable(Declarable::kMacro, std::move(external_name),
std::move(readable_name), signature, transitioning, body),
protected:
Macro(Declarable::Kind kind, std::string external_name,
std::string readable_name, std::string external_assembler_name,
const Signature& signature, bool transitioning,
base::Optional<Statement*> body)
: Callable(kind, std::move(external_name), std::move(readable_name),
signature, transitioning, body),
external_assembler_name_(std::move(external_assembler_name)) {
if (signature.parameter_types.var_args) {
ReportError("Varargs are not supported for macros.");
}
}
private:
friend class Declarations;
Macro(std::string external_name, std::string readable_name,
std::string external_assembler_name, const Signature& signature,
bool transitioning, base::Optional<Statement*> body)
: Macro(Declarable::kMacro, std::move(external_name),
std::move(readable_name), external_assembler_name, signature,
transitioning, body) {}
std::string external_assembler_name_;
};
class Method : public Macro {
public:
DECLARE_DECLARABLE_BOILERPLATE(Method, Method);
bool ShouldBeInlined() const override {
return signature().parameter_types.types[0]->IsStructType();
}
AggregateType* aggregate_type() const { return aggregate_type_; }
private:
friend class Declarations;
Method(AggregateType* aggregate_type, std::string external_name,
std::string readable_name, std::string external_assembler_name,
const Signature& signature, bool transitioning, Statement* body)
: Macro(Declarable::kMethod, std::move(external_name),
std::move(readable_name), std::move(external_assembler_name),
signature, transitioning, body),
aggregate_type_(aggregate_type) {}
AggregateType* aggregate_type_;
};
class Builtin : public Callable {
public:
enum Kind { kStub, kFixedArgsJavaScript, kVarArgsJavaScript };
......
......@@ -163,6 +163,13 @@ void DeclarationVisitor::Visit(GenericDeclaration* decl) {
Declarations::DeclareGeneric(decl->callable->name, decl);
}
static Statement* WrapBodyWithNoThrow(Statement* body, std::string reason) {
return MakeNode<ExpressionStatement>(MakeNode<TryLabelExpression>(
true, MakeNode<StatementExpression>(body),
MakeNode<LabelBlock>("_catch", ParameterList{},
MakeNode<DebugStatement>(reason, true))));
}
void DeclarationVisitor::Visit(SpecializationDeclaration* decl) {
if ((decl->body != nullptr) == decl->external) {
std::stringstream stream;
......@@ -229,13 +236,124 @@ void DeclarationVisitor::Visit(ExternConstDeclaration* decl) {
Declarations::DeclareExternConstant(decl->name, type, decl->literal);
}
void DeclarationVisitor::DeclareMethods(
AggregateType* container_type, const std::vector<Declaration*>& methods) {
// Declare the class' methods
IdentifierExpression* constructor_this = MakeNode<IdentifierExpression>(
std::vector<std::string>{}, kThisParameterName);
for (auto declaration : methods) {
StandardDeclaration* standard_declaration =
StandardDeclaration::DynamicCast(declaration);
DCHECK(standard_declaration);
TorqueMacroDeclaration* method =
TorqueMacroDeclaration::DynamicCast(standard_declaration->callable);
Signature signature = MakeSignature(method->signature.get());
signature.parameter_names.insert(signature.parameter_names.begin(),
kThisParameterName);
signature.parameter_types.types.insert(
signature.parameter_types.types.begin(), container_type);
signature.implicit_count++;
Statement* body = *(standard_declaration->body);
std::string method_name(method->name);
if (method->name == kConstructMethodName) {
// Constructor
if (!signature.return_type->IsVoid()) {
ReportError("constructors musn't have a return type");
}
if (signature.labels.size() != 0) {
ReportError("constructors musn't have labels");
}
method_name = kConstructMethodName;
signature.return_type = container_type;
ReturnStatement* return_statement = MakeNode<ReturnStatement>(
MakeNode<IdentifierExpression>(kThisParameterName));
body = MakeNode<BlockStatement>(
false, std::vector<Statement*>{body, return_statement});
body = WrapBodyWithNoThrow(body, "exception thrown from constructor");
}
Declarations::CreateMethod(container_type, method_name, signature, false,
body);
}
if (container_type->Constructors().size() != 0) return;
// Generate default constructor.
Signature constructor_signature;
constructor_signature.parameter_types.var_args = false;
constructor_signature.return_type = container_type;
std::vector<const AggregateType*> hierarchy = container_type->GetHierarchy();
std::vector<Statement*> statements;
std::vector<Statement*> initializer_statements;
size_t parameter_number = 0;
constructor_signature.parameter_names.push_back(kThisParameterName);
constructor_signature.parameter_types.types.push_back(container_type);
constructor_signature.implicit_count = 1;
std::vector<Expression*> super_arguments;
for (auto current_type : hierarchy) {
for (auto& f : current_type->fields()) {
std::string parameter_name("p" + std::to_string(parameter_number++));
constructor_signature.parameter_names.push_back(parameter_name);
constructor_signature.parameter_types.types.push_back(
f.name_and_type.type);
IdentifierExpression* value = MakeNode<IdentifierExpression>(
std::vector<std::string>{}, parameter_name);
if (container_type != current_type) {
super_arguments.push_back(MakeNode<IdentifierExpression>(
std::vector<std::string>{}, parameter_name));
} else if (container_type->IsClassType()) {
Statement* statement =
MakeNode<ExpressionStatement>(MakeNode<StoreObjectFieldExpression>(
constructor_this, f.name_and_type.name, value));
initializer_statements.push_back(statement);
} else {
DCHECK(container_type->IsStructType());
LocationExpression* location = MakeNode<FieldAccessExpression>(
constructor_this, f.name_and_type.name);
Statement* statement = MakeNode<ExpressionStatement>(
MakeNode<AssignmentExpression>(location, base::nullopt, value));
initializer_statements.push_back(statement);
}
}
}
if (hierarchy.size() > 1) {
IdentifierExpression* super_identifier = MakeNode<IdentifierExpression>(
std::vector<std::string>{}, kSuperMethodName);
Statement* super_call_statement =
MakeNode<ExpressionStatement>(MakeNode<CallMethodExpression>(
constructor_this, super_identifier, super_arguments,
std::vector<std::string>{}));
statements.push_back(super_call_statement);
}
for (auto s : initializer_statements) {
statements.push_back(s);
}
statements.push_back(MakeNode<ReturnStatement>(MakeNode<IdentifierExpression>(
std::vector<std::string>{}, kThisParameterName)));
Statement* constructor_body = MakeNode<BlockStatement>(false, statements);
constructor_body = WrapBodyWithNoThrow(constructor_body,
"exception thrown from constructor");
Declarations::CreateMethod(container_type, kConstructMethodName,
constructor_signature, false, constructor_body);
}
void DeclarationVisitor::Visit(StructDeclaration* decl) {
std::vector<Field> fields;
size_t offset = 0;
for (auto& field : decl->fields) {
const Type* field_type = Declarations::GetType(field.type);
fields.push_back({{field.name, field_type}, 0, false});
fields.push_back({{field.name, field_type}, offset, false});
offset += LoweredSlotCount(field_type);
}
Declarations::DeclareStruct(decl->name, fields);
StructType* struct_type = Declarations::DeclareStruct(decl->name, fields);
DeclareMethods(struct_type, decl->methods);
}
void DeclarationVisitor::Visit(ClassDeclaration* decl) {
......@@ -243,14 +361,15 @@ void DeclarationVisitor::Visit(ClassDeclaration* decl) {
// another class, it's the size of the extended class, otherwise zero.
size_t first_field_offset = 0;
if (decl->extends) {
const Type* extends_type = Declarations::LookupType(*decl->extends);
if (extends_type != TypeOracle::GetTaggedType()) {
if (!extends_type->IsClassType()) {
const Type* super_type = Declarations::LookupType(*decl->extends);
if (super_type != TypeOracle::GetTaggedType()) {
const ClassType* super_class = ClassType::DynamicCast(super_type);
if (!super_class) {
ReportError(
"class \"", decl->name,
"\" must extend either Tagged or an already declared class");
}
first_field_offset = ClassType::DynamicCast(extends_type)->size();
first_field_offset = super_class->size();
}
}
......@@ -300,19 +419,19 @@ void DeclarationVisitor::Visit(ClassDeclaration* decl) {
auto new_class = Declarations::DeclareClass(
decl->extends, decl->name, decl->transient, generates, fields, offset);
DeclareMethods(new_class, decl->methods);
// For each field, construct AST snippits that implement a CSA accessor
// function and define a corresponding '.field' operator. The
// implementation iterator will turn the snippits into code.
for (auto& field : fields) {
CurrentSourcePosition::Scope source_position(decl->pos);
IdentifierExpression* parameter = MakeNode<IdentifierExpression>(
std::vector<std::string>{}, std::string{"o"});
for (auto& field : new_class->fields()) {
IdentifierExpression* parameter =
MakeNode<IdentifierExpression>(std::string{"o"});
// Load accessor
std::string load_macro_name =
"Load" + decl->name + CamelifyString(field.name_and_type.name);
std::string get_operator_name = "." + field.name_and_type.name;
std::string camel_field_name = CamelifyString(field.name_and_type.name);
std::string load_macro_name = "Load" + new_class->name() + camel_field_name;
std::string load_operator_name = "." + field.name_and_type.name;
Signature load_signature;
load_signature.parameter_names.push_back("o");
load_signature.parameter_types.types.push_back(new_class);
......@@ -322,13 +441,13 @@ void DeclarationVisitor::Visit(ClassDeclaration* decl) {
MakeNode<ReturnStatement>(MakeNode<LoadObjectFieldExpression>(
parameter, field.name_and_type.name));
Declarations::DeclareMacro(load_macro_name, base::nullopt, load_signature,
false, load_body, get_operator_name);
false, load_body, load_operator_name);
// Store accessor
IdentifierExpression* value = MakeNode<IdentifierExpression>(
std::vector<std::string>{}, std::string{"v"});
std::string store_macro_name =
"Store" + decl->name + CamelifyString(field.name_and_type.name);
"Store" + new_class->name() + camel_field_name;
std::string store_operator_name = "." + field.name_and_type.name + "=";
Signature store_signature;
store_signature.parameter_names.push_back("o");
......
......@@ -44,6 +44,10 @@ class DeclarationVisitor : public FileVisitor {
}
void Visit(TypeDeclaration* decl);
void DeclareMethods(AggregateType* container,
const std::vector<Declaration*>& methods);
void Visit(StructDeclaration* decl);
void Visit(ClassDeclaration* decl);
void Visit(TypeAliasDeclaration* decl) {
......@@ -81,7 +85,6 @@ class DeclarationVisitor : public FileVisitor {
void Visit(GenericDeclaration* decl);
void Visit(SpecializationDeclaration* decl);
void Visit(ExternConstDeclaration* decl);
void Visit(StructDeclaration* decl);
void Visit(CppIncludeDeclaration* decl);
Signature MakeSpecializedSignature(const SpecializationKey& key);
......
......@@ -19,7 +19,7 @@ template <class T>
std::vector<T> EnsureNonempty(std::vector<T> list, const std::string& name,
const char* kind) {
if (list.empty()) {
ReportError("there is no ", kind, "named ", name);
ReportError("there is no ", kind, " named ", name);
}
return std::move(list);
}
......@@ -27,7 +27,7 @@ std::vector<T> EnsureNonempty(std::vector<T> list, const std::string& name,
template <class T, class Name>
T EnsureUnique(const std::vector<T>& list, const Name& name, const char* kind) {
if (list.empty()) {
ReportError("there is no ", kind, "named ", name);
ReportError("there is no ", kind, " named ", name);
}
if (list.size() >= 2) {
ReportError("ambiguous reference to ", kind, " ", name);
......@@ -167,20 +167,22 @@ void Declarations::DeclareType(const std::string& name, const Type* type,
Declare(name, std::unique_ptr<TypeAlias>(new TypeAlias(type, redeclaration)));
}
void Declarations::DeclareStruct(const std::string& name,
const std::vector<Field>& fields) {
const StructType* new_type = TypeOracle::GetStructType(name, fields);
StructType* Declarations::DeclareStruct(const std::string& name,
const std::vector<Field>& fields) {
StructType* new_type = TypeOracle::GetStructType(name, fields);
DeclareType(name, new_type, false);
return new_type;
}
const ClassType* Declarations::DeclareClass(
base::Optional<std::string> parent, const std::string& name, bool transient,
const std::string& generates, std::vector<Field> fields, size_t size) {
ClassType* Declarations::DeclareClass(base::Optional<std::string> parent,
const std::string& name, bool transient,
const std::string& generates,
std::vector<Field> fields, size_t size) {
const Type* parent_type = nullptr;
if (parent) {
parent_type = LookupType(QualifiedName{*parent});
}
const ClassType* new_type = TypeOracle::GetClassType(
ClassType* new_type = TypeOracle::GetClassType(
parent_type, name, transient, generates, std::move(fields), size);
DeclareType(name, new_type, false);
return new_type;
......@@ -216,11 +218,23 @@ Macro* Declarations::DeclareMacro(
ReportError("cannot redeclare operator ", name,
" with identical explicit parameters");
}
Declare(*op, macro);
DeclareOperator(*op, macro);
}
return macro;
}
Method* Declarations::CreateMethod(AggregateType* container_type,
const std::string& name, Signature signature,
bool transitioning, Statement* body) {
std::string generated_name{container_type->GetGeneratedMethodName(name)};
Method* result = RegisterDeclarable(std::unique_ptr<Method>(
new Method(container_type, container_type->GetGeneratedMethodName(name),
name, CurrentNamespace()->ExternalName(), std::move(signature),
transitioning, body)));
container_type->RegisterMethod(result);
return result;
}
Intrinsic* Declarations::CreateIntrinsic(const std::string& name,
const Signature& signature) {
Intrinsic* result = RegisterDeclarable(std::unique_ptr<Intrinsic>(
......@@ -293,6 +307,11 @@ std::string Declarations::GetGeneratedCallableName(
return result;
}
Macro* Declarations::DeclareOperator(const std::string& name, Macro* m) {
GlobalContext::GetDefaultNamespace()->AddDeclarable(name, m);
return m;
}
} // namespace torque
} // namespace internal
} // namespace v8
......@@ -81,13 +81,13 @@ class Declarations {
static void DeclareType(const std::string& name, const Type* type,
bool redeclaration);
static void DeclareStruct(const std::string& name,
const std::vector<Field>& fields);
static StructType* DeclareStruct(const std::string& name,
const std::vector<Field>& fields);
static const ClassType* DeclareClass(base::Optional<std::string> parent,
const std::string& name, bool transient,
const std::string& generates,
std::vector<Field> fields, size_t size);
static ClassType* DeclareClass(base::Optional<std::string> parent,
const std::string& name, bool transient,
const std::string& generates,
std::vector<Field> fields, size_t size);
static Macro* CreateMacro(std::string external_name,
std::string readable_name,
......@@ -100,6 +100,10 @@ class Declarations {
const Signature& signature, bool transitioning,
base::Optional<Statement*> body, base::Optional<std::string> op = {});
static Method* CreateMethod(AggregateType* class_type,
const std::string& name, Signature signature,
bool transitioning, Statement* body);
static Intrinsic* CreateIntrinsic(const std::string& name,
const Signature& signature);
......@@ -137,6 +141,7 @@ class Declarations {
return CurrentScope::Get()->AddDeclarable(name,
RegisterDeclarable(std::move(d)));
}
static Macro* DeclareOperator(const std::string& name, Macro* m);
static std::string GetGeneratedCallableName(
const std::string& name, const TypeVector& specialized_types);
......
......@@ -28,10 +28,6 @@ class FileVisitor {
}
protected:
std::string GetParameterVariableFromName(const std::string& name) {
return std::string("p_") + name;
}
Signature MakeSignature(const CallableNodeSignature* signature);
};
......
This diff is collapsed.
......@@ -69,6 +69,13 @@ class LocationReference {
DCHECK(IsTemporary());
return *temporary_;
}
const VisitResult& GetVisitResult() const {
if (IsVariableAccess()) return variable();
DCHECK(IsTemporary());
return temporary();
}
// For error reporting.
const std::string& temporary_description() const {
DCHECK(IsTemporary());
......@@ -230,13 +237,17 @@ class ImplementationVisitor : public FileVisitor {
void Visit(Declarable* delarable);
void Visit(TypeAlias* decl);
VisitResult InlineMacro(Macro* macro,
base::Optional<LocationReference> this_reference,
const std::vector<VisitResult>& arguments,
const std::vector<Block*> label_blocks);
void VisitMacroCommon(Macro* macro);
void Visit(Macro* macro);
void Visit(Method* macro);
void Visit(Builtin* builtin);
void Visit(NamespaceConstant* decl);
VisitResult Visit(CallExpression* expr, bool is_tail = false);
VisitResult Visit(CallMethodExpression* expr);
VisitResult Visit(IntrinsicCallExpression* intrinsic);
VisitResult Visit(LoadObjectFieldExpression* intrinsic);
VisitResult Visit(StoreObjectFieldExpression* intrinsic);
......@@ -254,6 +265,7 @@ class ImplementationVisitor : public FileVisitor {
VisitResult Visit(AssumeTypeImpossibleExpression* expr);
VisitResult Visit(TryLabelExpression* expr);
VisitResult Visit(StatementExpression* expr);
VisitResult Visit(NewExpression* expr);
const Type* Visit(ReturnStatement* stmt);
const Type* Visit(GotoStatement* stmt);
......@@ -276,12 +288,19 @@ class ImplementationVisitor : public FileVisitor {
void GenerateImplementation(const std::string& dir, Namespace* nspace);
struct ConstructorInfo {
int super_calls;
bool accessed_this;
};
DECLARE_CONTEXTUAL_VARIABLE(ValueBindingsManager,
BindingsManager<LocalValue>);
DECLARE_CONTEXTUAL_VARIABLE(LabelBindingsManager,
BindingsManager<LocalLabel>);
DECLARE_CONTEXTUAL_VARIABLE(CurrentCallable, Callable*);
DECLARE_CONTEXTUAL_VARIABLE(CurrentReturnValue, base::Optional<VisitResult>);
DECLARE_CONTEXTUAL_VARIABLE(CurrentConstructorInfo,
base::Optional<ConstructorInfo>);
// A BindingsManagersScope has to be active for local bindings to be created.
// Shadowing an existing BindingsManagersScope by creating a new one hides all
......@@ -376,7 +395,10 @@ class ImplementationVisitor : public FileVisitor {
base::Optional<Binding<LocalLabel>*> TryLookupLabel(const std::string& name);
Binding<LocalLabel>* LookupLabel(const std::string& name);
Block* LookupSimpleLabel(const std::string& name);
Callable* LookupCall(const QualifiedName& name, const Arguments& arguments,
template <class Container>
Callable* LookupCall(const QualifiedName& name,
const Container& declaration_container,
const Arguments& arguments,
const TypeVector& specialization_types);
const Type* GetCommonType(const Type* left, const Type* right);
......@@ -386,6 +408,17 @@ class ImplementationVisitor : public FileVisitor {
void GenerateAssignToLocation(const LocationReference& reference,
const VisitResult& assignment_value);
void AddCallParameter(Callable* callable, VisitResult parameter,
const Type* parameter_type,
std::vector<VisitResult>* converted_arguments,
StackRange* argument_range,
std::vector<std::string>* constexpr_arguments);
VisitResult GenerateCall(Callable* callable,
base::Optional<LocationReference> this_parameter,
Arguments parameters,
const TypeVector& specialization_types = {},
bool tail_call = false);
VisitResult GenerateCall(const QualifiedName& callable_name,
Arguments parameters,
const TypeVector& specialization_types = {},
......
......@@ -125,6 +125,17 @@ class Instruction {
}
InstructionKind kind() const { return kind_; }
const char* Mnemonic() const {
switch (kind()) {
#define ENUM_ITEM(name) \
case InstructionKind::k##name: \
return #name;
TORQUE_INSTRUCTION_LIST(ENUM_ITEM)
#undef ENUM_ITEM
default:
UNREACHABLE();
}
}
void TypeInstruction(Stack<const Type*>* stack, ControlFlowGraph* cfg) const {
return instruction_->TypeInstruction(stack, cfg);
}
......
......@@ -212,7 +212,8 @@ void CheckNotDeferredStatement(Statement* statement) {
}
Expression* MakeCall(IdentifierExpression* callee,
const std::vector<Expression*>& arguments,
base::Optional<Expression*> target,
std::vector<Expression*> arguments,
const std::vector<Statement*>& otherwise) {
std::vector<std::string> labels;
......@@ -240,7 +241,13 @@ Expression* MakeCall(IdentifierExpression* callee,
// Create nested try-label expression for all of the temporary Labels that
// were created.
Expression* result = MakeNode<CallExpression>(callee, arguments, labels);
Expression* result = nullptr;
if (target) {
result = MakeNode<CallMethodExpression>(*target, callee, arguments, labels);
} else {
result = MakeNode<CallExpression>(callee, arguments, labels);
}
for (auto* label : temp_labels) {
result = MakeNode<TryLabelExpression>(false, result, label);
}
......@@ -252,15 +259,42 @@ Expression* MakeCall(const std::string& callee,
const std::vector<Expression*>& arguments,
const std::vector<Statement*>& otherwise) {
return MakeCall(MakeNode<IdentifierExpression>(callee, generic_arguments),
arguments, otherwise);
base::nullopt, arguments, otherwise);
}
base::Optional<ParseResult> MakeCall(ParseResultIterator* child_results) {
auto callee = child_results->NextAs<LocationExpression*>();
auto args = child_results->NextAs<std::vector<Expression*>>();
auto otherwise = child_results->NextAs<std::vector<Statement*>>();
return ParseResult{
MakeCall(IdentifierExpression::cast(callee), args, otherwise)};
IdentifierExpression* target = IdentifierExpression::cast(callee);
if (target->name == kSuperMethodName) {
if (target->namespace_qualification.size() != 0) {
ReportError(
"\"super\" invocation cannot be used with namespace qualification");
}
target = MakeNode<IdentifierExpression>(kSuperMethodName);
return ParseResult{
MakeCall(target, MakeNode<IdentifierExpression>(kThisParameterName),
args, otherwise)};
} else {
return ParseResult{MakeCall(target, base::nullopt, args, otherwise)};
}
}
base::Optional<ParseResult> MakeMethodCall(ParseResultIterator* child_results) {
auto this_arg = child_results->NextAs<Expression*>();
auto callee = child_results->NextAs<std::string>();
auto args = child_results->NextAs<std::vector<Expression*>>();
auto otherwise = child_results->NextAs<std::vector<Statement*>>();
return ParseResult{MakeCall(MakeNode<IdentifierExpression>(callee), this_arg,
args, otherwise)};
}
base::Optional<ParseResult> MakeNew(ParseResultIterator* child_results) {
TypeExpression* type = child_results->NextAs<TypeExpression*>();
auto args = child_results->NextAs<std::vector<Expression*>>();
Expression* result = MakeNode<NewExpression>(type, args);
return ParseResult{result};
}
base::Optional<ParseResult> MakeBinaryOperator(
......@@ -521,6 +555,25 @@ base::Optional<ParseResult> MakeTypeDeclaration(
return ParseResult{result};
}
base::Optional<ParseResult> MakeMethodDeclaration(
ParseResultIterator* child_results) {
auto transitioning = child_results->NextAs<bool>();
auto operator_name = child_results->NextAs<base::Optional<std::string>>();
auto name = child_results->NextAs<std::string>();
if (name != kConstructMethodName && !IsUpperCamelCase(name)) {
NamingConventionError("Method", name, "UpperCamelCase");
}
auto args = child_results->NextAs<ParameterList>();
auto return_type = child_results->NextAs<TypeExpression*>();
auto labels = child_results->NextAs<LabelAndTypesVector>();
auto body = child_results->NextAs<Statement*>();
MacroDeclaration* macro = MakeNode<TorqueMacroDeclaration>(
transitioning, name, operator_name, args, return_type, labels);
Declaration* result = MakeNode<StandardDeclaration>(macro, body);
return ParseResult{result};
}
base::Optional<ParseResult> MakeClassDeclaration(
ParseResultIterator* child_results) {
auto transient = child_results->NextAs<bool>();
......@@ -530,10 +583,11 @@ base::Optional<ParseResult> MakeClassDeclaration(
}
auto extends = child_results->NextAs<base::Optional<std::string>>();
auto generates = child_results->NextAs<base::Optional<std::string>>();
auto methods = child_results->NextAs<std::vector<Declaration*>>();
auto fields = child_results->NextAs<std::vector<ClassFieldExpression>>();
Declaration* result =
MakeNode<ClassDeclaration>(std::move(name), transient, std::move(extends),
std::move(generates), fields);
Declaration* result = MakeNode<ClassDeclaration>(
std::move(name), transient, std::move(extends), std::move(generates),
std::move(methods), fields);
return ParseResult{result};
}
......@@ -568,9 +622,10 @@ base::Optional<ParseResult> MakeSpecializationDeclaration(
base::Optional<ParseResult> MakeStructDeclaration(
ParseResultIterator* child_results) {
auto name = child_results->NextAs<std::string>();
auto methods = child_results->NextAs<std::vector<Declaration*>>();
auto fields = child_results->NextAs<std::vector<NameAndTypeExpression>>();
Declaration* result =
MakeNode<StructDeclaration>(std::move(name), std::move(fields));
Declaration* result = MakeNode<StructDeclaration>(
std::move(name), std::move(methods), std::move(fields));
return ParseResult{result};
}
......@@ -1321,6 +1376,17 @@ struct TorqueGrammar : Grammar {
Symbol callExpression = {Rule(
{&identifierExpression, &argumentList, optionalOtherwise}, MakeCall)};
Symbol callMethodExpression = {
Rule({&primaryExpression, Token("."), &identifier, &argumentList,
optionalOtherwise},
MakeMethodCall)};
Symbol initializerList = {Rule(
{Token("{"), List<Expression*>(expression, Token(",")), Token("}")})};
Symbol newExpression = {
Rule({Token("new"), &type, &initializerList}, MakeNew)};
// Result: Expression*
Symbol intrinsicCallExpression = {Rule(
{&intrinsicName, TryOrDefault<TypeList>(&genericSpecializationTypeList),
......@@ -1329,7 +1395,9 @@ struct TorqueGrammar : Grammar {
// Result: Expression*
Symbol primaryExpression = {
Rule({&newExpression}),
Rule({&callExpression}),
Rule({&callMethodExpression}),
Rule({&intrinsicCallExpression}),
Rule({&locationExpression},
CastParseResult<LocationExpression*, Expression*>),
......@@ -1504,6 +1572,14 @@ struct TorqueGrammar : Grammar {
Rule({&block}, CastParseResult<Statement*, base::Optional<Statement*>>),
Rule({Token(";")}, YieldDefaultValue<base::Optional<Statement*>>)};
// Result: Declaration*
Symbol method = {Rule(
{CheckIf(Token("transitioning")),
Optional<std::string>(Sequence({Token("operator"), &externalString})),
&identifier, &parameterListNoVararg, &optionalReturnType,
optionalLabelList, &block},
MakeMethodDeclaration)};
// Result: Declaration*
Symbol declaration = {
Rule({Token("const"), &identifier, Token(":"), &type, Token("="),
......@@ -1516,8 +1592,14 @@ struct TorqueGrammar : Grammar {
Optional<std::string>(Sequence({Token("extends"), &identifier})),
Optional<std::string>(
Sequence({Token("generates"), &externalString})),
Token("{"), List<ClassFieldExpression>(&classField), Token("}")},
Token("{"), List<Declaration*>(&method),
List<ClassFieldExpression>(&classField), Token("}")},
MakeClassDeclaration),
Rule({Token("struct"), &identifier, Token("{"),
List<Declaration*>(&method),
List<NameAndTypeExpression>(Sequence({&nameAndType, Token(";")})),
Token("}")},
MakeStructDeclaration),
Rule({CheckIf(Token("transient")), Token("type"), &identifier,
Optional<std::string>(Sequence({Token("extends"), &identifier})),
Optional<std::string>(
......@@ -1567,10 +1649,6 @@ struct TorqueGrammar : Grammar {
&parameterListAllowVararg, &optionalReturnType, optionalLabelList,
&block},
MakeSpecializationDeclaration),
Rule({Token("struct"), &identifier, Token("{"),
List<NameAndTypeExpression>(Sequence({&nameAndType, Token(";")})),
Token("}")},
MakeStructDeclaration),
Rule({Token("#include"), &externalString}, MakeCppIncludeDeclaration)};
// Result: Declaration*
......
......@@ -28,18 +28,17 @@ class TypeOracle : public ContextualClass<TypeOracle> {
return result;
}
static const StructType* GetStructType(const std::string& name,
const std::vector<Field>& fields) {
static StructType* GetStructType(const std::string& name,
const std::vector<Field>& fields) {
StructType* result = new StructType(CurrentNamespace(), name, fields);
Get().struct_types_.push_back(std::unique_ptr<StructType>(result));
return result;
}
static const ClassType* GetClassType(const Type* parent,
const std::string& name, bool transient,
const std::string& generates,
const std::vector<Field>& fields,
size_t size) {
static ClassType* GetClassType(const Type* parent, const std::string& name,
bool transient, const std::string& generates,
const std::vector<Field>& fields,
size_t size) {
ClassType* result = new ClassType(parent, CurrentNamespace(), name,
transient, generates, fields, size);
Get().struct_types_.push_back(std::unique_ptr<ClassType>(result));
......
......@@ -184,7 +184,21 @@ const Type* SubtractType(const Type* a, const Type* b) {
return TypeOracle::GetUnionType(result);
}
const Field& NameAndTypeListType::LookupField(const std::string& name) const {
std::vector<const AggregateType*> AggregateType::GetHierarchy() {
std::vector<const AggregateType*> hierarchy;
const AggregateType* current_container_type = this;
while (current_container_type != nullptr) {
hierarchy.push_back(current_container_type);
current_container_type =
current_container_type->IsClassType()
? ClassType::cast(current_container_type)->GetSuperClass()
: nullptr;
}
std::reverse(hierarchy.begin(), hierarchy.end());
return hierarchy;
}
const Field& AggregateType::LookupField(const std::string& name) const {
for (auto& field : fields_) {
if (field.name_and_type.name == name) return field;
}
......@@ -200,6 +214,17 @@ std::string StructType::GetGeneratedTypeName() const {
return nspace()->ExternalName() + "::" + name();
}
std::vector<Method*> AggregateType::Methods(const std::string& name) const {
std::vector<Method*> result;
std::copy_if(methods_.begin(), methods_.end(), std::back_inserter(result),
[&](Macro* macro) { return macro->ReadableName() == name; });
return result;
}
std::vector<Method*> AggregateType::Constructors() const {
return Methods(kConstructMethodName);
}
std::string StructType::ToExplicitString() const {
std::stringstream result;
result << "struct " << name() << "{";
......
......@@ -40,6 +40,9 @@ static const char* const CONST_INT31_TYPE_STRING = "constexpr int31";
static const char* const CONST_INT32_TYPE_STRING = "constexpr int32";
static const char* const CONST_FLOAT64_TYPE_STRING = "constexpr float64";
class Macro;
class Method;
class StructType;
class Value;
class Namespace;
......@@ -62,6 +65,7 @@ class TypeBase {
bool IsUnionType() const { return kind() == Kind::kUnionType; }
bool IsStructType() const { return kind() == Kind::kStructType; }
bool IsClassType() const { return kind() == Kind::kClassType; }
bool IsAggregateType() const { return IsStructType() || IsClassType(); }
protected:
explicit TypeBase(Kind kind) : kind_(kind) {}
......@@ -376,8 +380,9 @@ class UnionType final : public Type {
const Type* SubtractType(const Type* a, const Type* b);
class NameAndTypeListType : public Type {
class AggregateType : public Type {
public:
DECLARE_TYPE_BOILERPLATE(AggregateType);
std::string MangledName() const override { return name_; }
std::string GetGeneratedTypeName() const override { UNREACHABLE(); };
std::string GetGeneratedTNodeTypeName() const override { UNREACHABLE(); }
......@@ -391,18 +396,30 @@ class NameAndTypeListType : public Type {
const std::string& name() const { return name_; }
Namespace* nspace() const { return namespace_; }
std::string GetGeneratedMethodName(const std::string& name) const {
return "_method_" + name_ + "_" + name;
}
void RegisterMethod(Method* method) { methods_.push_back(method); }
std::vector<Method*> Constructors() const;
const std::vector<Method*>& Methods() const { return methods_; }
std::vector<Method*> Methods(const std::string& name) const;
std::vector<const AggregateType*> GetHierarchy();
protected:
NameAndTypeListType(Kind kind, const Type* parent, Namespace* nspace,
const std::string& name, const std::vector<Field>& fields)
AggregateType(Kind kind, const Type* parent, Namespace* nspace,
const std::string& name, const std::vector<Field>& fields)
: Type(kind, parent), namespace_(nspace), name_(name), fields_(fields) {}
private:
Namespace* namespace_;
std::string name_;
std::vector<Method*> methods_;
std::vector<Field> fields_;
};
class StructType final : public NameAndTypeListType {
class StructType final : public AggregateType {
public:
DECLARE_TYPE_BOILERPLATE(StructType);
std::string ToExplicitString() const override;
......@@ -412,12 +429,12 @@ class StructType final : public NameAndTypeListType {
friend class TypeOracle;
StructType(Namespace* nspace, const std::string& name,
const std::vector<Field>& fields)
: NameAndTypeListType(Kind::kStructType, nullptr, nspace, name, fields) {}
: AggregateType(Kind::kStructType, nullptr, nspace, name, fields) {}
const std::string& GetStructName() const { return name(); }
};
class ClassType final : public NameAndTypeListType {
class ClassType final : public AggregateType {
public:
DECLARE_TYPE_BOILERPLATE(ClassType);
std::string ToExplicitString() const override;
......@@ -427,13 +444,16 @@ class ClassType final : public NameAndTypeListType {
std::string GetGeneratedTNodeTypeName() const override;
bool IsTransient() const override { return transient_; }
size_t size() const { return size_; }
const ClassType* GetSuperClass() const {
return parent()->IsClassType() ? ClassType::DynamicCast(parent()) : nullptr;
}
private:
friend class TypeOracle;
ClassType(const Type* parent, Namespace* nspace, const std::string& name,
bool transient, const std::string& generates,
const std::vector<Field>& fields, size_t size)
: NameAndTypeListType(Kind::kClassType, parent, nspace, name, fields),
: AggregateType(Kind::kClassType, parent, nspace, name, fields),
transient_(transient),
size_(size),
generates_(generates) {}
......
......@@ -168,6 +168,10 @@ class StackRange {
BottomOffset end_;
};
inline std::ostream& operator<<(std::ostream& out, StackRange range) {
return out << "StackRange{" << range.begin() << ", " << range.end() << "}";
}
template <class T>
class Stack {
public:
......@@ -266,6 +270,9 @@ class ToString {
constexpr int kTaggedSize = sizeof(void*);
static const char* const kConstructMethodName = "constructor";
static const char* const kSuperMethodName = "super";
} // namespace torque
} // namespace internal
} // namespace v8
......
......@@ -391,6 +391,38 @@ TEST(TestFrame1) {
ft.Call();
}
TEST(TestNew) {
CcTest::InitializeVM();
Isolate* isolate(CcTest::i_isolate());
i::HandleScope scope(isolate);
Handle<Context> context =
Utils::OpenHandle(*v8::Isolate::GetCurrent()->GetCurrentContext());
CodeAssemblerTester asm_tester(isolate);
TestTorqueAssembler m(asm_tester.state());
{
m.TestNew(m.UncheckedCast<Context>(m.HeapConstant(context)));
m.Return(m.UndefinedConstant());
}
FunctionTester ft(asm_tester.GenerateCode(), 0);
ft.Call();
}
TEST(TestStructConstructor) {
CcTest::InitializeVM();
Isolate* isolate(CcTest::i_isolate());
i::HandleScope scope(isolate);
Handle<Context> context =
Utils::OpenHandle(*v8::Isolate::GetCurrent()->GetCurrentContext());
CodeAssemblerTester asm_tester(isolate);
TestTorqueAssembler m(asm_tester.state());
{
m.TestStructConstructor(m.UncheckedCast<Context>(m.HeapConstant(context)));
m.Return(m.UndefinedConstant());
}
FunctionTester ft(asm_tester.GenerateCode(), 0);
ft.Call();
}
} // namespace compiler
} // namespace internal
} // namespace v8
......@@ -689,4 +689,33 @@ namespace test {
}
}
macro TestNew(implicit context: Context)() {
const f: JSArray = new JSArray{};
assert(f.IsEmpty());
f.length = 0;
}
struct TestInner {
SetX(newValue: int32) {
this.x = newValue;
}
GetX(): int32 {
return this.x;
}
x: int32;
y: int32;
}
struct TestOuter {
a: int32;
b: TestInner;
c: int32;
}
macro TestStructConstructor(implicit context: Context)() {
let a: TestOuter = TestOuter{0, TestInner{0, 0}, 0};
a.b.SetX(2);
assert(a.b.x == 2);
assert(a.b.GetX() == 2);
}
}
......@@ -50,7 +50,7 @@ def postprocess(output):
output = re.sub(r'% RawPointerCast', r'%RawPointerCast', output)
output = re.sub(r'% RawConstexprCast', r'%RawConstexprCast', output)
output = re.sub(r'% FromConstexpr', r'%FromConstexpr', output)
output = re.sub(r'% Allocate', r'%Allocate ', output)
output = re.sub(r'% Allocate', r'%Allocate', output)
output = re.sub(r'\/\*COxp\*\/', r'constexpr', output)
output = re.sub(r'(\S+)\s*: type([,>])', r'\1: type\2', output)
output = re.sub(r'(\n\s*)labels( [A-Z])', r'\1 labels\2', output)
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment