Introduced properties

private fun class_colors=(class_colors: Map[MClass, Int])

nitc :: SeparateErasureCompiler :: class_colors=

private fun class_ids=(class_ids: Map[MClass, Int])

nitc :: SeparateErasureCompiler :: class_ids=

private fun class_tables=(class_tables: Map[MClass, Array[nullable MClass]])

nitc :: SeparateErasureCompiler :: class_tables=

init defaultinit(mainmodule: MModule, modelbuilder: ModelBuilder, runtime_type_analysis: nullable RapidTypeAnalysis)

nitc :: SeparateErasureCompiler :: defaultinit

private fun retrieve_vt_bound(anchor: MClassType, mtype: nullable MType): MType

nitc :: SeparateErasureCompiler :: retrieve_vt_bound

private fun vt_tables=(vt_tables: Map[MClass, Array[nullable MPropDef]])

nitc :: SeparateErasureCompiler :: vt_tables=

Redefined properties

redef type SELF: SeparateErasureCompiler

nitc $ SeparateErasureCompiler :: SELF

Type of this instance, automatically specialized in every class
redef fun compile_class_if_universal(ccinfo: ClassCompilationInfo, v: SeparateCompilerVisitor): Bool

nitc $ SeparateErasureCompiler :: compile_class_if_universal

Given a MClass, if it's a universal class and if it needs to be handle
redef fun compile_class_to_c(mclass: MClass)

nitc $ SeparateErasureCompiler :: compile_class_to_c

Globally compile the table of the class mclass
redef fun compile_header_structs

nitc $ SeparateErasureCompiler :: compile_header_structs

Declaration of structures for live Nit types
redef fun compile_types

nitc $ SeparateErasureCompiler :: compile_types

Color and compile type structures and cast information
redef fun new_visitor: VISITOR

nitc $ SeparateErasureCompiler :: new_visitor

Initialize a visitor specific for a compiler engine

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
fun ==(other: nullable Object): Bool

core :: Object :: ==

Have self and other the same value?
type CLASS: Class[SELF]

core :: Object :: CLASS

The type of the class of self.
type SELF: Object

core :: Object :: SELF

Type of this instance, automatically specialized in every class
private var _class_conflict_graph: POSetConflictGraph[MClass]

nitc :: SeparateCompiler :: _class_conflict_graph

The conflict graph of classes used for coloration
private var _compiled_callref_thunk: HashSet[MMethodDef]

nitc :: AbstractCompiler :: _compiled_callref_thunk

All methods who already has a callref_thunk generated for
private var _compiled_null_types: Array[MNullableType]

nitc :: AbstractCompiler :: _compiled_null_types

Cache to avoid multiple compilation of NULL values
private var _extern_bodies: Array[ExternFile]

nitc :: AbstractCompiler :: _extern_bodies

List of additional files required to compile (FFI)
private var _files: Array[CodeFile]

nitc :: AbstractCompiler :: _files

The list of all associated files
private var _files_to_copy: Array[String]

nitc :: AbstractCompiler :: _files_to_copy

List of source files to copy over to the compile dir
private var _header: CodeWriter

nitc :: AbstractCompiler :: _header

Where global declaration are stored (the main .h)
private var _linker_script: Array[String]

nitc :: AbstractCompiler :: _linker_script

Additionnal linker script for ld.
private var _mainmodule: MModule

nitc :: AbstractCompiler :: _mainmodule

The main module of the program currently compiled
private var _modelbuilder: ModelBuilder

nitc :: AbstractCompiler :: _modelbuilder

The modelbuilder used to know the model and the AST
private var _names: HashMap[String, String]

nitc :: AbstractCompiler :: _names

Table corresponding c_names to nit names (methods)
private var _realmainmodule: MModule

nitc :: AbstractCompiler :: _realmainmodule

The real main module of the program
private var _runtime_type_analysis: nullable RapidTypeAnalysis

nitc :: SeparateCompiler :: _runtime_type_analysis

The result of the RTA (used to know live types and methods)
private var _seen_extern: ArraySet[String]

nitc :: AbstractCompiler :: _seen_extern

This is used to avoid adding an extern file more than once
private var _target_platform: Platform

nitc :: AbstractCompiler :: _target_platform

The targeted specific platform
private var _toolchain: Toolchain

nitc :: AbstractCompiler :: _toolchain

The associated toolchain
private var _type_tables: Map[MType, Array[nullable MType]]

nitc :: SeparateCompiler :: _type_tables

protected fun all_routine_types_name=(all_routine_types_name: Set[String])

nitc :: AbstractCompiler :: all_routine_types_name=

protected fun attr_read_count=(attr_read_count: Int)

nitc :: SeparateCompiler :: attr_read_count=

protected fun attr_tables: Map[MClass, Array[nullable MProperty]]

nitc :: SeparateCompiler :: attr_tables

protected fun attr_tables=(attr_tables: Map[MClass, Array[nullable MProperty]])

nitc :: SeparateCompiler :: attr_tables=

protected fun box_kinds=(box_kinds: HashMap[MClass, Int])

nitc :: SeparateCompiler :: box_kinds=

fun build_c_to_nit_bindings

nitc :: AbstractCompiler :: build_c_to_nit_bindings

Builds the .c and .h files to be used when generating a Stack Trace
fun build_type_tables(mtypes: POSet[MType]): Map[MType, Array[nullable MType]]

nitc :: SeparateCompiler :: build_type_tables

Build type tables
private fun class_colors=(class_colors: Map[MClass, Int])

nitc :: SeparateErasureCompiler :: class_colors=

fun class_conflict_graph: POSetConflictGraph[MClass]

nitc :: SeparateCompiler :: class_conflict_graph

The conflict graph of classes used for coloration
protected fun class_conflict_graph=(class_conflict_graph: POSetConflictGraph[MClass])

nitc :: SeparateCompiler :: class_conflict_graph=

The conflict graph of classes used for coloration
protected fun class_factory(name: String): CLASS

core :: Object :: class_factory

Implementation used by get_class to create the specific class.
private fun class_ids=(class_ids: Map[MClass, Int])

nitc :: SeparateErasureCompiler :: class_ids=

fun class_name: String

core :: Object :: class_name

The class name of the object.
private fun class_tables=(class_tables: Map[MClass, Array[nullable MClass]])

nitc :: SeparateErasureCompiler :: class_tables=

private fun color_consts_done=(color_consts_done: HashSet[Object])

nitc :: SeparateCompiler :: color_consts_done=

fun compile_before_main(v: VISITOR)

nitc :: AbstractCompiler :: compile_before_main

Hook to add specif piece of code before the the main C function.
fun compile_begin_main(v: VISITOR)

nitc :: AbstractCompiler :: compile_begin_main

Hook to add specif piece of code at the begin on the main C function.
protected fun compile_catch_stack

nitc :: AbstractCompiler :: compile_catch_stack

Stack stocking environment for longjumps
fun compile_class_if_universal(ccinfo: ClassCompilationInfo, v: SeparateCompilerVisitor): Bool

nitc :: SeparateCompiler :: compile_class_if_universal

Given a MClass, if it's a universal class and if it needs to be handle
fun compile_class_infos

nitc :: SeparateCompiler :: compile_class_infos

Compile structures used to map tagged primitive values to their classes and types.
fun compile_class_to_c(mclass: MClass)

nitc :: SeparateCompiler :: compile_class_to_c

Globally compile the table of the class mclass
fun compile_header

nitc :: AbstractCompiler :: compile_header

Compile C headers
protected abstract fun compile_header_structs

nitc :: AbstractCompiler :: compile_header_structs

Declaration of structures for live Nit types
fun compile_main_function

nitc :: AbstractCompiler :: compile_main_function

Generate the main C function.
fun compile_module_to_c(mmodule: MModule)

nitc :: SeparateCompiler :: compile_module_to_c

Separately compile all the method definitions of the module
fun compile_nitni_global_ref_functions

nitc :: AbstractCompiler :: compile_nitni_global_ref_functions

Copile all C functions related to the [incr|decr]_ref features of the FFI
protected fun compile_nitni_structs

nitc :: AbstractCompiler :: compile_nitni_structs

Declaration of structures for nitni undelying the FFI
fun compile_type_to_c(mtype: MType)

nitc :: SeparateCompiler :: compile_type_to_c

Globaly compile the type structure of a live type
fun compile_types

nitc :: SeparateCompiler :: compile_types

Color and compile type structures and cast information
fun compiled_callref_thunk: HashSet[MMethodDef]

nitc :: AbstractCompiler :: compiled_callref_thunk

All methods who already has a callref_thunk generated for
protected fun compiled_callref_thunk=(compiled_callref_thunk: HashSet[MMethodDef])

nitc :: AbstractCompiler :: compiled_callref_thunk=

All methods who already has a callref_thunk generated for
private fun compiled_null_types: Array[MNullableType]

nitc :: AbstractCompiler :: compiled_null_types

Cache to avoid multiple compilation of NULL values
private fun compiled_null_types=(compiled_null_types: Array[MNullableType])

nitc :: AbstractCompiler :: compiled_null_types=

Cache to avoid multiple compilation of NULL values
private fun compute_resolution_tables(mtypes: Set[MType])

nitc :: SeparateCompiler :: compute_resolution_tables

resolution_tables is used to perform a type resolution at runtime in O(1)
protected fun count_type_test_resolved=(count_type_test_resolved: HashMap[String, Int])

nitc :: AbstractCompiler :: count_type_test_resolved=

protected fun count_type_test_skipped=(count_type_test_skipped: HashMap[String, Int])

nitc :: AbstractCompiler :: count_type_test_skipped=

protected fun count_type_test_tags=(count_type_test_tags: Array[String])

nitc :: AbstractCompiler :: count_type_test_tags=

protected fun count_type_test_unresolved=(count_type_test_unresolved: HashMap[String, Int])

nitc :: AbstractCompiler :: count_type_test_unresolved=

init defaultinit(mainmodule: MModule, modelbuilder: ModelBuilder, runtime_type_analysis: nullable RapidTypeAnalysis)

nitc :: SeparateCompiler :: defaultinit

init defaultinit(mainmodule: MModule, modelbuilder: ModelBuilder, runtime_type_analysis: nullable RapidTypeAnalysis)

nitc :: SeparateErasureCompiler :: defaultinit

init defaultinit(mainmodule: MModule, modelbuilder: ModelBuilder)

nitc :: AbstractCompiler :: defaultinit

fun display_stats

nitc :: AbstractCompiler :: display_stats

Display stats about compilation process
abstract fun do_compilation

nitc :: AbstractCompiler :: do_compilation

Do the full code generation of the program mainmodule
fun do_property_coloring

nitc :: SeparateCompiler :: do_property_coloring

colorize classe properties
private fun do_type_coloring: Collection[MType]

nitc :: SeparateCompiler :: do_type_coloring

colorize live types of the program
fun extern_bodies: Array[ExternFile]

nitc :: AbstractCompiler :: extern_bodies

List of additional files required to compile (FFI)
protected fun extern_bodies=(extern_bodies: Array[ExternFile])

nitc :: AbstractCompiler :: extern_bodies=

List of additional files required to compile (FFI)
fun files: Array[CodeFile]

nitc :: AbstractCompiler :: files

The list of all associated files
protected fun files=(files: Array[CodeFile])

nitc :: AbstractCompiler :: files=

The list of all associated files
fun files_to_copy: Array[String]

nitc :: AbstractCompiler :: files_to_copy

List of source files to copy over to the compile dir
protected fun files_to_copy=(files_to_copy: Array[String])

nitc :: AbstractCompiler :: files_to_copy=

List of source files to copy over to the compile dir
fun generate_check_attr(v: VISITOR, recv: RuntimeVariable, mtype: MClassType)

nitc :: AbstractCompiler :: generate_check_attr

Generate code that check if an attribute is correctly initialized
fun generate_init_attr(v: VISITOR, recv: RuntimeVariable, mtype: MClassType)

nitc :: AbstractCompiler :: generate_init_attr

Generate code that initialize the attributes on a new instance
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun hardening: Bool

nitc :: AbstractCompiler :: hardening

Is hardening asked? (see --hardening)
fun hardening_live_type(v: VISITOR, t: String)

nitc :: SeparateCompiler :: hardening_live_type

Add a dynamic test to ensure that the type referenced by t is a live type
fun hash: Int

core :: Object :: hash

The hash code of the object.
fun header: CodeWriter

nitc :: AbstractCompiler :: header

Where global declaration are stored (the main .h)
fun header=(header: CodeWriter)

nitc :: AbstractCompiler :: header=

Where global declaration are stored (the main .h)
init init

core :: Object :: init

fun inspect: String

core :: Object :: inspect

Developer readable representation of self.
protected fun inspect_head: String

core :: Object :: inspect_head

Return "CLASSNAME:#OBJECTID".
fun is_monomorphic(m: MMethod): nullable MMethodDef

nitc :: SeparateCompiler :: is_monomorphic

The single mmethodef called in case of monomorphism.
intern fun is_same_instance(other: nullable Object): Bool

core :: Object :: is_same_instance

Return true if self and other are the same instance (i.e. same identity).
fun is_same_serialized(other: nullable Object): Bool

core :: Object :: is_same_serialized

Is self the same as other in a serialization context?
intern fun is_same_type(other: Object): Bool

core :: Object :: is_same_type

Return true if self and other have the same dynamic type.
protected fun isset_checks_count=(isset_checks_count: Int)

nitc :: SeparateCompiler :: isset_checks_count=

fun linker_script: Array[String]

nitc :: AbstractCompiler :: linker_script

Additionnal linker script for ld.
protected fun linker_script=(linker_script: Array[String])

nitc :: AbstractCompiler :: linker_script=

Additionnal linker script for ld.
private fun live_unresolved_types=(live_unresolved_types: Map[MClassDef, Set[MType]])

nitc :: SeparateCompiler :: live_unresolved_types=

fun mainmodule: MModule

nitc :: AbstractCompiler :: mainmodule

The main module of the program currently compiled
fun mainmodule=(mainmodule: MModule)

nitc :: AbstractCompiler :: mainmodule=

The main module of the program currently compiled
protected fun method_tables=(method_tables: Map[MClass, Array[nullable MPropDef]])

nitc :: SeparateCompiler :: method_tables=

fun modelbuilder: ModelBuilder

nitc :: AbstractCompiler :: modelbuilder

The modelbuilder used to know the model and the AST
protected fun modelbuilder=(modelbuilder: ModelBuilder)

nitc :: AbstractCompiler :: modelbuilder=

The modelbuilder used to know the model and the AST
fun names: HashMap[String, String]

nitc :: AbstractCompiler :: names

Table corresponding c_names to nit names (methods)
protected fun names=(names: HashMap[String, String])

nitc :: AbstractCompiler :: names=

Table corresponding c_names to nit names (methods)
private intern fun native_class_name: CString

core :: Object :: native_class_name

The class name of the object in CString format.
fun new_file(name: String): CodeFile

nitc :: AbstractCompiler :: new_file

Force the creation of a new file
abstract fun new_visitor: VISITOR

nitc :: AbstractCompiler :: new_visitor

Initialize a visitor specific for a compiler engine
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
private fun opentype_colors=(opentype_colors: Map[MType, Int])

nitc :: SeparateCompiler :: opentype_colors=

fun output

core :: Object :: output

Display self on stdout (debug only).
intern fun output_class_name

core :: Object :: output_class_name

Display class name on stdout (debug only).
private fun poset_from_mtypes(mtypes: Set[MType], cast_types: Set[MType]): POSet[MType]

nitc :: SeparateCompiler :: poset_from_mtypes

fun provide_declaration(key: String, s: String)

nitc :: AbstractCompiler :: provide_declaration

Provide a declaration that can be requested (before or latter) by a visitor
fun realmainmodule: MModule

nitc :: AbstractCompiler :: realmainmodule

The real main module of the program
protected fun realmainmodule=(realmainmodule: MModule)

nitc :: AbstractCompiler :: realmainmodule=

The real main module of the program
private fun resolution_tables=(resolution_tables: Map[MClassType, Array[nullable MType]])

nitc :: SeparateCompiler :: resolution_tables=

private fun retrieve_vt_bound(anchor: MClassType, mtype: nullable MType): MType

nitc :: SeparateErasureCompiler :: retrieve_vt_bound

fun runtime_type_analysis: nullable RapidTypeAnalysis

nitc :: SeparateCompiler :: runtime_type_analysis

The result of the RTA (used to know live types and methods)
protected fun runtime_type_analysis=(runtime_type_analysis: nullable RapidTypeAnalysis)

nitc :: SeparateCompiler :: runtime_type_analysis=

The result of the RTA (used to know live types and methods)
private fun seen_extern: ArraySet[String]

nitc :: AbstractCompiler :: seen_extern

This is used to avoid adding an extern file more than once
private fun seen_extern=(seen_extern: ArraySet[String])

nitc :: AbstractCompiler :: seen_extern=

This is used to avoid adding an extern file more than once
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
fun target_platform: Platform

nitc :: AbstractCompiler :: target_platform

The targeted specific platform
protected fun target_platform=(target_platform: Platform)

nitc :: AbstractCompiler :: target_platform=

The targeted specific platform
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_s: String

core :: Object :: to_s

User readable representation of self.
fun toolchain: Toolchain

nitc :: AbstractCompiler :: toolchain

The associated toolchain
protected fun toolchain=(toolchain: Toolchain)

nitc :: AbstractCompiler :: toolchain=

The associated toolchain
private fun type_colors=(type_colors: Map[MType, Int])

nitc :: SeparateCompiler :: type_colors=

private fun type_ids=(type_ids: Map[MType, Int])

nitc :: SeparateCompiler :: type_ids=

private fun type_tables: Map[MType, Array[nullable MType]]

nitc :: SeparateCompiler :: type_tables

private fun type_tables=(type_tables: Map[MType, Array[nullable MType]])

nitc :: SeparateCompiler :: type_tables=

private fun undead_types=(undead_types: Set[MType])

nitc :: SeparateCompiler :: undead_types=

private fun vt_tables=(vt_tables: Map[MClass, Array[nullable MPropDef]])

nitc :: SeparateErasureCompiler :: vt_tables=

package_diagram nitc::SeparateErasureCompiler SeparateErasureCompiler nitc::SeparateCompiler SeparateCompiler nitc::SeparateErasureCompiler->nitc::SeparateCompiler nitc::AbstractCompiler AbstractCompiler nitc::SeparateCompiler->nitc::AbstractCompiler ...nitc::AbstractCompiler ... ...nitc::AbstractCompiler->nitc::AbstractCompiler

Ancestors

abstract class AbstractCompiler

nitc :: AbstractCompiler

Singleton that store the knowledge about the compilation process
interface Object

core :: Object

The root of the class hierarchy.

Parents

class SeparateCompiler

nitc :: SeparateCompiler

Singleton that store the knowledge about the separate compilation process

Class definitions

nitc $ SeparateErasureCompiler
class SeparateErasureCompiler
	super SeparateCompiler

	private var class_ids: Map[MClass, Int] is noinit
	private var class_colors: Map[MClass, Int] is noinit
	protected var vt_colors: Map[MVirtualTypeProp, Int] is noinit

	init do

		# Class coloring
		var poset = mainmodule.flatten_mclass_hierarchy
		var mclasses = new HashSet[MClass].from(poset)
		var colorer = new POSetColorer[MClass]
		colorer.colorize(poset)
		class_ids = colorer.ids
		class_colors = colorer.colors
		class_tables = self.build_class_typing_tables(mclasses)

		# lookup vt to build layout with
		var vts = new HashMap[MClass, Set[MVirtualTypeProp]]
		for mclass in mclasses do
			vts[mclass] = new HashSet[MVirtualTypeProp]
			for mprop in self.mainmodule.properties(mclass) do
				if mprop isa MVirtualTypeProp then
					vts[mclass].add(mprop)
				end
			end
		end

		# vt coloration
		var vt_colorer = new POSetBucketsColorer[MClass, MVirtualTypeProp](poset, colorer.conflicts)
		vt_colors = vt_colorer.colorize(vts)
		vt_tables = build_vt_tables(mclasses)
	end

	fun build_vt_tables(mclasses: Set[MClass]): Map[MClass, Array[nullable MPropDef]] do
		var tables = new HashMap[MClass, Array[nullable MPropDef]]
		for mclass in mclasses do
			var table = new Array[nullable MPropDef]
			# first, fill table from parents by reverse linearization order
			var parents = new Array[MClass]
			if mainmodule.flatten_mclass_hierarchy.has(mclass) then
				parents = mclass.in_hierarchy(mainmodule).greaters.to_a
				self.mainmodule.linearize_mclasses(parents)
			end
			for parent in parents do
				if parent == mclass then continue
				for mproperty in self.mainmodule.properties(parent) do
					if not mproperty isa MVirtualTypeProp then continue
					var color = vt_colors[mproperty]
					if table.length <= color then
						for i in [table.length .. color[ do
							table[i] = null
						end
					end
					for mpropdef in mproperty.mpropdefs do
						if mpropdef.mclassdef.mclass == parent then
							table[color] = mpropdef
						end
					end
				end
			end

			# then override with local properties
			for mproperty in self.mainmodule.properties(mclass) do
				if not mproperty isa MVirtualTypeProp then continue
				var color = vt_colors[mproperty]
				if table.length <= color then
					for i in [table.length .. color[ do
						table[i] = null
					end
				end
				for mpropdef in mproperty.mpropdefs do
					if mpropdef.mclassdef.mclass == mclass then
						table[color] = mpropdef
					end
				end
			end
			tables[mclass] = table
		end
		return tables
	end

	# Build class tables
	fun build_class_typing_tables(mclasses: Set[MClass]): Map[MClass, Array[nullable MClass]] do
		var tables = new HashMap[MClass, Array[nullable MClass]]
		for mclass in mclasses do
			var table = new Array[nullable MClass]
			var supers = new Array[MClass]
			if mainmodule.flatten_mclass_hierarchy.has(mclass) then
				supers = mclass.in_hierarchy(mainmodule).greaters.to_a
			end
			for sup in supers do
				var color = class_colors[sup]
				if table.length <= color then
					for i in [table.length .. color[ do
						table[i] = null
					end
				end
				table[color] = sup
			end
			tables[mclass] = table
		end
		return tables
	end

	redef fun compile_header_structs do
		self.header.add_decl("typedef void(*nitmethod_t)(void); /* general C type representing a Nit method. */")
		self.compile_header_attribute_structs
		self.header.add_decl("struct class \{ int id; const char *name; int box_kind; int color; const struct vts_table *vts_table; const struct type_table *type_table; nitmethod_t vft[]; \}; /* general C type representing a Nit class. */")
		self.header.add_decl("struct type_table \{ int size; int table[]; \}; /* colorized type table. */")
		self.header.add_decl("struct vts_entry \{ short int is_nullable; const struct class *class; \}; /* link (nullable or not) between the vts and is bound. */")
		self.header.add_decl("struct vts_table \{ int dummy; const struct vts_entry vts[]; \}; /* vts list of a C type representation. */")
		self.header.add_decl("typedef struct instance \{ const struct class *class; nitattribute_t attrs[1]; \} val; /* general C type representing a Nit instance. */")
	end

	redef fun compile_class_if_universal(ccinfo, v)
	do
		var mclass = ccinfo.mclass
		var mtype = ccinfo.mtype
		var c_name = mclass.c_name
		var is_dead = ccinfo.is_dead

		if mtype.is_c_primitive or mtype.mclass.name == "Pointer" then
			#Build instance struct
			self.header.add_decl("struct instance_{c_name} \{")
			self.header.add_decl("const struct class *class;")
			self.header.add_decl("{mtype.ctype} value;")
			self.header.add_decl("\};")

			#Build BOX
			self.provide_declaration("BOX_{c_name}", "val* BOX_{c_name}({mtype.ctype_extern});")
			v.add_decl("/* allocate {mtype} */")
			v.add_decl("val* BOX_{mtype.c_name}({mtype.ctype_extern} value) \{")
			v.add("struct instance_{c_name}*res = nit_alloc(sizeof(struct instance_{c_name}));")
			v.require_declaration("class_{c_name}")
			v.add("res->class = &class_{c_name};")
			v.add("res->value = value;")
			v.add("return (val*)res;")
			v.add("\}")

			if mtype.mclass.name != "Pointer" then return true

			v = new_visitor
			self.provide_declaration("NEW_{c_name}", "{mtype.ctype} NEW_{c_name}();")
			v.add_decl("/* allocate {mtype} */")
			v.add_decl("{mtype.ctype} NEW_{c_name}() \{")
			if is_dead then
				v.add_abort("{mclass} is DEAD")
			else
				var res = v.new_named_var(mtype, "self")
				res.is_exact = true
				v.add("{res} = nit_alloc(sizeof(struct instance_{mtype.c_name}));")
				v.require_declaration("class_{c_name}")
				v.add("{res}->class = &class_{c_name};")
				v.add("((struct instance_{mtype.c_name}*){res})->value = NULL;")
				v.add("return {res};")
			end
			v.add("\}")
			return true
		else if mclass.name == "NativeArray" then
			#Build instance struct
			self.header.add_decl("struct instance_{c_name} \{")
			self.header.add_decl("const struct class *class;")
			self.header.add_decl("int length;")
			self.header.add_decl("val* values[];")
			self.header.add_decl("\};")

			#Build NEW
			self.provide_declaration("NEW_{c_name}", "{mtype.ctype} NEW_{c_name}(int length);")
			v.add_decl("/* allocate {mtype} */")
			v.add_decl("{mtype.ctype} NEW_{c_name}(int length) \{")
			var res = v.get_name("self")
			v.add_decl("struct instance_{c_name} *{res};")
			var mtype_elt = mtype.arguments.first
			v.add("{res} = nit_alloc(sizeof(struct instance_{c_name}) + length*sizeof({mtype_elt.ctype}));")
			v.require_declaration("class_{c_name}")
			v.add("{res}->class = &class_{c_name};")
			v.add("{res}->length = length;")
			v.add("return (val*){res};")
			v.add("\}")
			return true
                else if mclass.name == "RoutineRef" then
                        self.header.add_decl("struct instance_{c_name} \{")
                        self.header.add_decl("const struct class *class;")
                        self.header.add_decl("val* recv;")
                        self.header.add_decl("nitmethod_t method;")
                        self.header.add_decl("\};")

                        self.provide_declaration("NEW_{c_name}", "{mtype.ctype} NEW_{c_name}(val* recv, nitmethod_t method, const struct class* class);")
                        v.add_decl("/* allocate {mtype} */")
                        v.add_decl("{mtype.ctype} NEW_{c_name}(val* recv, nitmethod_t method, const struct class* class)\{")
                        var res = v.get_name("self")
                        v.add_decl("struct instance_{c_name} *{res};")
                        var alloc = v.nit_alloc("sizeof(struct instance_{c_name})", mclass.full_name)
                        v.add("{res} = {alloc};")
                        v.add("{res}->class = class;")
                        v.add("{res}->recv = recv;")
                        v.add("{res}->method = method;")
                        v.add("return (val*){res};")
                        v.add("\}")
                        return true
		else if mtype.mclass.kind == extern_kind and mtype.mclass.name != "CString" then
			var pointer_type = mainmodule.pointer_type

			self.provide_declaration("NEW_{c_name}", "{mtype.ctype} NEW_{c_name}();")
			v.add_decl("/* allocate {mtype} */")
			v.add_decl("{mtype.ctype} NEW_{c_name}() \{")
			if is_dead then
				v.add_abort("{mclass} is DEAD")
			else
				var res = v.new_named_var(mtype, "self")
				res.is_exact = true
				v.add("{res} = nit_alloc(sizeof(struct instance_{pointer_type.c_name}));")
				#v.add("{res}->type = type;")
				v.require_declaration("class_{c_name}")
				v.add("{res}->class = &class_{c_name};")
				v.add("((struct instance_{pointer_type.c_name}*){res})->value = NULL;")
				v.add("return {res};")
			end
			v.add("\}")
			return true
		end
		return false
	end

	redef fun compile_class_vft(ccinfo, v)
	do
		var mclass = ccinfo.mclass
		var mtype = ccinfo.mtype
		var c_name = mclass.c_name
		var is_dead = ccinfo.is_dead
		var rta = runtime_type_analysis

		# Build class vft
		self.provide_declaration("class_{c_name}", "extern const struct class class_{c_name};")

		v.add_decl("const struct class class_{c_name} = \{")
		v.add_decl("{class_ids[mclass]},")
		v.add_decl("\"{mclass.name}\", /* class_name_string */")
		v.add_decl("{self.box_kind_of(mclass)}, /* box_kind */")
		v.add_decl("{class_colors[mclass]},")
		if not is_dead then
			if build_class_vts_table(mclass) then
				v.require_declaration("vts_table_{c_name}")
				v.add_decl("&vts_table_{c_name},")
			else
				v.add_decl("NULL,")
			end
			v.add_decl("&type_table_{c_name},")
			v.add_decl("\{")
			var vft = self.method_tables.get_or_null(mclass)
			if vft != null then for i in [0 .. vft.length[ do
				var mpropdef = vft[i]
				if mpropdef == null then
					v.add_decl("NULL, /* empty */")
				else
					assert mpropdef isa MMethodDef
					if rta != null and not rta.live_methoddefs.has(mpropdef) then
						v.add_decl("NULL, /* DEAD {mclass.intro_mmodule}:{mclass}:{mpropdef} */")
						continue
					end
					var rf = mpropdef.virtual_runtime_function
					v.require_declaration(rf.c_name)
					v.add_decl("(nitmethod_t){rf.c_name}, /* pointer to {mpropdef.full_name} */")
				end
			end
			v.add_decl("\}")
		end
		v.add_decl("\};")
	end

	protected fun compile_class_type_table(ccinfo: ClassCompilationInfo, v: SeparateCompilerVisitor)
	do
		var mclass = ccinfo.mclass
		var c_name = mclass.c_name
		var class_table = self.class_tables[mclass]

		# Build class type table
		v.add_decl("const struct type_table type_table_{c_name} = \{")
		v.add_decl("{class_table.length},")
		v.add_decl("\{")
		for msuper in class_table do
			if msuper == null then
				v.add_decl("-1, /* empty */")
			else
				v.add_decl("{self.class_ids[msuper]}, /* {msuper} */")
			end
		end
		v.add_decl("\}")
		v.add_decl("\};")
	end

	redef fun compile_default_new(ccinfo, v)
	do
		var mclass = ccinfo.mclass
		var mtype = ccinfo.mtype
		var c_name = mclass.c_name
		var is_dead = ccinfo.is_dead

		#Build NEW
		self.provide_declaration("NEW_{c_name}", "{mtype.ctype} NEW_{c_name}(void);")
		v.add_decl("/* allocate {mtype} */")
		v.add_decl("{mtype.ctype} NEW_{c_name}(void) \{")
		if is_dead then
			v.add_abort("{mclass} is DEAD")
		else

			var res = v.new_named_var(mtype, "self")
			res.is_exact = true
			var attrs = self.attr_tables.get_or_null(mclass)
			if attrs == null then
				v.add("{res} = nit_alloc(sizeof(struct instance));")
			else
				v.add("{res} = nit_alloc(sizeof(struct instance) + {attrs.length}*sizeof(nitattribute_t));")
			end
			v.require_declaration("class_{c_name}")
			v.add("{res}->class = &class_{c_name};")
			if attrs != null then
				self.generate_init_attr(v, res, mtype)
				v.set_finalizer res
			end
			v.add("return {res};")
		end
		v.add("\}")
	end

	redef fun build_class_compilation_info(mclass)
	do
		var ccinfo = super
		var mtype = ccinfo.mtype
		var rta = runtime_type_analysis
		var is_dead = false # mclass.kind == abstract_kind or mclass.kind == interface_kind
		if not is_dead and rta != null and not rta.live_classes.has(mclass) and not mtype.is_c_primitive and mclass.name != "NativeArray" then
			is_dead = true
		end
		ccinfo.is_dead = is_dead
		return ccinfo
	end

	redef fun compile_class_to_c(mclass: MClass)
	do
		var ccinfo = build_class_compilation_info(mclass)
		var v = new_visitor
		v.add_decl("/* runtime class {mclass.c_name} */")
		self.provide_declaration("class_{mclass.c_name}", "extern const struct class class_{mclass.c_name};")
		v.add_decl("extern const struct type_table type_table_{mclass.c_name};")
		self.compile_class_vft(ccinfo, v)
		self.compile_class_type_table(ccinfo, v)
		if not self.compile_class_if_universal(ccinfo, v) then
			self.compile_default_new(ccinfo, v)
		end
	end

	private fun build_class_vts_table(mclass: MClass): Bool do
		if self.vt_tables[mclass].is_empty then return false

		self.provide_declaration("vts_table_{mclass.c_name}", "extern const struct vts_table vts_table_{mclass.c_name};")

		var v = new_visitor
		v.add_decl("const struct vts_table vts_table_{mclass.c_name} = \{")
		v.add_decl("0, /* dummy */")
		v.add_decl("\{")

		for vt in self.vt_tables[mclass] do
			if vt == null then
				v.add_decl("\{-1, NULL\}, /* empty */")
			else
				var is_null = 0
				var bound = retrieve_vt_bound(mclass.intro.bound_mtype, vt.as(MVirtualTypeDef).bound)
				while bound isa MNullableType do
					bound = retrieve_vt_bound(mclass.intro.bound_mtype, bound.mtype)
					is_null = 1
				end
				var vtclass = bound.as(MClassType).mclass
				v.require_declaration("class_{vtclass.c_name}")
				v.add_decl("\{{is_null}, &class_{vtclass.c_name}\}, /* {vt} */")
			end
		end
		v.add_decl("\},")
		v.add_decl("\};")
		return true
	end

	private fun retrieve_vt_bound(anchor: MClassType, mtype: nullable MType): MType do
		if mtype == null then
			print "NOT YET IMPLEMENTED: retrieve_vt_bound on null"
			abort
		end
		if mtype isa MVirtualType then
			return mtype.anchor_to(mainmodule, anchor)
		else if mtype isa MParameterType then
			return mtype.anchor_to(mainmodule, anchor)
		else
			return mtype
		end
	end

	redef fun compile_types
	do
		compile_color_consts(vt_colors)
	end

	redef fun new_visitor do return new SeparateErasureCompilerVisitor(self)

	# Stats

	private var class_tables: Map[MClass, Array[nullable MClass]] is noinit
	private var vt_tables: Map[MClass, Array[nullable MPropDef]] is noinit

	redef fun display_sizes
	do
		print "# size of subtyping tables"
		print "\ttotal \tholes"
		var total = 0
		var holes = 0
		for t, table in class_tables do
			total += table.length
			for e in table do if e == null then holes += 1
		end
		print "\t{total}\t{holes}"

		print "# size of resolution tables"
		print "\ttotal \tholes"
		total = 0
		holes = 0
		for t, table in vt_tables do
			total += table.length
			for e in table do if e == null then holes += 1
		end
		print "\t{total}\t{holes}"

		print "# size of methods tables"
		print "\ttotal \tholes"
		total = 0
		holes = 0
		for t, table in method_tables do
			total += table.length
			for e in table do if e == null then holes += 1
		end
		print "\t{total}\t{holes}"

		print "# size of attributes tables"
		print "\ttotal \tholes"
		total = 0
		holes = 0
		for t, table in attr_tables do
			total += table.length
			for e in table do if e == null then holes += 1
		end
		print "\t{total}\t{holes}"
	end
end
src/compiler/separate_erasure_compiler.nit:81,1--533,3