Shadow mapping using a depth texture

The default light does not cast any shadows. It can be changed to a ParallelLight in client games to cast sun-like shadows:

import more_lights

var sun = new ParallelLight
sun.pitch = 0.25*pi
sun.yaw = 0.25*pi
app.light = sun

Introduced classes

class ShadowDepthProgram

gamnit :: ShadowDepthProgram

Efficiently draw actors from the light view

Redefined classes

redef class App

gamnit :: shadow $ App

App subclasses are cross-platform applications
redef abstract class Material

gamnit :: shadow $ Material

Material for models, or how to draw the model

All class definitions

redef class App

gamnit :: shadow $ App

App subclasses are cross-platform applications
redef abstract class Material

gamnit :: shadow $ Material

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

gamnit $ ShadowDepthProgram

Efficiently draw actors from the light view
package_diagram gamnit::shadow shadow gamnit::depth_core depth_core gamnit::shadow->gamnit::depth_core gamnit::flat_core flat_core gamnit::depth_core->gamnit::flat_core ...gamnit::flat_core ... ...gamnit::flat_core->gamnit::flat_core gamnit::more_materials more_materials gamnit::more_materials->gamnit::shadow gamnit::more_models more_models gamnit::more_models->gamnit::more_materials gamnit::selection selection gamnit::selection->gamnit::more_materials gamnit::more_models... ... gamnit::more_models...->gamnit::more_models gamnit::selection... ... gamnit::selection...->gamnit::selection

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 aware

android :: aware

Android compatibility module
module bitset

core :: bitset

Services to handle BitSet
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 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 display

gamnit :: display

Abstract display services
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

core :: flat

All the array-based text representations
module flat_core

gamnit :: flat_core

Core services for the flat API for 2D games
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 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 native

core :: native

Native structures for text and bytes
module numeric

core :: numeric

Advanced services for Numeric types
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 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 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

Parents

module depth_core

gamnit :: depth_core

Base entities of the depth 3D game framework

Children

module more_materials

gamnit :: more_materials

Various material implementations

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 depth

gamnit :: depth

Framework for 3D games in Nit
module more_models

gamnit :: more_models

Services to load models from the assets folder
module selection

gamnit :: selection

Select Actor from a screen coordinate
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
# Shadow mapping using a depth texture
#
# The default light does not cast any shadows. It can be changed to a
# `ParallelLight` in client games to cast sun-like shadows:
#
# ~~~
# import more_lights
#
# var sun = new ParallelLight
# sun.pitch = 0.25*pi
# sun.yaw = 0.25*pi
# app.light = sun
# ~~~
module shadow

intrude import gamnit::depth_core

redef class App

	# Resolution of the shadow texture, defaults to 4096 pixels
	#
	# TODO make configurable / ask the hardware for gl_MAX_TEXTURE_SIZE
	var shadow_resolution = 4096

	# Are shadows supported by the current hardware configuration?
	#
	# The implementation may change in the future, but it currently relies on
	# the GL extension `GL_EOS_depth_texture`.
	var supports_shadows: Bool is lazy do
		return display.as(not null).gl_extensions.has("GL_OES_depth_texture")
	end

	# Is `shadow_context.depth_texture` ready to be used?
	fun shadow_depth_texture_available: Bool
	do return supports_shadows and shadow_context.depth_texture != -1

	private var shadow_depth_program = new ShadowDepthProgram

	private var perf_clock_shadow = new Clock is lazy

	redef fun create_gamnit
	do
		super

		var program = shadow_depth_program
		program.compile_and_link
		var error = program.error
		assert error == null else print_error error
	end

	private var shadow_context: ShadowContext = create_shadow_context is lazy

	private fun create_shadow_context: ShadowContext
	do
		var display = display
		assert display != null

		var context = new ShadowContext
		context.prepare_once(display, shadow_resolution)
		return context
	end

	# Update the depth texture from the light point of view
	#
	# This method updates `shadow_context.depth_texture`.
	protected fun frame_core_shadow_prep(display: GamnitDisplay)
	do
		if not supports_shadows then return

		var light = app.light
		if not light isa LightCastingShadows then return

		# Make sure there's no errors pending
		assert glGetError == gl_NO_ERROR

		# Bind the framebuffer and make sure it is OK
		glBindFramebuffer(gl_FRAMEBUFFER, shadow_context.light_view_framebuffer)
		assert glGetError == gl_NO_ERROR
		assert glCheckFramebufferStatus(gl_FRAMEBUFFER) == gl_FRAMEBUFFER_COMPLETE

		# Draw to fill the depth texture and only the depth
		glViewport(0, 0, shadow_resolution, shadow_resolution)
		glColorMask(false, false, false, false)
		glClear gl_COLOR_BUFFER_BIT | gl_DEPTH_BUFFER_BIT
		assert glGetError == gl_NO_ERROR

		# Update light position
		var camera = light.camera
		camera.position.x = app.world_camera.position.x
		camera.position.y = app.world_camera.position.y
		camera.position.z = app.world_camera.position.z

		# Draw all actors
		for actor in actors do
			for leaf in actor.model.leaves do
				leaf.material.draw_depth(actor, leaf, camera)
			end
		end

		# Take down, bring back default values
		bind_screen_framebuffer shadow_context.screen_framebuffer
		glColorMask(true, true, true, true)
	end

	# ---
	# Debug: show light view in the bottom left of the screen

	# Lazy load the debugging program
	private var shadow_debug_program: LightPointOfViewProgram is lazy do
		var program = new LightPointOfViewProgram
		program.compile_and_link
		var error = program.error
		assert error == null else print_error error
		return program
	end

	# Draw the light view in the bottom left of the screen, for debugging only
	#
	# The shadow depth texture is a square that can be deformed by this projection.
	protected fun frame_core_shadow_debug(display: GamnitDisplay)
	do
		if not supports_shadows then
			print_error "Error: Shadows are not supported by the current hardware configuration"
			return
		end

		perf_clock_shadow.lapse

		var program = shadow_debug_program

		glBindBuffer(gl_ARRAY_BUFFER, shadow_context.buffer_array)
		glViewport(0, 0, display.width/3, display.height/3)
		glClear gl_DEPTH_BUFFER_BIT
		program.use

		# Uniforms
		glActiveTexture gl_TEXTURE0
		glBindTexture(gl_TEXTURE_2D, shadow_context.depth_texture)
		program.texture.uniform 0

		# Attributes
		var sizeof_gl_float = 4
		var n_floats = 3
		glEnableVertexAttribArray program.coord.location
		glVertexAttribPointeri(program.coord.location, n_floats, gl_FLOAT, false, 0, 0)
		var offset = 4 * n_floats * sizeof_gl_float

		n_floats = 2
		glEnableVertexAttribArray program.tex_coord.location
		glVertexAttribPointeri(program.tex_coord.location, n_floats, gl_FLOAT, false, 0, offset)
		var gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error

		# Draw
		glDrawArrays(gl_TRIANGLE_STRIP, 0, 4)
		gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error

		# Take down
		glBindBuffer(gl_ARRAY_BUFFER, 0)
		gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error

		sys.perfs["gamnit shadow debug"].add app.perf_clock_shadow.lapse
	end
end

# Handles to reused GL buffers and texture
private class ShadowContext

	# Real screen framebuffer
	var screen_framebuffer: Int = -1

	# Framebuffer for the light point of view
	var light_view_framebuffer: Int = -1

	# Depth attached to `light_view_framebuffer`
	var depth_texture: Int = -1

	# Buffer name for vertex data
	var buffer_array: Int = -1

	# Prepare all attributes once per resolution change
	fun prepare_once(display: GamnitDisplay, shadow_resolution: Int)
	do
		assert display.gl_extensions.has("GL_OES_depth_texture")

		# Set aside the real screen framebuffer name
		var screen_framebuffer = glGetIntegerv(gl_FRAMEBUFFER_BINDING, 0)
		self.screen_framebuffer = screen_framebuffer

		# Framebuffer
		var framebuffer = glGenFramebuffers(1).first
		glBindFramebuffer(gl_FRAMEBUFFER, framebuffer)
		assert glIsFramebuffer(framebuffer)
		self.light_view_framebuffer = framebuffer
		var gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error

		# Depth & texture/color
		var textures = glGenTextures(1)
		self.depth_texture = textures[0]
		gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error

		resize(display, shadow_resolution)

		# Array buffer
		buffer_array = glGenBuffers(1).first
		glBindBuffer(gl_ARRAY_BUFFER, buffer_array)
		assert glIsBuffer(buffer_array)
		gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error

		## coord
		var data = new Array[Float]
		data.add_all([-1.0, -1.0, 0.0,
	                   1.0, -1.0, 0.0,
	                  -1.0,  1.0, 0.0,
	                   1.0,  1.0, 0.0])
		## tex_coord
		data.add_all([0.0, 0.0,
		              1.0, 0.0,
		              0.0, 1.0,
		              1.0, 1.0])
		var c_data = new GLfloatArray.from(data)
		glBufferData(gl_ARRAY_BUFFER, data.length*4, c_data.native_array, gl_STATIC_DRAW)

		glBindBuffer(gl_ARRAY_BUFFER, 0)

		gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error
	end

	# Init size or resize `depth_texture`
	fun resize(display: GamnitDisplay, shadow_resolution: Int)
	do
		glBindFramebuffer(gl_FRAMEBUFFER, light_view_framebuffer)
		var gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error

		# Depth texture
		var depth_texture = self.depth_texture
		glActiveTexture gl_TEXTURE0
		glBindTexture(gl_TEXTURE_2D, depth_texture)
		glTexParameteri(gl_TEXTURE_2D, gl_TEXTURE_MIN_FILTER, gl_LINEAR)
		glTexParameteri(gl_TEXTURE_2D, gl_TEXTURE_MAG_FILTER, gl_NEAREST)
		glTexParameteri(gl_TEXTURE_2D, gl_TEXTURE_WRAP_S, gl_CLAMP_TO_EDGE)
		glTexParameteri(gl_TEXTURE_2D, gl_TEXTURE_WRAP_T, gl_CLAMP_TO_EDGE)
		gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error

		# TODO support hardware shadows with GL ES 3.0 or GL_EXT_shadow_samplers
		#glTexParameteri(gl_TEXTURE_2D, gl_TEXTURE_COMPARE_MODE, ...)

		glTexImage2D(gl_TEXTURE_2D, 0, gl_DEPTH_COMPONENT,
		             shadow_resolution, shadow_resolution,
		             0, gl_DEPTH_COMPONENT, gl_UNSIGNED_SHORT, new Pointer.nul)
		gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error

		glFramebufferTexture2D(gl_FRAMEBUFFER, gl_DEPTH_ATTACHMENT, gl_TEXTURE_2D, depth_texture, 0)
		gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error

		# Check if the framebuffer is complete and valid
		assert glCheckFramebufferStatus(gl_FRAMEBUFFER) == gl_FRAMEBUFFER_COMPLETE

		# Take down
		glBindTexture(gl_TEXTURE_2D, 0)
		glBindFramebuffer(gl_FRAMEBUFFER, 0)
		gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error
	end

	var destroyed = false

	fun destroy
	do
		if destroyed then return
		destroyed = true

		# Free the buffer
		glDeleteBuffers([buffer_array])
		var gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error
		buffer_array = -1

		# Free the array and framebuffer plus its attachments
		glDeleteBuffers([buffer_array])
		glDeleteFramebuffers([light_view_framebuffer])
		glDeleteTextures([depth_texture])
	end
end

redef class Material
	# Optimized draw of `model`, a part of `actor`, from the view of `camera`
	#
	# This drawing should only produce usable depth data. The default behavior,
	# uses `shadow_depth_program`.
	protected fun draw_depth(actor: Actor, model: LeafModel, camera: Camera)
	do
		var program = app.shadow_depth_program
		program.use
		program.mvp.uniform camera.mvp_matrix

		var mesh = model.mesh

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

		program.tex_coord.array_enabled = true
		program.tex_coord.array(mesh.texture_coords, 2)

		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)

		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

end

# Efficiently draw actors from the light view
class ShadowDepthProgram
	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;

		// Vertex normal
		attribute vec3 normal;

		// Model view projection matrix
		uniform mat4 mvp;

		// Rotation matrix
		uniform mat4 rotation;

		// Output for the fragment shader
		varying vec2 v_tex_coord;

		void main()
		{
			vec4 pos = (vec4(coord.xyz * scale, 1.0) * rotation + translation);
			gl_Position = pos * mvp;

			// Pass varyings to the fragment shader
			v_tex_coord = vec2(tex_coord.x, 1.0 - tex_coord.y);
		}
		""" @ glsl_vertex_shader

	redef var fragment_shader_source = """
		precision mediump float;

		// Diffuse map
		uniform bool use_map_diffuse;
		uniform sampler2D map_diffuse;

		varying vec2 v_tex_coord;

		void main()
		{
			if (use_map_diffuse && texture2D(map_diffuse, v_tex_coord).a <= 0.01) {
				discard;
			}
		}
		""" @ 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

	# Diffuse color
	var diffuse_color = uniforms["diffuse_color"].as(UniformVec4) 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
end

# Draw the camera point of view on screen
private class LightPointOfViewProgram
	super GamnitProgramFromSource

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

		// Vertex coordinates on textures
		attribute vec2 tex_coord;

		// Output to the fragment shader
		varying vec2 v_coord;

		void main()
		{
			gl_Position = vec4(coord, 1.0);
			v_coord = tex_coord;
		}
		""" @ glsl_vertex_shader

	redef var fragment_shader_source = """
		precision mediump float;

		// Virtual screen texture / color attachment
		uniform sampler2D texture0;

		// Input from the vertex shader
		varying vec2 v_coord;

		void main()
		{
			gl_FragColor = texture2D(texture0, v_coord);
		}
		""" @ glsl_fragment_shader

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

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

	# Visible texture
	var texture = uniforms["texture0"].as(UniformSampler2D) is lazy
end
lib/gamnit/depth/shadow.nit:15,1--472,3