Files
kraken/stdlib/c_generator.krak

1102 lines
73 KiB
Plaintext

import io:*
import mem:*
import map:*
import stack:*
import string:*
import util:*
import tree:*
import symbol:*
import ast_nodes:*
import poset:*
// we import ast_transformation for its make_method_call function
import ast_transformation:*
fun code_triple(): code_triple return code_triple(string(), string(), string());
fun code_triple(only: *char): code_triple return code_triple(string(), string(only), string());
fun code_triple(only: string): code_triple return code_triple(string(), only, string());
fun code_triple(first: string, second: string, third: string): code_triple {
var to_ret.construct(first, second, third): code_triple
return to_ret
}
obj code_triple (Object) {
var pre: string
var value: string
var post: string
fun construct(first: string, second: string, third: string): *code_triple {
pre.copy_construct(&first)
value.copy_construct(&second)
post.copy_construct(&third)
return this
}
fun copy_construct(old: *code_triple) {
pre.copy_construct(&old->pre)
value.copy_construct(&old->value)
post.copy_construct(&old->post)
}
fun operator=(other: code_triple) {
destruct()
copy_construct(&other)
}
fun destruct() {
pre.destruct()
value.destruct()
post.destruct()
}
fun operator==(other: code_triple): bool return pre == other.pre && value == other.value && post == other.value;
fun operator==(other: string): bool return (pre + value + post) == other;
fun operator==(other: *char): bool return (pre + value + post) == other;
fun operator!=(other: code_triple): bool return pre != other.pre || value != other.value || post != other.value;
fun operator!=(other: string): bool return (pre + value + post) != other;
fun operator!=(other: *char): bool return (pre + value + post) != other;
fun operator+(other: code_triple): code_triple {
return code_triple(pre+other.pre, value+other.value, other.post+post);
}
fun operator+(other: string): code_triple {
return code_triple(pre, value+other, post);
}
fun operator+(other: *char): code_triple {
return code_triple(pre, value + other, post);
}
fun operator+=(other: string) {
value += other
}
fun operator+=(other: *char) {
value += other
}
fun operator+=(other: code_triple) {
pre += other.pre
value += other.value
post += other.post
}
fun one_string():string {
return pre+value+post
}
}
obj c_generator (Object) {
var id_counter: int
var ast_to_syntax: map<*ast_node, *tree<symbol>>
var ast_name_map: map<*ast_node, string>
var closure_struct_map: map<set<*ast_node>, string>
var function_type_map: map<type, string>
var function_typedef_string: string
var closure_struct_definitions: string
var c_keyword_avoid: set<string>
var replacement_map: map<string, string>
var longest_replacement: int
var linker_string: string
fun construct(): *c_generator {
id_counter = 0
ast_to_syntax.construct()
ast_name_map.construct()
closure_struct_map.construct()
function_type_map.construct()
function_typedef_string.construct()
closure_struct_definitions.construct()
linker_string.construct()
c_keyword_avoid.construct()
c_keyword_avoid.add(string("extern"))
replacement_map.construct()
// IMPORTANT
longest_replacement = 3
replacement_map[string("+")] = string("plus")
replacement_map[string("-")] = string("minus")
replacement_map[string("*")] = string("star")
replacement_map[string("/")] = string("div")
replacement_map[string("%")] = string("mod")
replacement_map[string("^")] = string("carat")
replacement_map[string("&")] = string("amprsd")
replacement_map[string("|")] = string("pipe")
replacement_map[string("~")] = string("tilde")
replacement_map[string("!")] = string("exlmtnpt")
replacement_map[string(",")] = string("comma")
replacement_map[string("=")] = string("eq")
replacement_map[string("++")] = string("dbplus")
replacement_map[string("--")] = string("dbminus")
replacement_map[string("<<")] = string("dbleft")
replacement_map[string(">>")] = string("dbright")
replacement_map[string("::")] = string("scopeop")
replacement_map[string(":")] = string("colon")
replacement_map[string("==")] = string("dbq")
replacement_map[string("!=")] = string("notequals")
replacement_map[string("&&")] = string("doubleamprsnd")
replacement_map[string("||")] = string("doublepipe")
replacement_map[string("+=")] = string("plusequals")
replacement_map[string("-=")] = string("minusequals")
replacement_map[string("/=")] = string("divequals")
replacement_map[string("%=")] = string("modequals")
replacement_map[string("^=")] = string("caratequals")
replacement_map[string("&=")] = string("amprsdequals")
replacement_map[string("|=")] = string("pipeequals")
replacement_map[string("*=")] = string("starequals")
replacement_map[string("<<=")] = string("doublerightequals")
replacement_map[string("<")] = string("lt")
replacement_map[string(">")] = string("gt")
replacement_map[string(">>=")] = string("doubleleftequals")
replacement_map[string("(")] = string("openparen")
replacement_map[string(")")] = string("closeparen")
replacement_map[string("[")] = string("obk")
replacement_map[string("]")] = string("cbk")
replacement_map[string(" ")] = string("_")
replacement_map[string(".")] = string("dot")
replacement_map[string("->")] = string("arrow")
return this
}
fun copy_construct(old: *c_generator) {
id_counter = old->id_counter
ast_to_syntax.copy_construct(&old->ast_to_syntax)
ast_name_map.copy_construct(&old->ast_name_map)
closure_struct_map.copy_construct(&old->closure_struct_map)
function_type_map.copy_construct(&old->function_type_map)
function_typedef_string.copy_construct(&old->function_typedef_string)
closure_struct_definitions.copy_construct(&old->closure_struct_definitions)
c_keyword_avoid.copy_construct(&old->c_keyword_avoid)
replacement_map.copy_construct(&old->replacement_map)
longest_replacement = old->longest_replacement
linker_string.copy_construct(&old->linker_string)
}
fun operator=(other: ref c_generator) {
destruct()
copy_construct(&other)
}
fun destruct() {
ast_to_syntax.destruct()
ast_name_map.destruct()
closure_struct_map.destruct()
function_type_map.destruct()
function_typedef_string.destruct()
closure_struct_definitions.destruct()
c_keyword_avoid.destruct()
replacement_map.destruct()
linker_string.destruct()
}
fun get_id(): string return to_string(id_counter++);
fun generate_function_prototype_and_header(child: *ast_node, enclosing_object: *ast_node, is_lambda: bool, defer_stack: *stack<pair<bool,stack<*ast_node>>>):pair<string,string> {
var backing = child->function
var parameter_types = string()
var parameters = string()
// lambdas can have the enclosing object too, if it's needed (lambda in a method)
if (enclosing_object && !is_lambda) {
parameter_types = type_to_c(enclosing_object->type_def.self_type) + "*"
parameters = type_to_c(enclosing_object->type_def.self_type) + "* this"
}
if (backing.closed_variables.size()) {
/*println("HAS CLOSED VARIABLES")*/
if (parameter_types != "") { parameter_types += ", "; parameters += ", ";}
var closed_type_name = get_closure_struct_type(backing.closed_variables)
parameter_types += closed_type_name + "*"
parameters += closed_type_name + "* closure_data"
}
var decorated_name = string()
if (backing.is_extern)
decorated_name = backing.name
else
decorated_name = generate_function(child, enclosing_object, null<ast_node>(), false, false).one_string()
backing.parameters.for_each(fun(parameter: *ast_node) {
if (parameter_types != "") { parameter_types += ", "; parameters += ", ";}
parameter_types += type_to_c(parameter->identifier.type)
parameters += type_to_c(parameter->identifier.type) + " " + get_name(parameter)
// add parameters to destructor thingy (for returns)? Or should that be a different pass?
var parameter_type = parameter->identifier.type
if (!parameter_type->is_ref && parameter_type->indirection == 0 && (parameter_type->is_adt() || (parameter_type->is_object() && has_method(parameter_type->type_def, "destruct", vector<*type>()))))
defer_stack->top().second.push(ast_statement_ptr(make_method_call(parameter, "destruct", vector<*ast_node>())))
})
return make_pair(type_to_c(backing.type->return_type) + " " + decorated_name + "(" + parameter_types + ");\n",
type_to_c(backing.type->return_type) + " " + decorated_name + "(" + parameters + ")")
}
fun generate_c(name_ast_map: map<string, pair<*tree<symbol>,*ast_node>>, ast_to_syntax_in: map<*ast_node, *tree<symbol>> ): pair<string,string> {
ast_to_syntax = ast_to_syntax_in
var prequal: string = "#include <stdbool.h>\n"
var plain_typedefs: string = "\n/**Plain Typedefs**/\n"
var top_level_c_passthrough: string = ""
var variable_extern_declarations: string = ""
var structs: string = "\n/**Type Structs**/\n"
function_typedef_string = "\n/**Typedefs**/\n"
closure_struct_definitions = "\n/**Closure Struct Definitions**/\n"
var function_prototypes: string = "\n/**Function Prototypes**/\n"
var function_definitions: string = "\n/**Function Definitions**/\n"
var variable_declarations: string = "\n/**Variable Declarations**/\n"
// moved out from below so that it can be used for methods as well as regular functions (and eventually lambdas...)
var generate_function_definition = fun(child: *ast_node, enclosing_object: *ast_node, is_lambda: bool) {
var backing = child->function
// stack-stack thing // this could be a stack of strings too, maybe
// start out with one stack on the stack
var defer_stack = stack<pair<bool,stack<*ast_node>>>(make_pair(false, stack<*ast_node>()))
var prototype_and_header = generate_function_prototype_and_header(child, enclosing_object, is_lambda, &defer_stack)
function_prototypes += prototype_and_header.first
if (!backing.is_extern)
function_definitions += prototype_and_header.second
if (backing.body_statement) {
function_definitions += string(" {\n") + generate_statement(backing.body_statement, enclosing_object, child, &defer_stack).one_string()
function_definitions += generate_from_defer_stack(&defer_stack, -1, enclosing_object, child).one_string()
function_definitions += "}\n"
} else if (!backing.is_extern) {
// adt constructor if no body and not extern
// wow. no pass in for no this
enclosing_object = get_ast_scope(child)->get(string("~enclosing_scope"))[0]
// if this is an option constructor
if (enclosing_object->adt_def.options.any_true(fun(opt: *ast_node): bool return opt->identifier.name == backing.name;)) {
var option_ident = enclosing_object->adt_def.options.find_first_satisfying(fun(opt: *ast_node): bool return opt->identifier.name == backing.name;)
var option_type = option_ident->identifier.type
function_definitions += " { \n"
var to_ret_ident = ast_identifier_ptr("to_ret", enclosing_object->type_def.self_type, enclosing_object)
function_definitions += type_to_c(enclosing_object->adt_def.self_type) + " "+ get_name(to_ret_ident) + ";\n"
function_definitions += get_name(to_ret_ident) + ".flag = " + string("enum_opt_") + get_name(option_ident) + ";\n"
if (option_type->is_empty_adt_option())
function_definitions += "/*no inner data*/\n"
else {
var param = backing.parameters[0]
if (option_type->indirection == 0 && (option_type->is_adt() || (option_type->is_object() && has_method(option_type->type_def, "copy_construct", vector(option_type->clone_with_increased_indirection()))))) {
function_definitions += generate(ast_statement_ptr(make_method_call(make_operator_call(".", vector(to_ret_ident, option_ident)), "copy_construct", vector(make_operator_call("&", vector(param))))), null<ast_node>(), null<ast_node>(), &defer_stack, false).one_string()
function_definitions += generate_from_defer_stack(&defer_stack, -1, enclosing_object, child).one_string()
} else {
function_definitions += get_name(to_ret_ident) +".data." + get_name(option_ident) + " = " + get_name(param) + ";\n"
}
}
function_definitions += "return " + get_name(to_ret_ident) + ";\n"
function_definitions += "}\n"
} else {
// this is one of the other functions instead
var adt_this = ast_identifier_ptr("this", enclosing_object->type_def.self_type->clone_with_indirection(1), enclosing_object)
function_definitions += "{\n"
if (backing.name == "operator==") {
var param = backing.parameters[0]
function_definitions += "/*operator==*/"
function_definitions += string("if (this->flag != ") + generate_identifier(param, null<ast_node>(), null<ast_node>()).one_string() + ".flag) return false;\n"
enclosing_object->adt_def.options.for_each(fun(option: *ast_node) {
var option_type = option->identifier.type
function_definitions += string("if (this->flag == ") + string("enum_opt_") + generate_identifier(option, null<ast_node>(), null<ast_node>()).one_string() + ") {\n"
if (option_type->is_empty_adt_option()) {
function_definitions += "return true;"
} else {
if (option_type->indirection == 0 && (option_type->is_adt() || (option_type->is_object() && has_method(option_type->type_def, "operator==", vector(option_type))))) {
defer_stack.push(make_pair(false, stack<*ast_node>()))
var equals_res = generate(ast_statement_ptr(make_method_call(make_operator_call("->", vector(adt_this, option)), "operator==", vector(make_operator_call(".", vector(param, option))))), null<ast_node>(), null<ast_node>(), &defer_stack, false)
equals_res.value = string("bool result = ") + equals_res.value + ";\n"
equals_res.post += generate_from_defer_stack(&defer_stack, -1, enclosing_object, child).one_string()
defer_stack.pop()
function_definitions += equals_res.one_string() + "return result;\n"
} else if (option_type->is_object()) {
// if we are an object but don't define an operator== function (or it is templated)
// always return false.
function_definitions += "return false;\n"
} else {
var option_name = generate_identifier(option, null<ast_node>(), null<ast_node>()).one_string()
var param_name = generate_identifier(param, null<ast_node>(), null<ast_node>()).one_string()
function_definitions += string("return this->data.") + option_name + " == " + param_name + ".data." + option_name + ";\n"
}
}
function_definitions += "}\n"
})
} else if (backing.name == "operator!=") {
var param = backing.parameters[0]
function_definitions += "/*operator!=*/"
defer_stack.push(make_pair(false, stack<*ast_node>()))
var equals_res = generate(ast_statement_ptr(make_method_call(make_operator_call("*", vector(adt_this)), "operator==", vector(param))), null<ast_node>(), null<ast_node>(), &defer_stack, false)
equals_res.value = string("bool result = !") + equals_res.value + ";\n"
equals_res.post += generate_from_defer_stack(&defer_stack, -1, enclosing_object, child).one_string()
defer_stack.pop()
function_definitions += equals_res.one_string() + "return result;\n"
} else if (backing.name == "copy_construct") {
var param = backing.parameters[0]
function_definitions += "/*copy_construct*/"
function_definitions += string("this->flag = ") + generate_identifier(param, null<ast_node>(), null<ast_node>()).one_string() + "->flag;\n"
enclosing_object->adt_def.options.for_each(fun(option: *ast_node) {
var option_type = option->identifier.type
function_definitions += string("if (this->flag == ") + string("enum_opt_") + generate_identifier(option, null<ast_node>(), null<ast_node>()).one_string() + ") {\n"
if (option_type->is_empty_adt_option()) {
function_definitions += "/*no data to copy*/;"
} else {
if (option_type->indirection == 0 && (option_type->is_adt() || (option_type->is_object() && has_method(option_type->type_def, "copy_construct", vector(option_type->clone_with_increased_indirection()))))) {
// don't really need the defer_stack
function_definitions += generate(ast_statement_ptr(make_method_call(make_operator_call("->", vector(adt_this, option)), "copy_construct", vector(make_operator_call("&", vector(make_operator_call("->", vector(param, option))))))), null<ast_node>(), null<ast_node>(), &defer_stack, false).one_string()
} else {
var option_name = generate_identifier(option, null<ast_node>(), null<ast_node>()).one_string()
var param_name = generate_identifier(param, null<ast_node>(), null<ast_node>()).one_string()
function_definitions += string("this->data.") + option_name + " = " + param_name + "->data." + option_name + ";\n"
}
}
function_definitions += "}\n"
})
} else if (backing.name == "operator=") {
var param = backing.parameters[0]
function_definitions += "/*operator=*/"
defer_stack.push(make_pair(false, stack<*ast_node>()))
function_definitions += generate(ast_statement_ptr(make_method_call(make_operator_call("*", vector(adt_this)), "destruct", vector<*ast_node>())), null<ast_node>(), null<ast_node>(), &defer_stack, false).one_string()
function_definitions += generate(ast_statement_ptr(make_method_call(make_operator_call("*", vector(adt_this)), "copy_construct", vector(make_operator_call("&", vector(param))))), null<ast_node>(), null<ast_node>(), &defer_stack, false).one_string()
function_definitions += generate_from_defer_stack(&defer_stack, -1, enclosing_object, child).one_string()
defer_stack.pop()
} else if (backing.name == "destruct") {
function_definitions += "/*destruct*/"
enclosing_object->adt_def.options.for_each(fun(option: *ast_node) {
var option_type = option->identifier.type
function_definitions += string("if (this->flag == ") + string("enum_opt_") + generate_identifier(option, null<ast_node>(), null<ast_node>()).one_string() + ") {\n"
if (option_type->indirection == 0 && (option_type->is_adt() || (option_type->is_object() && has_method(option_type->type_def, "destruct", vector<*type>())))) {
// don't really need the defer_stack
function_definitions += generate(ast_statement_ptr(make_method_call(make_operator_call("->", vector(adt_this, option)), "destruct", vector<*ast_node>())), null<ast_node>(), null<ast_node>(), &defer_stack, false).one_string()
}
function_definitions += "}\n"
})
}
function_definitions += "}\n"
}
}
}
var type_poset = poset<*ast_node>()
// iterate through asts
name_ast_map.for_each(fun(name: string, tree_pair: pair<*tree<symbol>,*ast_node>) {
// iterate through children for each ast
// assert translation_unit?
// do lambdas seperatly, so we can reconstitute the enclosing object if it has one
tree_pair.second->translation_unit.lambdas.for_each(fun(child: *ast_node) {
var enclosing_object_traverse = child
while(enclosing_object_traverse && !is_type_def(enclosing_object_traverse) &&
get_ast_scope(enclosing_object_traverse) && get_ast_scope(enclosing_object_traverse)->contains_key(string("~enclosing_scope")))
enclosing_object_traverse = get_ast_scope(enclosing_object_traverse)->get(string("~enclosing_scope"))[0]
if (enclosing_object_traverse && is_type_def(enclosing_object_traverse))
generate_function_definition(child, enclosing_object_traverse, true)
else
generate_function_definition(child, null<ast_node>(), true)
})
tree_pair.second->translation_unit.children.for_each(fun(child: *ast_node) {
match (*child) {
// should really check the genrator
ast_node::if_comp(backing) {
if (is_simple_passthrough(backing.statement->statement.child))
top_level_c_passthrough += generate_simple_passthrough(backing.statement->statement.child, true)
}
ast_node::simple_passthrough(backing) top_level_c_passthrough += generate_simple_passthrough(child, true)
ast_node::declaration_statement(backing) variable_declarations += generate_declaration_statement(child, null<ast_node>(), null<ast_node>(), null<stack<pair<bool,stack<*ast_node>>>>(), false).one_string() + ";\n" // false - don't do defer
ast_node::function(backing) {
// check for and add to parameters if a closure
generate_function_definition(child, null<ast_node>(), false)
}
ast_node::template(backing) {
backing.instantiated.for_each(fun(node: *ast_node) {
match (*node) {
ast_node::function(backing) generate_function_definition(node, null<ast_node>(), false)
ast_node::type_def(backing) {
type_poset.add_vertex(node)
backing.variables.for_each(fun(i: *ast_node) {
var var_type = get_ast_type(i->declaration_statement.identifier)
if (!var_type->indirection && var_type->type_def)
type_poset.add_relationship(node, var_type->type_def)
})
}
}
})
}
ast_node::type_def(backing) {
type_poset.add_vertex(child)
backing.variables.for_each(fun(i: *ast_node) {
var var_type = get_ast_type(i->declaration_statement.identifier)
if (!var_type->indirection && var_type->type_def)
type_poset.add_relationship(child, var_type->type_def)
})
}
ast_node::adt_def(backing) {
type_poset.add_vertex(child)
backing.options.for_each(fun(i: *ast_node) {
var var_type = get_ast_type(i)
if (!var_type->indirection && var_type->type_def)
type_poset.add_relationship(child, var_type->type_def)
})
}
}
})
})
type_poset.get_sorted().for_each(fun(vert: *ast_node) {
/*var base_name = vert->type_def.name*/
var base_name = get_name(vert)
plain_typedefs += string("typedef struct ") + base_name + "_dummy " + base_name + ";\n"
structs += string("struct ") + base_name + "_dummy {\n"
if (is_type_def(vert)) {
vert->type_def.variables.for_each(fun(variable_declaration: *ast_node) structs += generate_declaration_statement(variable_declaration, null<ast_node>(), null<ast_node>(), null<stack<pair<bool,stack<*ast_node>>>>(), false).one_string() + ";\n";) // also no defer stack
// generate the methods (note some of these may be templates)
vert->type_def.methods.for_each(fun(method: *ast_node) {
if (is_template(method))
method->template.instantiated.for_each(fun(m: *ast_node) generate_function_definition(m, vert, false);)
else
generate_function_definition(method, vert, false);
})
} else {
// adt
var add_to_structs = string()
var add_to_enum = string()
vert->adt_def.options.for_each(fun(option: *ast_node) {
add_to_enum += string("enum_opt_") + get_name(option) + ","
if (!option->identifier.type->is_empty_adt_option())
add_to_structs += generate_declaration_statement(ast_declaration_statement_ptr(option, null<ast_node>()), null<ast_node>(), null<ast_node>(), null<stack<pair<bool,stack<*ast_node>>>>(), false).one_string() + ";\n"
})
structs += string("enum { ") + add_to_enum + " } flag;\n"
structs += string("union { ") + add_to_structs + " } data;\n"
// now do methods and generation functions
vert->adt_def.option_funcs.for_each(fun(option_func: *ast_node) {
// no vert so no this
generate_function_definition(option_func, null<ast_node>(), false);
})
vert->adt_def.regular_funcs.for_each(fun(regular_func: *ast_node) {
// want the this this time
generate_function_definition(regular_func, vert, false);
})
}
structs += "};\n"
})
/*return make_pair(prequal+plain_typedefs+top_level_c_passthrough+variable_extern_declarations+structs+function_typedef_string+closure_struct_definitions+function_prototypes+variable_declarations+function_definitions + "\n", linker_string)*/
return make_pair(prequal+plain_typedefs+function_typedef_string+top_level_c_passthrough+variable_extern_declarations+structs+closure_struct_definitions+function_prototypes+variable_declarations+function_definitions + "\n", linker_string)
}
fun get_closure_struct_type(closed_variables: set<*ast_node>): string {
if (!closure_struct_map.contains_key(closed_variables)) {
var closure_name = string("closure_data_type") + get_id()
closure_struct_definitions += "typedef struct {\n"
// note that we keep our is_ref, which would not normally happen on a clone with increased indirection
// closed_variables.for_each(fun(i: *ast_node) closure_struct_definitions += type_to_c(i->identifier.type->clone_with_increased_indirection(1,i->identifier.type->is_ref)) +
// NO, now we don't keep our ref. Too hard to make, as &(&*i) isn't legal C
closed_variables.for_each(fun(i: *ast_node) closure_struct_definitions += type_to_c(i->identifier.type->clone_with_increased_indirection()) +
" " + get_name(i) + ";\n";)
closure_struct_definitions += string("} ") + closure_name + ";\n"
closure_struct_map[closed_variables] = closure_name
}
return closure_struct_map[closed_variables]
}
fun generate_if_comp(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>): code_triple {
if (node->if_comp.wanted_generator == "__C__")
return generate(node->if_comp.statement, enclosing_object, enclosing_func, defer_stack, false)
return code_triple()
}
fun generate_simple_passthrough(node: *ast_node, is_top_level: bool): string {
// deal with all the passthrough params
var result = string()
var pre = string()
var post = string()
if (node->simple_passthrough.linker_str != "")
linker_string += node->simple_passthrough.linker_str + " "
node->simple_passthrough.in_params.for_each(fun(i: pair<*ast_node, string>) {
var wanted_name = i.second
var current_name = generate_identifier(i.first, null<ast_node>(), null<ast_node>()).one_string()
if (wanted_name != current_name)
result += type_to_c(i.first->identifier.type) + " " + wanted_name + " = " + current_name + ";\n"
})
result += node->simple_passthrough.passthrough_str
node->simple_passthrough.out_params.for_each(fun(i: pair<*ast_node, string>) {
var temp_name = string("out_temp") + get_id()
pre += type_to_c(i.first->identifier.type) + " " + temp_name + ";\n"
result += temp_name + " = " + i.second + ";\n"
post += generate_identifier(i.first, null<ast_node>(), null<ast_node>()).one_string() + " = " + temp_name + ";\n"
})
if (is_top_level)
return pre + result + post
return pre + "{" + result + "}" + post
}
fun generate_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>): code_triple return generate(node->statement.child, enclosing_object, enclosing_func, defer_stack, false) + ";\n";
fun generate_declaration_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>, add_to_defer: bool): code_triple {
// add destruct to defer_stack
var identifier = node->declaration_statement.identifier
var ident_type = identifier->identifier.type
// we do the declaration in the pre now so that we can take it's address to close over it for things like recursive closures
// we only make it first if it's a function type though, so that global levels still work
var to_ret = code_triple(type_to_c(identifier->identifier.type) + " " + get_name(identifier), string(), string())
if (node->declaration_statement.expression) {
if (ident_type->indirection == 0 && (ident_type->is_adt() || (ident_type->is_object() && has_method(ident_type->type_def, "copy_construct", vector(get_ast_type(node->declaration_statement.expression)->clone_with_increased_indirection()))))) {
to_ret.pre += ";\n"
to_ret += generate(ast_statement_ptr(make_method_call(identifier, "copy_construct", vector(make_operator_call("&", vector(node->declaration_statement.expression))))), enclosing_object, enclosing_func, defer_stack, false)
} else {
if (ident_type->is_function()) {
to_ret.pre += string(";\n")
to_ret += code_triple() + get_name(identifier) + " = " + generate(node->declaration_statement.expression, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
} else {
// some shifting around to get it to work in all cases
// what cases?
to_ret.value = to_ret.pre
to_ret.pre = ""
to_ret += code_triple() + string(" = ") + generate(node->declaration_statement.expression, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
}
}
}
if (node->declaration_statement.init_method_call) {
to_ret.pre += ";\n"
to_ret += code_triple() + generate(node->declaration_statement.init_method_call, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
}
if (add_to_defer && ident_type->indirection == 0 && (ident_type->is_adt() || (ident_type->is_object() && has_method(ident_type->type_def, "destruct", vector<*type>()))))
defer_stack->top().second.push(ast_statement_ptr(make_method_call(identifier, "destruct", vector<*ast_node>())))
return to_ret
}
fun generate_assignment_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): code_triple {
return generate(node->assignment_statement.to, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false) + " = " + generate(node->assignment_statement.from, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
}
fun generate_if_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>): code_triple {
var if_str = code_triple("if (") + generate(node->if_statement.condition, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false) + ") {\n" + generate(node->if_statement.then_part, enclosing_object, enclosing_func, defer_stack, false).one_string() + "}"
if (node->if_statement.else_part)
if_str += code_triple(" else {\n") + generate(node->if_statement.else_part, enclosing_object, enclosing_func, defer_stack, false).one_string() + "}"
return if_str + "\n"
}
fun generate_while_loop(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>): code_triple {
// stick another stack on
defer_stack->push(make_pair(true, stack<*ast_node>()))
var condition = generate(node->while_loop.condition, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
var to_ret = code_triple("while (1) {\n") + condition.pre + "if(!" + condition.value + ") {" + condition.post + "break;}" + condition.post
to_ret += generate(node->while_loop.statement, enclosing_object, enclosing_func, defer_stack, false).one_string()
to_ret += generate_from_defer_stack(defer_stack, 1, enclosing_object, enclosing_func)
defer_stack->pop()
to_ret += "}\n"
return to_ret
}
fun generate_for_loop(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>): code_triple {
// stick another stack on
defer_stack->push(make_pair(true, stack<*ast_node>()))
// gotta take off last semicolon
var init = generate(node->for_loop.init, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
var cond = generate(node->for_loop.condition, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
var update = generate(node->for_loop.update, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
var do_update_name = string("do_update") + get_id()
var to_ret = string("{\n") + init.one_string() + "bool " + do_update_name + " = false;\nfor (;;) {\n"
to_ret += string("if (") + do_update_name + ") {" + update.one_string() + "}\n" + do_update_name + " = true;\n"
to_ret += cond.pre + "if (!" + cond.value + ") {" + cond.post + "break;}" + cond.post
to_ret += generate(node->for_loop.body, enclosing_object, enclosing_func, defer_stack, false).one_string()
to_ret += generate_from_defer_stack(defer_stack, 1, enclosing_object, enclosing_func).one_string()
defer_stack->pop()
to_ret += "}/*end inner for*/}/*end for's enclosing block*/\n"
return code_triple(to_ret)
}
fun generate_identifier(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): code_triple {
var pre = string()
var post = string()
// note that we get rid of references on closing over, (or maybe everything's kind of a reference)
// so we do else if here
if (enclosing_func && enclosing_func->function.closed_variables.contains(node))
return code_triple(pre + string("(*(closure_data->") + get_name(node) + "))" + post)
else if (get_ast_type(node)->is_ref) {
pre += "(*"
post += ")"
}
if (enclosing_object && get_ast_scope(enclosing_object)->contains_key(node->identifier.name) && get_ast_scope(enclosing_object)->get(node->identifier.name).contains(node))
return code_triple(pre + "(this->" + get_name(node) + ")" + post)
return code_triple(pre + get_name(node) + post)
}
fun generate_return_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>): code_triple {
var return_value = node->return_statement.return_value
var function_return_type = get_ast_type(enclosing_func)->return_type
var to_ret = code_triple()
if (return_value) {
var return_value_type = get_ast_type(return_value)
// always need a return temp so we don't destruct things the return depends on before they're calculated
// if we're returning an object, copy_construct a new one to return
// if we're returning a ref, we need to account for that in the temp type
// note the temp type is a pointer, not a ref so we don't have the deref/ref thing on return
// now use the function_return_type instead so we don't make a ref
// var temp_ident_type = return_value_type
var temp_ident_type = function_return_type
if (function_return_type->is_ref)
temp_ident_type = temp_ident_type->clone_with_increased_indirection()
var temp_ident = ast_identifier_ptr(string("temporary_return")+get_id(), temp_ident_type, null<ast_node>())
var declaration = ast_declaration_statement_ptr(temp_ident, null<ast_node>())
// have to pass false to the declaration generator, so can't do it through generate_statement
to_ret.pre = generate_declaration_statement(declaration, enclosing_object, enclosing_func, defer_stack, false).one_string() + ";\n"
if ((function_return_type->is_object() || return_value_type->is_object()) && !function_return_type->equality(return_value_type, false))
// note the clone with decreased indirection because of the clone with increased indirection above
error(ast_to_syntax[node], string("return type does not match: ") + function_return_type->to_string() + ", " + return_value_type->to_string());
if (!function_return_type->is_ref && return_value_type->indirection == 0 && (return_value_type->is_adt() || (return_value_type->is_object() && has_method(return_value_type->type_def, "copy_construct", vector(return_value_type->clone_with_indirection(1)))))) {
to_ret.pre += generate_statement(ast_statement_ptr(make_method_call(temp_ident, "copy_construct", vector(make_operator_call("&", vector(return_value))))), enclosing_object, enclosing_func, defer_stack).one_string()
} else {
var refamp = string()
if (function_return_type->is_ref)
refamp = "&"
to_ret.pre += (generate(temp_ident, enclosing_object, enclosing_func, defer_stack, false) + " = " + refamp + generate(return_value, enclosing_object, enclosing_func, defer_stack, false) + ";").one_string() + ";\n"
}
// make this new identifier the new return value
return_value = temp_ident
}
to_ret += code_triple("return")
if (return_value)
to_ret += code_triple(" ") + generate(return_value, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
// generate all in stack by passing -1, make sure added after we calculate the return value
to_ret.pre += generate_from_defer_stack(defer_stack, -1, enclosing_object, enclosing_func).one_string()
return to_ret
}
fun generate_branching_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>): code_triple {
// -2 means generate up through loop
var to_ret = generate_from_defer_stack(defer_stack, -2, enclosing_object, enclosing_func)
match(node->branching_statement.b_type) {
branching_type::break_stmt() return to_ret + string("break")
branching_type::continue_stmt() return to_ret + string("continue")
}
}
fun generate_from_defer_stack(defer_stack: *stack<pair<bool,stack<*ast_node>>>, num: int, enclosing_object: *ast_node, enclosing_func: *ast_node): code_triple {
var to_ret = code_triple()
if (num == -1)
num = defer_stack->size()
if (num == -2) {
num = 1
for (var i = 0; i < defer_stack->size(); i++;)
if (defer_stack->from_top(i).first)
break
else
num++
}
for (var i = 0; i < num; i++;) {
defer_stack->push(make_pair(false, stack<*ast_node>()))
/*defer_stack->from_top(i+1).second.for_each_reverse(fun(node: *ast_node) to_ret += generate(node, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false);)*/
defer_stack->from_top(i+1).second.for_each_reverse(fun(node: *ast_node) to_ret += generate(node, enclosing_object, enclosing_func, defer_stack, false);)
if (defer_stack->top().second.size())
to_ret += generate_from_defer_stack(defer_stack, 1, enclosing_object, enclosing_func);
defer_stack->pop()
}
return to_ret
}
fun generate_defer_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>): code_triple {
defer_stack->top().second.push(node->defer_statement.statement)
return code_triple("/*defer wanna know what*/")
}
fun generate_match_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>): code_triple {
var to_ret = code_triple("/* begin match */")
var matching_value = generate(node->match_statement.value, enclosing_object, enclosing_func, defer_stack, true)
to_ret.pre += matching_value.pre
to_ret.post += matching_value.post
node->match_statement.cases.for_each(fun(case_node: *ast_node) {
var option_str = generate(case_node->case_statement.option, enclosing_object, enclosing_func, defer_stack, false).one_string()
var to_ret_case = code_triple("/*case ") + option_str + "*/ if(" + matching_value.value + ".flag == " + string("enum_opt_") + option_str + ") {\n"
if (case_node->case_statement.unpack_ident) {
to_ret_case += generate_declaration_statement(ast_declaration_statement_ptr(case_node->case_statement.unpack_ident, null<ast_node>()), null<ast_node>(), null<ast_node>(), null<stack<pair<bool,stack<*ast_node>>>>(), false).one_string()
to_ret_case += string(" = ") + matching_value.value + ".data." + option_str + ";\n"
} else {
to_ret_case += "/*no unpack_ident*/\n"
}
to_ret_case += generate(case_node->case_statement.statement, enclosing_object, enclosing_func, defer_stack, false).one_string() + "\n}\n"
to_ret += to_ret_case.one_string()
})
return to_ret
}
fun generate_cast(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>, need_variable: bool): code_triple {
return code_triple("(") + type_to_c(node->cast.to_type) + ")(" + generate(node->cast.value, enclosing_object, enclosing_func, defer_stack, false) + ")"
}
fun generate_value(node: *ast_node, need_variable: bool): code_triple {
var value = node->value.string_value
var to_ret = string()
if (value[0] != '"') {
to_ret = value;
} else {
to_ret = string("\"")
var triple_quoted = value.slice(0,3) == "\"\"\""
if (triple_quoted)
value = value.slice(3,-4)
else
value = value.slice(1,-2)
value.for_each(fun(c: char) {
if (c == '\n')
to_ret += "\\n"
else if (c == '"' && triple_quoted)
to_ret += "\\\""
else
to_ret += c
})
to_ret += "\""
}
if (need_variable) {
var temp_ident = ast_identifier_ptr(string("temporary_value")+get_id(), get_ast_type(node), null<ast_node>())
var declaration = ast_declaration_statement_ptr(temp_ident, null<ast_node>())
// have to pass false to the declaration generator, so can't do it through generate_statement
var trip_ret = code_triple()
// trip_ret.pre += generate_declaration_statement(declaration, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false).one_string() + " = " + to_ret + ";\n"
// trip_ret.value = generate_identifier(temp_ident, enclosing_object, enclosing_func).one_string()
trip_ret.pre += generate_declaration_statement(declaration, null<ast_node>(), null<ast_node>(), null<stack<pair<bool,stack<*ast_node>>>>(), false).one_string() + " = " + to_ret + ";\n"
trip_ret.value = generate_identifier(temp_ident, null<ast_node>(), null<ast_node>()).one_string()
return trip_ret
}
return code_triple(to_ret)
}
fun generate_code_block(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>): code_triple {
var to_ret = code_triple("{\n")
// stick another stack on
defer_stack->push(make_pair(false, stack<*ast_node>()))
node->code_block.children.for_each(fun(child: *ast_node) to_ret += generate(child, enclosing_object, enclosing_func, defer_stack, false).one_string();)
to_ret += generate_from_defer_stack(defer_stack, 1, enclosing_object, enclosing_func)
defer_stack->pop()
return to_ret + "}"
}
// this generates the function as a value, not the actual function
fun generate_function(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, as_value: bool, need_variable: bool): code_triple {
if (as_value) {
var closed_vars = node->function.closed_variables
if (closed_vars.size() == 0)
return code_triple(string("((") + type_to_c(node->function.type) + "){(void*)0,(void*)" + get_name(node) + "})")
var temp_closure_struct = string("closure_struct_temp") + get_id()
var to_ret = code_triple()
var closure_type_str = get_closure_struct_type(closed_vars)
to_ret.pre += closure_type_str + " " + temp_closure_struct + " = (" + closure_type_str + "){"
closed_vars.for_each(fun(i: *ast_node) {
// note that we get/have gotten rid of refs here, or maybe more accurately, everything is a ref
// should be a variable anyway?
to_ret.pre += string(".") + get_name(i) + "=(void*)&" + generate(i, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), true).one_string() + ","
})
to_ret.pre += "};\n"
return to_ret + string("((") + type_to_c(node->function.type) + "){(void*)&" + temp_closure_struct + ",(void*)" + get_name(node) + "})"
}
return code_triple(get_name(node))
}
fun generate_function_call(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, need_variable: bool): code_triple {
var func_name = string()
var call_string = code_triple()
var func_return_type = get_ast_type(node)
// handle the obj.method() style of method call
var dot_style_method_call = is_function_call(node->function_call.func) &&
is_function(node->function_call.func->function_call.func) &&
(node->function_call.func->function_call.func->function.name == "->" || node->function_call.func->function_call.func->function.name == ".") &&
is_function(node->function_call.func->function_call.parameters[1]) &&
(is_type_def(get_ast_scope(node->function_call.func->function_call.parameters[1])->get(string("~enclosing_scope"))[0]) ||
// or if it's a templated method (yes, this has gotten uuuuugly)
is_type_def(get_ast_scope(get_ast_scope(node->function_call.func->function_call.parameters[1])->get(string("~enclosing_scope"))[0])->get(string("~enclosing_scope"))[0]) ||
// or it's in an adt
is_adt_def(get_ast_scope(node->function_call.func->function_call.parameters[1])->get(string("~enclosing_scope"))[0]))
// should get uglier when we have to figure out if it's just an inside lambda
if (dot_style_method_call) {
func_name = generate_function(node->function_call.func->function_call.parameters[1], enclosing_object, enclosing_func, false, false).one_string()
// don't add & if it was ->
if (node->function_call.func->function_call.func->function.name == ".")
call_string += "&"
// having a null defer stack should be ok, as the only things we should get through here are identifiers and function calls
// XXX should it? wouldn't function calls be a problem?
// should this be true if ref?
call_string += generate(node->function_call.func->function_call.parameters[0], enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), true)
} else if (is_identifier(node->function_call.func) || is_function(node->function_call.func)) {
// we handle the case when it's not this later, i.e. it's a lambda returned from another function or something
func_name = generate_function(node->function_call.func, enclosing_object, enclosing_func, false, false).one_string()
}
// handle method call from inside method of same object
if (!dot_style_method_call && enclosing_object) {
var methods = enclosing_object->type_def.methods
for (var i = 0; i < methods.size; i++;) {
if (methods[i] == node->function_call.func || (is_template(methods[i]) && methods[i]->template.instantiated.contains(node->function_call.func))) {
if (enclosing_func && enclosing_func->function.closed_variables.size())
call_string += "(*(closure_data->this))";
else
call_string += "this";
break
}
}
}
var parameters = node->function_call.parameters
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 code_triple("(") + generate(parameters[0], enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false) + func_name + generate(parameters[1], enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false) + string(")")
if ( parameters.size == 2 && (func_name == "||" || func_name == "&&")) {
var first = generate(parameters[0], enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
var second = generate(parameters[1], enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
var result = code_triple()
result.pre += first.pre;
var temp_bool = string("temp_bool") + get_id()
result.pre += string("bool ") + temp_bool + " = " + first.value + ";\n"
result.pre += first.post;
if (func_name == "||")
result.pre += string("if (!") + temp_bool + ") {"
else
result.pre += string("if (") + temp_bool + ") {"
result.pre += second.pre
result.pre += temp_bool + " = " + second.value + ";\n"
result.pre += second.post
result.pre += "}"
result.value = temp_bool
return result
}
// don't propegate enclosing function down right of access
// XXX what about enclosing object? should it be the thing on the left?
if (func_name == "." || func_name == "->") {
// special case right hand side is an adt to access inside of adt
var in_between = string()
if (get_ast_type(parameters[0])->is_adt())
in_between = "data."
return code_triple("(") + generate(parameters[0], enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false) + func_name + in_between + generate(parameters[1], null<ast_node>(), null<ast_node>(), null<stack<pair<bool,stack<*ast_node>>>>(), false) + string(")")
}
if (func_name == "[]")
return code_triple("(") + generate(parameters[0], enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false) + "[" + generate(parameters[1], enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false) + string("])")
// the post ones need to be post-ed specifically, and take the p off
if (func_name == "++p" || func_name == "--p")
return code_triple("(") + generate(parameters[0], enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false) + ")" + func_name.slice(0,-2)
// So we don't end up copy_constructing etc, we just handle the unary operators right here
// note also the passing down need_variable for &
if (func_name == "*" || func_name == "&")
return code_triple("(") + func_name + generate(parameters[0], enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), func_name == "&") + ")"
// for checking if we pass in a ref
var func_type = get_ast_type(node->function_call.func)
// regular parameter generation
// parameters.for_each(fun(param: *ast_node) {
for (var i = 0; i < parameters.size; i++;) {
var param = parameters[i]
var in_function_param_type = func_type->parameter_types[i]
if (call_string != "")
call_string += ", "
if (in_function_param_type->is_ref)
call_string += "&"
var param_type = get_ast_type(param)
if (!in_function_param_type->is_ref && param_type->indirection == 0 && (param_type->is_adt() || (param_type->is_object() && has_method(param_type->type_def, "copy_construct", vector(param_type->clone_with_indirection(1)))))) {
var temp_ident = ast_identifier_ptr(string("temporary_param")+get_id(), param_type->clone_without_ref(), null<ast_node>())
var declaration = ast_declaration_statement_ptr(temp_ident, null<ast_node>())
// have to pass false to the declaration generator, so can't do it through generate_statement
call_string.pre += generate_declaration_statement(declaration, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false).one_string() + ";\n"
call_string.pre += generate_statement(ast_statement_ptr(make_method_call(temp_ident, "copy_construct", vector(make_operator_call("&", vector(param))))), enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>()).one_string()
call_string += generate(temp_ident, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
} else {
call_string += generate(param, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), in_function_param_type->is_ref)
}
}
var pre_call = string()
// temporary returns if we're asked for them or we need them for destruct
var needs_temp_for_destruct = func_return_type->indirection == 0 && (func_return_type->is_adt() || (func_return_type->is_object() && has_method(func_return_type->type_def, "destruct", vector<*type>())))
if (!func_return_type->is_ref && (needs_temp_for_destruct || (!func_return_type->is_void() && need_variable)) ) {
// kind of ugly combo here of
var temp_ident = ast_identifier_ptr(string("temporary_return")+get_id(), func_return_type, null<ast_node>())
var declaration = ast_declaration_statement_ptr(temp_ident, null<ast_node>())
// have to pass false to the declaration generator, so can't do it through generate_statement
call_string.pre += generate_declaration_statement(declaration, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false).one_string() + ";\n"
pre_call = generate_identifier(temp_ident, enclosing_object, enclosing_func).one_string()
// move destruct condition inside
if (needs_temp_for_destruct)
call_string.post += generate_statement(ast_statement_ptr(make_method_call(temp_ident, "destruct", vector<*ast_node>())), enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>()).one_string()
}
var ref_pre = string()
var ref_post = string()
if (func_return_type->is_ref) {
ref_pre += "(*"
ref_post += ")"
}
if (!is_function(node->function_call.func) || node->function_call.func->function.closed_variables.size()) {
// not function, so we must be an identifier or function call return or something
/*println(get_ast_name(node->function_call.func) + " is not a function! must be a lambda or something")*/
if (!dot_style_method_call) {
// lambda
if (pre_call == "" && (!func_return_type->is_void() || func_return_type->indirection)) {
var temp_ident = ast_identifier_ptr(string("temporary_return")+get_id(), func_return_type, null<ast_node>())
var declaration = ast_declaration_statement_ptr(temp_ident, null<ast_node>())
// have to pass false to the declaration generator, so can't do it through generate_statement
call_string.pre += generate_declaration_statement(declaration, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false).one_string() + ";\n"
pre_call = generate_identifier(temp_ident, enclosing_object, enclosing_func).one_string()
}
var name_temp = generate(node->function_call.func, enclosing_object, enclosing_func, null<stack<pair<bool,stack<*ast_node>>>>(), false)
call_string.pre += name_temp.pre
call_string.post += name_temp.post
func_name = name_temp.value
// should not have return var because is void
if (pre_call == "") {
var func_type = get_ast_type(node->function_call.func)
call_string.pre += string("if (")+func_name+".data) ((" + type_to_c(func_type) + "_with_data) "+func_name+".func)("+func_name +".data"
if (call_string.value != "")
call_string.pre += string(",") + call_string.value
call_string.pre += ");\n"
call_string.pre += string("else ((") + type_to_c(func_type) + "_without_data) " + func_name+".func)(" + call_string.value + ");\n"
call_string.value = ""
} else {
var func_type = get_ast_type(node->function_call.func)
call_string.pre += string("if (")+func_name+".data) " + pre_call + " = ((" + type_to_c(func_type) + "_with_data) "+func_name+".func)("+func_name +".data"
if (call_string.value != "")
call_string.pre += string(",") + call_string.value
call_string.pre += ");\n"
call_string.pre += string("else ") + pre_call + " = ((" + type_to_c(func_type) + "_without_data) " + func_name+".func)(" + call_string.value + ");\n"
call_string.value = pre_call
}
call_string.value = ref_pre + call_string.value + ref_post
return call_string
}
}
if (pre_call != "") {
call_string.pre += pre_call + " = " + func_name + "(" + call_string.value + ");"
call_string.value = pre_call
} else {
call_string.value = func_name + "(" + call_string.value + ")"
}
call_string.value = ref_pre + call_string.value + ref_post
return call_string
}
fun generate_compiler_intrinsic(node: *ast_node): code_triple {
if (node->compiler_intrinsic.intrinsic == "sizeof") {
if (node->compiler_intrinsic.parameters.size || node->compiler_intrinsic.type_parameters.size != 1)
error("wrong parameters to sizeof compiler intrinsic")
return code_triple("sizeof(") + type_to_c(node->compiler_intrinsic.type_parameters[0]) + ")"
}
error(node->compiler_intrinsic.intrinsic + ": unknown intrinsic")
return code_triple("ERROR")
}
// for now, anyway
fun generate(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, defer_stack: *stack<pair<bool,stack<*ast_node>>>, need_variable: bool): code_triple {
if (!node) return code_triple("/*NULL*/")
match (*node) {
ast_node::if_comp(backing) return generate_if_comp(node, enclosing_object, enclosing_func, defer_stack)
ast_node::simple_passthrough(backing) return code_triple() + generate_simple_passthrough(node, false)
ast_node::statement(backing) return generate_statement(node, enclosing_object, enclosing_func, defer_stack)
ast_node::declaration_statement(backing) return generate_declaration_statement(node, enclosing_object, enclosing_func, defer_stack, true)
ast_node::assignment_statement(backing) return generate_assignment_statement(node, enclosing_object, enclosing_func)
ast_node::if_statement(backing) return generate_if_statement(node, enclosing_object, enclosing_func, defer_stack)
ast_node::while_loop(backing) return generate_while_loop(node, enclosing_object, enclosing_func, defer_stack)
ast_node::for_loop(backing) return generate_for_loop(node, enclosing_object, enclosing_func, defer_stack)
ast_node::function(backing) return generate_function(node, enclosing_object, enclosing_func, true, need_variable)
ast_node::function_call(backing) return generate_function_call(node, enclosing_object, enclosing_func, need_variable)
ast_node::compiler_intrinsic(backing) return generate_compiler_intrinsic(node)
ast_node::code_block(backing) return generate_code_block(node, enclosing_object, enclosing_func, defer_stack)
ast_node::return_statement(backing) return generate_return_statement(node, enclosing_object, enclosing_func, defer_stack)
ast_node::branching_statement(backing) return generate_branching_statement(node, enclosing_object, enclosing_func, defer_stack)
ast_node::defer_statement(backing) return generate_defer_statement(node, enclosing_object, enclosing_func, defer_stack)
ast_node::match_statement(backing) return generate_match_statement(node, enclosing_object, enclosing_func, defer_stack)
ast_node::cast(backing) return generate_cast(node, enclosing_object, enclosing_func, defer_stack, need_variable)
ast_node::value(backing) return generate_value(node, need_variable)
ast_node::identifier(backing) return generate_identifier(node, enclosing_object, enclosing_func)
}
return code_triple("/* COULD NOT GENERATE */")
}
fun type_decoration(type: *type): string {
var indirection = string()
if (type->is_ref) indirection += "ref_"
for (var i = 0; i < type->indirection; i++;) indirection += "p"
if (type->indirection) indirection += "_"
match (type->base) {
base_type::none() return indirection + string("none")
base_type::template() return indirection + string("template")
base_type::template_type() return indirection + string("template_type")
base_type::void_return() return indirection + string("void")
base_type::boolean() return indirection + string("bool")
base_type::character() return indirection + string("char")
base_type::ucharacter() return indirection + string("uchar")
base_type::short_int() return indirection + string("short")
base_type::ushort_int() return indirection + string("ushort")
base_type::integer() return indirection + string("int")
base_type::uinteger() return indirection + string("uint")
base_type::long_int() return indirection + string("long")
base_type::ulong_int() return indirection + string("ulong")
base_type::floating() return indirection + string("float")
base_type::double_precision() return indirection + string("double")
base_type::object() return cify_name(type->type_def->type_def.name)
base_type::adt() return type->type_def->adt_def.name
base_type::function() {
var temp = indirection + string("function_")
type->parameter_types.for_each(fun(parameter_type: *type) temp += type_decoration(parameter_type) + "_";)
return indirection + temp + "_" + type_decoration(type->return_type)
}
}
return string("impossible type") + indirection
}
fun type_to_c(type: *type): string {
var indirection = string()
if (type->is_ref) indirection += "/*ref*/ *"
for (var i = 0; i < type->indirection; i++;) indirection += "*"
match (type->base) {
base_type::none() return string("none") + indirection
base_type::template() return string("template") + indirection
base_type::template_type() return string("template_type") + indirection
base_type::void_return() return string("void") + indirection
base_type::boolean() return string("bool") + indirection
base_type::character() return string("char") + indirection
base_type::ucharacter() return string("unsigned char") + indirection
base_type::short_int() return string("short") + indirection
base_type::ushort_int() return string("unsigned short") + indirection
base_type::integer() return string("int") + indirection
base_type::uinteger() return string("unsigned int") + indirection
base_type::long_int() return string("long") + indirection
base_type::ulong_int() return string("unsigned long") + indirection
base_type::floating() return string("float") + indirection
base_type::double_precision() return string("double") + indirection
base_type::object() return get_name(type->type_def) + indirection
base_type::adt() return get_name(type->type_def) + indirection
base_type::function() {
// maybe disregard indirection in the future?
if (function_type_map.contains_key(*type))
return function_type_map[*type]
var temp_name = string("function_struct") + get_id()
var temp = string()
type->parameter_types.for_each(fun(parameter_type: *type) temp += string(", ") + type_to_c(parameter_type) + " ";)
var with_data = string("typedef ") + type_to_c(type->return_type) + " (*" + temp_name + "_with_data)(void*" + temp + ");\n"
var without_data = string("typedef ") + type_to_c(type->return_type) + " (*" + temp_name + "_without_data)(" + temp.slice(1,-1) + ");\n"
function_typedef_string += with_data
function_typedef_string += without_data
function_typedef_string += string("typedef struct {\nvoid* data;\n") + temp_name + "_with_data func;\n} " + temp_name + ";\n"
// again, the indirection
function_type_map[*type] = temp_name+indirection
return temp_name + indirection
}
}
return string("impossible type") + indirection
}
fun get_name(node: *ast_node): string {
if (ast_name_map.contains_key(node))
return ast_name_map[node]
var result = string("impossible name")
match (*node) {
ast_node::type_def(backing) {
var upper = backing.scope[string("~enclosing_scope")][0]
result = cify_name(backing.name)
if (is_template(upper))
upper->template.instantiated_map.reverse_get(node).for_each(fun(t: ref type) result += string("_") + type_decoration(&t);)
}
ast_node::adt_def(backing) {
result = backing.name
}
ast_node::function(backing) {
// be careful, operators like . come through this, but so do adt constructor funcs
if (!backing.body_statement && !backing.scope.contains_key(string("~enclosing_scope")))
return backing.name
if (backing.name == "main")
return backing.name
if (backing.is_extern)
return backing.name
result = "fun_"
var upper = backing.scope.get_with_default(string("~enclosing_scope"), vector(null<ast_node>()))[0]
if (upper && is_type_def(upper))
result += get_name(upper) + "_"
result += cify_name(node->function.name)
node->function.parameters.for_each(fun(param: *ast_node) result += string("_") + type_decoration(param->identifier.type);)
}
ast_node::identifier(backing) {
if (backing.name == "this")
return backing.name
result = backing.name
}
}
if (result == "impossible name")
error("HUGE PROBLEMS")
// TODO keyword avoid seems not to work
if (ast_name_map.contains_value(result) || c_keyword_avoid.contains(result))
result += get_id()
/*println("HERE: " + result)*/
ast_name_map.set(node, result)
return result
}
fun cify_name(name: string): string {
var to_ret = string()
for (var i = 0; i < name.length(); i++;) {
var replaced = false
for (var j = longest_replacement; j > 0; j--;) {
if (i + j <= name.length() && replacement_map.contains_key(name.slice(i,i+j))) {
to_ret += replacement_map[name.slice(i,i+j)]
replaced = true
i += j-1;
break
}
}
if (!replaced)
to_ret += name[i]
}
return to_ret
}
}