Graphic program to display 3D models with Blinn-Phong specular lighting

Introduced properties

fun alpha: AttributeFloat

gamnit :: BlinnPhongProgram :: alpha

Scaling per vertex
protected fun alpha=(alpha: AttributeFloat)

gamnit :: BlinnPhongProgram :: alpha=

Scaling per vertex
protected fun ambient_color=(ambient_color: UniformVec4)

gamnit :: BlinnPhongProgram :: ambient_color=

Ambient color
fun camera: UniformVec3

gamnit :: BlinnPhongProgram :: camera

Camera position
protected fun camera=(camera: UniformVec3)

gamnit :: BlinnPhongProgram :: camera=

Camera position
fun coord: AttributeVec4

gamnit :: BlinnPhongProgram :: coord

Vertices coordinates
protected fun coord=(coord: AttributeVec4)

gamnit :: BlinnPhongProgram :: coord=

Vertices coordinates
protected fun depth_texture=(depth_texture: UniformSampler2D)

gamnit :: BlinnPhongProgram :: depth_texture=

Diffuse texture unit
fun depth_texture_size: UniformFloat

gamnit :: BlinnPhongProgram :: depth_texture_size

Size, in pixels, of depth_texture
protected fun depth_texture_size=(depth_texture_size: UniformFloat)

gamnit :: BlinnPhongProgram :: depth_texture_size=

Size, in pixels, of depth_texture
fun depth_texture_taps: UniformInt

gamnit :: BlinnPhongProgram :: depth_texture_taps

Times to tap the depth_texture, square root (set to 3 for a total of 9 taps)
protected fun depth_texture_taps=(depth_texture_taps: UniformInt)

gamnit :: BlinnPhongProgram :: depth_texture_taps=

Times to tap the depth_texture, square root (set to 3 for a total of 9 taps)
protected fun diffuse_color=(diffuse_color: UniformVec4)

gamnit :: BlinnPhongProgram :: diffuse_color=

Diffuse color
protected fun fragment_shader_source=(fragment_shader_source: Text)

gamnit :: BlinnPhongProgram :: fragment_shader_source=

fun light_center: UniformVec3

gamnit :: BlinnPhongProgram :: light_center

Center position of the light or vector to parallel light source
protected fun light_center=(light_center: UniformVec3)

gamnit :: BlinnPhongProgram :: light_center=

Center position of the light or vector to parallel light source
fun light_kind: UniformInt

gamnit :: BlinnPhongProgram :: light_kind

Kind of lights: 0 -> no light, 1 -> parallel, 2 -> point
protected fun light_kind=(light_kind: UniformInt)

gamnit :: BlinnPhongProgram :: light_kind=

Kind of lights: 0 -> no light, 1 -> parallel, 2 -> point
fun light_mvp: UniformMat4

gamnit :: BlinnPhongProgram :: light_mvp

Light model view projection matrix
protected fun light_mvp=(light_mvp: UniformMat4)

gamnit :: BlinnPhongProgram :: light_mvp=

Light model view projection matrix
protected fun map_ambient=(map_ambient: UniformSampler2D)

gamnit :: BlinnPhongProgram :: map_ambient=

Ambient texture unit
protected fun map_bump=(map_bump: UniformSampler2D)

gamnit :: BlinnPhongProgram :: map_bump=

Bump texture unit
protected fun map_diffuse=(map_diffuse: UniformSampler2D)

gamnit :: BlinnPhongProgram :: map_diffuse=

Diffuse texture unit
fun map_specular: UniformSampler2D

gamnit :: BlinnPhongProgram :: map_specular

Specularity texture unit
protected fun map_specular=(map_specular: UniformSampler2D)

gamnit :: BlinnPhongProgram :: map_specular=

Specularity texture unit
fun mvp: UniformMat4

gamnit :: BlinnPhongProgram :: mvp

Camera model view projection matrix
protected fun mvp=(mvp: UniformMat4)

gamnit :: BlinnPhongProgram :: mvp=

Camera model view projection matrix
fun normal: AttributeVec3

gamnit :: BlinnPhongProgram :: normal

Normal per vertex
protected fun normal=(normal: AttributeVec3)

gamnit :: BlinnPhongProgram :: normal=

Normal per vertex
fun rotation=(mat: Matrix)

gamnit :: BlinnPhongProgram :: rotation=

Set mat at the uniform rotation matrix
protected fun rotation_row0=(rotation_row0: AttributeVec4)

gamnit :: BlinnPhongProgram :: rotation_row0=

Rotation matrix, row0
protected fun rotation_row1=(rotation_row1: AttributeVec4)

gamnit :: BlinnPhongProgram :: rotation_row1=

Rotation matrix, row 1
protected fun rotation_row2=(rotation_row2: AttributeVec4)

gamnit :: BlinnPhongProgram :: rotation_row2=

Rotation matrix, row 2
protected fun rotation_row3=(rotation_row3: AttributeVec4)

gamnit :: BlinnPhongProgram :: rotation_row3=

Rotation matrix, row 3
fun scale: AttributeFloat

gamnit :: BlinnPhongProgram :: scale

Scaling per vertex
protected fun scale=(scale: AttributeFloat)

gamnit :: BlinnPhongProgram :: scale=

Scaling per vertex
protected fun specular_color=(specular_color: UniformVec4)

gamnit :: BlinnPhongProgram :: specular_color=

Specular color
fun tex_coord: AttributeVec2

gamnit :: BlinnPhongProgram :: tex_coord

Coordinates on the textures, per vertex
protected fun tex_coord=(tex_coord: AttributeVec2)

gamnit :: BlinnPhongProgram :: tex_coord=

Coordinates on the textures, per vertex
fun translation: AttributeVec4

gamnit :: BlinnPhongProgram :: translation

Translation applied to each vertex
protected fun translation=(translation: AttributeVec4)

gamnit :: BlinnPhongProgram :: translation=

Translation applied to each vertex
fun use_map_ambient: UniformBool

gamnit :: BlinnPhongProgram :: use_map_ambient

Should this program use the texture map_ambient?
protected fun use_map_ambient=(use_map_ambient: UniformBool)

gamnit :: BlinnPhongProgram :: use_map_ambient=

Should this program use the texture map_ambient?
fun use_map_bump: UniformBool

gamnit :: BlinnPhongProgram :: use_map_bump

Should this program use the texture map_bump?
protected fun use_map_bump=(use_map_bump: UniformBool)

gamnit :: BlinnPhongProgram :: use_map_bump=

Should this program use the texture map_bump?
fun use_map_diffuse: UniformBool

gamnit :: BlinnPhongProgram :: use_map_diffuse

Should this program use the texture map_diffuse?
protected fun use_map_diffuse=(use_map_diffuse: UniformBool)

gamnit :: BlinnPhongProgram :: use_map_diffuse=

Should this program use the texture map_diffuse?
fun use_map_specular: UniformBool

gamnit :: BlinnPhongProgram :: use_map_specular

Should this program use the texture map_specular?
protected fun use_map_specular=(use_map_specular: UniformBool)

gamnit :: BlinnPhongProgram :: use_map_specular=

Should this program use the texture map_specular?
fun use_shadows: UniformBool

gamnit :: BlinnPhongProgram :: use_shadows

Should shadow be drawn? Would use depth_texture and light_mvp.
protected fun use_shadows=(use_shadows: UniformBool)

gamnit :: BlinnPhongProgram :: use_shadows=

Should shadow be drawn? Would use depth_texture and light_mvp.
protected fun vertex_shader_source=(vertex_shader_source: Text)

gamnit :: BlinnPhongProgram :: vertex_shader_source=

Redefined properties

redef type SELF: BlinnPhongProgram

gamnit $ BlinnPhongProgram :: SELF

Type of this instance, automatically specialized in every class
redef fun fragment_shader_source: Text

gamnit $ BlinnPhongProgram :: fragment_shader_source

Source code of the fragment shader
redef fun vertex_shader_source: Text

gamnit $ BlinnPhongProgram :: vertex_shader_source

Source code of the vertex shader

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
fun alpha: AttributeFloat

gamnit :: BlinnPhongProgram :: alpha

Scaling per vertex
protected fun alpha=(alpha: AttributeFloat)

gamnit :: BlinnPhongProgram :: alpha=

Scaling per vertex
protected fun ambient_color=(ambient_color: UniformVec4)

gamnit :: BlinnPhongProgram :: ambient_color=

Ambient color
fun attributes: AttributeMap

gamnit :: GamnitProgram :: attributes

Attributes of this program organized by name
protected fun attributes=(attributes: AttributeMap)

gamnit :: GamnitProgram :: attributes=

Attributes of this program organized by name
fun camera: UniformVec3

gamnit :: BlinnPhongProgram :: camera

Camera position
protected fun camera=(camera: UniformVec3)

gamnit :: BlinnPhongProgram :: camera=

Camera position
protected fun class_factory(name: String): CLASS

core :: Object :: class_factory

Implementation used by get_class to create the specific class.
fun class_name: String

core :: Object :: class_name

The class name of the object.
fun coord: AttributeVec4

gamnit :: BlinnPhongProgram :: coord

Vertices coordinates
protected fun coord=(coord: AttributeVec4)

gamnit :: BlinnPhongProgram :: coord=

Vertices coordinates
fun delete

gamnit :: GamnitProgram :: delete

Delete this program if it has not already been deleted
fun deleted: Bool

gamnit :: GamnitProgram :: deleted

Has this program been deleted?
protected fun deleted=(deleted: Bool)

gamnit :: GamnitProgram :: deleted=

Has this program been deleted?
protected fun depth_texture=(depth_texture: UniformSampler2D)

gamnit :: BlinnPhongProgram :: depth_texture=

Diffuse texture unit
fun depth_texture_size: UniformFloat

gamnit :: BlinnPhongProgram :: depth_texture_size

Size, in pixels, of depth_texture
protected fun depth_texture_size=(depth_texture_size: UniformFloat)

gamnit :: BlinnPhongProgram :: depth_texture_size=

Size, in pixels, of depth_texture
fun depth_texture_taps: UniformInt

gamnit :: BlinnPhongProgram :: depth_texture_taps

Times to tap the depth_texture, square root (set to 3 for a total of 9 taps)
protected fun depth_texture_taps=(depth_texture_taps: UniformInt)

gamnit :: BlinnPhongProgram :: depth_texture_taps=

Times to tap the depth_texture, square root (set to 3 for a total of 9 taps)
fun diagnose

gamnit :: GamnitProgram :: diagnose

Diagnose possible problems with the shaders of the program
protected fun diffuse_color=(diffuse_color: UniformVec4)

gamnit :: BlinnPhongProgram :: diffuse_color=

Diffuse color
fun error: nullable Error

gamnit :: GamnitProgram :: error

Last error raised by compile_and_link
protected fun error=(error: nullable Error)

gamnit :: GamnitProgram :: error=

Last error raised by compile_and_link
abstract fun fragment_shader: FragmentShader

gamnit :: GamnitProgram :: fragment_shader

Fragment shader to attach to this program
abstract fun fragment_shader_source: Text

gamnit :: GamnitProgramFromSource :: fragment_shader_source

Source code of the fragment shader
protected fun fragment_shader_source=(fragment_shader_source: Text)

gamnit :: BlinnPhongProgram :: fragment_shader_source=

fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun hash: Int

core :: Object :: hash

The hash code of the object.
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".
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.
fun light_center: UniformVec3

gamnit :: BlinnPhongProgram :: light_center

Center position of the light or vector to parallel light source
protected fun light_center=(light_center: UniformVec3)

gamnit :: BlinnPhongProgram :: light_center=

Center position of the light or vector to parallel light source
fun light_kind: UniformInt

gamnit :: BlinnPhongProgram :: light_kind

Kind of lights: 0 -> no light, 1 -> parallel, 2 -> point
protected fun light_kind=(light_kind: UniformInt)

gamnit :: BlinnPhongProgram :: light_kind=

Kind of lights: 0 -> no light, 1 -> parallel, 2 -> point
fun light_mvp: UniformMat4

gamnit :: BlinnPhongProgram :: light_mvp

Light model view projection matrix
protected fun light_mvp=(light_mvp: UniformMat4)

gamnit :: BlinnPhongProgram :: light_mvp=

Light model view projection matrix
protected fun map_ambient=(map_ambient: UniformSampler2D)

gamnit :: BlinnPhongProgram :: map_ambient=

Ambient texture unit
protected fun map_bump=(map_bump: UniformSampler2D)

gamnit :: BlinnPhongProgram :: map_bump=

Bump texture unit
protected fun map_diffuse=(map_diffuse: UniformSampler2D)

gamnit :: BlinnPhongProgram :: map_diffuse=

Diffuse texture unit
fun map_specular: UniformSampler2D

gamnit :: BlinnPhongProgram :: map_specular

Specularity texture unit
protected fun map_specular=(map_specular: UniformSampler2D)

gamnit :: BlinnPhongProgram :: map_specular=

Specularity texture unit
fun mvp: UniformMat4

gamnit :: BlinnPhongProgram :: mvp

Camera model view projection matrix
protected fun mvp=(mvp: UniformMat4)

gamnit :: BlinnPhongProgram :: mvp=

Camera model view projection matrix
fun normal: AttributeVec3

gamnit :: BlinnPhongProgram :: normal

Normal per vertex
protected fun normal=(normal: AttributeVec3)

gamnit :: BlinnPhongProgram :: normal=

Normal per vertex
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
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).
fun rotation=(mat: Matrix)

gamnit :: BlinnPhongProgram :: rotation=

Set mat at the uniform rotation matrix
protected fun rotation_row0=(rotation_row0: AttributeVec4)

gamnit :: BlinnPhongProgram :: rotation_row0=

Rotation matrix, row0
protected fun rotation_row1=(rotation_row1: AttributeVec4)

gamnit :: BlinnPhongProgram :: rotation_row1=

Rotation matrix, row 1
protected fun rotation_row2=(rotation_row2: AttributeVec4)

gamnit :: BlinnPhongProgram :: rotation_row2=

Rotation matrix, row 2
protected fun rotation_row3=(rotation_row3: AttributeVec4)

gamnit :: BlinnPhongProgram :: rotation_row3=

Rotation matrix, row 3
fun scale: AttributeFloat

gamnit :: BlinnPhongProgram :: scale

Scaling per vertex
protected fun scale=(scale: AttributeFloat)

gamnit :: BlinnPhongProgram :: scale=

Scaling per vertex
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
protected fun specular_color=(specular_color: UniformVec4)

gamnit :: BlinnPhongProgram :: specular_color=

Specular color
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
fun tex_coord: AttributeVec2

gamnit :: BlinnPhongProgram :: tex_coord

Coordinates on the textures, per vertex
protected fun tex_coord=(tex_coord: AttributeVec2)

gamnit :: BlinnPhongProgram :: tex_coord=

Coordinates on the textures, per vertex
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 translation: AttributeVec4

gamnit :: BlinnPhongProgram :: translation

Translation applied to each vertex
protected fun translation=(translation: AttributeVec4)

gamnit :: BlinnPhongProgram :: translation=

Translation applied to each vertex
fun uniforms: UniformMap

gamnit :: GamnitProgram :: uniforms

Uniforms of this program organized by name
protected fun uniforms=(uniforms: UniformMap)

gamnit :: GamnitProgram :: uniforms=

Uniforms of this program organized by name
fun use

gamnit :: GamnitProgram :: use

Notify the GPU to use this program
fun use_map_ambient: UniformBool

gamnit :: BlinnPhongProgram :: use_map_ambient

Should this program use the texture map_ambient?
protected fun use_map_ambient=(use_map_ambient: UniformBool)

gamnit :: BlinnPhongProgram :: use_map_ambient=

Should this program use the texture map_ambient?
fun use_map_bump: UniformBool

gamnit :: BlinnPhongProgram :: use_map_bump

Should this program use the texture map_bump?
protected fun use_map_bump=(use_map_bump: UniformBool)

gamnit :: BlinnPhongProgram :: use_map_bump=

Should this program use the texture map_bump?
fun use_map_diffuse: UniformBool

gamnit :: BlinnPhongProgram :: use_map_diffuse

Should this program use the texture map_diffuse?
protected fun use_map_diffuse=(use_map_diffuse: UniformBool)

gamnit :: BlinnPhongProgram :: use_map_diffuse=

Should this program use the texture map_diffuse?
fun use_map_specular: UniformBool

gamnit :: BlinnPhongProgram :: use_map_specular

Should this program use the texture map_specular?
protected fun use_map_specular=(use_map_specular: UniformBool)

gamnit :: BlinnPhongProgram :: use_map_specular=

Should this program use the texture map_specular?
fun use_shadows: UniformBool

gamnit :: BlinnPhongProgram :: use_shadows

Should shadow be drawn? Would use depth_texture and light_mvp.
protected fun use_shadows=(use_shadows: UniformBool)

gamnit :: BlinnPhongProgram :: use_shadows=

Should shadow be drawn? Would use depth_texture and light_mvp.
abstract fun vertex_shader: VertexShader

gamnit :: GamnitProgram :: vertex_shader

Vertex shader to attach to this program
abstract fun vertex_shader_source: Text

gamnit :: GamnitProgramFromSource :: vertex_shader_source

Source code of the vertex shader
protected fun vertex_shader_source=(vertex_shader_source: Text)

gamnit :: BlinnPhongProgram :: vertex_shader_source=

package_diagram gamnit::BlinnPhongProgram BlinnPhongProgram gamnit::GamnitProgramFromSource GamnitProgramFromSource gamnit::BlinnPhongProgram->gamnit::GamnitProgramFromSource gamnit::GamnitProgram GamnitProgram gamnit::GamnitProgramFromSource->gamnit::GamnitProgram ...gamnit::GamnitProgram ... ...gamnit::GamnitProgram->gamnit::GamnitProgram gamnit::NormalProgram NormalProgram gamnit::NormalProgram->gamnit::BlinnPhongProgram

Ancestors

abstract class GamnitProgram

gamnit :: GamnitProgram

Gamnit graphical program
interface Object

core :: Object

The root of the class hierarchy.

Parents

class GamnitProgramFromSource

gamnit :: GamnitProgramFromSource

Gamnit graphical program from the shaders source code

Children

class NormalProgram

gamnit :: NormalProgram

Program to color objects from their normal vectors

Class definitions

gamnit $ BlinnPhongProgram
# Graphic program to display 3D models with Blinn-Phong specular lighting
class BlinnPhongProgram
	super GamnitProgramFromSource

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

		// Vertex translation
		attribute vec4 translation;

		// Vertex scaling
		attribute float scale;

		attribute float alpha;

		// Vertex coordinates on textures
		attribute vec2 tex_coord;

		// Vertex normal
		attribute vec3 normal;

		// Camera model view projection matrix
		uniform mat4 mvp;

		// Actor rotation
		attribute vec4 rotation_row0;
		attribute vec4 rotation_row1;
		attribute vec4 rotation_row2;
		attribute vec4 rotation_row3;

		mat4 rotation()
		{
			return mat4(rotation_row0, rotation_row1, rotation_row2, rotation_row3);
		}

		// Lights config
		uniform lowp int light_kind;
		uniform vec3 light_center;
		uniform mat4 light_mvp;

		// Coordinates of the camera
		uniform vec3 camera;

		// Output for the fragment shader
		varying vec2 v_tex_coord;
		varying vec3 v_normal;
		varying vec4 v_to_light;
		varying vec4 v_to_camera;
		varying vec4 v_depth_pos;
		varying float v_alpha;

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

			// Pass varyings to the fragment shader
			v_tex_coord = vec2(tex_coord.x, 1.0 - tex_coord.y);
			v_normal = normalize(vec4(normal, 0.0) * rotation).xyz;
			v_to_camera = normalize(vec4(camera, 1.0) - pos);

			if (light_kind == 0) {
				// No light
			} else if (light_kind == 1) {
				// Parallel
				v_to_light = normalize(vec4(light_center, 1.0));
			} else {
				// Point light (and others?)
				v_to_light = normalize(vec4(light_center, 1.0) - pos);
			}

			v_alpha = alpha;
		}
		""" @ glsl_vertex_shader

	redef var fragment_shader_source = """
		precision mediump float;

		// Input from the vertex shader
		varying vec2 v_tex_coord;
		varying vec3 v_normal;
		varying vec4 v_to_light;
		varying vec4 v_to_camera;
		varying vec4 v_depth_pos;
		varying float v_alpha;

		// Colors
		uniform vec4 ambient_color;
		uniform vec4 diffuse_color;
		uniform vec4 specular_color;

		// Ambient map
		uniform bool use_map_ambient;
		uniform sampler2D map_ambient;

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

		// Specular map
		uniform bool use_map_specular;
		uniform sampler2D map_specular;

		// Bump map
		uniform bool use_map_bump;
		uniform sampler2D map_bump;

		// Normal map
		uniform bool use_map_normal;
		uniform sampler2D map_normal;

		// Shadow
		uniform lowp int light_kind;
		uniform bool use_shadows;
		uniform sampler2D depth_texture;
		uniform float depth_size;
		uniform int depth_taps;

		// Shadow effect on the diffuse colors of the fragment at offset `x, y`
		float shadow_lookup(vec2 depth_coord, float x, float y) {
			float tap_width = 1.0;
			float pixel_size = tap_width/depth_size;

			vec2 offset = vec2(x * pixel_size * v_depth_pos.w,
			                   y * pixel_size * v_depth_pos.w);
			depth_coord += offset;

			float depth = v_depth_pos.z/v_depth_pos.w;
			//vec2 depth_coord = v_depth_pos.xy/v_depth_pos.w;
			if (depth_coord.x < 0.0 || depth_coord.x > 1.0 || depth_coord.y < 0.0 || depth_coord.y > 1.0) {
				// Out of the shadow map texture
				//gl_FragColor = vec4(1.0, 0.0, 0.0, 1.0); // debug, red out of the light view
				return 1.0;
			}

			float shadow_depth = texture2D(depth_texture, depth_coord).r;
			float bias = 0.0001;
			if (shadow_depth == 1.0) {
				// Too far to be in depth texture
				return 1.0;
			} else if (shadow_depth <= depth - bias) {
				// In a shadow
				//gl_FragColor = vec4(0.0, 0.0, 1.0, 1.0); // debug, blue shadows
				return 0.2; // TODO replace with a configurable ambient light
			}

			//gl_FragColor = vec4(0.0, 1.0-(shadow_depth-depth), 0.0, 1.0); // debug, green lit surfaces
			return 1.0;
		}

		// Shadow effect on the diffuse colors of the fragment
		float shadow() {
			if (!use_shadows) return 1.0;

			vec2 depth_coord = v_depth_pos.xy/v_depth_pos.w;

			float taps = float(depth_taps);
			float tap_step = 2.00/taps;
			float sum = 0.0;
			for (float x = -1.0; x <= 0.99; x += tap_step)
				for (float y = -1.0; y <= 0.99; y += tap_step)
					sum += shadow_lookup(depth_coord, x, y);
			return sum / taps / taps;
		}

		void main()
		{
			// Normal
			vec3 normal = v_normal;
			if (use_map_bump) {
				// TODO
				vec3 bump = 2.0 * texture2D(map_bump, v_tex_coord).rgb - 1.0;
			}

			// Ambient light
			vec4 ambient = ambient_color * v_alpha;
			if (use_map_ambient) ambient *= texture2D(map_ambient, v_tex_coord);

			if (light_kind == 0) {
				// No light, show diffuse and ambient

				vec4 diffuse = diffuse_color * v_alpha;
				if (use_map_diffuse) diffuse *= texture2D(map_diffuse, v_tex_coord);

				gl_FragColor = ambient + diffuse;
			} else {
				// Parallel light or point light (1 or 2)

				// Diffuse Lambert light
				vec3 to_light = v_to_light.xyz;
				float lambert = clamp(dot(normal, to_light), 0.0, 1.0);

				vec4 diffuse = lambert * diffuse_color;
				if (use_map_diffuse) diffuse *= texture2D(map_diffuse, v_tex_coord);

				// Specular Phong light
				float s = 0.0;
				if (lambert > 0.0) {
					// In light
					vec3 l = reflect(-to_light, normal);
					s = clamp(dot(l, v_to_camera.xyz), 0.0, 1.0);
					s = pow(s, 8.0); // TODO make this `shininess` a material attribute

					// Shadows
					diffuse *= shadow();
				}

				vec4 specular = s * specular_color * v_alpha;
				if (use_map_specular) specular *= texture2D(map_specular, v_tex_coord).x;

				gl_FragColor = ambient + diffuse + specular;
			}

			if (gl_FragColor.a < 0.01) discard;

			//gl_FragColor = vec4(normalize(normal).rgb, 1.0); // Debug normals
		}
		""" @ glsl_fragment_shader

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

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

	# Ambient texture unit
	var map_ambient = uniforms["map_ambient"].as(UniformSampler2D) 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

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

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

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

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

	# Normal per vertex
	var normal = attributes["normal"].as(AttributeVec3) is lazy

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

	# Ambient color
	var ambient_color = uniforms["ambient_color"].as(UniformVec4) is lazy

	# Diffuse color
	var diffuse_color = uniforms["diffuse_color"].as(UniformVec4) is lazy

	# Specular color
	var specular_color = uniforms["specular_color"].as(UniformVec4) is lazy

	# Kind of lights: 0 -> no light, 1 -> parallel, 2 -> point
	var light_kind = uniforms["light_kind"].as(UniformInt) is lazy

	# Center position of the light *or* vector to parallel light source
	var light_center = uniforms["light_center"].as(UniformVec3) is lazy

	# Light model view projection matrix
	var light_mvp = uniforms["light_mvp"].as(UniformMat4) is lazy

	# Should shadow be drawn? Would use `depth_texture` and `light_mvp`.
	var use_shadows = uniforms["use_shadows"].as(UniformBool) is lazy

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

	# Size, in pixels, of `depth_texture`
	var depth_texture_size = uniforms["depth_size"].as(UniformFloat) is lazy

	# Times to tap the `depth_texture`, square root (set to 3 for a total of 9 taps)
	var depth_texture_taps = uniforms["depth_taps"].as(UniformInt) is lazy

	# Camera position
	var camera = uniforms["camera"].as(UniformVec3) is lazy

	# Translation applied to each vertex
	var translation = attributes["translation"].as(AttributeVec4) is lazy # TODO attribute

	# Set `mat` at the uniform rotation matrix
	fun rotation=(mat: Matrix)
	do
		var i = 0
		for r in [rotation_row0, rotation_row1, rotation_row2, rotation_row3] do
			if r.is_active then
				glDisableVertexAttribArray r.location
				r.uniform(mat[0, i], mat[1, i], mat[2, i], mat[3, i])
			end
			i += 1
		end
		var gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error
	end

	# Rotation matrix, row0
	var rotation_row0 = attributes["rotation_row0"].as(AttributeVec4) is lazy

	# Rotation matrix, row 1
	var rotation_row1 = attributes["rotation_row1"].as(AttributeVec4) is lazy

	# Rotation matrix, row 2
	var rotation_row2 = attributes["rotation_row2"].as(AttributeVec4) is lazy

	# Rotation matrix, row 3
	var rotation_row3 = attributes["rotation_row3"].as(AttributeVec4) is lazy

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

	# Scaling per vertex
	var alpha = attributes["alpha"].as(AttributeFloat) is lazy

	# Camera model view projection matrix
	var mvp = uniforms["mvp"].as(UniformMat4) is lazy
end
lib/gamnit/depth/more_materials.nit:314,1--640,3