compiler: move lowering pass after check types pass

This change moves the lowering pass after the type determination and
the type checking passes.  This lets us simplify some of the code that
determines the type of an expression, which previously had to work
correctly both before and after type determination.

I'm doing this to help with future generic support.  For example, with
generics, we can see code like

    func ident[T any](v T) T { return v }

    func F() int32 {
	s := int32(1)
	return ident(s)
    }

Before this change, we would type check return statements in the
lowering pass (see Return_statement::do_lower).  With a generic
example like the above, that means we have to determine the type of s,
and use that to infer the type arguments passed to ident, and use that
to determine the result type of ident.  That is too much to do at
lowering time.  Of course we can change the way that return statements
work, but similar issues arise with index expressions, the types of
closures for function literals, and probably other cases as well.

Rather than try to deal with all those cases, we move the lowering
pass after type checking.  This requires a bunch of changes, notably
for determining constant types.  We have to add type checking for
various constructs that formerly disappeared in the lowering pass.
So it's a lot of shuffling.  Sorry for the size of the patch.

Change-Id: Ic269e816f324c87feb708ca4cde0eff7f2f70c7b
Reviewed-on: https://go-review.googlesource.com/c/gofrontend/+/536643
Reviewed-by: Ian Lance Taylor <iant@google.com>
Reviewed-by: Than McIntosh <thanm@google.com>
This commit is contained in:
Ian Lance Taylor 2023-10-19 19:34:31 -07:00
Родитель f5d708fd90
Коммит 61b29a99da
12 изменённых файлов: 4077 добавлений и 1638 удалений

Разница между файлами не показана из-за своего большого размера Загрузить разницу

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

@ -596,7 +596,8 @@ class Expression
{ return this->do_is_static_initializer(); }
// If this is not a numeric constant, return false. If it is one,
// return true, and set VAL to hold the value.
// return true, and set VAL to hold the value. This method can be
// called before the determine_types pass.
bool
numeric_constant_value(Numeric_constant* val)
{ return this->do_numeric_constant_value(val); }
@ -633,8 +634,7 @@ class Expression
// Return whether this expression really represents a type.
bool
is_type_expression() const
{ return this->classification_ == EXPRESSION_TYPE; }
is_type_expression() const;
// If this is a const reference, return the Const_expression
// structure. Otherwise, return NULL. This is a controlled dynamic
@ -735,6 +735,10 @@ class Expression
unary_expression()
{ return this->convert<Unary_expression, EXPRESSION_UNARY>(); }
const Unary_expression*
unary_expression() const
{ return this->convert<const Unary_expression, EXPRESSION_UNARY>(); }
// If this is a binary expression, return the Binary_expression
// structure. Otherwise return NULL.
Binary_expression*
@ -1022,10 +1026,8 @@ class Expression
void
determine_type_no_context(Gogo*);
// Return the current type of the expression. This may be changed
// by determine_type. This should not be called before the lowering
// pass, unless the is_type_expression method returns true (i.e.,
// this is an EXPRESSION_TYPE).
// Return the type of the expression. This should not be called
// before the determine_types pass.
Type*
type()
{ return this->do_type(); }
@ -1472,17 +1474,6 @@ class Parser_expression : public Expression
virtual Expression*
do_lower(Gogo*, Named_object*, Statement_inserter*, int) = 0;
Type*
do_type();
void
do_determine_type(Gogo*, const Type_context*)
{ go_unreachable(); }
void
do_check_types(Gogo*)
{ go_unreachable(); }
Bexpression*
do_get_backend(Translate_context*)
{ go_unreachable(); }
@ -1495,7 +1486,8 @@ class Const_expression : public Expression
public:
Const_expression(Named_object* constant, Location location)
: Expression(EXPRESSION_CONST_REFERENCE, location),
constant_(constant), type_(NULL), seen_(false)
constant_(constant), type_(NULL), iota_value_(0), seen_(false),
is_iota_(false)
{ }
Named_object*
@ -1510,6 +1502,10 @@ class Const_expression : public Expression
void
check_for_init_loop();
// Set the iota value if this is a reference to iota.
void
set_iota_value(int);
protected:
int
do_traverse(Traverse*);
@ -1576,9 +1572,14 @@ class Const_expression : public Expression
// The type of this reference. This is used if the constant has an
// abstract type.
Type* type_;
// If this const is a reference to the predeclared iota value, the
// value to use.
int iota_value_;
// Used to prevent infinite recursion when a constant incorrectly
// refers to itself.
mutable bool seen_;
// Whether this const is a reference to the predeclared iota value.
bool is_iota_;
};
// An expression which is simply a variable.
@ -1976,8 +1977,7 @@ class Type_conversion_expression : public Expression
do_boolean_constant_value(bool*);
Type*
do_type()
{ return this->type_; }
do_type();
void
do_determine_type(Gogo*, const Type_context*);
@ -2074,7 +2074,7 @@ class Unary_expression : public Expression
Unary_expression(Operator op, Expression* expr, Location location)
: Expression(EXPRESSION_UNARY, location),
op_(op), escapes_(true), create_temp_(false), is_gc_root_(false),
is_slice_init_(false), expr_(expr),
is_slice_init_(false), expr_(expr), type_(NULL),
issue_nil_check_(NIL_CHECK_DEFAULT)
{ }
@ -2131,7 +2131,7 @@ class Unary_expression : public Expression
// could be done, false if not. On overflow, issues an error and
// sets *ISSUED_ERROR.
static bool
eval_constant(Operator op, const Numeric_constant* unc,
eval_constant(Type*, Operator op, const Numeric_constant* unc,
Location, Numeric_constant* nc, bool *issued_error);
static Expression*
@ -2246,6 +2246,8 @@ class Unary_expression : public Expression
bool is_slice_init_;
// The operand.
Expression* expr_;
// The type of the expression. Not used for AND and MULT.
Type* type_;
// Whether or not to issue a nil check for this expression if its address
// is being taken.
Nil_check_classification issue_nil_check_;
@ -2372,15 +2374,15 @@ class Binary_expression : public Expression
static bool
eval_integer(Operator op, const Numeric_constant*, const Numeric_constant*,
Location, Numeric_constant*);
Location, Numeric_constant*, bool* issued_error);
static bool
eval_float(Operator op, const Numeric_constant*, const Numeric_constant*,
Location, Numeric_constant*);
Location, Numeric_constant*, bool* issued_error);
static bool
eval_complex(Operator op, const Numeric_constant*, const Numeric_constant*,
Location, Numeric_constant*);
Location, Numeric_constant*, bool* issued_error);
static bool
compare_integer(const Numeric_constant*, const Numeric_constant*, int*);
@ -2412,7 +2414,7 @@ class Binary_expression : public Expression
Expression* left_;
// The right hand side operand.
Expression* right_;
// The type of a comparison operation.
// The type of the expression.
Type* type_;
};
@ -2493,8 +2495,8 @@ class Call_expression : public Expression
Call_expression(Expression* fn, Expression_list* args, bool is_varargs,
Location location)
: Expression(EXPRESSION_CALL, location),
fn_(fn), args_(args), type_(NULL), call_(NULL), call_temp_(NULL)
, expected_result_count_(0), is_varargs_(is_varargs),
fn_(fn), args_(args), type_(NULL), lowered_(NULL), call_(NULL),
call_temp_(NULL), expected_result_count_(0), is_varargs_(is_varargs),
varargs_are_lowered_(false), types_are_determined_(false),
is_deferred_(false), is_concurrent_(false), is_equal_function_(false),
issued_error_(false), is_multi_value_arg_(false), is_flattened_(false)
@ -2530,7 +2532,8 @@ class Call_expression : public Expression
// Set the number of results expected from this call. This is used
// when the call appears in a context that expects multiple results,
// such as a, b = f().
// such as a, b = f(). This must be called before the
// determine_types pass.
void
set_expected_result_count(size_t);
@ -2616,6 +2619,10 @@ class Call_expression : public Expression
inline const Builtin_call_expression*
builtin_call_expression() const;
// Lower to a Builtin_call_expression if appropriate.
Expression*
lower_builtin(Gogo*);
protected:
int
do_traverse(Traverse*);
@ -2627,12 +2634,20 @@ class Call_expression : public Expression
do_flatten(Gogo*, Named_object*, Statement_inserter*);
bool
do_discarding_value()
{ return true; }
do_discarding_value();
virtual Type*
do_type();
virtual bool
do_is_constant() const;
bool
do_is_untyped(Type**) const;
bool
do_numeric_constant_value(Numeric_constant*);
virtual void
do_determine_type(Gogo*, const Type_context*);
@ -2665,17 +2680,26 @@ class Call_expression : public Expression
set_args(Expression_list* args)
{ this->args_ = args; }
// Let a builtin expression lower varargs.
void
lower_varargs(Gogo*, Named_object* function, Statement_inserter* inserter,
Type* varargs_type, size_t param_count,
Slice_storage_escape_disp escape_disp);
// Let a builtin expression check whether types have been
// determined.
bool
determining_types();
// Let a builtin expression retrieve the expected type.
Type*
type()
{ return this->type_; }
// Let a builtin expression set the expected type.
void
set_type(Type* type)
{ this->type_ = type; }
// Let a builtin expression simply f(g()) where g returns multiple
// results.
void
simplify_multiple_results(Gogo*);
void
export_arguments(Export_function_body*) const;
@ -2687,7 +2711,10 @@ class Call_expression : public Expression
private:
bool
check_argument_type(int, const Type*, const Type*, Location, bool);
rewrite_varargs();
bool
check_argument_type(int, const Type*, const Type*, Location);
Expression*
intrinsify(Gogo*, Statement_inserter*);
@ -2706,6 +2733,8 @@ class Call_expression : public Expression
Expression_list* args_;
// The type of the expression, to avoid recomputing it.
Type* type_;
// If not NULL, this is a lowered version of this Call_expression.
Expression* lowered_;
// The backend expression for the call, used for a call which returns a tuple.
Bexpression* call_;
// A temporary variable to store this call if the function returns a tuple.
@ -3087,7 +3116,8 @@ class Unknown_expression : public Parser_expression
public:
Unknown_expression(Named_object* named_object, Location location)
: Parser_expression(EXPRESSION_UNKNOWN_REFERENCE, location),
named_object_(named_object), no_error_message_(false)
named_object_(named_object), lowered_(NULL), iota_value_(0),
no_error_message_(false), is_iota_(false)
{ }
// The associated named object.
@ -3106,7 +3136,38 @@ class Unknown_expression : public Parser_expression
set_no_error_message()
{ this->no_error_message_ = true; }
// Set the iota value if this is a reference to iota.
void
set_iota_value(int);
protected:
int
do_traverse(Traverse*);
Type*
do_type();
void
do_determine_type(Gogo*, const Type_context*);
bool
do_is_constant() const;
bool
do_is_untyped(Type**) const;
virtual bool
do_numeric_constant_value(Numeric_constant*);
virtual bool
do_string_constant_value(std::string*);
virtual bool
do_boolean_constant_value(bool*);
bool
do_is_addressable() const;
Expression*
do_lower(Gogo*, Named_object*, Statement_inserter*, int);
@ -3120,9 +3181,15 @@ class Unknown_expression : public Parser_expression
private:
// The unknown name.
Named_object* named_object_;
// The fully resolved expression.
Expression* lowered_;
// The iota value if this turns out to be a reference to iota.
int iota_value_;
// True if we should not give errors if this is undefined. This is
// used if there was a parse failure.
bool no_error_message_;
// True if this could be a reference to iota.
bool is_iota_;
};
// An index expression. This is lowered to an array index, a string
@ -3134,9 +3201,15 @@ class Index_expression : public Parser_expression
Index_expression(Expression* left, Expression* start, Expression* end,
Expression* cap, Location location)
: Parser_expression(EXPRESSION_INDEX, location),
left_(left), start_(start), end_(end), cap_(cap)
left_(left), start_(start), end_(end), cap_(cap),
needs_nil_check_(false)
{ }
// Return the expression being indexed.
Expression*
left() const
{ return this->left_; }
// Dump an index expression, i.e. an expression of the form
// expr[expr], expr[expr:expr], or expr[expr:expr:expr] to a dump context.
static void
@ -3144,24 +3217,44 @@ class Index_expression : public Parser_expression
const Expression* start, const Expression* end,
const Expression* cap);
// Report whether EXPR is a map index expression.
static bool
is_map_index(Expression* expr);
protected:
int
do_traverse(Traverse*);
Type*
do_type();
void
do_determine_type(Gogo*, const Type_context*);
void
do_check_types(Gogo*);
bool
do_is_addressable() const;
Expression*
do_lower(Gogo*, Named_object*, Statement_inserter*, int);
Expression*
do_copy()
{
return new Index_expression(this->left_->copy(), this->start_->copy(),
(this->end_ == NULL
? NULL
: this->end_->copy()),
(this->cap_ == NULL
? NULL
: this->cap_->copy()),
this->location());
Index_expression* ret =
new Index_expression(this->left_->copy(), this->start_->copy(),
(this->end_ == NULL
? NULL
: this->end_->copy()),
(this->cap_ == NULL
? NULL
: this->cap_->copy()),
this->location());
if (this->needs_nil_check_)
ret->needs_nil_check_ = true;
return ret;
}
// This shouldn't be called--we don't know yet.
@ -3173,8 +3266,8 @@ class Index_expression : public Parser_expression
do_dump_expression(Ast_dump_context*) const;
void
do_issue_nil_check()
{ this->left_->issue_nil_check(); }
do_issue_nil_check();
private:
// The expression being indexed.
Expression* left_;
@ -3187,6 +3280,9 @@ class Index_expression : public Parser_expression
// default capacity, non-NULL for indices and slices that specify the
// capacity.
Expression* cap_;
// True if this needs a nil check. This changes how we handle
// dereferencing a pointer to an array.
bool needs_nil_check_;
};
// An array index. This is used for both indexing and slicing.
@ -3234,6 +3330,11 @@ class Array_index_expression : public Expression
set_needs_bounds_check(bool b)
{ this->needs_bounds_check_ = b; }
// Check indexes.
static bool
check_indexes(Expression* array, Expression* start, Expression* len,
Expression* cap, Location);
protected:
int
do_traverse(Traverse*);
@ -3339,6 +3440,11 @@ class String_index_expression : public Expression
end() const
{ return this->end_; }
// Check indexes.
static bool
check_indexes(Expression* string, Expression* start, Expression* len,
Location);
protected:
int
do_traverse(Traverse*);
@ -3832,7 +3938,8 @@ class Composite_literal_expression : public Parser_expression
Location location)
: Parser_expression(EXPRESSION_COMPOSITE_LITERAL, location),
type_(type), depth_(depth), vals_(vals), has_keys_(has_keys),
all_are_names_(all_are_names), key_path_(std::vector<bool>(depth))
all_are_names_(all_are_names), key_path_(std::vector<bool>(depth)),
traverse_order_(NULL)
{}
@ -3848,6 +3955,15 @@ class Composite_literal_expression : public Parser_expression
int
do_traverse(Traverse* traverse);
Type*
do_type();
void
do_determine_type(Gogo*, const Type_context*);
void
do_check_types(Gogo*);
Expression*
do_lower(Gogo*, Named_object*, Statement_inserter*, int);
@ -3858,8 +3974,14 @@ class Composite_literal_expression : public Parser_expression
do_dump_expression(Ast_dump_context*) const;
private:
bool
resolve_struct_keys(Gogo*, Type* type);
void
resolve_array_length(Type*);
Expression*
lower_struct(Gogo*, Type*);
lower_struct(Type*);
Expression*
lower_array(Type*);
@ -3888,6 +4010,10 @@ class Composite_literal_expression : public Parser_expression
// a value. This is used to decide which type to use when given a map literal
// with omitted key types.
std::vector<bool> key_path_;
// If not NULL, the order in which to traverse vals_ for a struct
// composite literal. This is used so that we implement the order
// of evaluation rules correctly.
std::vector<unsigned long>* traverse_order_;
};
// Helper/mixin class for struct and array construction expressions;
@ -3948,6 +4074,10 @@ class Struct_construction_expression : public Expression,
bool
is_constant_struct() const;
// Check types of a struct composite literal.
static bool
check_value_types(Gogo*, Type*, Expression_list*, Location);
protected:
int
do_traverse(Traverse* traverse);

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

@ -118,36 +118,39 @@ go_parse_input_files(const char** filenames, unsigned int filename_count,
::gogo->add_linkname(p->first, p->second.is_exported, p->second.ext_name,
p->second.loc);
// Lower calls to builtin functions.
::gogo->lower_builtin_calls();
// Finalize method lists and build stub methods for named types.
::gogo->finalize_methods();
// Check that functions have a terminating statement.
::gogo->check_return_statements();
// Now that we have seen all the names, lower the parse tree into a
// form which is easier to use.
::gogo->lower_parse_tree();
// At this point we have handled all inline functions, so we no
// longer need the linemap.
::gogo->linemap()->stop();
// Create function descriptors as needed.
::gogo->create_function_descriptors();
// Work out types of unspecified constants and variables.
::gogo->determine_types();
// Now that we have seen all the names, verify that types are
// correct.
::gogo->verify_types();
// Work out types of unspecified constants and variables.
::gogo->determine_types();
// Check types and issue errors as appropriate.
::gogo->check_types();
// Now that we have seen all the names and we know all the types,
// lower the parse tree into a form which is easier to use.
::gogo->lower_parse_tree();
if (only_check_syntax)
return;
// Create function descriptors as needed.
::gogo->create_function_descriptors();
// Record global variable initializer dependencies.
::gogo->record_global_init_refs();

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

@ -2998,10 +2998,7 @@ Lower_parse_tree::constant(Named_object* no, bool)
return TRAVERSE_CONTINUE;
nc->set_lowering();
go_assert(this->iota_value_ == -1);
this->iota_value_ = nc->iota_value();
nc->traverse_expression(this);
this->iota_value_ = -1;
nc->clear_lowering();
@ -3018,8 +3015,6 @@ Lower_parse_tree::constant(Named_object* no, bool)
int
Lower_parse_tree::function(Named_object* no)
{
no->func_value()->set_closure_type();
go_assert(this->function_ == NULL);
this->function_ = no;
int t = no->func_value()->traverse(this);
@ -3482,6 +3477,43 @@ Gogo::create_function_descriptors()
this->traverse(&cfd);
}
// Lower calls to builtin functions. We need to do this early because
// some builtin calls are constant expressions. In particular we need
// to do this before finalize_methods, because finalize_methods calls
// is_direct_iface_type, which needs to know whether something like
// [unsafe.Sizeof(byte(0))]*byte is a direct-iface type.
class Lower_builtin_calls : public Traverse
{
public:
Lower_builtin_calls(Gogo* gogo)
: Traverse(traverse_expressions),
gogo_(gogo)
{ }
int
expression(Expression**);
private:
Gogo* gogo_;
};
int
Lower_builtin_calls::expression(Expression** pexpr)
{
Call_expression* ce = (*pexpr)->call_expression();
if (ce != NULL)
*pexpr = ce->lower_builtin(this->gogo_);
return TRAVERSE_CONTINUE;
}
void
Gogo::lower_builtin_calls()
{
Lower_builtin_calls lbc(this);
this->traverse(&lbc);
}
// Finalize the methods of an interface type.
int
@ -3625,47 +3657,7 @@ Gogo::finalize_methods_for_type(Type* type)
void
Gogo::determine_types()
{
Bindings* bindings = this->current_bindings();
for (Bindings::const_definitions_iterator p = bindings->begin_definitions();
p != bindings->end_definitions();
++p)
{
if ((*p)->is_function())
(*p)->func_value()->determine_types(this);
else if ((*p)->is_variable())
(*p)->var_value()->determine_type(this);
else if ((*p)->is_const())
(*p)->const_value()->determine_type(this);
// See if a variable requires us to build an initialization
// function. We know that we will see all global variables
// here.
if (!this->need_init_fn_ && (*p)->is_variable())
{
Variable* variable = (*p)->var_value();
// If this is a global variable which requires runtime
// initialization, we need an initialization function.
if (!variable->is_global())
;
else if (variable->init() == NULL)
;
else if (variable->type()->interface_type() != NULL)
this->need_init_fn_ = true;
else if (variable->init()->is_constant())
;
else if (!variable->init()->is_composite_literal())
this->need_init_fn_ = true;
else if (variable->init()->is_nonconstant_composite_literal())
this->need_init_fn_ = true;
// If this is a global variable which holds a pointer value,
// then we need an initialization function to register it as a
// GC root.
if (variable->is_global() && variable->type()->has_pointer())
this->need_init_fn_ = true;
}
}
this->current_bindings()->determine_types(this);
// Determine the types of constants in packages.
for (Packages::const_iterator p = this->packages_.begin();
@ -3756,6 +3748,7 @@ Check_types_traverse::variable(Named_object* named_object)
no->message_name().c_str());
}
}
if (!var->is_used()
&& !var->is_global()
&& !var->is_parameter()
@ -3763,8 +3756,15 @@ Check_types_traverse::variable(Named_object* named_object)
&& !var->type()->is_error()
&& (init == NULL || !init->is_error_expression())
&& !Lex::is_invalid_identifier(named_object->name()))
go_error_at(var->location(), "%qs declared but not used",
named_object->message_name().c_str());
{
// Avoid giving an error if the initializer is invalid.
if (init != NULL)
init->check_types(this->gogo_);
if (init == NULL || !init->is_error_expression())
go_error_at(var->location(), "%qs declared but not used",
named_object->message_name().c_str());
}
}
return TRAVERSE_CONTINUE;
}
@ -3788,6 +3788,11 @@ Check_types_traverse::constant(Named_object* named_object, bool)
go_error_at(constant->location(), "invalid constant type");
constant->set_error();
}
else if (constant->expr()->is_error_expression())
{
go_assert(saw_errors());
constant->set_error();
}
else if (!constant->expr()->is_constant())
{
go_error_at(constant->expr()->location(), "expression is not constant");
@ -4396,6 +4401,7 @@ Shortcuts::convert_shortcut(Block* enclosing, Expression** pshortcut)
Statement* if_statement = Statement::make_if_statement(cond, block, NULL,
loc);
if_statement->determine_types(this->gogo_);
retblock->add_statement(if_statement);
*pshortcut = Expression::make_temporary_reference(ts, loc);
@ -4817,7 +4823,7 @@ Build_recover_thunks::function(Named_object* orig_no)
// Any varargs call has already been lowered.
call->set_varargs_are_lowered();
Statement* s = Statement::make_return_from_call(call, location);
Statement* s = Statement::make_return_from_call(new_no, call, location);
s->determine_types(this->gogo_);
gogo->add_statement(s);
@ -5894,6 +5900,7 @@ Function::traverse(Traverse* traverse)
void
Function::determine_types(Gogo* gogo)
{
this->set_closure_type();
if (this->block_ != NULL)
this->block_->determine_types(gogo);
}
@ -7465,8 +7472,8 @@ Function_declaration::import_function_body(Gogo* gogo, Named_object* no)
if (!Block::import_block(outer, &ifb, start_loc))
return;
gogo->lower_block(no, outer);
outer->determine_types(gogo);
gogo->lower_block(no, outer);
gogo->add_imported_inline_function(no);
}
@ -7670,9 +7677,13 @@ Variable::has_type() const
Type*
Variable::type_from_tuple(Expression* expr, bool report_error) const
{
if (expr->map_index_expression() != NULL)
if (Index_expression::is_map_index(expr))
{
Map_type* mt = expr->map_index_expression()->get_map_type();
Map_type* mt;
if (expr->map_index_expression() != NULL)
mt = expr->map_index_expression()->get_map_type();
else
mt = expr->index_expression()->left()->type()->map_type();
if (mt == NULL)
return Type::make_error_type();
return mt->val_type();
@ -7701,7 +7712,9 @@ Variable::type_from_range(Expression* expr, bool get_index_type,
bool report_error) const
{
Type* t = expr->type();
if (t->array_type() != NULL
if (t->is_error_type())
return t;
else if (t->array_type() != NULL
|| (t->points_to() != NULL
&& t->points_to()->array_type() != NULL
&& !t->points_to()->is_slice_type()))
@ -8211,14 +8224,50 @@ Named_constant::traverse_expression(Traverse* traverse)
return Expression::traverse(&this->expr_, traverse);
}
// Set the iota value in a constant expression.
class Set_iota_value : public Traverse
{
public:
Set_iota_value(int iota_value)
: Traverse(traverse_expressions),
iota_value_(iota_value)
{ }
int
expression(Expression**);
private:
int iota_value_;
};
int
Set_iota_value::expression(Expression** pexpr)
{
Expression* expr = *pexpr;
if (expr->const_expression() != NULL)
expr->const_expression()->set_iota_value(this->iota_value_);
else if (expr->unknown_expression() != NULL)
{
// This case can happen for an array length that is not set in
// the determine types pass.
expr->unknown_expression()->set_iota_value(this->iota_value_);
}
return TRAVERSE_CONTINUE;
}
// Determine the type of the constant.
void
Named_constant::determine_type(Gogo* gogo)
{
if (this->type_is_determined_)
return;
this->type_is_determined_ = true;
if (this->type_ != NULL)
{
Type_context context(this->type_, false);
Type_context context(this->type_, this->type_->is_abstract());
this->expr_->determine_type(gogo, &context);
}
else
@ -8229,6 +8278,9 @@ Named_constant::determine_type(Gogo* gogo)
this->type_ = this->expr_->type();
go_assert(this->type_ != NULL);
}
Set_iota_value siv(this->iota_value_);
this->traverse_expression(&siv);
}
// Indicate that we found and reported an error for this constant.
@ -9353,6 +9405,55 @@ Bindings::traverse(Traverse* traverse, bool is_global)
return TRAVERSE_CONTINUE;
}
// Determine types for the objects.
void
Bindings::determine_types(Gogo* gogo)
{
// We don't use an iterator because the traversal can add new
// bindings.
for (size_t i = 0; i < this->named_objects_.size(); ++i)
{
Named_object* no = this->named_objects_[i];
if (no->is_function())
no->func_value()->determine_types(gogo);
else if (no->is_variable())
no->var_value()->determine_type(gogo);
else if (no->is_const())
no->const_value()->determine_type(gogo);
// See if a variable requires us to build an initialization
// function. We know that we will see all global variables
// here.
if (!gogo->need_init_fn() && no->is_variable())
{
Variable* variable = no->var_value();
// If this is a global variable which requires runtime
// initialization, we need an initialization function.
if (!variable->is_global())
continue;
if (variable->init() == NULL)
;
else if (variable->type()->interface_type() != NULL)
gogo->set_need_init_fn();
else if (variable->init()->is_constant())
;
else if (!variable->init()->is_composite_literal())
gogo->set_need_init_fn();
else if (variable->init()->is_nonconstant_composite_literal())
gogo->set_need_init_fn();
// If this global variable holds a pointer value, we need an
// initialization function to register it as a GC root.
if (variable->type()->has_pointer())
gogo->set_need_init_fn();
}
}
}
void
Bindings::debug_dump()
{

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

@ -703,6 +703,11 @@ class Gogo
void
record_interface_type(Interface_type*);
// Whether we need an initialization function.
bool
need_init_fn() const
{ return this->need_init_fn_; }
// Note that we need an initialization function.
void
set_need_init_fn()
@ -820,6 +825,10 @@ class Gogo
void
create_function_descriptors();
// Lower calls to builtin functions.
void
lower_builtin_calls();
// Finalize the method lists and build stub methods for named types.
void
finalize_methods();
@ -2569,7 +2578,8 @@ class Named_constant
Named_constant(Type* type, Expression* expr, int iota_value,
Location location)
: type_(type), expr_(expr), iota_value_(iota_value), location_(location),
lowering_(false), is_sink_(false), bconst_(NULL)
lowering_(false), is_sink_(false), type_is_determined_(false),
bconst_(NULL)
{ }
Type*
@ -2655,6 +2665,8 @@ class Named_constant
bool lowering_;
// Whether this constant is blank named and needs only type checking.
bool is_sink_;
// Whether we have determined the type of the constants.
bool type_is_determined_;
// The backend representation of the constant value.
Bexpression* bconst_;
};
@ -3276,6 +3288,10 @@ class Bindings
int
traverse(Traverse*, bool is_global);
// Determine types for the objects.
void
determine_types(Gogo*);
// Iterate over definitions. This does not include things which
// were only declared.

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

@ -2318,6 +2318,7 @@ Parse::simple_var_decl_or_assignment(const std::string& name,
go_error_at(id_location,
"%qs repeated on left side of %s",
Gogo::message_name(id).c_str(), ":=");
id = this->gogo_->pack_hidden_name("_", false);
}
til.push_back(Typed_identifier(id, NULL, location));
}
@ -2330,10 +2331,12 @@ Parse::simple_var_decl_or_assignment(const std::string& name,
id = this->gogo_->pack_hidden_name(id, is_id_exported);
ins = uniq_idents.insert(id);
std::string name = id;
if (!ins.second && !Gogo::is_sink_name(id))
{
dup_name = Gogo::message_name(id);
dup_loc = id_location;
id = this->gogo_->pack_hidden_name("_", false);
}
til.push_back(Typed_identifier(id, NULL, location));
}
@ -3511,9 +3514,9 @@ Parse::id_to_expression(const std::string& name, Location location,
if (is_composite_literal_key)
{
// This is a composite literal key, which means that it
// could just be a struct field name, so avoid confusiong by
// could just be a struct field name, so avoid confusion by
// not adding it to the bindings. We'll look up the name
// later during the lowering phase if necessary.
// later during the determine types phase if necessary.
return Expression::make_composite_literal_key(name, location);
}
named_object = this->gogo_->add_unknown_name(name, location);
@ -4496,12 +4499,12 @@ Parse::return_stat()
Expression_list* vals = NULL;
if (this->expression_may_start_here())
vals = this->expression_list(NULL, false, true);
this->gogo_->add_statement(Statement::make_return_statement(vals, location));
Named_object* function = this->gogo_->current_function();
this->gogo_->add_statement(Statement::make_return_statement(function, vals,
location));
if (vals == NULL
&& this->gogo_->current_function()->func_value()->results_are_named())
if (vals == NULL && function->func_value()->results_are_named())
{
Named_object* function = this->gogo_->current_function();
Function::Results* results = function->func_value()->result_variables();
for (Function::Results::const_iterator p = results->begin();
p != results->end();

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

@ -256,8 +256,8 @@ runtime_function_type(Runtime_function_type bft)
// Convert an expression to the type to pass to a runtime function.
static Expression*
convert_to_runtime_function_type(Runtime_function_type bft, Expression* e,
Location loc)
convert_to_runtime_function_type(Gogo* gogo, Runtime_function_type bft,
Expression* e, Location loc)
{
switch (bft)
{
@ -284,6 +284,8 @@ convert_to_runtime_function_type(Runtime_function_type bft, Expression* e,
case RFT_POINTER:
{
Type* t = runtime_function_type(bft);
Type_context context(t, false);
e->determine_type(gogo, &context);
if (!Type::are_identical(t, e->type(), true, NULL))
e = Expression::make_cast(t, e, loc);
return e;
@ -414,7 +416,7 @@ Runtime::runtime_declaration(Function code)
// Make a call to a runtime function.
Call_expression*
Runtime::make_call(Gogo*, Runtime::Function code, Location loc,
Runtime::make_call(Gogo* gogo, Runtime::Function code, Location loc,
int param_count, ...)
{
go_assert(code < Runtime::NUMBER_OF_FUNCTIONS);
@ -436,7 +438,7 @@ Runtime::make_call(Gogo*, Runtime::Function code, Location loc,
{
Expression* e = va_arg(ap, Expression*);
Runtime_function_type rft = pb->parameter_types[i];
args->push_back(convert_to_runtime_function_type(rft, e, loc));
args->push_back(convert_to_runtime_function_type(gogo, rft, e, loc));
}
va_end(ap);

Разница между файлами не показана из-за своего большого размера Загрузить разницу

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

@ -171,16 +171,17 @@ class Statement
static Statement*
make_defer_statement(Call_expression* call, Location);
// Make a return statement.
// Make a return statement. FUNCTION is a backpointer to the
// function that this statement is returning from.
static Return_statement*
make_return_statement(Expression_list*, Location);
make_return_statement(Named_object* function, Expression_list*, Location);
// Make a statement that returns the result of a call expression.
// If the call does not return any results, this just returns the
// call expression as a statement, assuming that the function will
// end immediately afterward.
static Statement*
make_return_from_call(Call_expression*, Location);
make_return_from_call(Named_object* function, Call_expression*, Location);
// Make a break statement.
static Statement*
@ -580,6 +581,11 @@ class Assignment_statement : public Statement
set_omit_write_barrier()
{ this->omit_write_barrier_ = true; }
// Check if we can assign RHS to LHS. If we can, return true. If
// we can't, report an error and return false.
static bool
check_assignment_types(Expression* lhs, Type* rhs_type, Location);
protected:
int
do_traverse(Traverse* traverse);
@ -765,6 +771,9 @@ class Variable_declaration_statement : public Statement
int
do_traverse(Traverse*);
void
do_determine_types(Gogo*);
Statement*
do_lower(Gogo*, Named_object*, Block*, Statement_inserter*);
@ -796,9 +805,11 @@ class Variable_declaration_statement : public Statement
class Return_statement : public Statement
{
public:
Return_statement(Expression_list* vals, Location location)
Return_statement(Named_object* function, Expression_list* vals,
Location location)
: Statement(STATEMENT_RETURN, location),
vals_(vals), is_lowered_(false)
function_(function), vals_(vals), types_are_determined_(false),
is_lowered_(false)
{ }
// The list of values being returned. This may be NULL.
@ -811,6 +822,12 @@ class Return_statement : public Statement
do_traverse(Traverse* traverse)
{ return this->traverse_expression_list(traverse, this->vals_); }
void
do_determine_types(Gogo*);
void
do_check_types(Gogo*);
Statement*
do_lower(Gogo*, Named_object*, Block*, Statement_inserter*);
@ -832,8 +849,12 @@ class Return_statement : public Statement
do_dump_statement(Ast_dump_context*) const;
private:
// A backpointer to the function we are returning from.
Named_object* function_;
// Return values. This may be NULL.
Expression_list* vals_;
// True if types have been determined.
bool types_are_determined_;
// True if this statement has been lowered.
bool is_lowered_;
};
@ -1185,14 +1206,14 @@ class Select_clauses
private:
void
lower_send(Block*, Expression*, Expression*);
lower_send(Gogo*, Block*, Expression*, Expression*);
void
lower_recv(Gogo*, Named_object*, Block*, Expression*, Expression*,
Temporary_statement*);
void
set_case(Block*, Expression*, Expression*, Expression*);
set_case(Gogo*, Block*, Expression*, Expression*, Expression*);
// The channel.
Expression* channel_;
@ -1655,6 +1676,12 @@ class For_statement : public Statement
int
do_traverse(Traverse*);
void
do_determine_types(Gogo*);
void
do_check_types(Gogo*);
Statement*
do_lower(Gogo*, Named_object*, Block*, Statement_inserter*);
@ -1715,6 +1742,12 @@ class For_range_statement : public Statement
int
do_traverse(Traverse*);
void
do_determine_types(Gogo*);
void
do_check_types(Gogo*);
Statement*
do_lower(Gogo*, Named_object*, Block*, Statement_inserter*);
@ -1817,7 +1850,7 @@ class Case_clauses
// Lower for a nonconstant switch.
void
lower(Block*, Temporary_statement*, Unnamed_label*) const;
lower(Gogo*, Block*, Temporary_statement*, Unnamed_label*) const;
// Determine types of expressions. The Type parameter is the type
// of the switch value.
@ -1892,7 +1925,8 @@ class Case_clauses
// Lower for a nonconstant switch.
void
lower(Block*, Temporary_statement*, Unnamed_label*, Unnamed_label*) const;
lower(Gogo*, Block*, Temporary_statement*, Unnamed_label*,
Unnamed_label*) const;
// Determine types.
void
@ -1970,6 +2004,12 @@ class Switch_statement : public Statement
int
do_traverse(Traverse*);
void
do_determine_types(Gogo*);
void
do_check_types(Gogo*);
Statement*
do_lower(Gogo*, Named_object*, Block*, Statement_inserter*);
@ -2028,9 +2068,17 @@ class Type_case_clauses
void
check_duplicates() const;
// Determine types of expressions.
void
determine_types(Gogo*);
// Check types.
bool
check_types(Type*);
// Lower to if and goto statements.
void
lower(Gogo*, Type*, Block*, Temporary_statement* descriptor_temp,
lower(Gogo*, Block*, Temporary_statement* descriptor_temp,
Unnamed_label* break_label) const;
// Return true if these clauses may fall through to the statements
@ -2077,9 +2125,17 @@ class Type_case_clauses
int
traverse(Traverse*);
// Determine types.
void
determine_types(Gogo*);
// Check types.
bool
check_types(Type*);
// Lower to if and goto statements.
void
lower(Gogo*, Type*, Block*, Temporary_statement* descriptor_temp,
lower(Gogo*, Block*, Temporary_statement* descriptor_temp,
Unnamed_label* break_label, Unnamed_label** stmts_label) const;
// Return true if this clause may fall through to execute the
@ -2140,6 +2196,12 @@ class Type_switch_statement : public Statement
int
do_traverse(Traverse*);
void
do_determine_types(Gogo*);
void
do_check_types(Gogo*);
Statement*
do_lower(Gogo*, Named_object*, Block*, Statement_inserter*);

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

@ -1377,6 +1377,7 @@ Type::make_type_descriptor_var(Gogo* gogo)
// Build the contents of the type descriptor.
Expression* initializer = this->do_type_descriptor(gogo, NULL);
initializer->determine_type_no_context(gogo);
Btype* initializer_btype = initializer->type()->get_backend(gogo);
@ -1492,7 +1493,9 @@ Type::type_descriptor_defined_elsewhere(Named_type* nt,
Expression*
Type::type_descriptor(Gogo* gogo, Type* type)
{
return type->do_type_descriptor(gogo, NULL);
Expression* ret = type->do_type_descriptor(gogo, NULL);
ret->determine_type_no_context(gogo);
return ret;
}
// Return a composite literal for a type descriptor with a name.
@ -1501,7 +1504,9 @@ Expression*
Type::named_type_descriptor(Gogo* gogo, Type* type, Named_type* name)
{
go_assert(name != NULL && type->named_type() != name);
return type->do_type_descriptor(gogo, name);
Expression* ret = type->do_type_descriptor(gogo, name);
ret->determine_type_no_context(gogo);
return ret;
}
// Make a builtin struct type from a list of fields. The fields are
@ -1989,16 +1994,17 @@ Type::write_hash_function(Gogo* gogo, int64_t size, const Backend_name* bname,
gogo->start_block(bloc);
if (size != -1)
this->write_identity_hash(gogo, size);
this->write_identity_hash(gogo, hash_fn, size);
else if (this->struct_type() != NULL)
this->struct_type()->write_hash_function(gogo, hash_fntype);
this->struct_type()->write_hash_function(gogo, hash_fn, hash_fntype);
else if (this->array_type() != NULL)
this->array_type()->write_hash_function(gogo, hash_fntype);
this->array_type()->write_hash_function(gogo, hash_fn, hash_fntype);
else
go_unreachable();
Block* b = gogo->finish_block(bloc);
gogo->add_block(b, bloc);
b->determine_types(gogo);
gogo->lower_block(hash_fn, b);
gogo->order_block(b);
gogo->remove_shortcuts_in_block(b);
@ -2016,7 +2022,7 @@ Type::write_hash_function(Gogo* gogo, int64_t size, const Backend_name* bname,
// is called), and the constant size.
void
Type::write_identity_hash(Gogo* gogo, int64_t size)
Type::write_identity_hash(Gogo* gogo, Named_object* function, int64_t size)
{
Location bloc = Linemap::predeclared_location();
@ -2057,7 +2063,8 @@ Type::write_identity_hash(Gogo* gogo, int64_t size)
Expression_list* vals = new Expression_list();
vals->push_back(call);
Statement* s = Statement::make_return_statement(vals, bloc);
Statement* s = Statement::make_return_statement(function, vals, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
}
@ -2329,18 +2336,19 @@ Type::write_equal_function(Gogo* gogo, Named_type* name, int64_t size,
gogo->start_block(bloc);
if (size != -1)
this->write_identity_equal(gogo, size);
this->write_identity_equal(gogo, equal_fn, size);
else if (name != NULL && name->real_type()->named_type() != NULL)
this->write_named_equal(gogo, name);
this->write_named_equal(gogo, equal_fn, name);
else if (this->struct_type() != NULL)
this->struct_type()->write_equal_function(gogo, name);
this->struct_type()->write_equal_function(gogo, equal_fn, name);
else if (this->array_type() != NULL)
this->array_type()->write_equal_function(gogo, name);
this->array_type()->write_equal_function(gogo, equal_fn, name);
else
go_unreachable();
Block* b = gogo->finish_block(bloc);
gogo->add_block(b, bloc);
b->determine_types(gogo);
gogo->lower_block(equal_fn, b);
gogo->order_block(b);
gogo->remove_shortcuts_in_block(b);
@ -2358,7 +2366,7 @@ Type::write_equal_function(Gogo* gogo, Named_type* name, int64_t size,
// constructed before this is called), and the constant size.
void
Type::write_identity_equal(Gogo* gogo, int64_t size)
Type::write_identity_equal(Gogo* gogo, Named_object* function, int64_t size)
{
Location bloc = Linemap::predeclared_location();
@ -2399,7 +2407,8 @@ Type::write_identity_equal(Gogo* gogo, int64_t size)
Expression_list* vals = new Expression_list();
vals->push_back(call);
Statement* s = Statement::make_return_statement(vals, bloc);
Statement* s = Statement::make_return_statement(function, vals, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
}
@ -2410,7 +2419,7 @@ Type::write_identity_equal(Gogo* gogo, int64_t size)
// functions defined only in that package.
void
Type::write_named_equal(Gogo* gogo, Named_type* name)
Type::write_named_equal(Gogo* gogo, Named_object* function, Named_type* name)
{
Location bloc = Linemap::predeclared_location();
@ -2429,11 +2438,13 @@ Type::write_named_equal(Gogo* gogo, Named_type* name)
Expression* ref = Expression::make_var_reference(key1_arg, bloc);
ref = Expression::make_cast(pt, ref, bloc);
Temporary_statement* p1 = Statement::make_temporary(pt, ref, bloc);
p1->determine_types(gogo);
gogo->add_statement(p1);
ref = Expression::make_var_reference(key2_arg, bloc);
ref = Expression::make_cast(pt, ref, bloc);
Temporary_statement* p2 = Statement::make_temporary(pt, ref, bloc);
p2->determine_types(gogo);
gogo->add_statement(p2);
// Compare the values for equality.
@ -2448,7 +2459,8 @@ Type::write_named_equal(Gogo* gogo, Named_type* name)
// Return the equality comparison.
Expression_list* vals = new Expression_list();
vals->push_back(cond);
Statement* s = Statement::make_return_statement(vals, bloc);
Statement* s = Statement::make_return_statement(function, vals, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
}
@ -6658,7 +6670,8 @@ Struct_type::do_type_descriptor(Gogo* gogo, Named_type* name)
// function.
void
Struct_type::write_hash_function(Gogo* gogo, Function_type* hash_fntype)
Struct_type::write_hash_function(Gogo* gogo, Named_object* function,
Function_type* hash_fntype)
{
Location bloc = Linemap::predeclared_location();
@ -6678,6 +6691,7 @@ Struct_type::write_hash_function(Gogo* gogo, Function_type* hash_fntype)
Expression* ref = Expression::make_var_reference(seed_arg, bloc);
Temporary_statement* retval = Statement::make_temporary(uintptr_type, ref,
bloc);
retval->determine_types(gogo);
gogo->add_statement(retval);
// Make a temporary to hold the key as a uintptr.
@ -6685,6 +6699,7 @@ Struct_type::write_hash_function(Gogo* gogo, Function_type* hash_fntype)
ref = Expression::make_cast(uintptr_type, ref, bloc);
Temporary_statement* key = Statement::make_temporary(uintptr_type, ref,
bloc);
key->determine_types(gogo);
gogo->add_statement(key);
// Loop over the struct fields.
@ -6720,6 +6735,7 @@ Struct_type::write_hash_function(Gogo* gogo, Function_type* hash_fntype)
Expression::make_temporary_reference(retval, bloc);
tref->set_is_lvalue();
Statement* s = Statement::make_assignment(tref, call, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
}
@ -6727,7 +6743,8 @@ Struct_type::write_hash_function(Gogo* gogo, Function_type* hash_fntype)
Expression_list* vals = new Expression_list();
ref = Expression::make_temporary_reference(retval, bloc);
vals->push_back(ref);
Statement* s = Statement::make_return_statement(vals, bloc);
Statement* s = Statement::make_return_statement(function, vals, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
}
@ -6735,7 +6752,8 @@ Struct_type::write_hash_function(Gogo* gogo, Function_type* hash_fntype)
// identity function.
void
Struct_type::write_equal_function(Gogo* gogo, Named_type* name)
Struct_type::write_equal_function(Gogo* gogo, Named_object* function,
Named_type* name)
{
Location bloc = Linemap::predeclared_location();
@ -6752,11 +6770,13 @@ Struct_type::write_equal_function(Gogo* gogo, Named_type* name)
Expression* ref = Expression::make_var_reference(key1_arg, bloc);
ref = Expression::make_unsafe_cast(pt, ref, bloc);
Temporary_statement* p1 = Statement::make_temporary(pt, ref, bloc);
p1->determine_types(gogo);
gogo->add_statement(p1);
ref = Expression::make_var_reference(key2_arg, bloc);
ref = Expression::make_unsafe_cast(pt, ref, bloc);
Temporary_statement* p2 = Statement::make_temporary(pt, ref, bloc);
p2->determine_types(gogo);
gogo->add_statement(p2);
const Struct_field_list* fields = this->fields_;
@ -6785,18 +6805,21 @@ Struct_type::write_equal_function(Gogo* gogo, Named_type* name)
gogo->start_block(bloc);
Expression_list* vals = new Expression_list();
vals->push_back(Expression::make_boolean(false, bloc));
Statement* s = Statement::make_return_statement(vals, bloc);
Statement* s = Statement::make_return_statement(function, vals, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
Block* then_block = gogo->finish_block(bloc);
s = Statement::make_if_statement(cond, then_block, NULL, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
}
// All the fields are equal, so return true.
Expression_list* vals = new Expression_list();
vals->push_back(Expression::make_boolean(true, bloc));
Statement* s = Statement::make_return_statement(vals, bloc);
Statement* s = Statement::make_return_statement(function, vals, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
}
@ -7342,8 +7365,9 @@ Array_type::verify_length(Gogo* gogo)
if (this->length_ == NULL)
return true;
Type_context context(Type::lookup_integer_type("int"), false);
this->length_->determine_type(gogo, &context);
Type* int_type = Type::lookup_integer_type("int");
Type_context int_context(int_type, false);
this->length_->determine_type(gogo, &int_context);
if (this->length_->is_error_expression()
|| this->length_->type()->is_error())
@ -7379,7 +7403,6 @@ Array_type::verify_length(Gogo* gogo)
return false;
}
Type* int_type = Type::lookup_integer_type("int");
unsigned int tbits = int_type->integer_type()->bits();
unsigned long val;
switch (nc.to_unsigned_long(&val))
@ -7514,7 +7537,8 @@ Array_type::do_hash_for_method(Gogo* gogo, int flags) const
// function.
void
Array_type::write_hash_function(Gogo* gogo, Function_type* hash_fntype)
Array_type::write_hash_function(Gogo* gogo, Named_object* function,
Function_type* hash_fntype)
{
Location bloc = Linemap::predeclared_location();
@ -7534,6 +7558,7 @@ Array_type::write_hash_function(Gogo* gogo, Function_type* hash_fntype)
Expression* ref = Expression::make_var_reference(seed_arg, bloc);
Temporary_statement* retval = Statement::make_temporary(uintptr_type, ref,
bloc);
retval->determine_types(gogo);
gogo->add_statement(retval);
// Make a temporary to hold the key as a uintptr.
@ -7541,12 +7566,14 @@ Array_type::write_hash_function(Gogo* gogo, Function_type* hash_fntype)
ref = Expression::make_cast(uintptr_type, ref, bloc);
Temporary_statement* key = Statement::make_temporary(uintptr_type, ref,
bloc);
key->determine_types(gogo);
gogo->add_statement(key);
// Loop over the array elements.
// for i = range a
Type* int_type = Type::lookup_integer_type("int");
Temporary_statement* index = Statement::make_temporary(int_type, NULL, bloc);
index->determine_types(gogo);
gogo->add_statement(index);
Expression* iref = Expression::make_temporary_reference(index, bloc);
@ -7585,6 +7612,7 @@ Array_type::write_hash_function(Gogo* gogo, Function_type* hash_fntype)
Expression::make_temporary_reference(retval, bloc);
tref->set_is_lvalue();
Statement* s = Statement::make_assignment(tref, call, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
// Increase the element pointer.
@ -7595,13 +7623,15 @@ Array_type::write_hash_function(Gogo* gogo, Function_type* hash_fntype)
Block* statements = gogo->finish_block(bloc);
for_range->add_statements(statements);
for_range->determine_types(gogo);
gogo->add_statement(for_range);
// Return retval to the caller of the hash function.
Expression_list* vals = new Expression_list();
ref = Expression::make_temporary_reference(retval, bloc);
vals->push_back(ref);
s = Statement::make_return_statement(vals, bloc);
s = Statement::make_return_statement(function, vals, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
}
@ -7609,7 +7639,8 @@ Array_type::write_hash_function(Gogo* gogo, Function_type* hash_fntype)
// identity function.
void
Array_type::write_equal_function(Gogo* gogo, Named_type* name)
Array_type::write_equal_function(Gogo* gogo, Named_object* function,
Named_type* name)
{
Location bloc = Linemap::predeclared_location();
@ -7626,17 +7657,20 @@ Array_type::write_equal_function(Gogo* gogo, Named_type* name)
Expression* ref = Expression::make_var_reference(key1_arg, bloc);
ref = Expression::make_unsafe_cast(pt, ref, bloc);
Temporary_statement* p1 = Statement::make_temporary(pt, ref, bloc);
p1->determine_types(gogo);
gogo->add_statement(p1);
ref = Expression::make_var_reference(key2_arg, bloc);
ref = Expression::make_unsafe_cast(pt, ref, bloc);
Temporary_statement* p2 = Statement::make_temporary(pt, ref, bloc);
p2->determine_types(gogo);
gogo->add_statement(p2);
// Loop over the array elements.
// for i = range a
Type* int_type = Type::lookup_integer_type("int");
Temporary_statement* index = Statement::make_temporary(int_type, NULL, bloc);
index->determine_types(gogo);
gogo->add_statement(index);
Expression* iref = Expression::make_temporary_reference(index, bloc);
@ -7665,22 +7699,26 @@ Array_type::write_equal_function(Gogo* gogo, Named_type* name)
gogo->start_block(bloc);
Expression_list* vals = new Expression_list();
vals->push_back(Expression::make_boolean(false, bloc));
Statement* s = Statement::make_return_statement(vals, bloc);
Statement* s = Statement::make_return_statement(function, vals, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
Block* then_block = gogo->finish_block(bloc);
s = Statement::make_if_statement(cond, then_block, NULL, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
Block* statements = gogo->finish_block(bloc);
for_range->add_statements(statements);
for_range->determine_types(gogo);
gogo->add_statement(for_range);
// All the elements are equal, so return true.
vals = new Expression_list();
vals->push_back(Expression::make_boolean(true, bloc));
s = Statement::make_return_statement(vals, bloc);
s = Statement::make_return_statement(function, vals, bloc);
s->determine_types(gogo);
gogo->add_statement(s);
}
@ -11805,9 +11843,9 @@ Type::build_stub_methods(Gogo* gogo, const Type* type, const Methods* methods,
{
stub = gogo->start_function(stub_name, stub_type, false,
fntype->location());
Type::build_one_stub_method(gogo, m, buf, receiver_type, stub_params,
fntype->is_varargs(), stub_results,
location);
Type::build_one_stub_method(gogo, m, stub, buf, receiver_type,
stub_params, fntype->is_varargs(),
stub_results, location);
gogo->finish_function(fntype->location());
if (type->named_type() == NULL && stub->is_function())
@ -11826,6 +11864,7 @@ Type::build_stub_methods(Gogo* gogo, const Type* type, const Methods* methods,
void
Type::build_one_stub_method(Gogo* gogo, Method* method,
Named_object* stub,
const char* receiver_name,
const Type* receiver_type,
const Typed_identifier_list* params,
@ -11865,7 +11904,7 @@ Type::build_one_stub_method(Gogo* gogo, Method* method,
go_assert(func != NULL);
Call_expression* call = Expression::make_call(func, arguments, is_varargs,
location);
Type::add_return_from_results(gogo, call, results, location);
Type::add_return_from_results(gogo, stub, call, results, location);
}
// Build direct interface stub methods for TYPE as needed. METHODS
@ -11974,7 +12013,7 @@ Type::build_direct_iface_stub_methods(Gogo* gogo, const Type* type,
{
stub = gogo->start_function(stub_name, stub_type, false,
fntype->location());
Type::build_one_iface_stub_method(gogo, m, buf, stub_params,
Type::build_one_iface_stub_method(gogo, m, stub, buf, stub_params,
fntype->is_varargs(), stub_results,
loc);
gogo->finish_function(fntype->location());
@ -12001,6 +12040,7 @@ Type::build_direct_iface_stub_methods(Gogo* gogo, const Type* type,
void
Type::build_one_iface_stub_method(Gogo* gogo, Method* method,
Named_object* stub,
const char* receiver_name,
const Typed_identifier_list* params,
bool is_varargs,
@ -12037,7 +12077,7 @@ Type::build_one_iface_stub_method(Gogo* gogo, Method* method,
go_assert(func != NULL);
Call_expression* call = Expression::make_call(func, arguments, is_varargs,
loc);
Type::add_return_from_results(gogo, call, results, loc);
Type::add_return_from_results(gogo, stub, call, results, loc);
}
// Build and add a return statement from a call expression and a list
@ -12045,9 +12085,10 @@ Type::build_one_iface_stub_method(Gogo* gogo, Method* method,
// results.
void
Type::add_return_from_results(Gogo* gogo, Call_expression* call,
const Typed_identifier_list* results,
Location loc)
Type::add_return_from_results(Gogo* gogo, Named_object* stub,
Call_expression* call,
const Typed_identifier_list* results,
Location loc)
{
Statement* s;
if (results == NULL || results->empty())
@ -12063,9 +12104,10 @@ Type::add_return_from_results(Gogo* gogo, Call_expression* call,
for (size_t i = 0; i < rc; ++i)
vals->push_back(Expression::make_call_result(call, i));
}
s = Statement::make_return_statement(vals, loc);
s = Statement::make_return_statement(stub, vals, loc);
}
s->determine_types(gogo);
gogo->add_statement(s);
}

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

@ -1300,13 +1300,13 @@ class Type
Function_type* equal_fntype);
void
write_identity_hash(Gogo*, int64_t size);
write_identity_hash(Gogo*, Named_object* function, int64_t size);
void
write_identity_equal(Gogo*, int64_t size);
write_identity_equal(Gogo*, Named_object* function, int64_t size);
void
write_named_equal(Gogo*, Named_type*);
write_named_equal(Gogo*, Named_object* function, Named_type*);
// Build a composite literal for the uncommon type information.
Expression*
@ -1354,8 +1354,8 @@ class Type
Location);
static void
build_one_stub_method(Gogo*, Method*, const char* receiver_name,
const Type* receiver_type,
build_one_stub_method(Gogo*, Method*, Named_object* stub,
const char* receiver_name, const Type* receiver_type,
const Typed_identifier_list*, bool is_varargs,
const Typed_identifier_list*, Location);
@ -1364,12 +1364,12 @@ class Type
build_direct_iface_stub_methods(Gogo*, const Type*, Methods*, Location);
static void
build_one_iface_stub_method(Gogo*, Method*, const char*,
build_one_iface_stub_method(Gogo*, Method*, Named_object* stub, const char*,
const Typed_identifier_list*, bool,
const Typed_identifier_list*, Location);
static void
add_return_from_results(Gogo*, Call_expression*,
add_return_from_results(Gogo*, Named_object* stub, Call_expression*,
const Typed_identifier_list*, Location);
static Expression*
@ -2654,11 +2654,11 @@ class Struct_type : public Type
// Write the hash function for this type.
void
write_hash_function(Gogo*, Function_type*);
write_hash_function(Gogo*, Named_object* function, Function_type*);
// Write the equality function for this type.
void
write_equal_function(Gogo*, Named_type*);
write_equal_function(Gogo*, Named_object* function, Named_type*);
// Whether we can write this type to a C header file, to implement
// -fgo-c-header.
@ -2844,11 +2844,11 @@ class Array_type : public Type
// Write the hash function for this type.
void
write_hash_function(Gogo*, Function_type*);
write_hash_function(Gogo*, Named_object* function, Function_type*);
// Write the equality function for this type.
void
write_equal_function(Gogo*, Named_type*);
write_equal_function(Gogo*, Named_object* function, Named_type*);
protected:
int

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

@ -872,6 +872,7 @@ Gogo::assign_with_write_barrier(Function* function, Block* enclosing,
addr->unary_expression()->set_does_not_escape();
}
Temporary_statement* lhs_temp = Statement::make_temporary(NULL, addr, loc);
lhs_temp->determine_types(this);
inserter->insert(lhs_temp);
lhs = Expression::make_temporary_reference(lhs_temp, loc);
@ -883,6 +884,7 @@ Gogo::assign_with_write_barrier(Function* function, Block* enclosing,
{
// May need a temporary for interface conversion.
Temporary_statement* temp = Statement::make_temporary(NULL, rhs, loc);
temp->determine_types(this);
inserter->insert(temp);
rhs = Expression::make_temporary_reference(temp, loc);
}
@ -891,6 +893,7 @@ Gogo::assign_with_write_barrier(Function* function, Block* enclosing,
if (!rhs->is_multi_eval_safe())
{
rhs_temp = Statement::make_temporary(NULL, rhs, loc);
rhs_temp->determine_types(this);
inserter->insert(rhs_temp);
rhs = Expression::make_temporary_reference(rhs_temp, loc);
}
@ -940,6 +943,7 @@ Gogo::assign_with_write_barrier(Function* function, Block* enclosing,
Expression::STRING_INFO_LENGTH,
loc);
Statement* as = Statement::make_assignment(llen, rlen, loc);
as->determine_types(this);
inserter->insert(as);
// Assign the data field with a write barrier.
@ -978,6 +982,7 @@ Gogo::assign_with_write_barrier(Function* function, Block* enclosing,
Expression::INTERFACE_INFO_METHODS,
loc);
Statement* as = Statement::make_assignment(ltab, rtab, loc);
as->determine_types(this);
inserter->insert(as);
// Assign the data field with a write barrier.
@ -1010,6 +1015,7 @@ Gogo::assign_with_write_barrier(Function* function, Block* enclosing,
Expression::SLICE_INFO_LENGTH,
loc);
Statement* as = Statement::make_assignment(llen, rlen, loc);
as->determine_types(this);
inserter->insert(as);
// Assign the capacity fields directly.
@ -1022,6 +1028,7 @@ Gogo::assign_with_write_barrier(Function* function, Block* enclosing,
Expression::SLICE_INFO_CAPACITY,
loc);
as = Statement::make_assignment(lcap, rcap, loc);
as->determine_types(this);
inserter->insert(as);
// Assign the data field with a write barrier.
@ -1097,5 +1104,8 @@ Gogo::check_write_barrier(Block* enclosing, Statement* without,
Block* else_block = new Block(enclosing, loc);
else_block->add_statement(with);
return Statement::make_if_statement(cond, then_block, else_block, loc);
Statement* s = Statement::make_if_statement(cond, then_block, else_block,
loc);
s->determine_types(this);
return s;
}