Select Actor from a screen coordinate

The two main services are App::visible_at and ; App::visible_in_center`.

This is implemented with simple pixel picking. This algorithm draws each actor in a unique color to the display buffer, using the color as an ID to detect which actor is visible at each pixel.

It is implemented at the level of the material, so it can be applied to any gamnit programs. However it is not optimal performance wise, so client programs should implement a more efficient algorithm.

By default, the actors are drawn as opaque objects. This behavior can be refined, as does TexturedMaterial to use its diffuse_texture for partial opacity.

Introduced classes

class SelectionProgram

gamnit :: SelectionProgram

Program to draw selection values

Redefined classes

redef class App

gamnit :: selection $ App

App subclasses are cross-platform applications
redef abstract class Material

gamnit :: selection $ Material

Material for models, or how to draw the model
redef class TexturedMaterial

gamnit :: selection $ TexturedMaterial

Material with potential diffuse_texture and specular_texture

All class definitions

redef class App

gamnit :: selection $ App

App subclasses are cross-platform applications
redef abstract class Material

gamnit :: selection $ Material

Material for models, or how to draw the model
class SelectionProgram

gamnit $ SelectionProgram

Program to draw selection values
redef class TexturedMaterial

gamnit :: selection $ TexturedMaterial

Material with potential diffuse_texture and specular_texture
package_diagram gamnit::selection selection gamnit::more_materials more_materials gamnit::selection->gamnit::more_materials 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\>flat\> ... ...gamnit\>flat\>->gamnit\>flat\> ...gamnit::shadow ... ...gamnit::shadow->gamnit::shadow ...gamnit::more_lights ... ...gamnit::more_lights->gamnit::more_lights gamnit::depth depth gamnit::depth->gamnit::selection 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 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

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
# Select `Actor` from a screen coordinate
#
# The two main services are `App::visible_at` and ; App::visible_in_center`.
#
# This is implemented with simple pixel picking.
# This algorithm draws each actor in a unique color to the display buffer,
# using the color as an ID to detect which actor is visible at each pixel.
#
# It is implemented at the level of the material,
# so it can be applied to any _gamnit_ programs.
# However it is not optimal performance wise,
# so client programs should implement a more efficient algorithm.
#
# By default, the actors are drawn as opaque objects.
# This behavior can be refined, as does `TexturedMaterial` to use its
# `diffuse_texture` for partial opacity.
module selection

# TODO support `sprites` and `ui_sprites`

import more_materials
intrude import depth_core

redef class App

	# Which `Actor` is at the center of the screen?
	fun visible_in_center: nullable Actor
	do
		var display = display
		assert display != null
		return visible_at(display.width/2, display.height/2)
	end

	# Which `Actor` is on screen at `x, y`?
	fun visible_at(x, y: Numeric): nullable Actor
	do
		var display = display
		assert display != null

		if not selection_calculated then draw_selection_screen

		x = x.to_i
		y = y.to_i
		y = display.height - y

		# Read selection values
		var data = once new NativeCByteArray(4)
		glReadPixels(x, y, 1, 1, gl_RGBA, gl_UNSIGNED_BYTE, data)
		assert_no_gl_error

		var r = display.red_bits
		var g = display.green_bits
		var b = display.blue_bits

		# Rebuild ID from pixel color
		var rv = data[0].to_i >> (8-r)
		var gv = data[1].to_i >> (8-g) << (r)
		var bv = data[2].to_i >> (8-b) << (r+g)
		if data[0].to_i & (2**(8-r)-1) > (2**(8-r-1)) then rv += 1
		if data[1].to_i & (2**(8-g)-1) > (2**(8-g-1)) then gv += 1 << r
		if data[2].to_i & (2**(8-b)-1) > (2**(8-b-1)) then bv += 1 << (r+g)
		var id = rv + gv + bv

		# ID 0 is the background
		if id == 0 then return null

		# Wrongful selection? This should not happen.
		if not selection_map.keys.has(id) then
			print_error "Gamnit Warning: Invalid selection {id}"
			return null
		end

		return selection_map[id]
	end

	# Program drawing selection values to the buffer
	var selection_program = new SelectionProgram

	# Map IDs to actors
	private var selection_map = new Map[Int, Actor]

	# Is there a valid selection draw in the buffer?
	private var selection_calculated = false

	# Draw the selection values to the buffer
	private fun draw_selection_screen
	do
		selection_calculated = true

		app.selection_program.use
		app.selection_program.mvp.uniform app.world_camera.mvp_matrix

		# Set aside previous buffer clear color
		var user_r = glGetFloatv(gl_COLOR_CLEAR_VALUE, 0)
		var user_g = glGetFloatv(gl_COLOR_CLEAR_VALUE, 1)
		var user_b = glGetFloatv(gl_COLOR_CLEAR_VALUE, 2)
		var user_a = glGetFloatv(gl_COLOR_CLEAR_VALUE, 3)

		glClearColor(0.0, 0.0, 0.0, 1.0)
		glClear(gl_DEPTH_BUFFER_BIT | gl_COLOR_BUFFER_BIT)

		# TODO restrict the list of actors with a valid ID, maybe with an `active_actors` list?

		var id = 1
		for actor in actors do
			selection_map[id] = actor
			for leaf in actor.model.leaves do
				leaf.material.draw_selection(actor, leaf, id)
			end

			id += 1
			#id += 100 # Debug
		end

		# Debug, show the selection values for half a second
		#display.flip
		#0.5.sleep

		glClearColor(user_r, user_g, user_b, user_a)
	end

	redef fun frame_core(display)
	do
		super

		# Invalidate the selection values
		selection_calculated = false
	end
end

redef class Material

	# Draw `actor` to selection values
	protected fun draw_selection(actor: Actor, model: LeafModel, id: Int)
	do
		var program = app.selection_program
		var mesh = model.mesh

		draw_selection_texture(actor, model)

		program.translation.uniform(actor.center.x, actor.center.y, actor.center.z, 0.0)
		program.scale.uniform actor.scale

		program.coord.array_enabled = true
		program.coord.array(mesh.vertices, 3)
		program.rotation.uniform new Matrix.gamnit_euler_rotation(actor.pitch, actor.yaw, actor.roll)

		var display = app.display
		assert display != null
		var r = display.red_bits
		var g = display.green_bits
		var b = display.blue_bits

		# Build ID as a color
		var p1 = id & ((2**r)-1)
		var p2 = id >> r & ((2**g)-1)
		var p3 = id >> (r+g) & ((2**b)-1)
		program.color_id.uniform(
			p1.to_f/((2**r)-1).to_f,
			p2.to_f/((2**g)-1).to_f,
			p3.to_f/((2**b)-1).to_f, 1.0)

		if mesh.indices.is_empty then
			glDrawArrays(mesh.draw_mode, 0, mesh.vertices.length/3)
		else
			glDrawElements(mesh.draw_mode, mesh.indices.length, gl_UNSIGNED_SHORT, mesh.indices_c.native_array)
		end
	end

	private fun draw_selection_texture(actor: Actor, model: LeafModel)
	do
		var program = app.selection_program
		program.use_map_diffuse.uniform false
	end
end

redef class TexturedMaterial
	redef fun draw_selection_texture(actor, model)
	do
		var program = app.selection_program
		var mesh = model.mesh

		# One of the textures used, if any
		var sample_used_texture = null
		var texture = diffuse_texture
		if texture != null then
			glActiveTexture gl_TEXTURE1
			glBindTexture(gl_TEXTURE_2D, texture.gl_texture)
			program.use_map_diffuse.uniform true
			program.map_diffuse.uniform 1
			sample_used_texture = texture
		else
			program.use_map_diffuse.uniform false
		end

		# If using a texture, set `texture_coords`
		program.tex_coord.array_enabled = sample_used_texture != null
		if sample_used_texture != null then
			if sample_used_texture isa RootTexture then
				# Coordinates are directly valid
				program.tex_coord.array(mesh.texture_coords, 2)
			else
				# Correlate texture coordinates from the subtexture sand the mesh.
				# This is slow, but should be cached on the GPU.
				var xa = sample_used_texture.offset_left
				var xd = sample_used_texture.offset_right - xa
				var ya = sample_used_texture.offset_top
				var yd = sample_used_texture.offset_bottom - ya

				var tex_coords = new Array[Float].with_capacity(mesh.texture_coords.length)
				for i in [0..mesh.texture_coords.length/2[ do
					tex_coords[i*2]   = xa + xd * mesh.texture_coords[i*2]
					tex_coords[i*2+1] = ya + yd * mesh.texture_coords[i*2+1]
				end

				program.tex_coord.array(tex_coords, 2)
			end
		end
	end
end

# Program to draw selection values
class SelectionProgram
	super GamnitProgramFromSource

	redef var vertex_shader_source = """
		// Vertex coordinates
		attribute vec4 coord;

		// Vertex translation
		uniform vec4 translation;

		// Vertex scaling
		uniform float scale;

		// Vertex coordinates on textures
		attribute vec2 tex_coord;

		// Model view projection matrix
		uniform mat4 mvp;

		// Model rotation
		uniform mat4 rotation;

		// Output for the fragment shader
		varying vec2 v_tex_coord;

		void main()
		{
			v_tex_coord = vec2(tex_coord.x, 1.0 - tex_coord.y);

			gl_Position = (vec4(coord.xyz * scale, 1.0) * rotation + translation) * mvp;
		}
		""" @ glsl_vertex_shader

	#
	redef var fragment_shader_source = """
		precision highp float;

		varying vec2 v_tex_coord;

		// Map used as reference for opacity
		uniform sampler2D map_diffuse;

		// Should `map_diffuse` be used?
		uniform bool use_map_diffuse;

		// Color ID
		uniform vec4 color;

		void main()
		{
			gl_FragColor = vec4(color.rgb, 1.0);

			if (use_map_diffuse && texture2D(map_diffuse, v_tex_coord).a < 0.1) {
				gl_FragColor.a = 0.0;
			}
		}
		""" @ glsl_fragment_shader

	# Vertices coordinates
	var coord = attributes["coord"].as(AttributeVec4) is lazy

	# Should this program use the texture `map_diffuse`?
	var use_map_diffuse = uniforms["use_map_diffuse"].as(UniformBool) is lazy

	# Diffuse texture unit
	var map_diffuse = uniforms["map_diffuse"].as(UniformSampler2D) is lazy

	# Coordinates on the textures, per vertex
	var tex_coord = attributes["tex_coord"].as(AttributeVec2) is lazy

	# Translation applied to each vertex
	var translation = uniforms["translation"].as(UniformVec4) is lazy

	# Rotation matrix
	var rotation = uniforms["rotation"].as(UniformMat4) is lazy

	# Scaling per vertex
	var scale = uniforms["scale"].as(UniformFloat) is lazy

	# Model view projection matrix
	var mvp = uniforms["mvp"].as(UniformMat4) is lazy

	# ID as a color
	var color_id = uniforms["color"].as(UniformVec4) is lazy
end
lib/gamnit/depth/selection.nit:15,1--321,3