2018-06-22 20:58:47 -04:00
|
|
|
import mem:*
|
|
|
|
|
import str:*
|
|
|
|
|
import vec:*
|
|
|
|
|
import util:*
|
2018-06-22 23:13:08 -04:00
|
|
|
import tree:*
|
2018-06-22 20:58:47 -04:00
|
|
|
import ast:*
|
2018-10-08 00:28:42 -04:00
|
|
|
import binding:*
|
2018-06-22 20:58:47 -04:00
|
|
|
|
2018-12-29 12:19:54 -05:00
|
|
|
adt ref_type {
|
|
|
|
|
_unknown,
|
|
|
|
|
_ref,
|
|
|
|
|
_notref
|
|
|
|
|
}
|
|
|
|
|
fun to_string(r: ref_type): str {
|
|
|
|
|
match (r) {
|
|
|
|
|
ref_type::_unknown() return str("_ref/unknown")
|
|
|
|
|
ref_type::_ref() return str("_ref/ref")
|
|
|
|
|
ref_type::_notref() return str("_ref/notref")
|
|
|
|
|
}
|
|
|
|
|
}
|
|
|
|
|
|
2018-10-08 00:28:42 -04:00
|
|
|
adt type {
|
2018-06-22 20:58:47 -04:00
|
|
|
_unknown,
|
|
|
|
|
_void,
|
2018-10-08 00:28:42 -04:00
|
|
|
_template_placeholder,
|
|
|
|
|
_ptr: *binding<type>,
|
2018-06-22 23:13:08 -04:00
|
|
|
_obj: *tree<ast>,
|
2018-12-27 15:14:28 -05:00
|
|
|
// triple<pair<vec<pair<is_ref, param_type>>, pair<is_ref, return_type>>, is_variadic, is raw>
|
2018-12-29 12:19:54 -05:00
|
|
|
_fun: triple<pair<vec<pair<ref_type, *binding<type>>>, pair<ref_type, *binding<type>>>, bool, bool>,
|
2018-06-22 20:58:47 -04:00
|
|
|
_bool,
|
|
|
|
|
_char,
|
|
|
|
|
_uchar,
|
|
|
|
|
_short,
|
|
|
|
|
_ushort,
|
|
|
|
|
_int,
|
|
|
|
|
_uint,
|
|
|
|
|
_long,
|
|
|
|
|
_ulong,
|
|
|
|
|
_float,
|
|
|
|
|
_double
|
|
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
|
2019-01-06 01:06:15 -05:00
|
|
|
fun has_unknown(t: *binding<type>, epoch: binding_epoch): bool {
|
|
|
|
|
match (*t->get_bound_to(epoch)) {
|
2018-12-29 16:35:47 -05:00
|
|
|
type::_unknown() return true
|
2019-01-06 01:06:15 -05:00
|
|
|
type::_ptr(p) return has_unknown(p, epoch)
|
|
|
|
|
type::_obj(o) return o->data._binding.second.any_true(fun(inner_t: *binding<type>): bool return has_unknown(inner_t, epoch);)
|
|
|
|
|
type::_fun(f) return has_unknown(f.first.second.second, epoch) || f.first.first.any_true(fun(p: pair<ref_type, *binding<type>>): bool return has_unknown(p.second, epoch);)
|
2018-12-29 16:35:47 -05:00
|
|
|
}
|
|
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
|
2019-01-06 01:06:15 -05:00
|
|
|
fun unify(t1: *binding<type>, t2: *binding<type>, epoch: binding_epoch) {
|
|
|
|
|
println("attempting to unify " + to_string(t1->get_bound_to(epoch)) + " and " + to_string(t2->get_bound_to(epoch)))
|
|
|
|
|
if (is_unknown(t1->get_bound_to(epoch))) {
|
|
|
|
|
t1->set(t2->get_bound_to(epoch), epoch)
|
|
|
|
|
} else if (is_unknown(t2->get_bound_to(epoch))) {
|
|
|
|
|
t2->set(t1->get_bound_to(epoch), epoch)
|
2018-10-08 00:28:42 -04:00
|
|
|
} else {
|
2019-01-06 01:06:15 -05:00
|
|
|
if (shallow_equality(t1->get_bound_to(epoch), t2->get_bound_to(epoch), epoch)) {
|
|
|
|
|
if (is_fun(t1->get_bound_to(epoch))) {
|
|
|
|
|
unify(t1->get_bound_to(epoch)->_fun.first.second.second, t2->get_bound_to(epoch)->_fun.first.second.second, epoch)
|
2018-12-29 12:19:54 -05:00
|
|
|
// unify ref_types
|
2019-01-06 01:06:15 -05:00
|
|
|
if (t1->get_bound_to(epoch)->_fun.first.second.first == ref_type::_unknown())
|
|
|
|
|
t1->get_bound_to(epoch)->_fun.first.second.first = t2->get_bound_to(epoch)->_fun.first.second.first
|
|
|
|
|
if (t2->get_bound_to(epoch)->_fun.first.second.first == ref_type::_unknown())
|
|
|
|
|
t2->get_bound_to(epoch)->_fun.first.second.first = t1->get_bound_to(epoch)->_fun.first.second.first
|
2018-12-29 14:50:58 -05:00
|
|
|
// might be veradic...
|
2019-01-06 01:06:15 -05:00
|
|
|
for (var i = 0; i < t1->get_bound_to(epoch)->_fun.first.first.size && i < t2->get_bound_to(epoch)->_fun.first.first.size; i++;) {
|
|
|
|
|
unify(t1->get_bound_to(epoch)->_fun.first.first[i].second, t2->get_bound_to(epoch)->_fun.first.first[i].second, epoch)
|
|
|
|
|
if (t1->get_bound_to(epoch)->_fun.first.first[i].first == ref_type::_unknown())
|
|
|
|
|
t1->get_bound_to(epoch)->_fun.first.first[i].first = t2->get_bound_to(epoch)->_fun.first.first[i].first
|
|
|
|
|
if (t2->get_bound_to(epoch)->_fun.first.first[i].first == ref_type::_unknown())
|
|
|
|
|
t2->get_bound_to(epoch)->_fun.first.first[i].first = t1->get_bound_to(epoch)->_fun.first.first[i].first
|
2018-12-29 12:19:54 -05:00
|
|
|
}
|
2019-01-06 01:06:15 -05:00
|
|
|
} else if (is_ptr(t1->get_bound_to(epoch))) {
|
|
|
|
|
unify(t1->get_bound_to(epoch)->_ptr, t2->get_bound_to(epoch)->_ptr, epoch)
|
|
|
|
|
} else if (is_obj(t1->get_bound_to(epoch))) {
|
|
|
|
|
for (var i = 0; i < t1->get_bound_to(epoch)->_obj->data._binding.second.size; i++;) {
|
|
|
|
|
unify(t1->get_bound_to(epoch)->_obj->data._binding.second[i], t2->get_bound_to(epoch)->_obj->data._binding.second[i], epoch)
|
2018-12-05 23:43:24 -05:00
|
|
|
}
|
2018-09-24 00:08:07 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
} else {
|
2019-01-06 01:06:15 -05:00
|
|
|
error("Doesn't typecheck! Attempted to unify " + to_string(t1->get_bound_to(epoch)) + " and " + to_string(t2->get_bound_to(epoch)))
|
2018-09-24 00:08:07 -04:00
|
|
|
}
|
2018-10-01 01:19:51 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
}
|
2019-01-06 01:06:15 -05:00
|
|
|
fun shallow_equality(a: *type, b: *type, epoch: binding_epoch):bool {
|
2018-12-05 23:43:24 -05:00
|
|
|
if (is_ptr(a) != is_ptr(b))
|
|
|
|
|
return false
|
|
|
|
|
if (is_ptr(a) && is_ptr(b))
|
|
|
|
|
return true
|
|
|
|
|
match(*a) {
|
|
|
|
|
type::_fun(x) {
|
|
|
|
|
return is_fun(b) && a->_fun.third == b->_fun.third
|
|
|
|
|
}
|
|
|
|
|
type::_obj(x) {
|
2019-01-06 01:06:15 -05:00
|
|
|
return is_obj(b) && (get_ast_binding(x, epoch) == get_ast_binding(b->_obj, epoch) || ((!ast_bound(x) || !ast_bound(b->_obj))
|
2018-12-05 23:43:24 -05:00
|
|
|
&& x->data._binding.second.size == b->_obj->data._binding.second.size
|
|
|
|
|
&& x->data._binding.first == b->_obj->data._binding.first))
|
|
|
|
|
}
|
|
|
|
|
}
|
|
|
|
|
return *a == *b
|
|
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
|
2019-07-13 18:01:04 -04:00
|
|
|
fun inst_temp_type(t: *binding<type>, replacements: ref map<*binding<type>, *binding<type>>, read_epoch: binding_epoch, write_epoch: binding_epoch): *binding<type> {
|
|
|
|
|
match (*t->get_bound_to(read_epoch)) {
|
2018-10-09 23:00:57 -04:00
|
|
|
type::_unknown() error("Unknown in temp type")
|
2018-12-05 23:43:24 -05:00
|
|
|
type::_obj(o) {
|
2019-07-13 18:01:04 -04:00
|
|
|
var binding_types = o->data._binding.second.map(fun(b: *binding<type>): *binding<type> return inst_temp_type(b, replacements, read_epoch, write_epoch);)
|
2018-12-05 23:43:24 -05:00
|
|
|
for (var i = 0; i < o->data._binding.second.size; i++;) {
|
|
|
|
|
if (o->data._binding.second[i] != binding_types[i])
|
2019-07-13 18:01:04 -04:00
|
|
|
return binding_p(type::_obj(_binding(o->data._binding.first, binding_types, o->data._binding.third)), write_epoch)
|
2018-12-05 23:43:24 -05:00
|
|
|
}
|
|
|
|
|
}
|
2018-10-09 23:00:57 -04:00
|
|
|
type::_ptr(p) {
|
2019-07-13 18:01:04 -04:00
|
|
|
var cp = inst_temp_type(p, replacements, read_epoch, write_epoch)
|
2018-10-09 23:00:57 -04:00
|
|
|
if (cp == p)
|
|
|
|
|
return t
|
|
|
|
|
else
|
2019-07-13 18:01:04 -04:00
|
|
|
return binding_p(type::_ptr(cp), write_epoch)
|
2018-10-09 23:00:57 -04:00
|
|
|
}
|
|
|
|
|
type::_fun(b) {
|
|
|
|
|
// triple<pair<param_types, return_type>, is_variadic, is raw>
|
2019-07-13 18:01:04 -04:00
|
|
|
var rt = make_pair(b.first.second.first, inst_temp_type(b.first.second.second, replacements, read_epoch, write_epoch))
|
|
|
|
|
var pts = b.first.first.map(fun(pt: pair<ref_type, *binding<type>>): pair<ref_type, *binding<type>> return make_pair(pt.first, inst_temp_type(pt.second, replacements, read_epoch, write_epoch));)
|
2018-12-27 15:14:28 -05:00
|
|
|
if (rt.second != b.first.second.second)
|
2019-07-13 18:01:04 -04:00
|
|
|
return binding_p(type::_fun(make_triple(make_pair(pts, rt), b.second, b.third)), write_epoch)
|
2018-10-09 23:00:57 -04:00
|
|
|
for (var i = 0; i < pts.size; i++;)
|
2018-12-27 15:14:28 -05:00
|
|
|
if (pts[i].second != b.first.first[i].second)
|
2019-07-13 18:01:04 -04:00
|
|
|
return binding_p(type::_fun(make_triple(make_pair(pts, rt), b.second, b.third)), write_epoch)
|
2018-10-09 23:00:57 -04:00
|
|
|
return t
|
|
|
|
|
}
|
|
|
|
|
type::_template_placeholder() return replacements[t]
|
|
|
|
|
}
|
|
|
|
|
return t
|
|
|
|
|
}
|
|
|
|
|
|
2019-01-06 01:06:15 -05:00
|
|
|
fun equality(a: *type, b: *type, count_unknown_as_equal: bool, epoch: binding_epoch): bool {
|
2018-12-18 02:51:44 -05:00
|
|
|
/*println("equality of " + to_string(a) + " and " + to_string(b))*/
|
2018-10-08 00:28:42 -04:00
|
|
|
if (count_unknown_as_equal && (is_unknown(a) || is_unknown(b)))
|
|
|
|
|
return true
|
|
|
|
|
match(*a) {
|
2018-12-05 23:43:24 -05:00
|
|
|
type::_obj(x) {
|
|
|
|
|
if (!is_obj(b))
|
|
|
|
|
return false
|
2019-01-06 01:06:15 -05:00
|
|
|
if (get_ast_binding(x, epoch) == get_ast_binding(b->_obj, epoch))
|
2018-12-05 23:43:24 -05:00
|
|
|
return true
|
|
|
|
|
if (!count_unknown_as_equal || (ast_bound(x) && ast_bound(b->_obj)) || x->data._binding.first != b->_obj->data._binding.first || x->data._binding.second.size != b->_obj->data._binding.second.size)
|
|
|
|
|
return false
|
|
|
|
|
for (var i = 0; i < x->data._binding.second.size; i++;) {
|
2019-01-06 01:06:15 -05:00
|
|
|
if (!equality(x->data._binding.second[i]->get_bound_to(epoch), b->_obj->data._binding.second[i]->get_bound_to(epoch), count_unknown_as_equal, epoch))
|
2018-12-05 23:43:24 -05:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
return true
|
|
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
type::_ptr(p) {
|
|
|
|
|
if (!is_ptr(b))
|
|
|
|
|
return false
|
2019-01-06 01:06:15 -05:00
|
|
|
return equality(p->get_bound_to(epoch), b->_ptr->get_bound_to(epoch), count_unknown_as_equal, epoch)
|
2018-10-08 00:28:42 -04:00
|
|
|
}
|
|
|
|
|
type::_fun(i) {
|
|
|
|
|
if ( !(is_fun(b) && a->_fun.second == b->_fun.second && a->_fun.third == b->_fun.third) )
|
|
|
|
|
return false
|
2019-01-06 01:06:15 -05:00
|
|
|
if ( !equality(a->_fun.first.second.second->get_bound_to(epoch), b->_fun.first.second.second->get_bound_to(epoch), count_unknown_as_equal, epoch) )
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
if ( !(a->_fun.first.first.size == b->_fun.first.first.size) )
|
|
|
|
|
return false
|
|
|
|
|
for (var i = 0; i < a->_fun.first.first.size; i++;)
|
2019-01-06 01:06:15 -05:00
|
|
|
if ( !equality(a->_fun.first.first[i].second->get_bound_to(epoch), b->_fun.first.first[i].second->get_bound_to(epoch), count_unknown_as_equal, epoch) )
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
|
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return *a == *b
|
|
|
|
|
}
|
2019-07-13 18:01:04 -04:00
|
|
|
fun deref_to_string<T>(in: *T): str
|
|
|
|
|
if (in == mem::null<T>())
|
|
|
|
|
return str("null")
|
|
|
|
|
else
|
|
|
|
|
return to_string(in)
|
2018-10-08 00:28:42 -04:00
|
|
|
fun to_string(it: *type): str {
|
|
|
|
|
match (*it) {
|
|
|
|
|
type::_unknown() return str("_unknown")
|
|
|
|
|
type::_void() return str("_void")
|
2019-07-13 18:01:04 -04:00
|
|
|
type::_ptr(p) return "*(pre_ref:" + deref_to_string(p->get_bound_to(binding_epoch::pre_ref())) + "/post_ref" + deref_to_string(p->get_bound_to(binding_epoch::post_ref())) + ")"
|
2018-10-08 00:28:42 -04:00
|
|
|
type::_obj(b) {
|
|
|
|
|
return "_obj(" + to_string(b->data) + ")"
|
|
|
|
|
}
|
|
|
|
|
type::_fun(b) {
|
|
|
|
|
// triple<pair<param_types, return_type>, is_variadic, is raw>
|
|
|
|
|
var to_ret = str()
|
|
|
|
|
if (b.second)
|
|
|
|
|
to_ret += "_run("
|
|
|
|
|
else
|
|
|
|
|
to_ret += "_fun("
|
2019-07-13 18:01:04 -04:00
|
|
|
to_ret += str(", ").join(b.first.first.map(fun(pt: pair<ref_type, *binding<type>>): str return to_string(pt.first) + "(pre_ref:" + deref_to_string(pt.second->get_bound_to(binding_epoch::pre_ref())) + "/post_ref" + deref_to_string(pt.second->get_bound_to(binding_epoch::post_ref())) + ")";))
|
2018-10-08 00:28:42 -04:00
|
|
|
if (b.third)
|
|
|
|
|
to_ret += " ..."
|
2019-07-13 18:01:04 -04:00
|
|
|
return to_ret + "): " + to_string(b.first.second.first) + ": (pre_ref:" + deref_to_string(b.first.second.second->get_bound_to(binding_epoch::pre_ref())) + "/post_ref:" + deref_to_string(b.first.second.second->get_bound_to(binding_epoch::post_ref())) + ")"
|
2018-10-08 00:28:42 -04:00
|
|
|
}
|
|
|
|
|
type::_template_placeholder() return str("_template_placeholder")
|
|
|
|
|
type::_bool() return str("_bool")
|
|
|
|
|
type::_char() return str("_char")
|
|
|
|
|
type::_uchar() return str("_uchar")
|
|
|
|
|
type::_short() return str("_short")
|
|
|
|
|
type::_ushort() return str("_ushort")
|
|
|
|
|
type::_int() return str("_int")
|
|
|
|
|
type::_uint() return str("_uint")
|
|
|
|
|
type::_long() return str("_long")
|
|
|
|
|
type::_ulong() return str("_ulong")
|
|
|
|
|
type::_float() return str("_float")
|
|
|
|
|
type::_double() return str("_double")
|
|
|
|
|
}
|
|
|
|
|
return str("impossible type")
|
|
|
|
|
}
|
|
|
|
|
fun is_unknown(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_unknown() return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_void(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_void() return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_ptr(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_ptr(p) return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_obj(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_obj() return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_fun(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_fun(b) return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_template_placeholder(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_template_placeholder() return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_bool(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_bool() return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_char(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_char() return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_uchar(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_uchar() return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_short(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_short() return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_ushort(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_ushort() return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_int(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_int() return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_uint(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_uint() return true
|
|
|
|
|
}
|
|
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_long(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_long() return true
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_ulong(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_ulong() return true
|
|
|
|
|
}
|
|
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_float(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_float() return true
|
|
|
|
|
}
|
|
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_double(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_double() return true
|
|
|
|
|
}
|
|
|
|
|
return false
|
|
|
|
|
}
|
|
|
|
|
fun is_signed(x: *type): bool {
|
|
|
|
|
match (*x) {
|
|
|
|
|
type::_char() return true
|
|
|
|
|
type::_int() return true
|
|
|
|
|
type::_long() return true
|
|
|
|
|
type::_short() return true
|
|
|
|
|
type::_float() return true
|
|
|
|
|
type::_double() return true
|
2018-06-22 20:58:47 -04:00
|
|
|
|
2018-10-08 00:28:42 -04:00
|
|
|
type::_uchar() return false
|
|
|
|
|
type::_ushort() return false
|
|
|
|
|
type::_uint() return false
|
|
|
|
|
type::_ulong() return false
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
2018-10-08 00:28:42 -04:00
|
|
|
return false
|
2018-06-22 20:58:47 -04:00
|
|
|
}
|
|
|
|
|
|