2016-01-04 00:38:59 -05:00
import io:*
import mem:*
import map:*
2017-01-22 16:36:04 -05:00
import hash_map:*
2016-01-25 13:48:27 -05:00
import stack:*
2016-01-04 00:38:59 -05:00
import string:*
import util:*
import tree:*
import symbol:*
import ast_nodes:*
2016-07-03 01:55:32 -07:00
// for error with syntax tree
2016-07-03 15:32:45 -07:00
import pass_common:*
2016-01-20 13:50:40 -05:00
import poset:*
2016-01-04 00:38:59 -05:00
obj c_generator (Object) {
2016-01-31 19:29:08 -05:00
var id_counter: int
2016-04-30 15:38:28 -04:00
var ast_to_syntax: map<*ast_node, *tree<symbol>>
2017-01-24 22:11:33 -05:00
var ast_name_map: map<*ast_node, string>
2016-02-24 01:54:20 -05:00
var function_type_map: map<type, string>
2016-02-20 21:02:41 -05:00
var function_typedef_string: string
2016-02-22 16:18:55 -05:00
var closure_struct_definitions: string
2016-04-29 01:14:26 -04:00
var c_keyword_avoid: set<string>
2016-02-24 15:25:58 -05:00
var replacement_map: map<string, string>
var longest_replacement: int
2016-03-28 17:12:53 -04:00
var linker_string: string
2016-01-04 00:38:59 -05:00
fun construct(): *c_generator {
2016-01-31 19:29:08 -05:00
id_counter = 0
2016-04-30 15:38:28 -04:00
ast_to_syntax.construct()
2017-01-24 22:11:33 -05:00
ast_name_map.construct()
2016-02-24 01:54:20 -05:00
function_type_map.construct()
2016-02-22 16:18:55 -05:00
function_typedef_string.construct()
closure_struct_definitions.construct()
2016-03-28 17:12:53 -04:00
linker_string.construct()
2016-04-29 01:14:26 -04:00
c_keyword_avoid.construct()
c_keyword_avoid.add(string("extern"))
2016-02-24 15:25:58 -05:00
2017-10-22 21:41:58 -04:00
replacement_map.construct()
2016-02-24 15:25:58 -05:00
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")
2016-03-26 04:39:26 -04:00
replacement_map[string(" ")] = string("_")
2016-02-24 15:25:58 -05:00
replacement_map[string(".")] = string("dot")
replacement_map[string("->")] = string("arrow")
2017-10-22 21:41:58 -04:00
longest_replacement = 0
replacement_map.for_each(fun(key: string, value: string) {
if (key.length() > longest_replacement)
longest_replacement = key.length()
})
2016-01-04 00:38:59 -05:00
return this
}
fun copy_construct(old: *c_generator) {
2016-01-31 19:29:08 -05:00
id_counter = old->id_counter
2016-04-30 15:38:28 -04:00
ast_to_syntax.copy_construct(&old->ast_to_syntax)
2017-01-24 22:11:33 -05:00
ast_name_map.copy_construct(&old->ast_name_map)
2016-02-24 01:54:20 -05:00
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)
2016-04-29 01:14:26 -04:00
c_keyword_avoid.copy_construct(&old->c_keyword_avoid)
2016-02-24 15:25:58 -05:00
replacement_map.copy_construct(&old->replacement_map)
longest_replacement = old->longest_replacement
2016-03-28 17:12:53 -04:00
linker_string.copy_construct(&old->linker_string)
2016-01-04 00:38:59 -05:00
}
fun operator=(other: ref c_generator) {
destruct()
copy_construct(&other)
}
fun destruct() {
2016-04-30 15:38:28 -04:00
ast_to_syntax.destruct()
2017-01-24 22:11:33 -05:00
ast_name_map.destruct()
2016-02-24 01:54:20 -05:00
function_type_map.destruct()
function_typedef_string.destruct()
closure_struct_definitions.destruct()
2016-04-29 01:14:26 -04:00
c_keyword_avoid.destruct()
2016-02-24 15:25:58 -05:00
replacement_map.destruct()
2016-03-28 17:12:53 -04:00
linker_string.destruct()
2016-01-04 00:38:59 -05:00
}
2016-02-07 16:22:55 -05:00
fun get_id(): string return to_string(id_counter++);
2016-06-26 04:44:54 -07:00
fun generate_function_prototype_and_header(child: *ast_node, enclosing_object: *ast_node, is_lambda: bool):pair<string,string> {
2016-03-19 21:45:07 -04:00
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"
}
2016-04-29 01:14:26 -04:00
var decorated_name = string()
if (backing.is_extern)
decorated_name = backing.name
else
2017-10-23 00:06:25 -04:00
decorated_name = generate_function(child)
2016-03-19 21:45:07 -04:00
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)
})
2016-05-19 23:17:32 -07:00
if (backing.is_variadic) {
parameter_types += ", ..."
parameters += ", ..."
}
2016-07-06 22:46:57 -07:00
var possibly_static = string()
2016-07-09 15:08:57 -07:00
// commented out to fix phantom crash
/*if (!backing.is_extern && decorated_name != "main")*/
/*possibly_static = "static "*/
2016-07-06 22:46:57 -07:00
return make_pair(possibly_static + type_to_c(backing.type->return_type) + " " + decorated_name + "(" + parameter_types + ");\n",
possibly_static + type_to_c(backing.type->return_type) + " " + decorated_name + "(" + parameters + ")")
2016-03-19 21:45:07 -04:00
}
2016-04-30 15:38:28 -04:00
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"
2016-01-21 03:18:02 -05:00
var plain_typedefs: string = "\n/**Plain Typedefs**/\n"
2016-01-04 00:38:59 -05:00
var top_level_c_passthrough: string = ""
var variable_extern_declarations: string = ""
2016-01-20 13:50:40 -05:00
var structs: string = "\n/**Type Structs**/\n"
2016-02-22 16:18:55 -05:00
function_typedef_string = "\n/**Typedefs**/\n"
closure_struct_definitions = "\n/**Closure Struct Definitions**/\n"
2016-01-06 02:46:42 -05:00
var function_prototypes: string = "\n/**Function Prototypes**/\n"
var function_definitions: string = "\n/**Function Definitions**/\n"
var variable_declarations: string = "\n/**Variable Declarations**/\n"
2016-01-04 00:38:59 -05:00
2016-01-21 12:54:21 -05:00
// moved out from below so that it can be used for methods as well as regular functions (and eventually lambdas...)
2016-03-10 14:08:56 -05:00
var generate_function_definition = fun(child: *ast_node, enclosing_object: *ast_node, is_lambda: bool) {
2016-01-21 12:54:21 -05:00
var backing = child->function
2016-06-26 04:44:54 -07:00
var prototype_and_header = generate_function_prototype_and_header(child, enclosing_object, is_lambda)
2016-03-19 21:45:07 -04:00
function_prototypes += prototype_and_header.first
2016-04-29 01:14:26 -04:00
if (!backing.is_extern)
function_definitions += prototype_and_header.second
2016-03-19 21:45:07 -04:00
if (backing.body_statement) {
2017-10-23 00:06:25 -04:00
function_definitions += " {\n" + generate(backing.body_statement, enclosing_object, child, false)
2016-07-03 22:50:42 -07:00
function_definitions += ";\n}\n"
2016-04-29 01:14:26 -04:00
} else if (!backing.is_extern) {
2016-06-20 01:52:28 -07:00
error("Empty function statement and not extern - no ADTs anymore!")
2016-03-19 21:45:07 -04:00
}
2016-01-21 12:54:21 -05:00
}
2016-01-20 13:50:40 -05:00
var type_poset = poset<*ast_node>()
2016-01-04 00:38:59 -05:00
// iterate through asts
name_ast_map.for_each(fun(name: string, tree_pair: pair<*tree<symbol>,*ast_node>) {
// iterate through children for each ast
2016-03-10 04:49:38 -05:00
// 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]
2016-03-19 21:45:07 -04:00
if (enclosing_object_traverse && is_type_def(enclosing_object_traverse))
2016-03-10 14:08:56 -05:00
generate_function_definition(child, enclosing_object_traverse, true)
2016-03-10 04:49:38 -05:00
else
2016-03-10 14:08:56 -05:00
generate_function_definition(child, null<ast_node>(), true)
2016-03-10 04:49:38 -05:00
})
tree_pair.second->translation_unit.children.for_each(fun(child: *ast_node) {
2016-01-04 00:38:59 -05:00
match (*child) {
2017-10-22 21:41:58 -04:00
ast_node::if_comp(backing) error("if_comp not currently supported")
ast_node::simple_passthrough(backing) error("simple_passthrough deprecated")
2017-10-23 00:06:25 -04:00
ast_node::declaration_statement(backing) variable_declarations += generate_declaration_statement(child, null<ast_node>(), null<ast_node>()) + ";\n" // false - don't do defer
2016-04-30 16:52:56 -04:00
// shouldn't need to do anything with return, as the intrinsic should be something like link
ast_node::compiler_intrinsic(backing) generate_compiler_intrinsic(child)
2016-01-06 02:46:42 -05:00
ast_node::function(backing) {
// check for and add to parameters if a closure
2016-04-30 15:38:28 -04:00
generate_function_definition(child, null<ast_node>(), false)
2016-01-06 02:46:42 -05:00
}
2016-02-13 16:56:37 -05:00
ast_node::template(backing) {
2016-02-20 02:36:35 -05:00
backing.instantiated.for_each(fun(node: *ast_node) {
match (*node) {
2016-03-10 14:08:56 -05:00
ast_node::function(backing) generate_function_definition(node, null<ast_node>(), false)
2016-02-20 02:36:35 -05:00
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)
})
2016-02-13 16:56:37 -05:00
}
2016-02-20 02:36:35 -05:00
}
2016-02-01 05:35:08 -05:00
})
}
2016-01-20 13:50:40 -05:00
ast_node::type_def(backing) {
type_poset.add_vertex(child)
2016-02-07 16:22:55 -05:00
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)
})
2016-01-20 13:50:40 -05:00
}
2016-03-19 21:45:07 -04:00
ast_node::adt_def(backing) {
2016-06-20 01:52:28 -07:00
error("ADT remaining!")
2016-03-19 21:45:07 -04:00
}
2016-01-04 00:38:59 -05:00
}
})
})
2016-01-20 13:50:40 -05:00
type_poset.get_sorted().for_each(fun(vert: *ast_node) {
2017-10-22 21:41:58 -04:00
if (!is_type_def(vert))
error("no adt, but how did we get this far?")
2016-02-15 16:31:01 -05:00
var base_name = get_name(vert)
2016-06-15 22:26:03 -07:00
plain_typedefs += string("typedef ")
2017-10-22 21:41:58 -04:00
if (vert->type_def.is_union) {
2016-06-16 23:06:38 -07:00
plain_typedefs += "union "
structs += "union "
} else {
2016-06-15 22:26:03 -07:00
plain_typedefs += "struct "
structs += "struct "
2016-06-16 23:06:38 -07:00
}
2016-06-15 22:26:03 -07:00
plain_typedefs += base_name + "_dummy " + base_name + ";\n"
structs += base_name + "_dummy {\n"
2017-10-23 00:06:25 -04:00
vert->type_def.variables.for_each(fun(variable_declaration: *ast_node) structs += generate_declaration_statement(variable_declaration, null<ast_node>(), null<ast_node>()) + ";\n";)
2017-10-22 21:41:58 -04:00
// 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);
})
2016-01-21 12:54:21 -05:00
structs += "};\n"
2016-01-20 13:50:40 -05:00
})
2016-01-04 00:38:59 -05:00
2016-04-30 15:38:28 -04:00
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)
2016-02-22 16:18:55 -05:00
}
2017-10-23 00:06:25 -04:00
fun generate_declaration_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): string {
2016-01-15 19:10:52 -05:00
var identifier = node->declaration_statement.identifier
2016-01-29 22:46:09 -05:00
var ident_type = identifier->identifier.type
2016-02-25 14:24:55 -05:00
// 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
2017-10-23 00:06:25 -04:00
var to_ret = type_to_c(identifier->identifier.type) + " " + get_name(identifier)
2017-01-23 01:09:31 -05:00
if (identifier->identifier.is_extern)
2017-10-23 00:06:25 -04:00
to_ret = "extern " + to_ret
2016-01-31 19:29:08 -05:00
if (node->declaration_statement.expression) {
2016-06-26 04:44:54 -07:00
if (ident_type->is_function()) {
2017-10-23 00:06:25 -04:00
to_ret += ";\n"
to_ret += get_name(identifier) + " = " + generate(node->declaration_statement.expression, enclosing_object, enclosing_func, false)
2016-01-31 19:29:08 -05:00
} else {
2016-06-26 04:44:54 -07:00
// some shifting around to get it to work in all cases
// what cases?
2017-10-23 00:06:25 -04:00
to_ret += " = " + generate(node->declaration_statement.expression, enclosing_object, enclosing_func, false)
2016-01-31 19:29:08 -05:00
}
}
2016-02-25 14:24:55 -05:00
if (node->declaration_statement.init_method_call) {
2017-10-23 00:06:25 -04:00
to_ret += ";\n"
to_ret += generate(node->declaration_statement.init_method_call, enclosing_object, enclosing_func, false)
2016-02-25 14:24:55 -05:00
}
2016-01-17 01:10:09 -05:00
return to_ret
2016-01-15 19:10:52 -05:00
}
2017-10-23 00:06:25 -04:00
fun generate_assignment_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): string {
2016-06-26 04:44:54 -07:00
return generate(node->assignment_statement.to, enclosing_object, enclosing_func, false) + " = " + generate(node->assignment_statement.from, enclosing_object, enclosing_func, false)
2016-01-16 22:14:59 -05:00
}
2017-10-23 00:06:25 -04:00
fun generate_if_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): string {
var if_str = "if (" + generate(node->if_statement.condition, enclosing_object, enclosing_func, false) + ") {\n" + generate(node->if_statement.then_part, enclosing_object, enclosing_func, false) + "}"
2016-01-19 02:06:30 -05:00
if (node->if_statement.else_part)
2017-10-23 00:06:25 -04:00
if_str += " else {\n" + generate(node->if_statement.else_part, enclosing_object, enclosing_func, false) + "}"
2016-01-19 02:06:30 -05:00
return if_str + "\n"
}
2017-10-23 00:06:25 -04:00
fun generate_while_loop(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): string {
return "while (" + generate(node->while_loop.condition, enclosing_object, enclosing_func, false) + ")\n" + generate(node->while_loop.statement, enclosing_object, enclosing_func, false)
2016-01-19 03:16:16 -05:00
}
2017-10-23 00:06:25 -04:00
fun generate_for_loop(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): string {
2016-01-19 11:47:09 -05:00
// gotta take off last semicolon
2017-10-23 00:06:25 -04:00
var init = string(";")
2016-06-25 16:02:53 -07:00
if (node->for_loop.init)
2016-06-26 04:44:54 -07:00
init = generate(node->for_loop.init, enclosing_object, enclosing_func, false)
2017-10-23 00:06:25 -04:00
var cond = string(";")
2016-06-25 16:02:53 -07:00
if (node->for_loop.condition)
2016-06-26 04:44:54 -07:00
cond = generate(node->for_loop.condition, enclosing_object, enclosing_func, false)
2017-01-23 23:00:26 -05:00
var update = string()
if (node->for_loop.update) {
2017-10-23 00:06:25 -04:00
update = generate(node->for_loop.update, enclosing_object, enclosing_func, false)
2017-01-23 23:00:26 -05:00
if (update.length() < 2)
error("update less than 2! Likely legal, but need easy compiler mod here")
update = update.slice(0,-2)
}
2017-10-23 00:06:25 -04:00
var to_ret = string("for (") + init + cond + "; " + update + ")\n" +
generate(node->for_loop.body, enclosing_object, enclosing_func, false)
return to_ret
2016-01-19 11:47:09 -05:00
}
2017-10-23 00:06:25 -04:00
fun generate_identifier(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): string {
2017-06-06 01:33:18 -04:00
if (get_ast_type(node)->is_ref)
2017-01-20 01:11:06 -05:00
error("still existin ref in identifier")
2016-02-09 02:59:38 -05:00
if (enclosing_object && get_ast_scope(enclosing_object)->contains_key(node->identifier.name) && get_ast_scope(enclosing_object)->get(node->identifier.name).contains(node))
2017-10-23 00:06:25 -04:00
return "(this->" + get_name(node) + ")"
return get_name(node)
2016-01-16 22:14:59 -05:00
}
2017-10-23 00:06:25 -04:00
fun generate_return_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): string {
2016-01-30 22:04:37 -05:00
var return_value = node->return_statement.return_value
2016-03-01 14:54:58 -05:00
var function_return_type = get_ast_type(enclosing_func)->return_type
2016-06-22 01:41:57 -07:00
2016-07-03 01:55:32 -07:00
if (!function_return_type->is_void() && !function_return_type->equality(get_ast_type(return_value), false))
2017-06-21 02:12:00 -04:00
error(ast_to_syntax[node], "return value type does not match function return type" + function_return_type->to_string() + " versus " + get_ast_type(return_value)->to_string())
2016-06-22 01:41:57 -07:00
if (function_return_type->is_ref)
2017-01-20 01:11:06 -05:00
error("still exsisting ref in return")
2017-08-27 14:15:09 -04:00
2016-06-22 01:41:57 -07:00
if (return_value)
2017-10-23 00:06:25 -04:00
return "return " + generate(return_value, enclosing_object, enclosing_func, false)
return string("return")
2016-01-25 13:48:27 -05:00
}
2017-10-23 00:06:25 -04:00
fun generate_branching_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): string {
2016-01-24 17:31:41 -05:00
match(node->branching_statement.b_type) {
2017-10-23 00:06:25 -04:00
branching_type::break_stmt() return string("break")
branching_type::continue_stmt() return string("continue")
2016-01-24 17:31:41 -05:00
}
}
2017-10-23 00:06:25 -04:00
fun generate_defer_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): string {
2016-06-15 01:36:59 -07:00
error("Unremoved defer!")
2016-01-25 13:48:27 -05:00
}
2017-10-23 00:06:25 -04:00
fun generate_match_statement(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): string {
2016-06-26 04:44:54 -07:00
error("remaining match")
2016-03-19 21:45:07 -04:00
}
2017-10-23 00:06:25 -04:00
fun generate_cast(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): string {
return "((" + type_to_c(node->cast.to_type) + ")(" + generate(node->cast.value, enclosing_object, enclosing_func, false) + "))"
2016-04-18 22:56:29 -04:00
}
2017-10-23 00:06:25 -04:00
fun generate_value(node: *ast_node): string {
2016-02-15 23:12:56 -05:00
var value = node->value.string_value
2016-03-12 03:23:43 -05:00
var to_ret = string()
if (value[0] != '"') {
to_ret = value;
} else {
to_ret = string("\"")
2016-03-26 04:39:26 -04:00
var triple_quoted = value.slice(0,3) == "\"\"\""
if (triple_quoted)
2016-03-12 03:23:43 -05:00
value = value.slice(3,-4)
2016-03-19 21:45:07 -04:00
else
2016-03-12 03:23:43 -05:00
value = value.slice(1,-2)
value.for_each(fun(c: char) {
if (c == '\n')
to_ret += "\\n"
2016-03-26 04:39:26 -04:00
else if (c == '"' && triple_quoted)
2016-03-12 03:23:43 -05:00
to_ret += "\\\""
else
to_ret += c
})
to_ret += "\""
}
2017-10-23 00:06:25 -04:00
return to_ret
2016-02-15 23:12:56 -05:00
}
2017-10-23 00:06:25 -04:00
fun generate_code_block(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node): string {
var to_ret = string("{\n")
node->code_block.children.for_each(fun(child: *ast_node) to_ret += generate(child, enclosing_object, enclosing_func, false) + ";\n";)
2016-01-08 00:33:05 -05:00
return to_ret + "}"
2016-01-07 02:52:22 -05:00
}
2016-01-20 13:50:40 -05:00
// this generates the function as a value, not the actual function
2017-10-23 00:06:25 -04:00
fun generate_function(node: *ast_node): string {
return get_name(node)
2016-01-11 23:41:09 -05:00
}
2017-10-23 00:06:25 -04:00
fun generate_function_call(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, need_variable: bool): string {
2016-02-29 19:18:22 -05:00
var func_name = string()
2017-10-23 00:06:25 -04:00
var call_string = string()
2016-01-31 19:29:08 -05:00
var func_return_type = get_ast_type(node)
2017-09-02 09:12:25 -04:00
if (func_return_type->is_ref)
2017-08-18 10:05:12 -04:00
error("still ref in function calling")
2016-01-24 01:49:14 -05:00
2017-08-27 14:15:09 -04:00
if (is_dot_style_method_call(node)) {
2017-10-23 00:06:25 -04:00
func_name = generate_function(node->function_call.func->function_call.parameters[1])
2016-01-24 01:02:56 -05:00
// don't add & if it was ->
if (node->function_call.func->function_call.func->function.name == ".")
2016-01-27 18:56:44 -05:00
call_string += "&"
2016-03-12 03:23:43 -05:00
2016-06-26 04:44:54 -07:00
call_string += generate(node->function_call.func->function_call.parameters[0], enclosing_object, enclosing_func, true)
2017-08-18 10:05:12 -04:00
} else {
2017-10-23 00:06:25 -04:00
func_name = generate(node->function_call.func, enclosing_object, enclosing_func, false)
2017-08-18 10:05:12 -04:00
2017-08-23 10:12:00 -04:00
// handle method call from inside method of same object
if (enclosing_object && method_in_object(node->function_call.func, enclosing_object)) {
2017-08-18 10:05:12 -04:00
call_string += "this";
2016-03-09 15:21:50 -05:00
}
}
2016-01-24 01:49:14 -05:00
2016-01-19 11:47:09 -05:00
var parameters = node->function_call.parameters
2016-03-09 15:21:50 -05:00
if ( parameters.size == 2 && (func_name == "+" || func_name == "-" || func_name == "*" || func_name == "/"
|| func_name == "<" || func_name == ">" || func_name == "<=" || func_name == ">="
2016-04-19 18:39:01 -04:00
|| func_name == "==" || func_name == "!=" || func_name == "%" || func_name == "^"
2017-01-23 01:09:31 -05:00
|| func_name == "|" || func_name == "&" || func_name == ">>" || func_name == "<<"
2016-01-28 12:55:51 -05:00
))
2017-10-23 00:06:25 -04:00
return "(" + generate(parameters[0], enclosing_object, enclosing_func, false) + func_name + generate(parameters[1], enclosing_object, enclosing_func, false) + ")"
2016-03-09 15:21:50 -05:00
if ( parameters.size == 2 && (func_name == "||" || func_name == "&&")) {
2016-06-25 23:56:07 -07:00
error("Remaining || or &&")
2016-03-09 15:21:50 -05:00
}
2016-01-23 20:39:06 -05:00
// don't propegate enclosing function down right of access
2016-03-08 16:04:59 -05:00
// XXX what about enclosing object? should it be the thing on the left?
2016-03-19 21:45:07 -04:00
if (func_name == "." || func_name == "->") {
2017-10-23 00:06:25 -04:00
return "(" + generate(parameters[0], enclosing_object, enclosing_func, false) + func_name + generate(parameters[1], null<ast_node>(), null<ast_node>(), false) + ")"
2016-03-19 21:45:07 -04:00
}
2016-03-02 20:23:25 -05:00
if (func_name == "[]")
2017-10-23 00:06:25 -04:00
return "(" + generate(parameters[0], enclosing_object, enclosing_func, false) + "[" + generate(parameters[1], enclosing_object, enclosing_func, false) + "])"
2016-01-19 03:16:16 -05:00
// the post ones need to be post-ed specifically, and take the p off
if (func_name == "++p" || func_name == "--p")
2017-10-23 00:06:25 -04:00
return "(" + generate(parameters[0], enclosing_object, enclosing_func, false) + ")" + func_name.slice(0,-2)
2016-01-24 01:49:14 -05:00
2016-01-30 23:59:21 -05:00
// So we don't end up copy_constructing etc, we just handle the unary operators right here
2016-03-12 03:23:43 -05:00
// note also the passing down need_variable for &
2016-01-30 23:59:21 -05:00
if (func_name == "*" || func_name == "&")
2017-10-23 00:06:25 -04:00
return "(" + func_name + generate(parameters[0], enclosing_object, enclosing_func, func_name == "&") + ")"
2016-01-30 23:59:21 -05:00
2016-03-01 14:54:58 -05:00
var func_type = get_ast_type(node->function_call.func)
2016-01-24 01:49:14 -05:00
// regular parameter generation
2016-03-01 14:54:58 -05:00
for (var i = 0; i < parameters.size; i++;) {
var param = parameters[i]
2016-05-19 23:17:32 -07:00
var in_function_param_type = null<type>()
// grab type from param itself if we're out of param types (because variadic function)
if (i < func_type->parameter_types.size)
in_function_param_type = func_type->parameter_types[i]
else
in_function_param_type = get_ast_type(param)->clone_without_ref()
2016-01-11 23:41:09 -05:00
if (call_string != "")
call_string += ", "
2016-03-19 21:45:07 -04:00
2017-01-20 01:11:06 -05:00
if (in_function_param_type->is_ref) {
error(string("problem :") + (node->function_call.func) cast int + " " + get_fully_scoped_name(node->function_call.func) + ": still ref in function calling, func_type: " + func_type->to_string())
}
2016-01-30 23:59:21 -05:00
var param_type = get_ast_type(param)
2017-08-27 14:15:09 -04:00
call_string += generate(param, enclosing_object, enclosing_func, false)
2016-03-01 14:54:58 -05:00
}
2017-10-23 00:06:25 -04:00
call_string = func_name + "(" + call_string + ")"
2016-03-10 16:07:12 -05:00
return call_string
2016-01-11 23:41:09 -05:00
}
2017-08-27 14:15:09 -04:00
2017-10-23 00:06:25 -04:00
fun generate_compiler_intrinsic(node: *ast_node): string {
2016-04-28 18:47:53 -04:00
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")
2017-10-23 00:06:25 -04:00
return "sizeof(" + type_to_c(node->compiler_intrinsic.type_parameters[0]) + ")"
2016-04-30 16:52:56 -04:00
} else if (node->compiler_intrinsic.intrinsic == "link") {
2016-07-03 22:50:42 -07:00
node->compiler_intrinsic.parameters.for_each(fun(value: *ast_node) {
linker_string += string("-l") + value->value.string_value.slice(1,-2) + " "
2016-04-30 16:52:56 -04:00
})
2017-10-23 00:06:25 -04:00
return string()
2016-04-28 18:47:53 -04:00
}
error(node->compiler_intrinsic.intrinsic + ": unknown intrinsic")
2017-10-23 00:06:25 -04:00
return string("ERROR")
2016-04-28 18:47:53 -04:00
}
2016-01-07 02:52:22 -05:00
2016-01-04 02:00:06 -05:00
// for now, anyway
2017-10-23 00:06:25 -04:00
fun generate(node: *ast_node, enclosing_object: *ast_node, enclosing_func: *ast_node, need_variable: bool): string {
if (!node) return string("/*NULL*/")
2016-01-04 02:00:06 -05:00
match (*node) {
2017-10-22 21:41:58 -04:00
ast_node::declaration_statement(backing) return generate_declaration_statement(node, enclosing_object, enclosing_func)
2016-02-24 01:54:20 -05:00
ast_node::assignment_statement(backing) return generate_assignment_statement(node, enclosing_object, enclosing_func)
2016-06-26 04:44:54 -07:00
ast_node::if_statement(backing) return generate_if_statement(node, enclosing_object, enclosing_func)
ast_node::while_loop(backing) return generate_while_loop(node, enclosing_object, enclosing_func)
ast_node::for_loop(backing) return generate_for_loop(node, enclosing_object, enclosing_func)
2017-08-23 10:12:00 -04:00
ast_node::function(backing) return generate_function(node)
2016-03-12 03:23:43 -05:00
ast_node::function_call(backing) return generate_function_call(node, enclosing_object, enclosing_func, need_variable)
2016-04-28 18:47:53 -04:00
ast_node::compiler_intrinsic(backing) return generate_compiler_intrinsic(node)
2016-06-26 04:44:54 -07:00
ast_node::code_block(backing) return generate_code_block(node, enclosing_object, enclosing_func)
ast_node::return_statement(backing) return generate_return_statement(node, enclosing_object, enclosing_func)
ast_node::branching_statement(backing) return generate_branching_statement(node, enclosing_object, enclosing_func)
ast_node::defer_statement(backing) return generate_defer_statement(node, enclosing_object, enclosing_func)
ast_node::match_statement(backing) return generate_match_statement(node, enclosing_object, enclosing_func)
ast_node::cast(backing) return generate_cast(node, enclosing_object, enclosing_func)
2017-10-23 00:06:25 -04:00
ast_node::value(backing) return generate_value(node)
2016-02-24 01:54:20 -05:00
ast_node::identifier(backing) return generate_identifier(node, enclosing_object, enclosing_func)
2016-01-04 02:00:06 -05:00
}
2016-06-14 02:14:25 -07:00
error(string("COULD NOT GENERATE ") + get_ast_name(node))
2017-10-23 00:06:25 -04:00
return string("/* COULD NOT GENERATE */")
2016-01-04 02:00:06 -05:00
}
2016-01-13 21:09:28 -05:00
fun type_decoration(type: *type): string {
var indirection = string()
2017-01-20 01:11:06 -05:00
if (type->is_ref) error("still ref in type decoration") //indirection += "ref_"
2016-01-13 21:09:28 -05:00
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")
2016-04-29 16:19:23 -04:00
base_type::ucharacter() return indirection + string("uchar")
base_type::short_int() return indirection + string("short")
base_type::ushort_int() return indirection + string("ushort")
2016-01-13 21:09:28 -05:00
base_type::integer() return indirection + string("int")
2016-04-29 16:19:23 -04:00
base_type::uinteger() return indirection + string("uint")
base_type::long_int() return indirection + string("long")
base_type::ulong_int() return indirection + string("ulong")
2016-01-13 21:09:28 -05:00
base_type::floating() return indirection + string("float")
base_type::double_precision() return indirection + string("double")
2016-03-24 21:32:28 -04:00
base_type::object() return cify_name(type->type_def->type_def.name)
2016-01-13 21:09:28 -05:00
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
}
2016-01-06 02:46:42 -05:00
fun type_to_c(type: *type): string {
2016-01-10 18:26:31 -05:00
var indirection = string()
2017-01-20 01:11:06 -05:00
if (type->is_ref) error("still ref in type_to_c") //indirection += "/*ref*/ *"
2016-01-10 18:26:31 -05:00
for (var i = 0; i < type->indirection; i++;) indirection += "*"
2016-01-06 02:46:42 -05:00
match (type->base) {
2016-01-10 18:26:31 -05:00
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
2016-04-29 16:19:23 -04:00
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
2016-01-10 18:26:31 -05:00
base_type::integer() return string("int") + indirection
2016-04-29 16:19:23 -04:00
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
2016-01-10 18:26:31 -05:00
base_type::floating() return string("float") + indirection
base_type::double_precision() return string("double") + indirection
2016-03-19 21:45:07 -04:00
base_type::object() return get_name(type->type_def) + indirection
2016-01-06 02:46:42 -05:00
base_type::function() {
2016-02-24 01:54:20 -05:00
// maybe disregard indirection in the future?
2016-06-14 02:14:25 -07:00
type = type->clone_with_indirection(0,false)
if (!function_type_map.contains_key(*type)) {
2017-01-26 23:58:48 -05:00
var temp_name = string("function") + get_id()
2016-06-14 02:14:25 -07:00
var temp = string()
type->parameter_types.for_each(fun(parameter_type: *type) temp += string(", ") + type_to_c(parameter_type) + " ";)
2017-01-26 23:58:48 -05:00
if (type->is_raw) {
function_typedef_string += string("typedef ") + type_to_c(type->return_type) + " (*" + temp_name + ")(" + temp.slice(1,-1) + ");\n"
} else {
2017-08-15 19:53:17 -04:00
error(type->to_string() + " is not raw!")
2017-08-15 01:55:44 -04:00
var with_data = string("/* not raw */ typedef ") + type_to_c(type->return_type) + " (*" + temp_name + "_with_data)(void*" + temp + ");\n"
2017-01-26 23:58:48 -05:00
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"
function_typedef_string += string("/* ") + type->to_string() + " */\n"
}
2016-06-14 02:14:25 -07:00
// again, the indirection
function_type_map[*type] = temp_name
}
return function_type_map[*type] + indirection
2016-01-06 02:46:42 -05:00
}
}
2016-01-10 18:26:31 -05:00
return string("impossible type") + indirection
2016-01-06 02:46:42 -05:00
}
2016-02-15 16:31:01 -05:00
fun get_name(node: *ast_node): string {
2017-01-24 22:11:33 -05:00
var maybe_it = ast_name_map.get_ptr_or_null(node);
if (maybe_it)
return *maybe_it
2016-02-17 13:37:48 -05:00
var result = string("impossible name")
2016-06-11 00:45:18 -07:00
var make_unique = true
2016-02-15 16:31:01 -05:00
match (*node) {
ast_node::type_def(backing) {
2017-01-24 22:11:33 -05:00
var upper = backing.scope[string("~enclosing_scope")][0]
2016-03-24 21:32:28 -04:00
result = cify_name(backing.name)
2017-01-24 22:11:33 -05:00
if (is_template(upper))
upper->template.instantiated_map.reverse_get(node).for_each(fun(t: ref type) result += string("_") + type_decoration(&t);)
2016-03-19 21:45:07 -04:00
}
ast_node::adt_def(backing) {
2016-06-20 01:52:28 -07:00
error("shouldn't have adt")
2016-02-15 16:31:01 -05:00
}
ast_node::function(backing) {
2016-03-19 21:45:07 -04:00
// be careful, operators like . come through this, but so do adt constructor funcs
2016-06-11 00:45:18 -07:00
if ((backing.name == "main") || backing.is_extern || (!backing.body_statement && !backing.scope.contains_key(string("~enclosing_scope")))) {
result = backing.name
make_unique = false
} else {
result = "fun_"
2017-01-24 22:11:33 -05:00
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) + "_"
2016-06-11 00:45:18 -07:00
result += cify_name(node->function.name)
2017-01-24 22:11:33 -05:00
node->function.parameters.for_each(fun(param: *ast_node) result += string("_") + type_decoration(param->identifier.type);)
2016-06-11 00:45:18 -07:00
}
2016-02-15 16:31:01 -05:00
}
2016-02-17 13:59:10 -05:00
ast_node::identifier(backing) {
2017-01-23 01:09:31 -05:00
if (backing.name == "this" || backing.is_extern)
2016-06-11 00:45:18 -07:00
make_unique = false
2016-02-17 13:59:10 -05:00
result = backing.name
}
2016-02-15 16:31:01 -05:00
}
2016-02-17 13:37:48 -05:00
if (result == "impossible name")
2016-02-29 19:18:22 -05:00
error("HUGE PROBLEMS")
2016-04-29 01:14:26 -04:00
// TODO keyword avoid seems not to work
2017-01-24 22:11:33 -05:00
if (make_unique && (ast_name_map.contains_value(result) || c_keyword_avoid.contains(result)))
result += get_id()
ast_name_map.set(node, result)
2016-02-17 13:37:48 -05:00
return result
2016-02-15 16:31:01 -05:00
}
2016-02-24 15:25:58 -05:00
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
}
2016-01-04 00:38:59 -05:00
}