2016-05-13 15:14:19 -04:00
import mem:*
2016-05-29 23:54:54 -07:00
import math:*
2016-05-12 02:03:20 -04:00
import map:*
2016-05-13 03:10:36 -04:00
import stack:*
2018-05-22 19:43:54 -04:00
import str:*
2016-05-12 02:03:20 -04:00
import util:*
import tree:*
import symbol:*
import ast_nodes:*
2016-05-13 15:14:19 -04:00
import type:*
2016-07-03 15:32:45 -07:00
import os:*
2016-05-15 22:05:12 -07:00
// for is_dot_style_method_call
2016-07-03 15:32:45 -07:00
import pass_common:*
2016-05-12 02:03:20 -04:00
adt value {
2016-05-15 11:09:12 -07:00
boolean: bool,
character: char,
ucharacter: uchar,
short_int: short,
ushort_int: ushort,
2016-05-12 02:03:20 -04:00
integer: int,
2016-05-15 11:09:12 -07:00
uinteger: uint,
long_int: long,
ulong_int: ulong,
2016-05-13 03:10:36 -04:00
floating: float,
2016-05-13 15:14:19 -04:00
double_precision: double,
void_nothing,
2016-05-13 18:34:06 -04:00
pointer: pair<*void,*type>,
2016-05-15 18:36:13 -07:00
object_like: pair<*void,*type>,
2016-06-01 23:28:32 -07:00
variable: pair<*void,*type>,
2016-06-30 17:06:34 -04:00
function: pair<*ast_node,*map<*ast_node,value>>
2016-05-13 03:10:36 -04:00
}
adt control_flow {
nor,
con,
bre,
ret
2016-05-12 02:03:20 -04:00
}
2016-05-15 11:09:12 -07:00
2016-05-15 18:36:13 -07:00
// note that there is not object_like, variable, or pointer raw_to_value
2016-05-15 11:09:12 -07:00
fun raw_to_value(data:bool): value
return value::boolean(data)
fun raw_to_value(data:char): value
return value::character(data)
fun raw_to_value(data:uchar): value
return value::ucharacter(data)
fun raw_to_value(data:short): value
return value::short_int(data)
fun raw_to_value(data:ushort): value
return value::ushort_int(data)
fun raw_to_value(data:int): value
return value::integer(data)
fun raw_to_value(data:uint): value
return value::uinteger(data)
fun raw_to_value(data:long): value
return value::long_int(data)
fun raw_to_value(data:ulong): value
return value::ulong_int(data)
fun raw_to_value(data:float): value
return value::floating(data)
fun raw_to_value(data:double): value
return value::double_precision(data)
2016-05-15 22:05:12 -07:00
fun wrap_value(val: *ast_node): value {
var value_str = val->value.string_value
2016-07-09 00:45:40 -07:00
var value_type = val->value.value_type
2016-05-15 22:05:12 -07:00
if (value_str[0] == '"') { // " // Comment hack for emacs now
2018-05-22 19:43:54 -04:00
var to_ret = str()
2016-05-29 23:54:54 -07:00
// triple quoted strings
2016-05-31 21:29:05 -07:00
if (value_str[1] == '"' && value_str.length() > 2 && value_str[2] == '"')
2016-05-29 23:54:54 -07:00
value_str = value_str.slice(3,-4)
else
value_str = value_str.slice(1,-2)
2016-05-15 22:05:12 -07:00
for (var i = 0; i < value_str.length()-1; i++;) {
if (value_str[i] == '\\' && value_str[i+1] == 'n') {
to_ret += '\n'
i++
} else if (value_str[i] == '\\' && value_str[i+1] == 't') {
to_ret += '\t'
i++
2016-07-03 01:55:32 -07:00
} else if (value_str[i] == '\\' && value_str[i+1] == '\\') {
to_ret += '\\'
i++
2016-05-15 22:05:12 -07:00
} else if (i == value_str.length()-2) {
to_ret += value_str[i]
to_ret += value_str[i+1]
} else {
to_ret += value_str[i]
}
}
2016-05-18 23:11:00 -07:00
// if there was only one character
if (value_str.length() == 1)
to_ret = value_str
2016-05-15 22:05:12 -07:00
return value::pointer(make_pair((to_ret.toCharArray()) cast *void, get_ast_type(val)))
} else if (value_str[0] == '\'') //'// lol, comment hack for vim syntax highlighting (my fault, of course)
return value::character(value_str[1])
else if (value_str == "true")
return value::boolean(true)
else if (value_str == "false")
return value::boolean(false)
else {
var contains_dot = false
for (var i = 0; i < value_str.length(); i++;) {
if (value_str[i] == '.') {
contains_dot = true
break
}
}
if (contains_dot)
if (value_str[value_str.length()-1] == 'f')
return value::floating((string_to_double(value_str.slice(0,-2))) cast float)
else
2016-07-01 09:37:14 -07:00
if (value_str[value_str.length()-1] == 'd')
return value::double_precision(string_to_double(value_str.slice(0,-2)))
else
return value::double_precision(string_to_double(value_str))
2016-07-09 00:45:40 -07:00
else {
match(value_type->base) {
base_type::character() return value::character(string_to_num<char>(value_str))
base_type::ucharacter() return value::ucharacter(string_to_num<uchar>(value_str))
base_type::short_int() return value::short_int(string_to_num<short>(value_str))
base_type::ushort_int() return value::ushort_int(string_to_num<ushort>(value_str))
base_type::integer() return value::integer(string_to_num<int>(value_str))
base_type::uinteger() return value::uinteger(string_to_num<uint>(value_str))
base_type::long_int() return value::long_int(string_to_num<long>(value_str))
base_type::ulong_int() return value::ulong_int(string_to_num<ulong>(value_str))
}
}
2016-05-15 22:05:12 -07:00
}
error("Could not wrap value")
return value::void_nothing()
}
2016-07-03 22:50:42 -07:00
fun unwrap_value(val: value): *ast_node {
2018-05-22 19:43:54 -04:00
// str, char, bool, floating
var value_string = str()
2016-07-03 22:50:42 -07:00
match (get_real_value(val)) {
value::boolean(data) value_string = to_string(data)
value::character(data) value_string = to_string(data)
value::ucharacter(data) value_string = to_string(data)
value::short_int(data) value_string = to_string(data)
value::ushort_int(data) value_string = to_string(data)
value::integer(data) value_string = to_string(data)
value::uinteger(data) value_string = to_string(data)
value::long_int(data) value_string = to_string(data)
value::ulong_int(data) value_string = to_string(data)
value::floating(data) value_string = to_string(data)
value::double_precision(data) value_string = to_string(data)
2018-05-22 20:14:15 -04:00
value::void_nothing() error("trying to unwrap a void into an _value")
2016-07-03 22:50:42 -07:00
value::pointer(point) {
if (point.second->base == base_type::character() && point.second->indirection == 1)
2018-05-22 19:43:54 -04:00
value_string = str("\"") + str((point.first) cast *char) + "\""
2016-07-03 22:50:42 -07:00
else
2018-05-22 20:14:15 -04:00
error("trying to unwrap a pointer into an _value")
2016-07-03 22:50:42 -07:00
}
2018-05-22 20:14:15 -04:00
value::object_like(ob) error("trying to unwrap an object_like into an _value")
value::function(fn) error("trying to unwrap a function into an _value")
2016-07-03 22:50:42 -07:00
}
2018-05-22 20:14:15 -04:00
return _value(value_string, get_type_from_primitive_value(get_real_value(val)))
2016-07-03 22:50:42 -07:00
}
2016-05-15 22:05:12 -07:00
2016-05-15 11:09:12 -07:00
fun is_boolean(it: value): bool { match(it) { value::boolean(var) return true; } return false; }
fun is_character(it: value): bool { match(it) { value::character(var) return true; } return false; }
fun is_ucharacter(it: value): bool { match(it) { value::ucharacter(var) return true; } return false; }
fun is_short_int(it: value): bool { match(it) { value::short_int(var) return true; } return false; }
fun is_ushort_int(it: value): bool { match(it) { value::ushort_int(var) return true; } return false; }
2016-05-13 15:14:19 -04:00
fun is_integer(it: value): bool { match(it) { value::integer(var) return true; } return false; }
2016-05-15 11:09:12 -07:00
fun is_uinteger(it: value): bool { match(it) { value::uinteger(var) return true; } return false; }
fun is_long_int(it: value): bool { match(it) { value::long_int(var) return true; } return false; }
fun is_ulong_int(it: value): bool { match(it) { value::ulong_int(var) return true; } return false; }
2016-05-13 15:14:19 -04:00
fun is_floating(it: value): bool { match(it) { value::floating(var) return true; } return false; }
fun is_double_precision(it: value): bool { match(it) { value::double_precision(var) return true; } return false; }
fun is_void_nothing(it: value): bool { match(it) { value::void_nothing() return true; } return false; }
2016-05-13 18:34:06 -04:00
fun is_pointer(it: value): bool { match(it) { value::pointer(var) return true; } return false; }
2016-05-15 18:36:13 -07:00
fun is_object_like(it: value): bool { match(it) { value::object_like(var) return true; } return false; }
2016-05-13 15:14:19 -04:00
fun is_variable(it: value): bool { match(it) { value::variable(var) return true; } return false; }
2016-06-01 23:28:32 -07:00
fun is_function(it: value): bool { match(it) { value::function(var) return true; } return false; }
2016-05-13 15:14:19 -04:00
2016-05-13 16:31:55 -04:00
fun print_value(v: ref value) {
match (get_real_value(v)) {
2016-05-15 11:09:12 -07:00
value::boolean(data) println(data)
value::character(data) println(data)
value::ucharacter(data) println(data)
value::short_int(data) println(data)
value::ushort_int(data) println(data)
2016-05-13 16:31:55 -04:00
value::integer(data) println(data)
2016-05-15 11:09:12 -07:00
value::uinteger(data) println(data)
value::long_int(data) println(data)
value::ulong_int(data) println(data)
2016-05-13 16:31:55 -04:00
value::floating(data) println(data)
value::double_precision(data) println(data)
value::void_nothing() println("void")
2016-05-13 18:34:06 -04:00
value::pointer(var) println("pointer")
2016-05-15 18:36:13 -07:00
value::object_like(var) println("object_like")
2016-05-13 18:34:06 -04:00
value::variable(var) println("variable")
2016-06-01 23:28:32 -07:00
value::function(var) println("function")
2016-05-13 16:31:55 -04:00
}
}
fun truthy(v: ref value):bool {
match (get_real_value(v)) {
2016-05-15 11:09:12 -07:00
value::boolean(data) return data
value::character(data) return data != 0
value::ucharacter(data) return data != 0
value::short_int(data) return data != 0
value::ushort_int(data) return data != 0
2016-05-13 16:31:55 -04:00
value::integer(data) return data != 0
2016-05-15 11:09:12 -07:00
value::uinteger(data) return data != 0
value::long_int(data) return data != 0
value::ulong_int(data) return data != 0
2016-05-13 16:31:55 -04:00
value::floating(data) return data != 0
value::double_precision(data) return data != 0
2016-05-13 18:34:06 -04:00
value::pointer(data) return data.first != 0
2016-05-13 16:31:55 -04:00
}
2016-05-15 18:36:13 -07:00
error("untruthy value")
2016-05-13 16:31:55 -04:00
}
2018-05-22 19:43:54 -04:00
fun do_basic_op(func_name: str, a: value, b: value): value {
2016-05-15 11:09:12 -07:00
match (get_real_value(a)) {
value::boolean(av) return do_basic_op_second_half(func_name, av, b, null<type>())
value::character(av) return do_basic_op_second_half(func_name, av, b, null<type>())
value::ucharacter(av) return do_basic_op_second_half(func_name, av, b, null<type>())
value::short_int(av) return do_basic_op_second_half(func_name, av, b, null<type>())
value::ushort_int(av) return do_basic_op_second_half(func_name, av, b, null<type>())
value::integer(av) return do_basic_op_second_half(func_name, av, b, null<type>())
value::uinteger(av) return do_basic_op_second_half(func_name, av, b, null<type>())
value::long_int(av) return do_basic_op_second_half(func_name, av, b, null<type>())
value::ulong_int(av) return do_basic_op_second_half(func_name, av, b, null<type>())
2016-05-15 22:05:12 -07:00
value::floating(av) return do_basic_floating_op_second_half(func_name, av, b, null<type>())
value::double_precision(av) return do_basic_floating_op_second_half(func_name, av, b, null<type>())
2016-05-15 11:09:12 -07:00
value::pointer(av) {
2016-07-03 01:55:32 -07:00
var real_b = get_real_value(b)
if (func_name == "==") {
if (!is_pointer(real_b)) {
print("equality between pointer and not pointer: ")
print_value(real_b)
error(":/")
}
return value::boolean(av.first == real_b.pointer.first)
2016-07-09 15:08:57 -07:00
} else if (func_name == "!=") {
if (!is_pointer(real_b)) {
print("inequality between pointer and not pointer: ")
print_value(real_b)
error(":/")
}
return value::boolean(av.first != real_b.pointer.first)
2016-07-03 01:55:32 -07:00
}
2016-05-15 11:09:12 -07:00
var inc_in_bytes = cast_value(b, type_ptr(base_type::ulong_int())).ulong_int * type_size(av.second->clone_with_decreased_indirection())
var ptr = null<void>()
if (func_name == "+") {
ptr = ((av.first) cast *char + inc_in_bytes) cast *void
} else if (func_name == "-") {
ptr = ((av.first) cast *char - inc_in_bytes) cast *void
} else {
2018-05-22 19:43:54 -04:00
println(str("pointer arithmatic is not +, -, ==, or !=: ") + func_name + ", b is: ")
2016-07-03 01:55:32 -07:00
print_value(b)
2018-05-22 19:43:54 -04:00
error(str("pointer arithmatic is not +, -, ==, or !=: ") + func_name)
2016-05-15 11:09:12 -07:00
}
return value::pointer(make_pair(ptr, av.second))
}
2018-05-22 19:43:54 -04:00
value::void_nothing() error(str("basic op called with void_nothing as first param: ") + func_name)
value::object_like() error(str("basic op called with object_like as first param: ") + func_name)
2016-05-15 11:09:12 -07:00
}
2018-05-22 19:43:54 -04:00
error(str("basic op called with something wrong as first param: ") + func_name)
2016-05-15 11:09:12 -07:00
}
2018-05-22 19:43:54 -04:00
fun do_basic_op_second_half<T>(func_name: str, av: T, b: value, ptr_type: *type): value {
2016-05-15 11:09:12 -07:00
// because of the trickery in do_basic_op, if either param is a pointer, it's b
match (get_real_value(b)) {
value::boolean(bv) return do_op(func_name, av, bv, ptr_type)
value::character(bv) return do_op(func_name, av, bv, ptr_type)
value::ucharacter(bv) return do_op(func_name, av, bv, ptr_type)
value::short_int(bv) return do_op(func_name, av, bv, ptr_type)
value::ushort_int(bv) return do_op(func_name, av, bv, ptr_type)
value::integer(bv) return do_op(func_name, av, bv, ptr_type)
value::uinteger(bv) return do_op(func_name, av, bv, ptr_type)
value::long_int(bv) return do_op(func_name, av, bv, ptr_type)
value::ulong_int(bv) return do_op(func_name, av, bv, ptr_type)
2016-05-15 22:05:12 -07:00
value::floating(bv) return do_floating_op(func_name, av, bv, ptr_type)
value::double_precision(bv) return do_floating_op(func_name, av, bv, ptr_type)
2018-05-22 19:43:54 -04:00
value::void_nothing() error(str("basic op called with void_nothing as second param: ") + func_name)
value::object_like() error(str("basic op called with object_like as second param: ") + func_name)
2016-05-15 11:09:12 -07:00
// if one is a pointer, we want it to be a
value::pointer(bv) return do_basic_op(func_name, b, raw_to_value(av))
}
2016-05-15 22:05:12 -07:00
print_value(b)
2018-05-22 19:43:54 -04:00
error(str("basic op called with something wrong as second param: ") + func_name)
2016-05-15 11:09:12 -07:00
}
2018-05-22 19:43:54 -04:00
fun do_op<T,U>(op: str, a: T, b: U, ptr_type: *type): value {
2016-05-15 11:09:12 -07:00
if (op == "+") return raw_to_value(a + b)
if (op == "-") return raw_to_value(a - b)
if (op == "*") return raw_to_value(a * b)
if (op == "/") return raw_to_value(a / b)
if (op == "<") return raw_to_value(a < b)
if (op == ">") return raw_to_value(a > b)
if (op == "<=") return raw_to_value(a <= b)
if (op == ">=") return raw_to_value(a >= b)
if (op == "==") return raw_to_value(a == b)
if (op == "!=") return raw_to_value(a != b)
if (op == "%") return raw_to_value(a % b)
if (op == "^") return raw_to_value(a ^ b)
if (op == "|") return raw_to_value(a | b)
if (op == "&") return raw_to_value(a & b)
2016-05-15 22:05:12 -07:00
error(("Invalid op: ") + op)
}
2018-05-22 19:43:54 -04:00
fun do_basic_floating_op_second_half<T>(func_name: str, av: T, b: value, ptr_type: *type): value {
2016-05-15 22:05:12 -07:00
// because of the trickery in do_basic_op, if either param is a pointer, it's b
match (get_real_value(b)) {
value::boolean(bv) return do_floating_op(func_name, av, bv, ptr_type)
value::character(bv) return do_floating_op(func_name, av, bv, ptr_type)
value::ucharacter(bv) return do_floating_op(func_name, av, bv, ptr_type)
value::short_int(bv) return do_floating_op(func_name, av, bv, ptr_type)
value::ushort_int(bv) return do_floating_op(func_name, av, bv, ptr_type)
value::integer(bv) return do_floating_op(func_name, av, bv, ptr_type)
value::uinteger(bv) return do_floating_op(func_name, av, bv, ptr_type)
value::long_int(bv) return do_floating_op(func_name, av, bv, ptr_type)
value::ulong_int(bv) return do_floating_op(func_name, av, bv, ptr_type)
value::floating(bv) return do_floating_op(func_name, av, bv, ptr_type)
value::double_precision(bv) return do_floating_op(func_name, av, bv, ptr_type)
2018-05-22 19:43:54 -04:00
value::void_nothing() error(str("basic op called with void_nothing as second param: ") + func_name)
value::object_like() error(str("basic op called with object_like as second param: ") + func_name)
2016-05-15 22:05:12 -07:00
// if one is a pointer, we want it to be a
value::pointer(bv) return do_basic_op(func_name, b, raw_to_value(av))
}
print_value(b)
2018-05-22 19:43:54 -04:00
error(str("basic op called with something wrong as second param: ") + func_name)
2016-05-15 22:05:12 -07:00
}
2018-05-22 19:43:54 -04:00
fun do_floating_op<T,U>(op: str, a: T, b: U, ptr_type: *type): value {
2016-05-15 22:05:12 -07:00
if (op == "+") return raw_to_value(a + b)
if (op == "-") return raw_to_value(a - b)
if (op == "*") return raw_to_value(a * b)
if (op == "/") return raw_to_value(a / b)
if (op == "<") return raw_to_value(a < b)
if (op == ">") return raw_to_value(a > b)
if (op == "<=") return raw_to_value(a <= b)
if (op == ">=") return raw_to_value(a >= b)
if (op == "==") return raw_to_value(a == b)
if (op == "!=") return raw_to_value(a != b)
2016-05-15 11:09:12 -07:00
error(("Invalid op: ") + op)
}
2016-06-28 01:35:54 -07:00
// the ref special case is interesting because it also means we have to take in the value by ref
fun store_into_variable(to: ref value, from: value) {
2016-05-13 15:14:19 -04:00
assert(is_variable(to), "trying to store into not variable")
var variable = to.variable
2016-06-28 01:35:54 -07:00
// NOTE
2016-06-27 01:21:24 -07:00
// we have a special case here - we allow assigning to a ref from a pointer, as this is used in adt_lower
2016-06-28 01:35:54 -07:00
if (variable.second->is_ref && is_pointer(from) && variable.second->clone_with_increased_indirection()->equality(from.pointer.second, false)) {
to.variable.first = from.pointer.first
return;
}
// check for indirection
if (variable.second->indirection) {
2016-05-13 18:34:06 -04:00
assert(is_pointer(from), "mismatching assignemnt types - from is not pointer")
*(variable.first) cast **void = from.pointer.first
return;
}
2016-05-15 18:36:13 -07:00
// TODO - check to make sure that we don't have to cast pre assign (perhaps alwyas send through the cast?)
2016-05-13 15:14:19 -04:00
match (variable.second->base) {
2016-05-15 18:36:13 -07:00
base_type::object() { assert(is_object_like(from), "mismatching assignemnt types - from is not object"); memmove(variable.first, from.object_like.first, type_size(from.object_like.second)); }
2016-06-30 17:06:34 -04:00
base_type::function() { assert(is_function(from), "mismatching assignemnt types - from is not function"); *(variable.first) cast *pair<*ast_node, *map<*ast_node,value>> = from.function; }
2016-05-15 11:09:12 -07:00
base_type::boolean() { assert(is_boolean(from), "mismatching assignemnt types - from is not boolean"); *(variable.first) cast *bool = from.boolean; }
base_type::character() { assert(is_character(from), "mismatching assignemnt types - from is not character"); *(variable.first) cast *char = from.character; }
base_type::ucharacter() { assert(is_ucharacter(from), "mismatching assignemnt types - from is not ucharacter"); *(variable.first) cast *uchar = from.ucharacter; }
base_type::short_int() { assert(is_short_int(from), "mismatching assignemnt types - from is not short_int"); *(variable.first) cast *short = from.short_int; }
base_type::ushort_int() { assert(is_ushort_int(from), "mismatching assignemnt types - from is not ushort_int"); *(variable.first) cast *ushort = from.ushort_int; }
2016-05-13 18:34:06 -04:00
base_type::integer() { assert(is_integer(from), "mismatching assignemnt types - from is not integer"); *(variable.first) cast *int = from.integer; }
2016-05-15 11:09:12 -07:00
base_type::uinteger() { assert(is_uinteger(from), "mismatching assignemnt types - from is not uinteger"); *(variable.first) cast *uint = from.uinteger; }
base_type::long_int() { assert(is_long_int(from), "mismatching assignemnt types - from is not long_int"); *(variable.first) cast *long = from.long_int; }
base_type::ulong_int() { assert(is_ulong_int(from), "mismatching assignemnt types - from is not ulong_int"); *(variable.first) cast *ulong = from.ulong_int; }
2016-05-13 18:34:06 -04:00
base_type::floating() { assert(is_floating(from), "mismatching assignemnt types - from is not floating"); *(variable.first) cast *float = from.floating; }
base_type::double_precision() { assert(is_double_precision(from), "mismatching assignemnt types - from is not double"); *(variable.first) cast *double = from.double_precision; }
2016-05-13 15:14:19 -04:00
}
}
fun get_real_value(v: value): value {
if (!is_variable(v))
return v
var variable = v.variable
2016-06-28 01:35:54 -07:00
var var_ptr = variable.first
var var_type = variable.second
// step through indirection first
if (var_type->indirection)
return value::pointer(make_pair(*(var_ptr) cast **void, var_type))
match (var_type->base) {
base_type::object() return value::object_like(make_pair(var_ptr, var_type))
base_type::boolean() return value::boolean(*(var_ptr) cast *bool)
base_type::character() return value::character(*(var_ptr) cast *char)
base_type::ucharacter() return value::ucharacter(*(var_ptr) cast *uchar)
base_type::short_int() return value::short_int(*(var_ptr) cast *short)
base_type::ushort_int() return value::ushort_int(*(var_ptr) cast *ushort)
base_type::integer() return value::integer(*(var_ptr) cast *int)
base_type::uinteger() return value::uinteger(*(var_ptr) cast *uint)
base_type::long_int() return value::long_int(*(var_ptr) cast *long)
base_type::ulong_int() return value::ulong_int(*(var_ptr) cast *ulong)
base_type::floating() return value::floating(*(var_ptr) cast *float)
base_type::double_precision() return value::double_precision(*(var_ptr) cast *double)
2016-06-30 17:06:34 -04:00
base_type::function() return value::function(*(var_ptr) cast *pair<*ast_node,*map<*ast_node,value>>)
2016-05-13 15:14:19 -04:00
}
2018-05-22 19:43:54 -04:00
error(str("Cannot get real value from variable: ") + variable.second->to_string())
2016-05-13 15:14:19 -04:00
}
2016-05-22 02:55:45 -07:00
fun wrap_into_variable(v: value): value {
if (is_variable(v))
return v
if (is_object_like(v))
return value::variable(make_pair(v.object_like.first, v.object_like.second))
var variable_type = get_type_from_primitive_value(v)
var to_ret = value::variable(make_pair(malloc(type_size(variable_type)), variable_type))
2016-07-03 15:32:45 -07:00
store_into_variable(to_ret, v)
2016-05-22 02:55:45 -07:00
return to_ret
}
fun get_type_from_primitive_value(v: value): *type {
match (v) {
value::boolean(data) return type_ptr(base_type::boolean())
value::character(data) return type_ptr(base_type::character())
value::ucharacter(data) return type_ptr(base_type::ucharacter())
value::short_int(data) return type_ptr(base_type::short_int())
value::ushort_int(data) return type_ptr(base_type::ushort_int())
value::integer(data) return type_ptr(base_type::integer())
value::uinteger(data) return type_ptr(base_type::uinteger())
value::long_int(data) return type_ptr(base_type::long_int())
value::ulong_int(data) return type_ptr(base_type::ulong_int())
value::floating(data) return type_ptr(base_type::floating())
value::double_precision(data) return type_ptr(base_type::double_precision())
value::pointer(data) return data.second
2016-05-29 23:54:54 -07:00
value::void_nothing() return type_ptr(base_type::void_return())
2016-06-01 23:28:32 -07:00
value::function(data) return data.first->function.type
2016-05-22 02:55:45 -07:00
}
println("Bad get_type_from_primitive_value!")
print_value(v)
error("Called get_type_from_primitive_value with non-primitive value (maybe in a variable?)")
}
2016-05-15 11:09:12 -07:00
fun cast_value(v: value, to_type: *type): value {
if (to_type->indirection) {
match (get_real_value(v)) {
value::boolean(data) return value::pointer(make_pair((data) cast *void, to_type))
value::character(data) return value::pointer(make_pair((data) cast *void, to_type))
value::ucharacter(data) return value::pointer(make_pair((data) cast *void, to_type))
value::short_int(data) return value::pointer(make_pair((data) cast *void, to_type))
value::ushort_int(data) return value::pointer(make_pair((data) cast *void, to_type))
value::integer(data) return value::pointer(make_pair((data) cast *void, to_type))
value::uinteger(data) return value::pointer(make_pair((data) cast *void, to_type))
value::long_int(data) return value::pointer(make_pair((data) cast *void, to_type))
value::ulong_int(data) return value::pointer(make_pair((data) cast *void, to_type))
2016-05-15 18:36:13 -07:00
// floats and anything object_like are illegal to cast from
2016-05-15 11:09:12 -07:00
/*value::floating(data) return value::pointer(make_pair((data) cast *void, to_type))*/
/*value::double_precision(data) return value::pointer(make_pair((data) cast *void, to_type))*/
value::pointer(data) return value::pointer(make_pair(data.first, to_type))
}
error("Bad cast to pointer")
}
match (to_type->base) {
2016-05-15 18:36:13 -07:00
// object_like can't be casted
2016-05-15 11:09:12 -07:00
base_type::boolean() return cast_value_second_half<bool>(v)
base_type::character() return cast_value_second_half<char>(v)
base_type::ucharacter() return cast_value_second_half<uchar>(v)
base_type::short_int() return cast_value_second_half<short>(v)
base_type::ushort_int() return cast_value_second_half<ushort>(v)
base_type::integer() return cast_value_second_half<int>(v)
base_type::uinteger() return cast_value_second_half<uint>(v)
base_type::long_int() return cast_value_second_half<long>(v)
base_type::ulong_int() return cast_value_second_half<ulong>(v)
// float and double need their own because it can't go from
base_type::floating() match (get_real_value(v)) {
value::boolean(data) return value::floating((data) cast float)
value::character(data) return value::floating((data) cast float)
value::ucharacter(data) return value::floating((data) cast float)
value::short_int(data) return value::floating((data) cast float)
value::ushort_int(data) return value::floating((data) cast float)
value::integer(data) return value::floating((data) cast float)
value::uinteger(data) return value::floating((data) cast float)
value::long_int(data) return value::floating((data) cast float)
value::ulong_int(data) return value::floating((data) cast float)
value::floating(data) return get_real_value(v)
value::double_precision(data) return value::floating((data) cast float)
}
base_type::double_precision() match (get_real_value(v)) {
value::boolean(data) return value::double_precision((data) cast double)
value::character(data) return value::double_precision((data) cast double)
value::ucharacter(data) return value::double_precision((data) cast double)
value::short_int(data) return value::double_precision((data) cast double)
value::ushort_int(data) return value::double_precision((data) cast double)
value::integer(data) return value::double_precision((data) cast double)
value::uinteger(data) return value::double_precision((data) cast double)
value::long_int(data) return value::double_precision((data) cast double)
value::ulong_int(data) return value::double_precision((data) cast double)
value::floating(data) return value::double_precision((data) cast double)
value::double_precision(data) return get_real_value(v)
}
}
2018-05-22 19:43:54 -04:00
error(str("Bad cast to ") + to_type->to_string())
2016-05-15 11:09:12 -07:00
}
fun cast_value_second_half<T>(v: value): value {
match (get_real_value(v)) {
2016-05-15 18:36:13 -07:00
// object_like can't be casted
2016-05-15 11:09:12 -07:00
value::boolean(data) return raw_to_value((data) cast T)
value::character(data) return raw_to_value((data) cast T)
value::ucharacter(data) return raw_to_value((data) cast T)
value::short_int(data) return raw_to_value((data) cast T)
value::ushort_int(data) return raw_to_value((data) cast T)
value::integer(data) return raw_to_value((data) cast T)
value::uinteger(data) return raw_to_value((data) cast T)
value::long_int(data) return raw_to_value((data) cast T)
value::ulong_int(data) return raw_to_value((data) cast T)
value::floating(data) return raw_to_value((data) cast T)
value::double_precision(data) return raw_to_value((data) cast T)
value::pointer(data) return raw_to_value((data.first) cast T)
}
error("Illegal type to cast cast from")
}
2016-07-09 00:45:40 -07:00
fun type_size(t: *type): ulong
return type_size_and_alignment(t).first
fun type_size_and_alignment(t: *type): pair<ulong,ulong> {
2016-05-13 15:14:19 -04:00
if (t->indirection)
2016-07-09 00:45:40 -07:00
return make_pair(#sizeof<*void>, #sizeof<*void>)
2016-05-13 15:14:19 -04:00
match (t->base) {
2016-05-15 18:36:13 -07:00
base_type::object() {
2016-07-09 00:45:40 -07:00
var total_size: ulong = 0
var max_size: ulong = 0
var max_align: ulong = 0
2016-06-28 01:35:54 -07:00
t->type_def->type_def.variables.for_each(fun(i: *ast_node) {
2016-07-09 00:45:40 -07:00
var individual = type_size_and_alignment(i->declaration_statement.identifier->identifier.type)
max_size = max(max_size, individual.first)
max_align = max(max_align, individual.second)
// increase total size by the individual size + padding to get alignment
var padding = 0
if (individual.second != 0)
padding = (individual.second - (total_size % individual.second)) % individual.second
total_size += individual.first + padding
2016-06-28 01:35:54 -07:00
})
2016-07-09 00:45:40 -07:00
if (t->type_def->type_def.is_union)
total_size = max_size
// pad the end so that consecutive objects in memory are aligned
if (max_align != 0)
total_size += (max_align - (total_size % max_align)) % max_align
return make_pair(total_size, max_align)
2016-05-15 18:36:13 -07:00
}
2016-07-09 00:45:40 -07:00
base_type::function() return make_pair(#sizeof<pair<*ast_node,*map<*ast_node,value>>>, #sizeof<*void>)
base_type::boolean() return make_pair(#sizeof<bool>, #sizeof<bool>)
base_type::character() return make_pair(#sizeof<char>, #sizeof<char>)
base_type::ucharacter() return make_pair(#sizeof<uchar>, #sizeof<uchar>)
base_type::short_int() return make_pair(#sizeof<short>, #sizeof<short>)
base_type::ushort_int() return make_pair(#sizeof<ushort>, #sizeof<ushort>)
base_type::integer() return make_pair(#sizeof<int>, #sizeof<int>)
base_type::uinteger() return make_pair(#sizeof<uint>, #sizeof<uint>)
base_type::long_int() return make_pair(#sizeof<long>, #sizeof<long>)
base_type::ulong_int() return make_pair(#sizeof<ulong>, #sizeof<ulong>)
base_type::floating() return make_pair(#sizeof<float>, #sizeof<float>)
base_type::double_precision() return make_pair(#sizeof<double>, #sizeof<double>)
2016-05-13 15:14:19 -04:00
}
2018-05-22 19:43:54 -04:00
error(str("Invalid type for type_size: ") + t->to_string())
2016-05-15 18:36:13 -07:00
}
fun offset_into_struct(struct_type: *type, ident: *ast_node): ulong {
2016-07-09 00:45:40 -07:00
var offset: ulong = 0
2016-07-03 01:55:32 -07:00
if (struct_type->type_def->type_def.is_union)
2016-07-09 00:45:40 -07:00
return offset
for (var i = 0; i < struct_type->type_def->type_def.variables.size; i++;) {
var size_and_align = type_size_and_alignment(struct_type->type_def->type_def.variables[i]->declaration_statement.identifier->identifier.type)
var align = size_and_align.second
if (align != 0)
offset += (align - (offset % align)) % align
2016-05-15 18:36:13 -07:00
if (struct_type->type_def->type_def.variables[i]->declaration_statement.identifier == ident)
break
else
2016-07-09 00:45:40 -07:00
offset += size_and_align.first
}
return offset
2016-05-13 15:14:19 -04:00
}
2016-07-03 15:32:45 -07:00
// to dereference, we basically take the pointer's value (maybe going through a variable to get it)
// and re-wrap it up into a variable value (so it can be assigned to, etc)
2016-07-03 01:55:32 -07:00
fun dereference_pointer_into_variable(dereference_val: value): value
return value::variable(make_pair(get_real_value(dereference_val).pointer.first, dereference_val.pointer.second->clone_with_decreased_indirection()))
2016-05-31 22:02:00 -07:00
fun pop_and_free(var_stack: *stack<map<*ast_node, value>>) {
var_stack->pop().for_each(fun(k: *ast_node, v: value) {
2016-05-13 16:31:55 -04:00
match(v) {
2016-05-18 23:11:00 -07:00
value::variable(backing) {
2016-06-27 01:21:24 -07:00
/*free(backing.first)*/
2016-05-18 23:11:00 -07:00
}
2016-05-13 16:31:55 -04:00
}
})
2016-05-12 02:03:20 -04:00
}
2018-05-22 19:43:54 -04:00
fun call_main(name_ast_map: ref map<str, pair<*tree<symbol>,*ast_node>>) {
var results = vec<*ast_node>()
name_ast_map.for_each(fun(key: str, value: pair<*tree<symbol>,*ast_node>) {
results += scope_lookup(str("main"), value.second)
2016-07-03 15:32:45 -07:00
})
if (results.size != 1)
2018-05-22 19:43:54 -04:00
error(str("wrong number of mains to call: ") + results.size)
2016-07-03 15:32:45 -07:00
var globals = setup_globals(name_ast_map)
2018-05-22 19:43:54 -04:00
var result = call_function(results[0], vec<value>(), &globals)
2016-07-03 15:32:45 -07:00
}
2016-07-06 00:16:39 -07:00
fun evaluate_constant_expression(node: *ast_node): value
2016-07-03 15:32:45 -07:00
return interpret(node, null<stack<map<*ast_node, value>>>(), value::void_nothing(), null<ast_node>(), null<map<*ast_node, value>>()).first
2016-07-06 00:16:39 -07:00
fun evaluate_with_globals(node: *ast_node, globals: *map<*ast_node, value>): value
return interpret(node, null<stack<map<*ast_node, value>>>(), value::void_nothing(), null<ast_node>(), globals).first
2018-05-22 19:43:54 -04:00
fun setup_globals(name_ast_map: ref map<str, pair<*tree<symbol>,*ast_node>>): map<*ast_node, value> {
2016-07-03 15:32:45 -07:00
var globals = map<*ast_node, value>()
2018-05-22 19:43:54 -04:00
name_ast_map.for_each(fun(key: str, value: pair<*tree<symbol>,*ast_node>) {
2016-07-03 15:32:45 -07:00
value.second->translation_unit.children.for_each(fun(child: *ast_node) {
if (is_declaration_statement(child)) {
var declaration = child->declaration_statement
var identifier = declaration.identifier->identifier
2017-01-23 01:09:31 -05:00
if (identifier.is_extern) {
2016-07-03 15:32:45 -07:00
if (identifier.name == "stderr") {
var stderr_type = type_ptr(base_type::void_return(), 1)
var stderr_pointer = malloc(type_size(stderr_type))
*(stderr_pointer) cast **void = stderr;
globals[declaration.identifier] = value::variable(make_pair(stderr_pointer, stderr_type))
} else if (identifier.name == "stdin") {
var stdin_type = type_ptr(base_type::void_return(), 1)
var stdin_pointer = malloc(type_size(stdin_type))
*(stdin_pointer) cast **void = stdin;
globals[declaration.identifier] = value::variable(make_pair(stdin_pointer, stdin_type))
2016-05-31 21:29:05 -07:00
} else {
2018-05-22 19:43:54 -04:00
error(str("unknown extern: ") + identifier.name)
2016-05-31 21:29:05 -07:00
}
2016-07-03 15:32:45 -07:00
} else {
globals[declaration.identifier] = value::variable(make_pair(calloc(type_size(identifier.type)), identifier.type))
if (declaration.expression)
store_into_variable(globals[declaration.identifier], get_real_value(interpret(declaration.expression, null<stack<map<*ast_node,value>>>(), value::void_nothing(), null<ast_node>(), null<map<*ast_node,value>>()).first))
2016-05-31 21:29:05 -07:00
}
2016-07-03 15:32:45 -07:00
}
2016-05-31 21:29:05 -07:00
})
2016-07-03 15:32:45 -07:00
})
return globals
}
fun interpret_function_call(func_call: *ast_node, var_stack: *stack<map<*ast_node, value>>, enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): pair<value, control_flow> {
var func_call_parameters = func_call->function_call.parameters
var func_call_func = func_call->function_call.func
var new_enclosing_object = value::void_nothing()
var dot_style_method_call = is_dot_style_method_call(func_call)
var possible_closure_map = map<*ast_node,value>()
// test for function value
if (!dot_style_method_call && (!is_function(func_call_func) || func_call_func->function.closed_variables.size())) {
var func_value = get_real_value(interpret(func_call_func, var_stack, enclosing_object, enclosing_func, globals).first)
func_call_func = func_value.function.first
possible_closure_map = *func_value.function.second
// if the closure closes over this, put it as the enclosing object inside the closure
possible_closure_map.for_each(fun(key: *ast_node, v: value) {
if (key->identifier.name == "this") {
new_enclosing_object = get_real_value(dereference_pointer_into_variable(v))
2016-05-18 23:11:00 -07:00
}
2016-07-03 15:32:45 -07:00
})
}
// note here also that this is likely not a foolproof method
if (dot_style_method_call) {
new_enclosing_object = get_real_value(interpret(func_call_func->function_call.parameters[0], var_stack, enclosing_object, enclosing_func, globals).first)
// do a dereference
if (is_pointer(new_enclosing_object))
new_enclosing_object = get_real_value(value::variable(make_pair(new_enclosing_object.pointer.first, new_enclosing_object.pointer.second->clone_with_decreased_indirection())))
func_call_func = func_call_func->function_call.parameters[1]
} else if (!is_void_nothing(enclosing_object)) {
if (method_in_object(func_call_func, enclosing_object.object_like.second->type_def)) {
// should maybe do something special for closure here
// copy over old enclosing object
new_enclosing_object = enclosing_object
2016-05-15 22:05:12 -07:00
}
2016-07-03 15:32:45 -07:00
}
var func_name = func_call_func->function.name
// some of these have to be done before parameters are evaluated (&&, ||, ., ->)
if (func_name == "&&" || func_name == "||") {
error("short circuit still in interpreter")
} else if (func_name == "." || func_name == "->") {
var left_side = get_real_value(interpret(func_call_parameters[0], var_stack, enclosing_object, enclosing_func, globals).first)
var ret_ptr = null<void>()
if (func_name == "->")
ret_ptr = ((left_side.pointer.first) cast *char + offset_into_struct(left_side.pointer.second->clone_with_decreased_indirection(), func_call_parameters[1])) cast *void
else
ret_ptr = ((left_side.object_like.first) cast *char + offset_into_struct(left_side.object_like.second, func_call_parameters[1])) cast *void
return make_pair(value::variable(make_pair(ret_ptr, func_call_parameters[1]->identifier.type)), control_flow::nor())
}
// so here we either do an operator, call call_func with value parameters, or call call_func with ast_expressions
// (so we can properly copy_construct if necessary)
2018-05-22 19:43:54 -04:00
var parameters = vec<value>()
var parameter_sources = vec<*ast_node>()
2016-07-03 15:32:45 -07:00
// if we don't have to copy_construct params (is an operator, or has no object params)
if (func_name == "&" || !func_call_parameters.any_true(fun(p: *ast_node): bool return get_ast_type(p)->is_object() && get_ast_type(p)->indirection == 0;)) {
parameters = func_call_parameters.map(fun(p: *ast_node): value return interpret(p, var_stack, enclosing_object, enclosing_func, globals).first;)
if ( parameters.size == 2 && (func_name == "+" || func_name == "-" || func_name == "*" || func_name == "/"
|| func_name == "<" || func_name == ">" || func_name == "<=" || func_name == ">="
|| func_name == "==" || func_name == "!=" || func_name == "%" || func_name == "^"
|| func_name == "|" || func_name == "&"
))
return make_pair(do_basic_op(func_name, parameters[0], parameters[1]), control_flow::nor())
// do negate by subtracting from zero
if (func_name == "-")
2018-05-22 19:43:54 -04:00
return make_pair(do_basic_op_second_half(str("-"), 0, parameters[0], null<type>()), control_flow::nor())
2016-07-03 15:32:45 -07:00
if (func_name == "!")
return make_pair(value::boolean(!truthy(get_real_value(parameters[0]))), control_flow::nor())
if (func_name == "++p" || func_name == "--p") {
var to_ret = get_real_value(parameters[0])
store_into_variable(parameters[0], do_basic_op(func_name.slice(0,1), parameters[0], value::integer(1)))
return make_pair(to_ret, control_flow::nor())
2016-05-15 11:09:12 -07:00
}
2016-07-03 15:32:45 -07:00
if (func_name == "++" || func_name == "--") {
store_into_variable(parameters[0], do_basic_op(func_name.slice(0,1), parameters[0], value::integer(1)))
return make_pair(get_real_value(parameters[0]), control_flow::nor())
2016-05-21 11:20:29 -07:00
}
2016-07-03 15:32:45 -07:00
if (func_name == "&") {
if (is_variable(parameters[0]))
return make_pair(value::pointer(make_pair(parameters[0].variable.first, parameters[0].variable.second->clone_with_increased_indirection())), control_flow::nor())
else if (is_object_like(parameters[0]))
return make_pair(value::pointer(make_pair(parameters[0].object_like.first, parameters[0].object_like.second->clone_with_increased_indirection())), control_flow::nor())
else {
print("can't take address of: ")
print_value(parameters[0])
error("Trying to take address of not a variable or object_like")
2016-05-21 11:20:29 -07:00
}
2016-05-13 16:31:55 -04:00
}
2016-07-03 15:32:45 -07:00
if (func_name == "*" || func_name == "[]") {
var dereference_val = parameters[0]
if (func_name == "[]")
2018-05-22 19:43:54 -04:00
dereference_val = do_basic_op(str("+"), parameters[0], parameters[1])
2016-07-03 15:32:45 -07:00
if (!is_pointer(get_real_value(parameters[0])))
error("Trying to take dereference not a pointer")
return make_pair(dereference_pointer_into_variable(dereference_val), control_flow::nor())
2016-05-22 00:40:48 -07:00
}
2016-07-03 15:32:45 -07:00
// check for built-in-ish externs (everything the standard library needs)
2016-07-06 00:16:39 -07:00
if (func_name == "printf" || func_name == "malloc" || func_name == "free" || func_name == "memmove" || func_name == "fflush" || func_name == "snprintf" || func_name == "fopen" || func_name == "fclose" || func_name == "ftell" || func_name == "fseek" || func_name == "fread" || func_name == "fwrite" || func_name == "atan" || func_name == "atan2" || func_name == "acos" || func_name == "asin" || func_name == "tan" || func_name == "cos" || func_name == "sin" || func_name == "fgets" || func_name == "popen" || func_name == "pclose")
2016-07-03 15:32:45 -07:00
return make_pair(call_built_in_extern(func_name, parameters), control_flow::nor())
if (!func_call_func->function.body_statement)
2018-05-22 19:43:54 -04:00
error(str("trying to call unsupported extern function: ") + func_name)
2016-07-03 15:32:45 -07:00
} else {
// not the operator & and at least one object like parameter
parameter_sources = func_call_parameters
}
return make_pair(call_function(func_call_func, parameters, parameter_sources, var_stack, possible_closure_map, enclosing_object, new_enclosing_object, enclosing_func, globals), control_flow::nor())
}
2016-07-09 15:08:57 -07:00
2018-05-22 19:43:54 -04:00
fun call_function(func: *ast_node, parameters: vec<value>, globals: *map<*ast_node, value>): value {
2016-07-09 15:08:57 -07:00
var var_stack = stack<map<*ast_node, value>>()
var_stack.push(map<*ast_node,value>())
2018-05-22 19:43:54 -04:00
var result = call_function(func, parameters, vec<*ast_node>(), &var_stack, map<*ast_node,value>(), value::void_nothing(), value::void_nothing(), null<ast_node>(), globals)
2016-07-09 15:08:57 -07:00
pop_and_free(&var_stack)
return result
}
2016-07-03 15:32:45 -07:00
// call_function can be called with either parameter values in parameters or ast expressions in parameter_sources
// this is to allow easy function calling if we already have the values (for main, say, or to make our job if it's not
// an operator easier), but we need to be able to be called with ast_expressions too so we can properly copy_construct once
2018-05-22 19:43:54 -04:00
fun call_function(func: *ast_node, parameters: vec<value>, parameter_sources: vec<*ast_node>, var_stack: *stack<map<*ast_node, value>>, possible_closure_map: ref map<*ast_node, value>, enclosing_object: value, new_enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): value {
2016-07-03 15:32:45 -07:00
// will need adjustment
if (!is_function(func))
error("Can't handle not function function calls (can do regular method, is this chained or something?)")
var func_name = func->function.name
// do regular function
// start out with the possible closure map as the highest scope (gloabals checked seperately)
var new_var_stack = stack(possible_closure_map)
new_var_stack.push(map<*ast_node,value>())
// if this is a value based call, pull from parameters
if (parameter_sources.size == 0) {
/*println(func_name + " being called with parameter values")*/
if (parameters.size != func->function.parameters.size)
2018-05-22 19:43:54 -04:00
error(str("calling function ") + func->function.name + " with wrong number of parameters (values)")
2016-07-03 15:32:45 -07:00
for (var i = 0; i < parameters.size; i++;) {
var param_type = get_ast_type(func)->parameter_types[i]
var param_ident = func->function.parameters[i]
if (param_type->is_ref) {
if (is_variable(parameters[i]))
new_var_stack.top()[param_ident] = parameters[i]
else
new_var_stack.top()[param_ident] = wrap_into_variable(parameters[i])
} else {
new_var_stack.top()[param_ident] = value::variable(make_pair(malloc(type_size(param_type)), param_type))
store_into_variable(new_var_stack.top()[param_ident], get_real_value(parameters[i]))
}
2016-05-15 11:09:12 -07:00
}
2016-07-03 15:32:45 -07:00
} else {
// on this side we construct temps in the old var stack, then move it over to the new one so that references resolve correctly
2016-05-31 22:02:00 -07:00
var_stack->push(map<*ast_node,value>())
2016-07-03 15:32:45 -07:00
/*println(func_name + " being called with parameter sources")*/
// need to pull from parameter_sources instead
if (parameter_sources.size != func->function.parameters.size)
2018-05-22 19:43:54 -04:00
error(str("calling function ") + func->function.name + " with wrong number of parameters (sources)")
2016-07-03 15:32:45 -07:00
for (var i = 0; i < parameter_sources.size; i++;) {
var param_type = get_ast_type(func)->parameter_types[i]
var param_ident = func->function.parameters[i]
if (param_type->is_ref) {
var param = interpret(parameter_sources[i], var_stack, enclosing_object, enclosing_func, globals).first
if (is_variable(param))
new_var_stack.top()[param_ident] = param
else
new_var_stack.top()[param_ident] = wrap_into_variable(param)
} else {
new_var_stack.top()[param_ident] = value::variable(make_pair(malloc(type_size(param_type)), param_type))
store_into_variable(new_var_stack.top()[param_ident], get_real_value(interpret(parameter_sources[i], var_stack, enclosing_object, enclosing_func, globals).first))
}
2016-05-13 16:31:55 -04:00
}
}
2016-07-03 15:32:45 -07:00
var to_ret = interpret(func->function.body_statement, &new_var_stack, new_enclosing_object, func, globals).first
// to_ret is on the new_var_stack, likely
/*pop_and_free(&new_var_stack)*/
if (parameter_sources.size) {
// pop off the temporaries if we needed to, but only after destructing any params we needed to
2016-05-13 16:31:55 -04:00
pop_and_free(var_stack)
}
2016-07-03 15:32:45 -07:00
return to_ret
}
2018-05-22 19:43:54 -04:00
fun call_built_in_extern(func_name: str, parameters: vec<value>): value {
2016-07-03 15:32:45 -07:00
for (var i = 0; i < parameters.size; i++;)
parameters[i] = get_real_value(parameters[i])
if (func_name == "printf") {
assert(parameters.size == 2 && is_pointer(parameters[0]) && is_pointer(parameters[1]), "Calling printf with wrong params")
printf((parameters[0].pointer.first) cast *char, (parameters[1].pointer.first) cast *char)
return value::integer(0)
} else if (func_name == "malloc") {
assert(parameters.size == 1 && is_ulong_int(parameters[0]), "Calling malloc with wrong params")
return value::pointer(make_pair(malloc(parameters[0].ulong_int), type_ptr(base_type::void_return())->clone_with_increased_indirection()))
} else if (func_name == "free") {
assert(parameters.size == 1 && is_pointer(parameters[0]), "Calling free with wrong params")
free(parameters[0].pointer.first)
} else if (func_name == "memmove") {
assert(parameters.size == 3 && is_pointer(parameters[0]) && is_pointer(parameters[1]) && is_ulong_int(parameters[2]), "Calling memmove with wrong params")
return value::pointer(make_pair(memmove((parameters[0].pointer.first) cast *void, (parameters[1].pointer.first) cast *void, parameters[2].ulong_int), type_ptr(base_type::void_return(), 1)))
} else if (func_name == "fflush") {
assert(parameters.size == 1 && is_integer(parameters[0]), "Calling fflush with wrong params")
fflush(parameters[0].integer)
} else if (func_name == "snprintf") {
assert(parameters.size == 4 && is_pointer(parameters[0]) && is_ulong_int(parameters[1]) && is_pointer(parameters[2]) && is_double_precision(parameters[3]), "Calling snprintf with wrong params")
return value::integer(snprintf((parameters[0].pointer.first) cast *char, parameters[1].ulong_int, (parameters[2].pointer.first) cast *char, parameters[3].double_precision))
} else if (func_name == "fopen") {
assert(parameters.size == 2 && is_pointer(parameters[0]) && is_pointer(parameters[1]), "Calling fopen with wrong params")
return value::pointer(make_pair(fopen((parameters[0].pointer.first) cast *char, (parameters[1].pointer.first) cast *char), type_ptr(base_type::void_return(), 1)))
} else if (func_name == "fclose") {
assert(parameters.size == 1 && is_pointer(parameters[0]), "Calling fclose with wrong params")
return value::integer(fclose((parameters[0].pointer.first) cast *void))
} else if (func_name == "ftell") {
assert(parameters.size == 1 && is_pointer(parameters[0]), "Calling ftell with wrong params")
return value::long_int(ftell((parameters[0].pointer.first) cast *void))
} else if (func_name == "fseek") {
assert(parameters.size == 3 && is_pointer(parameters[0]) && is_long_int(parameters[1]) && is_integer(parameters[2]), "Calling fseek with wrong params")
return value::integer(fseek((parameters[0].pointer.first) cast *void, parameters[1].long_int, parameters[2].integer))
} else if (func_name == "fread") {
assert(parameters.size == 4 && is_pointer(parameters[0]) && is_ulong_int(parameters[1]) && is_ulong_int(parameters[2]) && is_pointer(parameters[3]), "Calling fread with wrong params")
return value::ulong_int(fread((parameters[0].pointer.first) cast *void, parameters[1].ulong_int, parameters[2].ulong_int, parameters[3].pointer.first))
} else if (func_name == "fwrite") {
assert(parameters.size == 4 && is_pointer(parameters[0]) && is_ulong_int(parameters[1]) && is_ulong_int(parameters[2]) && is_pointer(parameters[3]), "Calling fwrite with wrong params")
return value::ulong_int(fwrite((parameters[0].pointer.first) cast *void, parameters[1].ulong_int, parameters[2].ulong_int, parameters[3].pointer.first))
} else if (func_name == "exit") {
assert(parameters.size == 1 && is_integer(parameters[0]), "Calling exit with wrong params")
exit(parameters[0].integer)
} else if (func_name == "atan") {
assert(parameters.size == 1 && is_double_precision(parameters[0]), "Calling atan with wrong params")
return value::double_precision(atan(parameters[0].double_precision))
} else if (func_name == "atan2") {
assert(parameters.size == 2 && is_double_precision(parameters[0]) && is_double_precision(parameters[1]), "Calling atan2 with wrong params")
return value::double_precision(atan2(parameters[0].double_precision, parameters[1].double_precision))
} else if (func_name == "acos") {
assert(parameters.size == 1 && is_double_precision(parameters[0]), "Calling acos with wrong params")
return value::double_precision(acos(parameters[0].double_precision))
} else if (func_name == "asin") {
assert(parameters.size == 1 && is_double_precision(parameters[0]), "Calling asin with wrong params")
return value::double_precision(asin(parameters[0].double_precision))
} else if (func_name == "tan") {
assert(parameters.size == 1 && is_double_precision(parameters[0]), "Calling tan with wrong params")
return value::double_precision(tan(parameters[0].double_precision))
} else if (func_name == "cos") {
assert(parameters.size == 1 && is_double_precision(parameters[0]), "Calling cos with wrong params")
return value::double_precision(cos(parameters[0].double_precision))
} else if (func_name == "sin") {
assert(parameters.size == 1 && is_double_precision(parameters[0]), "Calling sin with wrong params")
return value::double_precision(sin(parameters[0].double_precision))
2016-07-06 00:16:39 -07:00
} else if (func_name == "fgets") {
assert(parameters.size == 3 && is_pointer(parameters[0]) && is_integer(parameters[1]) && is_pointer(parameters[2]), "Calling fgets with wrong params")
// first param is *char, so reuse for return
return value::pointer(make_pair((fgets((parameters[0].pointer.first) cast *char, parameters[1].integer, parameters[2].pointer.first)) cast *void, parameters[0].pointer.second))
} else if (func_name == "popen") {
assert(parameters.size == 2 && is_pointer(parameters[0]) && is_pointer(parameters[1]), "Calling popen with wrong params")
return value::pointer(
make_pair(popen((parameters[0].pointer.first) cast *char, (parameters[1].pointer.first) cast *char), type_ptr(base_type::void_return(), 1)))
} else if (func_name == "pclose") {
assert(parameters.size == 1 && is_pointer(parameters[0]), "Calling pclose with wrong params")
return value::integer(pclose(parameters[0].pointer.first))
2016-07-03 15:32:45 -07:00
} else {
2018-05-22 19:43:54 -04:00
error(str("trying to call invalid func: ") + func_name)
2016-07-03 15:32:45 -07:00
}
return value::void_nothing()
}
fun interpret_function(function: *ast_node, var_stack: *stack<map<*ast_node, value>>, enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): pair<value, control_flow> {
var possible_closure_map = new<map<*ast_node,value>>()->construct()
function->function.closed_variables.for_each(fun(v: *ast_node) {
(*possible_closure_map)[v] = interpret_identifier(v, var_stack, enclosing_object, enclosing_func, globals).first
})
return make_pair(value::function(make_pair(function, possible_closure_map)), control_flow::nor())
}
fun interpret_if_statement(if_stmt: *ast_node, var_stack: *stack<map<*ast_node, value>>, enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): pair<value, control_flow> {
var_stack->push(map<*ast_node,value>())
var value_from_inside = make_pair(value::void_nothing(), control_flow::nor())
if (truthy(interpret(if_stmt->if_statement.condition, var_stack, enclosing_object, enclosing_func, globals).first)) {
value_from_inside = interpret(if_stmt->if_statement.then_part, var_stack, enclosing_object, enclosing_func, globals)
} else if (if_stmt->if_statement.else_part) {
value_from_inside = interpret(if_stmt->if_statement.else_part, var_stack, enclosing_object, enclosing_func, globals)
}
pop_and_free(var_stack)
return value_from_inside
}
fun interpret_while_loop(while_loop: *ast_node, var_stack: *stack<map<*ast_node, value>>, enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): pair<value, control_flow> {
var_stack->push(map<*ast_node,value>())
var value_from_inside = make_pair(value::void_nothing(), control_flow::nor())
var going = true
while (going && truthy(interpret(while_loop->while_loop.condition, var_stack, enclosing_object, enclosing_func, globals).first)) {
value_from_inside = interpret(while_loop->while_loop.statement, var_stack, enclosing_object, enclosing_func, globals)
if (value_from_inside.second == control_flow::ret() || value_from_inside.second == control_flow::bre())
going = false
if (value_from_inside.second == control_flow::bre() || value_from_inside.second == control_flow::con())
value_from_inside = make_pair(value::void_nothing(), control_flow::nor())
}
pop_and_free(var_stack)
return value_from_inside
}
fun interpret_for_loop(for_loop: *ast_node, var_stack: *stack<map<*ast_node, value>>, enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): pair<value, control_flow> {
var_stack->push(map<*ast_node,value>())
var value_from_inside = make_pair(value::void_nothing(), control_flow::nor())
var going = true
if (for_loop->for_loop.init)
interpret(for_loop->for_loop.init, var_stack, enclosing_object, enclosing_func, globals)
while (going && (!for_loop->for_loop.condition || truthy(interpret(for_loop->for_loop.condition, var_stack, enclosing_object, enclosing_func, globals).first))) {
value_from_inside = interpret(for_loop->for_loop.body, var_stack, enclosing_object, enclosing_func, globals)
if (value_from_inside.second == control_flow::ret() || value_from_inside.second == control_flow::bre())
going = false
if (value_from_inside.second == control_flow::bre() || value_from_inside.second == control_flow::con())
value_from_inside = make_pair(value::void_nothing(), control_flow::nor())
2016-05-29 23:54:54 -07:00
2016-07-03 15:32:45 -07:00
// only run update if we're not breaking or continuing
if (going && for_loop->for_loop.update)
interpret(for_loop->for_loop.update, var_stack, enclosing_object, enclosing_func, globals)
2016-05-13 16:31:55 -04:00
}
2016-07-03 15:32:45 -07:00
pop_and_free(var_stack)
return value_from_inside
}
fun interpret_branching_statement(bstatement: *ast_node): pair<value, control_flow> {
match (bstatement->branching_statement.b_type) {
branching_type::break_stmt() return make_pair(value::void_nothing(), control_flow::bre())
branching_type::continue_stmt() return make_pair(value::void_nothing(), control_flow::con())
2016-05-31 21:29:05 -07:00
}
2016-07-03 15:32:45 -07:00
error("bad branch type")
}
fun interpret_code_block(block: *ast_node, var_stack: *stack<map<*ast_node, value>>, enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): pair<value, control_flow> {
var_stack->push(map<*ast_node,value>())
for (var i = 0; i < block->code_block.children.size; i++;) {
var statement = interpret(block->code_block.children[i], var_stack, enclosing_object, enclosing_func, globals)
match (statement.second) {
control_flow::con() {
pop_and_free(var_stack)
return make_pair(value::void_nothing(), control_flow::con())
2016-05-13 03:10:36 -04:00
}
2016-07-03 15:32:45 -07:00
control_flow::bre() {
pop_and_free(var_stack)
return make_pair(value::void_nothing(), control_flow::bre())
}
control_flow::ret() {
pop_and_free(var_stack)
return statement
2016-06-30 22:41:32 -07:00
}
2016-05-21 14:38:57 -07:00
}
2016-07-03 15:32:45 -07:00
// if nor, continue on
2016-05-13 15:14:19 -04:00
}
2016-07-03 15:32:45 -07:00
pop_and_free(var_stack)
return make_pair(value::void_nothing(), control_flow::nor())
}
fun interpret_return_statement(stmt: *ast_node, var_stack: *stack<map<*ast_node, value>>, enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): pair<value, control_flow> {
if (stmt->return_statement.return_value == null<ast_node>())
return make_pair(value::void_nothing(), control_flow::ret())
var return_expression = stmt->return_statement.return_value
var return_type = get_ast_type(return_expression)
var to_ret.construct(): value
if (get_ast_type(enclosing_func)->return_type->is_ref) {
to_ret = interpret(return_expression, var_stack, enclosing_object, enclosing_func, globals).first
if (!is_variable(to_ret)) {
print("here is: ")
print_value(to_ret)
error("interpreter returning reference is not variable")
2016-05-18 23:11:00 -07:00
}
2016-07-03 15:32:45 -07:00
} else {
to_ret = interpret(return_expression, var_stack, enclosing_object, enclosing_func, globals).first
2016-05-13 15:14:19 -04:00
}
2016-07-03 15:32:45 -07:00
return make_pair(to_ret, control_flow::ret())
}
fun interpret_declaration_statement(stmt: *ast_node, var_stack: *stack<map<*ast_node, value>>, enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): pair<value, control_flow> {
var ident = stmt->declaration_statement.identifier
var ident_type = ident->identifier.type
var_stack->top()[ident] = value::variable(make_pair(malloc(type_size(ident_type)),ident_type))
// NOTE: store_into_variable takes to in as a ref because it might change it in the special case ref = ptr
if (stmt->declaration_statement.expression) {
store_into_variable(var_stack->top()[ident], get_real_value(interpret(stmt->declaration_statement.expression, var_stack, enclosing_object, enclosing_func, globals).first))
} else if (stmt->declaration_statement.init_method_call) {
interpret(stmt->declaration_statement.init_method_call, var_stack, enclosing_object, enclosing_func, globals)
}
return make_pair(value::void_nothing(), control_flow::nor())
}
fun interpret_assignment_statement(stmt: *ast_node, var_stack: *stack<map<*ast_node, value>>, enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): pair<value, control_flow> {
var to = interpret(stmt->assignment_statement.to, var_stack, enclosing_object, enclosing_func, globals).first
var from = interpret(stmt->assignment_statement.from, var_stack, enclosing_object, enclosing_func, globals).first
assert(is_variable(to), "assigning into not a variable")
// always do cast now to make our best effort at assignment (assign into a double from a float, etc)
// unless it's an object
var from_real = get_real_value(from)
// NOTE: store_into_variable takes to in as a ref because it might change it in the special case ref = ptr
if (is_object_like(from_real) || is_function(from_real))
store_into_variable(to, from_real)
else
store_into_variable(to, cast_value(from_real, to.variable.second))
return make_pair(value::void_nothing(), control_flow::nor())
}
fun interpret_identifier(ident: *ast_node, var_stack: *stack<map<*ast_node, value>>, enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): pair<value, control_flow> {
for (var i = 0; i < var_stack->size(); i++;)
if (var_stack->from_top(i).contains_key(ident))
return make_pair(var_stack->from_top(i)[ident], control_flow::nor())
// check for object member / this
if (is_object_like(enclosing_object)) {
if (ident->identifier.name == "this")
return make_pair(value::pointer(make_pair(enclosing_object.object_like.first, enclosing_object.object_like.second->clone_with_increased_indirection())), control_flow::nor())
var object_def = enclosing_object.object_like.second->type_def
for (var i = 0; i < object_def->type_def.variables.size; i++;) {
if (object_def->type_def.variables[i]->declaration_statement.identifier == ident) {
var ret_ptr = ((enclosing_object.object_like.first) cast *char + offset_into_struct(enclosing_object.object_like.second, ident)) cast *void
return make_pair(value::variable(make_pair(ret_ptr, ident->identifier.type)), control_flow::nor())
2016-07-03 01:55:32 -07:00
}
}
2016-05-13 03:10:36 -04:00
}
2016-07-03 15:32:45 -07:00
// check for global
if (globals->contains_key(ident))
return make_pair((*globals)[ident], control_flow::nor())
2017-01-20 01:11:06 -05:00
println("couldn't find " + get_ast_name(ident) + " in interpret identifier, scope:")
2016-07-03 15:32:45 -07:00
for (var i = 0; i < var_stack->size(); i++;) {
2018-05-22 19:43:54 -04:00
println(str("level: ") + i)
2016-07-03 15:32:45 -07:00
var_stack->from_top(i).for_each(fun(key: *ast_node, v: value) print(get_ast_name(key) + " ");)
println()
}
if (is_object_like(enclosing_object)) {
println("object scope:")
var object_def = enclosing_object.object_like.second->type_def
for (var i = 0; i < object_def->type_def.variables.size; i++;) {
2017-01-20 01:11:06 -05:00
print(get_ast_name(object_def->type_def.variables[i]->declaration_statement.identifier) + " ")
2016-05-13 03:10:36 -04:00
}
2016-07-03 15:32:45 -07:00
} else {
print("no object scope: ")
print_value(enclosing_object)
2016-05-13 03:10:36 -04:00
}
2018-05-22 19:43:54 -04:00
error(str("Cannot find variable: ") + ident->identifier.name)
2016-07-03 15:32:45 -07:00
}
fun interpret_cast(node: *ast_node, var_stack: *stack<map<*ast_node, value>>, enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): pair<value, control_flow> {
return make_pair(cast_value(interpret(node->cast.value, var_stack, enclosing_object, enclosing_func, globals).first, node->cast.to_type), control_flow::nor())
}
fun interpret_compiler_intrinsic(node: *ast_node, var_stack: *stack<map<*ast_node, value>>): pair<value, control_flow> {
var intrinsic_name = node->compiler_intrinsic.intrinsic
if (intrinsic_name == "sizeof")
return make_pair(value::ulong_int(type_size(node->compiler_intrinsic.type_parameters[0])), control_flow::nor())
2018-05-22 19:43:54 -04:00
error(str("bad intrinsic: ") + intrinsic_name)
2016-07-03 15:32:45 -07:00
}
fun interpret_value(val: *ast_node): pair<value, control_flow>
return make_pair(wrap_value(val), control_flow::nor())
fun interpret(node: *ast_node, var_stack: *stack<map<*ast_node, value>>, enclosing_object: value, enclosing_func: *ast_node, globals: *map<*ast_node, value>): pair<value, control_flow> {
if (!node) error("cannot interpret null node!")
match (*node) {
ast_node::function_call(backing) return interpret_function_call(node, var_stack, enclosing_object, enclosing_func, globals)
ast_node::function(backing) return interpret_function(node, var_stack, enclosing_object, enclosing_func, globals)
ast_node::if_statement(backing) return interpret_if_statement(node, var_stack, enclosing_object, enclosing_func, globals)
ast_node::while_loop(backing) return interpret_while_loop(node, var_stack, enclosing_object, enclosing_func, globals)
ast_node::for_loop(backing) return interpret_for_loop(node, var_stack, enclosing_object, enclosing_func, globals)
ast_node::branching_statement(backing) return interpret_branching_statement(node)
ast_node::code_block(backing) return interpret_code_block(node, var_stack, enclosing_object, enclosing_func, globals)
ast_node::return_statement(backing) return interpret_return_statement(node, var_stack, enclosing_object, enclosing_func, globals)
ast_node::declaration_statement(backing) return interpret_declaration_statement(node, var_stack, enclosing_object, enclosing_func, globals)
ast_node::assignment_statement(backing) return interpret_assignment_statement(node, var_stack, enclosing_object, enclosing_func, globals)
ast_node::identifier(backing) return interpret_identifier(node, var_stack, enclosing_object, enclosing_func, globals)
ast_node::cast(backing) return interpret_cast(node, var_stack, enclosing_object, enclosing_func, globals)
ast_node::compiler_intrinsic(backing) return interpret_compiler_intrinsic(node, var_stack)
ast_node::value(backing) return interpret_value(node)
}
2018-05-22 19:43:54 -04:00
error(str("Cannot interpret node: ") + get_ast_name(node))
2016-05-12 02:03:20 -04:00
}