Services to load models from the assets folder

Introduced classes

class ModelAsset

gamnit :: ModelAsset

Model loaded from a file in the asset folder

Redefined classes

redef abstract class Model

gamnit :: more_models $ Model

3D model composed of Mesh and Material, loaded from the assets folder by default
redef class Sys

gamnit :: more_models $ Sys

The main class of the program.

All class definitions

redef abstract class Model

gamnit :: more_models $ Model

3D model composed of Mesh and Material, loaded from the assets folder by default
class ModelAsset

gamnit $ ModelAsset

Model loaded from a file in the asset folder
redef class Sys

gamnit :: more_models $ Sys

The main class of the program.
package_diagram gamnit::more_models more_models gamnit::obj obj gamnit::more_models->gamnit::obj gamnit::mtl mtl gamnit::more_models->gamnit::mtl gamnit::more_materials more_materials gamnit::more_models->gamnit::more_materials gamnit::more_meshes more_meshes gamnit::more_models->gamnit::more_meshes gamnit::model_parser_base model_parser_base gamnit::obj->gamnit::model_parser_base gamnit::mtl->gamnit::model_parser_base gamnit\>flat\> flat gamnit::more_materials->gamnit\>flat\> gamnit::shadow shadow gamnit::more_materials->gamnit::shadow gamnit::more_lights more_lights gamnit::more_materials->gamnit::more_lights gamnit::model_dimensions model_dimensions gamnit::more_meshes->gamnit::model_dimensions ...gamnit::model_parser_base ... ...gamnit::model_parser_base->gamnit::model_parser_base ...gamnit\>flat\> ... ...gamnit\>flat\>->gamnit\>flat\> ...gamnit::shadow ... ...gamnit::shadow->gamnit::shadow ...gamnit::more_lights ... ...gamnit::more_lights->gamnit::more_lights ...gamnit::model_dimensions ... ...gamnit::model_dimensions->gamnit::model_dimensions gamnit::depth depth gamnit::depth->gamnit::more_models gamnit::cardboard cardboard gamnit::cardboard->gamnit::depth gamnit::stereoscopic_view stereoscopic_view gamnit::stereoscopic_view->gamnit::depth gamnit::cardboard... ... gamnit::cardboard...->gamnit::cardboard gamnit::stereoscopic_view... ... gamnit::stereoscopic_view...->gamnit::stereoscopic_view

Ancestors

module abstract_collection

core :: abstract_collection

Abstract collection classes and services.
module abstract_text

core :: abstract_text

Abstract class for manipulation of sequences of characters
module angles

geometry :: angles

Angle related service using Float to represent an angle in radians
module app

app :: app

app.nit is a framework to create cross-platform applications
module app_base

app :: app_base

Base of the app.nit framework, defines App
module array

core :: array

This module introduces the standard array structure.
module assets

app :: assets

Portable services to load resources from the assets folder
module audio

app :: audio

Services to load and play Sound and Music from the assets folder
module aware

android :: aware

Android compatibility module
module bitset

core :: bitset

Services to handle BitSet
module bmfont

gamnit :: bmfont

Parse Angel Code BMFont format and draw text
module boxes

geometry :: boxes

Provides interfaces and classes to represent basic geometry needs.
module bytes

core :: bytes

Services for byte streams and arrays
module c

c :: c

Structures and services for compatibility with the C language
module caching

serialization :: caching

Services for caching serialization engines
module camera_control

gamnit :: camera_control

Simple camera control for user, as the method accept_scroll_and_zoom
module cameras

gamnit :: cameras

Camera services producing Model-View-Projection matrices
module cameras_cache

gamnit :: cameras_cache

Cache the Matrix produced by Camera::mvp_matrix
module circular_array

core :: circular_array

Efficient data structure to access both end of the sequence.
module codec_base

core :: codec_base

Base for codecs to use with streams
module codecs

core :: codecs

Group module for all codec-related manipulations
module collection

core :: collection

This module define several collection classes.
module core

core :: core

Standard classes and methods used by default by Nit programs and libraries.
module depth_core

gamnit :: depth_core

Base entities of the depth 3D game framework
module display

gamnit :: display

Abstract display services
module dom

dom :: dom

Easy XML DOM parser
module dynamic_resolution

gamnit :: dynamic_resolution

Virtual screen with a resolution independent from the real screen
module engine_tools

serialization :: engine_tools

Advanced services for serialization engines
module environ

core :: environ

Access to the environment variables of the process
module error

core :: error

Standard error-management infrastructure.
module exec

core :: exec

Invocation and management of operating system sub-processes.
module file

core :: file

File manipulations (create, read, write, etc.)
module fixed_ints

core :: fixed_ints

Basic integers of fixed-precision
module fixed_ints_text

core :: fixed_ints_text

Text services to complement fixed_ints
module flat

gamnit :: flat

Simple API for 2D games, built around Sprite and App::update
module flat

core :: flat

All the array-based text representations
module flat_core

gamnit :: flat_core

Core services for the flat API for 2D games
module font

gamnit :: font

Abstract font drawing services, implemented by bmfont and tileset
module gamnit

gamnit :: gamnit

Game and multimedia framework for Nit
module gc

core :: gc

Access to the Nit internal garbage collection mechanism
module geometry

geometry :: geometry

Provides interfaces and classes to represent basic geometry needs.
module glesv2

glesv2 :: glesv2

OpenGL graphics rendering library for embedded systems, version 2.0
module hash_collection

core :: hash_collection

Introduce HashMap and HashSet.
module input

mnit :: input

Defines abstract classes for user and general inputs to the application.
module inspect

serialization :: inspect

Refine Serializable::inspect to show more useful information
module iso8859_1

core :: iso8859_1

Codec for ISO8859-1 I/O
module kernel

core :: kernel

Most basic classes and methods.
module keys

gamnit :: keys

Simple service keeping track of which keys are currently pressed
module limit_fps

gamnit :: limit_fps

Frame-rate control for applications
module list

core :: list

This module handle double linked lists
module math

core :: math

Mathematical operations
module matrix

matrix :: matrix

Services for matrices of Float values
module meta

meta :: meta

Simple user-defined meta-level to manipulate types of instances as object.
module model_dimensions

gamnit :: model_dimensions

Dimensions related services for Model and Mesh
module model_parser_base

gamnit :: model_parser_base

Services to parse models from a text description
module more_collections

more_collections :: more_collections

Highly specific, but useful, collections-related classes.
module more_lights

gamnit :: more_lights

More implementations of Light
module native

core :: native

Native structures for text and bytes
module numeric

core :: numeric

Advanced services for Numeric types
module parser

dom :: parser

XML DOM-parsing facilities
module parser_base

parser_base :: parser_base

Simple base for hand-made parsers of all kinds
module performance_analysis

performance_analysis :: performance_analysis

Services to gather information on the performance of events by categories
module points_and_lines

geometry :: points_and_lines

Interfaces and classes to represent basic geometry needs.
module poset

poset :: poset

Pre order sets and partial order set (ie hierarchies)
module programs

gamnit :: programs

Services for graphical programs with shaders, attributes and uniforms
module projection

matrix :: projection

Services on Matrix to transform and project 3D coordinates
module protocol

core :: protocol

module queue

core :: queue

Queuing data structures and wrappers
module range

core :: range

Module for range of discrete objects.
module re

core :: re

Regular expression support for all services based on Pattern
module realtime

realtime :: realtime

Services to keep time of the wall clock time
module ropes

core :: ropes

Tree-based representation of a String.
module serialization

serialization :: serialization

General serialization services
module serialization_core

serialization :: serialization_core

Abstract services to serialize Nit objects to different formats
module shadow

gamnit :: shadow

Shadow mapping using a depth texture
module sorter

core :: sorter

This module contains classes used to compare things and sorts arrays.
module stream

core :: stream

Input and output streams of characters
module text

core :: text

All the classes and methods related to the manipulation of text entities
module textures

gamnit :: textures

Load textures, create subtextures and manage their life-cycle
module tileset

gamnit :: tileset

Support for TileSet, TileSetFont and drawing text with TextSprites
module time

core :: time

Management of time and dates
module union_find

core :: union_find

union–find algorithm using an efficient disjoint-set data structure
module utf8

core :: utf8

Codec for UTF-8 I/O
module xml_entities

dom :: xml_entities

Basic blocks for DOM-XML representation

Parents

module more_materials

gamnit :: more_materials

Various material implementations
module more_meshes

gamnit :: more_meshes

More simple geometric meshes
module mtl

gamnit :: mtl

Services to parse .mtl material files
module obj

gamnit :: obj

Services to parse .obj geometry files

Children

module depth

gamnit :: depth

Framework for 3D games in Nit

Descendants

module a_star-m

a_star-m

module cardboard

gamnit :: cardboard

Update the orientation of world_camera at each frame using the head position given by android::cardboard
module stereoscopic_view

gamnit :: stereoscopic_view

Refine EulerCamera and App::frame_core_draw to get a stereoscopic view
module vr

gamnit :: vr

VR support for gamnit depth, for Android only
# Services to load models from the assets folder
module more_models

intrude import depth_core

import gamnit::obj
import gamnit::mtl

import more_materials
import more_meshes

redef class Model
	# Prepare to load a model from the assets folder
	new(path: Text) do return new ModelAsset(path.to_s)
end

# Model loaded from a file in the asset folder
#
# In case of error, `error` is set accordingly.
# If the error is on the mesh, `mesh` is set to a default `new Cube`.
# If the material is missing or it failed to load, `material` is set to the blueish `new Material`.
class ModelAsset
	super Model
	super Asset

	init do models.add self

	private var loaded = false

	redef fun load
	do
		if loaded then return

		var ext = path.file_extension
		if ext == "obj" then
			load_obj_file
		else
			errors.add new Error("Model at '{path}' failed to load: Extension '{ext or else "null"}' unrecognized")
		end

		if leaves_cache.is_empty then
			# Nothing was loaded, use a cube with the default material
			var leaf = placeholder_model
			leaves_cache.add leaf
		end

		loaded = true
	end

	private fun lazy_load
	do
		if loaded then return

		# Lazy load
		load

		# Print errors when lazy loading only
		if errors.length == 1 then
			print_error errors.first
		else if errors.length > 1 then
			print_error "Loading model at '{path}' raised {errors.length} errors:\n* "
			print_error errors.join("\n* ")
		end
	end

	private fun load_obj_file
	do
		# Read .obj description from assets
		var text_asset = new TextAsset(path)
		var content = text_asset.to_s
		if content.is_empty then
			errors.add new Error("Model failed to load: Asset empty at '{self.path}'")
			leaves_cache.add new LeafModel(new Cube, new Material)
			return
		end

		# Parse .obj description
		var parser = new ObjFileParser(content)
		var obj_def = parser.parse
		if obj_def == null then
			errors.add new Error("Model failed to load: .obj format error on '{self.path}'")
			leaves_cache.add new LeafModel(new Cube, new Material)
			return
		end

		# Check for errors
		if debug_gamnit then assert obj_def.is_coherent

		# Build models
		var converter = new BuildModelFromObj(path, obj_def)
		converter.fill_leaves self
		errors.add_all converter.errors
	end

	redef fun leaves
	do
		lazy_load
		return leaves_cache
	end

	private var leaves_cache = new Array[LeafModel]

	redef fun named_parts
	do
		lazy_load
		return named_leaves_cache
	end

	private var named_leaves_cache = new Map[String, Model]
end

# Short-lived service to convert an `ObjDef` to `fill_leaves`
#
# Limitations: This service only support faces with 3 or 4 vertices.
# Faces with more vertices should be triangulated by the modeling tool.
private class BuildModelFromObj

	# Path to the .obj file in the assets folder, used to find .mtl files
	var path: String

	# Parsed .obj definition
	var obj_def: ObjDef

	# Errors raised by calls to `fill_leaves`
	var errors = new Array[Error]

	# Fill `leaves` with objects described in `obj_def`
	fun fill_leaves(target_model: ModelAsset)
	do
		var leaves = target_model.leaves_cache

		# Sort faces by material
		var obj_mtl_to_faces = new Map[ObjObj, MultiHashMap[String, ObjFace]]
		for obj in obj_def.objects do
			var mtl_to_faces = new MultiHashMap[String, ObjFace]
			obj_mtl_to_faces[obj] = mtl_to_faces
			for face in obj.faces do
				var mtl_lib_name = face.material_lib
				var mtl_name = face.material_name

				var full_name = ""
				if mtl_lib_name != null and mtl_name != null then full_name = mtl_lib_name / mtl_name

				mtl_to_faces[full_name].add face
			end
		end

		# Load material libs
		var mtl_libs = sys.mtl_libs
		var lib_names = obj_def.material_libs
		for name in lib_names do
			var asset_path = self.path.dirname / name
			var lib_asset = new TextAsset(asset_path)
			lib_asset.load

			var error = lib_asset.error
			if error != null then
				errors.add error
				continue
			end

			var mtl_parser = new MtlFileParser(lib_asset.to_s)
			var mtl_lib = mtl_parser.parse
			mtl_libs[asset_path] = mtl_lib
		end

		# Create 1 mesh per material per object, and prepare materials
		var mesh_to_mtl = new Map[Mesh, nullable MtlDef]
		var mesh_to_name = new Map[Mesh, String]
		var texture_names = new Set[String]
		for obj in obj_def.objects do
			var mtl_to_faces = obj_mtl_to_faces[obj]
			for mtl_path, faces in mtl_to_faces do

				# Create mesh
				var mesh = new Mesh
				mesh.vertices = vertices(faces)
				mesh.normals = normals(faces)
				mesh.texture_coords = texture_coords(faces)

				# Material
				var mtl_def = null

				var mtl_lib_name = faces.first.material_lib
				var mtl_name = faces.first.material_name
				if mtl_lib_name != null and mtl_name != null then
					var asset_path = self.path.dirname / mtl_lib_name
					var mtl_lib = mtl_libs[asset_path]
					var mtl = mtl_lib.get_or_null(mtl_name)
					if mtl != null then
						mtl_def = mtl

						for e in mtl.maps do
							texture_names.add self.path.dirname / e
						end
					else
						errors.add new Error("Error loading model at '{path}': mtl '{mtl_name}' not found in '{asset_path}'")
					end
				end

				mesh_to_mtl[mesh] = mtl_def
				mesh_to_name[mesh] = obj.name
			end
		end

		# Load textures need for these materials
		for name in texture_names do
			if not asset_textures_by_name.keys.has(name) then
				var tex = new TextureAsset(name)
				asset_textures_by_name[name] = tex

				tex.load
				var error = tex.error
				if error != null then errors.add error
			end
		end

		# Create final `Materials` from defs and textures
		var materials = new Map[MtlDef, Material]
		for mtl in mesh_to_mtl.values do
			if mtl == null then continue

			var ambient = mtl.ambient.to_a
			ambient.add 1.0

			var diffuse = mtl.diffuse.to_a
			diffuse.add 1.0

			var specular = mtl.specular.to_a
			specular.add 1.0

			var material = new TexturedMaterial(ambient, diffuse, specular)
			materials[mtl] = material

			var tex_name = mtl.map_ambient
			if tex_name != null then
				tex_name = self.path.dirname / tex_name
				material.ambient_texture = asset_textures_by_name[tex_name]
			end

			tex_name = mtl.map_diffuse
			if tex_name != null then
				tex_name = self.path.dirname / tex_name
				material.diffuse_texture = asset_textures_by_name[tex_name]
			end

			tex_name = mtl.map_specular
			if tex_name != null then
				tex_name = self.path.dirname / tex_name
				material.specular_texture = asset_textures_by_name[tex_name]
			end
		end

		# Create models and store them
		var name_to_leaves = new MultiHashMap[String, LeafModel]
		for mesh, mtl_def in mesh_to_mtl do

			var material = materials.get_or_null(mtl_def)
			if material == null then material = new Material

			var model = new LeafModel(mesh, material)
			leaves.add model

			name_to_leaves[mesh_to_name[mesh]].add model
		end

		# Collect objects with a name
		for name, models in name_to_leaves do
			if models.length == 1 then
				target_model.named_leaves_cache[name] = models.first
			else
				var named_model = new CompositeModel
				named_model.leaves.add_all models
				target_model.named_leaves_cache[name] = named_model
			end
		end
	end

	# Compute the vertices coordinates of `faces` in a flat `Array[Float]`
	fun vertices(faces: Array[ObjFace]): Array[Float] do
		var obj_def = obj_def

		var vertices = new Array[Float]
		for face in faces do

			# 1st triangle
			var count = 0
			for e in face.vertices do
				var i = e.vertex_point_index - 1
				var v = obj_def.vertex_points[i]

				vertices.add v.x
				vertices.add v.y
				vertices.add v.z

				if count == 2 then break
				count += 1
			end

			# If square, 2nd triangle
			#
			# This may not support all vertices ordering.
			if face.vertices.length > 3 then
				for e in [face.vertices[0], face.vertices[2], face.vertices[3]] do
					var i = e.vertex_point_index - 1
					var v = obj_def.vertex_points[i]

					vertices.add v.x
					vertices.add v.y
					vertices.add v.z
				end
			end

			# TODO use polygon triangulation to support larger polygons
		end
		return vertices
	end

	# Compute the normals of `faces` in a flat `Array[Float]`
	fun normals(faces: Array[ObjFace]): Array[Float] do
		var obj_def = obj_def

		var normals = new Array[Float]
		for face in faces do
			# 1st triangle
			var count = 0
			for e in face.vertices do
				var i = e.normal_index
				if i == null then
					compute_and_append_normal(normals, face)
				else
					var v = obj_def.normals[i-1]
					normals.add v.x
					normals.add v.y
					normals.add v.z
				end

				if count == 2 then break
				count += 1
			end

			# If square, 2nd triangle
			#
			# This may not support all vertices ordering.
			if face.vertices.length > 3 then
				for e in [face.vertices[0], face.vertices[2], face.vertices[3]] do
					var i = e.normal_index
					if i == null then
						compute_and_append_normal(normals, face)
					else
						var v = obj_def.normals[i-1]
						normals.add v.x
						normals.add v.y
						normals.add v.z
					end
				end
			end
		end
		return normals
	end

	# Compute the normal of `face` and append it as 3 floats to `seq`
	#
	# Resulting normals are not normalized.
	fun compute_and_append_normal(seq: Sequence[Float], face: ObjFace)
	do
		var i1 = face.vertices[0].vertex_point_index
		var i2 = face.vertices[1].vertex_point_index
		var i3 = face.vertices[2].vertex_point_index

		var v1 = obj_def.vertex_points[i1-1]
		var v2 = obj_def.vertex_points[i2-1]
		var v3 = obj_def.vertex_points[i3-1]

		var vx = v2.x - v1.x
		var vy = v2.y - v1.y
		var vz = v2.z - v1.z
		var wx = v3.x - v1.x
		var wy = v3.y - v1.y
		var wz = v3.z - v1.z

		var nx = (vy*wz) - (vz*wy)
		var ny = (vz*wx) - (vx*wz)
		var nz = (vx*wy) - (vy*wx)

		# Append to `seq`
		seq.add nx
		seq.add ny
		seq.add nz
	end

	# Compute the texture coordinates of `faces` in a flat `Array[Float]`
	fun texture_coords(faces: Array[ObjFace]): Array[Float] do
		var obj_def = obj_def

		var coords = new Array[Float]
		for face in faces do

			# 1st triangle
			var count = 0
			for e in face.vertices do
				var i = e.texture_coord_index
				if i == null then
					coords.add 0.0
					coords.add 0.0
				else
					var tc = obj_def.texture_coords[i-1]
					coords.add tc.u
					coords.add tc.v
				end

				if count == 2 then break
				count += 1
			end

			# If square, 2nd triangle
			#
			# This may not support all vertices ordering.
			if face.vertices.length > 3 then
				for e in [face.vertices[0], face.vertices[2], face.vertices[3]] do
					var i = e.texture_coord_index
					if i == null then
						coords.add 0.0
						coords.add 0.0
					else
					var tc = obj_def.texture_coords[i-1]
					coords.add tc.u
					coords.add tc.v
					end
				end
			end
		end
		return coords
	end
end

redef class Sys
	# Textures loaded from .mtl files for models
	var asset_textures_by_name = new Map[String, TextureAsset]

	# Loaded .mtl material definitions, sorted by path in assets and material name
	private var mtl_libs = new Map[String, Map[String, MtlDef]]

	# All instantiated asset models
	var models = new Set[ModelAsset]

	# Blue cube of 1 unit on each side, acting as placeholder for models failing to load
	#
	# This model can be freely used by any `Actor` as placeholder or for debugging.
	var placeholder_model = new LeafModel(new Cube, new Material) is lazy
end
lib/gamnit/depth/more_models.nit:15,1--465,3