Services for graphical programs with shaders, attributes and uniforms

Introduced classes

class Attribute

gamnit :: Attribute

Shader attribute
class AttributeFloat

gamnit :: AttributeFloat

Shader attribute of GLSL type float
class AttributeMap

gamnit :: AttributeMap

Map to organize Attribute instances by their name
class AttributeVec2

gamnit :: AttributeVec2

Shader attribute of GLSL type vec2
class AttributeVec3

gamnit :: AttributeVec3

Shader attribute of GLSL type vec3
class AttributeVec4

gamnit :: AttributeVec4

Shader attribute of GLSL type vec4
class FragmentShader

gamnit :: FragmentShader

Gamnit fragment shader
abstract class GamnitProgram

gamnit :: GamnitProgram

Gamnit graphical program
class GamnitProgramFromSource

gamnit :: GamnitProgramFromSource

Gamnit graphical program from the shaders source code
class InactiveAttribute

gamnit :: InactiveAttribute

Attribute that does not exist or that has been optimized out
class InactiveUniform

gamnit :: InactiveUniform

Uniform that does not exist or that has been optimized out
abstract class InactiveVariable

gamnit :: InactiveVariable

Inactive shader variable, either optimized out or simple absent from the program
abstract class Shader

gamnit :: Shader

Gamnit shader
class ShaderVariable

gamnit :: ShaderVariable

Uniform or Attribute of a GamnitProgram
abstract class ShaderVariableMap[A: ShaderVariable]

gamnit :: ShaderVariableMap

Map to organize ShaderVariable instances by their name
class Uniform

gamnit :: Uniform

Shader uniform
class UniformBool

gamnit :: UniformBool

Shader uniform of GLSL type bool
class UniformFloat

gamnit :: UniformFloat

Shader uniform of GLSL type vec4
class UniformInt

gamnit :: UniformInt

Shader uniform of GLSL type int
class UniformMap

gamnit :: UniformMap

Map to organize Uniform instances by their name
class UniformMat4

gamnit :: UniformMat4

Shader uniform of GLSL type mat4
class UniformSampler2D

gamnit :: UniformSampler2D

Shader uniform of GLSL type sampler2D
class UniformVec2

gamnit :: UniformVec2

Shader uniform of GLSL type vec4
class UniformVec3

gamnit :: UniformVec3

Shader uniform of GLSL type vec4
class UniformVec4

gamnit :: UniformVec4

Shader uniform of GLSL type vec4
class VertexShader

gamnit :: VertexShader

Gamnit vertex shader

Redefined classes

redef class Matrix

gamnit :: programs $ Matrix

A rectangular array of Float
redef extern class NativeGLfloatArray

gamnit :: programs $ NativeGLfloatArray

An array of GLfloat in C (GLfloat*)
redef class Sys

gamnit :: programs $ Sys

The main class of the program.

All class definitions

class Attribute

gamnit $ Attribute

Shader attribute
class AttributeFloat

gamnit $ AttributeFloat

Shader attribute of GLSL type float
class AttributeMap

gamnit $ AttributeMap

Map to organize Attribute instances by their name
class AttributeVec2

gamnit $ AttributeVec2

Shader attribute of GLSL type vec2
class AttributeVec3

gamnit $ AttributeVec3

Shader attribute of GLSL type vec3
class AttributeVec4

gamnit $ AttributeVec4

Shader attribute of GLSL type vec4
class FragmentShader

gamnit $ FragmentShader

Gamnit fragment shader
abstract class GamnitProgram

gamnit $ GamnitProgram

Gamnit graphical program
class GamnitProgramFromSource

gamnit $ GamnitProgramFromSource

Gamnit graphical program from the shaders source code
class InactiveAttribute

gamnit $ InactiveAttribute

Attribute that does not exist or that has been optimized out
class InactiveUniform

gamnit $ InactiveUniform

Uniform that does not exist or that has been optimized out
abstract class InactiveVariable

gamnit $ InactiveVariable

Inactive shader variable, either optimized out or simple absent from the program
redef class Matrix

gamnit :: programs $ Matrix

A rectangular array of Float
redef extern class NativeGLfloatArray

gamnit :: programs $ NativeGLfloatArray

An array of GLfloat in C (GLfloat*)
abstract class Shader

gamnit $ Shader

Gamnit shader
class ShaderVariable

gamnit $ ShaderVariable

Uniform or Attribute of a GamnitProgram
abstract class ShaderVariableMap[A: ShaderVariable]

gamnit $ ShaderVariableMap

Map to organize ShaderVariable instances by their name
redef class Sys

gamnit :: programs $ Sys

The main class of the program.
class Uniform

gamnit $ Uniform

Shader uniform
class UniformBool

gamnit $ UniformBool

Shader uniform of GLSL type bool
class UniformFloat

gamnit $ UniformFloat

Shader uniform of GLSL type vec4
class UniformInt

gamnit $ UniformInt

Shader uniform of GLSL type int
class UniformMap

gamnit $ UniformMap

Map to organize Uniform instances by their name
class UniformMat4

gamnit $ UniformMat4

Shader uniform of GLSL type mat4
class UniformSampler2D

gamnit $ UniformSampler2D

Shader uniform of GLSL type sampler2D
class UniformVec2

gamnit $ UniformVec2

Shader uniform of GLSL type vec4
class UniformVec3

gamnit $ UniformVec3

Shader uniform of GLSL type vec4
class UniformVec4

gamnit $ UniformVec4

Shader uniform of GLSL type vec4
class VertexShader

gamnit $ VertexShader

Gamnit vertex shader
package_diagram gamnit::programs programs gamnit::display display gamnit::programs->gamnit::display matrix matrix gamnit::programs->matrix more_collections more_collections gamnit::programs->more_collections glesv2 glesv2 gamnit::display->glesv2 mnit::input input gamnit::display->mnit::input core core matrix->core serialization serialization more_collections->serialization poset poset more_collections->poset ...glesv2 ... ...glesv2->glesv2 ...mnit::input ... ...mnit::input->mnit::input ...core ... ...core->core ...serialization ... ...serialization->serialization ...poset ... ...poset->poset gamnit::gamnit gamnit gamnit::gamnit->gamnit::programs gamnit::gamnit_android gamnit_android gamnit::gamnit_android->gamnit::gamnit gamnit::dynamic_resolution dynamic_resolution gamnit::dynamic_resolution->gamnit::gamnit gamnit::camera_control camera_control gamnit::camera_control->gamnit::gamnit gamnit::gamnit_linux gamnit_linux gamnit::gamnit_linux->gamnit::gamnit gamnit::gamnit_ios gamnit_ios gamnit::gamnit_ios->gamnit::gamnit gamnit::keys keys gamnit::keys->gamnit::gamnit gamnit::limit_fps limit_fps gamnit::limit_fps->gamnit::gamnit gamnit::gamnit_android... ... gamnit::gamnit_android...->gamnit::gamnit_android gamnit::dynamic_resolution... ... gamnit::dynamic_resolution...->gamnit::dynamic_resolution gamnit::camera_control... ... gamnit::camera_control...->gamnit::camera_control gamnit::gamnit_linux... ... gamnit::gamnit_linux...->gamnit::gamnit_linux gamnit::gamnit_ios... ... gamnit::gamnit_ios...->gamnit::gamnit_ios gamnit::keys... ... gamnit::keys...->gamnit::keys gamnit::limit_fps... ... gamnit::limit_fps...->gamnit::limit_fps

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 array

core :: array

This module introduces the standard array structure.
module aware

android :: aware

Android compatibility module
module bitset

core :: bitset

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

core :: gc

Access to the Nit internal garbage collection mechanism
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 meta

meta :: meta

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

core :: native

Native structures for text and bytes
module numeric

core :: numeric

Advanced services for Numeric types
module poset

poset :: poset

Pre order sets and partial order set (ie hierarchies)
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 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 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 display

gamnit :: display

Abstract display services
module matrix

matrix :: matrix

Services for matrices of Float values
module more_collections

more_collections :: more_collections

Highly specific, but useful, collections-related classes.

Children

module gamnit

gamnit :: gamnit

Game and multimedia framework for Nit

Descendants

module a_star-m

a_star-m

module android19

gamnit :: android19

Variation using features from Android API 19
module bmfont

gamnit :: bmfont

Parse Angel Code BMFont format and draw text
module camera_control

gamnit :: camera_control

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

gamnit :: camera_control_android

Two fingers camera manipulation, pinch to zoom and slide to scroll
module camera_control_linux

gamnit :: camera_control_linux

Mouse wheel and middle mouse button to control camera
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 depth_core

gamnit :: depth_core

Base entities of the depth 3D game framework
module dynamic_resolution

gamnit :: dynamic_resolution

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

gamnit :: flat

Simple API for 2D games, built around Sprite and App::update
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_android

gamnit :: gamnit_android

Support services for Gamnit on Android
module gamnit_ios

gamnit :: gamnit_ios

Support services for gamnit on iOS
module gamnit_linux

gamnit :: gamnit_linux

Support services for Gamnit on GNU/Linux
module input_ios

gamnit :: input_ios

Gamnit event support for iOS
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 model_dimensions

gamnit :: model_dimensions

Dimensions related services for Model and Mesh
module more_lights

gamnit :: more_lights

More implementations of Light
module more_materials

gamnit :: more_materials

Various material implementations
module more_meshes

gamnit :: more_meshes

More simple geometric meshes
module more_models

gamnit :: more_models

Services to load models from the assets folder
module particles

gamnit :: particles

Particle effects
module selection

gamnit :: selection

Select Actor from a screen coordinate
module sensors

android :: sensors

Access Android sensors
module shadow

gamnit :: shadow

Shadow mapping using a depth texture
module stereoscopic_view

gamnit :: stereoscopic_view

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

gamnit :: tileset

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

gamnit :: virtual_gamepad

Virtual gamepad mapped to keyboard keys for quick and dirty mobile support
module vr

gamnit :: vr

VR support for gamnit depth, for Android only
# Services for graphical programs with shaders, attributes and uniforms
module programs

import display
import matrix

private import more_collections

# `Uniform` or `Attribute` of a `GamnitProgram`
class ShaderVariable

	# The `GamnitProgram` to which `self` belongs
	var program: GLProgram

	# Name of `self` in the `program` source
	var name: String

	# Location of `self` in the compiled `program`
	var location: Int

	# Number of elements in this array (1 for scalars and more for vectors)
	var size: Int

	# Is `self` an active uniform or attribute in the `program`?
	#
	# If `false`, the variable may have been optimized out by the compiler.
	fun is_active: Bool do return true

	redef fun to_s do return "<{class_name} name:{name} location:{location} size:{size}"
end

# Inactive shader variable, either optimized out or simple absent from the program
#
# Returned by `GamnitProgram::uniforms` or `GamnitProgram::attributes` when
# the uniform has not been identified as active by the driver.
# Operations on instances of this class have no effects.
#
# Act as a compatibility when a program expect a uniform to exist even in
# a context where the driver's compiler may have optimized it out.
# You must be careful when receiving an `InactiveVariable` as it may also
# silence real program errors, such type in variable name.
abstract class InactiveVariable
	super ShaderVariable

	redef fun is_active do return false
end

# Shader attribute
#
# It will use either the `uniform` value or the data at `array_pointer` if
# and only if `array_enabled`.
class Attribute
	super ShaderVariable

	private var array_enabled_cache = false

	# Is the array attribute enabled?
	fun array_enabled: Bool do return array_enabled_cache

	# Set whether to use the data at `array_pointer` over `uniform`.
	fun array_enabled=(value: Bool)
	do
		if not is_active then return

		glUseProgram program

		self.array_enabled_cache = value
		if value then
			glEnableVertexAttribArray location
		else glDisableVertexAttribArray location
	end

	# Define the `array` of vertex data
	fun array(array: Array[Float], data_per_vertex: Int)
	do
		# TODO move this and native_float_array to a subclass specific to float

		if not is_active then return

		var native = native_float_array
		if native == null or array.length > native.length then
			if native != null then native.finalize
			native = new GLfloatArray.from(array)
			self.native_float_array = native
		else
			native.fill_from(array)
		end

		glVertexAttribPointer(location, data_per_vertex, gl_FLOAT, false, 0, native.native_array)
	end

	private var native_float_array: nullable GLfloatArray = null
end

# Shader attribute of GLSL type `float`
class AttributeFloat
	super Attribute

	# Set the uniform value to use when the vertex array is disabled
	fun uniform(x: Float) do if is_active then glVertexAttrib1f(location, x)
end

# Shader attribute of GLSL type `vec2`
class AttributeVec2
	super Attribute

	# Set the uniform value to use when the vertex array is disabled
	fun uniform(x, y: Float) do if is_active then glVertexAttrib2f(location, x, y)
end

# Shader attribute of GLSL type `vec3`
class AttributeVec3
	super Attribute

	# Set the uniform value to use when the vertex array is disabled
	fun uniform(x, y, z: Float) do if is_active then glVertexAttrib3f(location, x, y, z)
end

# Shader attribute of GLSL type `vec4`
class AttributeVec4
	super Attribute

	# Set the uniform value to use when the vertex array is disabled
	fun uniform(x, y, z, w: Float) do if is_active then glVertexAttrib4f(location, x, y, z, w)
end

# `Attribute` that does not exist or that has been optimized out
class InactiveAttribute
	super InactiveVariable
	super AttributeFloat
	super AttributeVec2
	super AttributeVec3
	super AttributeVec4
end

# Shader uniform
class Uniform
	super ShaderVariable

	private fun uniform_1i(index, x: Int) `{ glUniform1i(index, x); `}
end

# Shader uniform of GLSL type `bool`
class UniformBool
	super Uniform

	# Set this uniform value
	fun uniform(val: Bool) do uniform_1i(location, if val then 1 else 0)
end

# Shader uniform of GLSL type `int`
class UniformInt
	super Uniform

	# Set this uniform value
	fun uniform(val: Int) do uniform_1i(location, val)
end

# Shader uniform of GLSL type `vec4`
class UniformFloat
	super Uniform

	# Set this uniform value
	fun uniform(x: Float) do glUniform1f(location, x)
end

# Shader uniform of GLSL type `vec4`
class UniformVec2
	super Uniform

	# Set this uniform value
	fun uniform(x, y: Float) do glUniform2f(location, x, y)
end

# Shader uniform of GLSL type `vec4`
class UniformVec3
	super Uniform

	# Set this uniform value
	fun uniform(x, y, z: Float) do glUniform3f(location, x, y, z)
end

# Shader uniform of GLSL type `vec4`
class UniformVec4
	super Uniform

	# Set this uniform value
	fun uniform(x, y, z, w: Float) do glUniform4f(location, x, y, z, w)
end

# Shader uniform of GLSL type `sampler2D`
class UniformSampler2D
	super Uniform

	# Set this uniform value
	fun uniform(val: Int) do uniform_1i(location, val)
end

# Shader uniform of GLSL type `mat4`
class UniformMat4
	super Uniform

	private var native_matrix_cache: nullable NativeGLfloatArray = null

	# Set this uniform value
	fun uniform(matrix: Matrix)
	do
		var native = native_matrix_cache
		if native == null then
			native = new NativeGLfloatArray.matrix
			self.native_matrix_cache = native
		end

		matrix.fill_native(native)
		uniform_matrix_4f(location, 1, false, native)
	end

	private fun uniform_matrix_4f(index, count: Int, transpose: Bool, data: NativeGLfloatArray) `{
		glUniformMatrix4fv(index, count, transpose, data);
	`}
end

# `Uniform` that does not exist or that has been optimized out
class InactiveUniform
	super InactiveVariable
	super UniformBool
	super UniformInt
	super UniformFloat
	super UniformSampler2D
	super UniformVec2
	super UniformVec3
	super UniformVec4
	super UniformMat4

	redef fun is_active do return false
end

# Gamnit shader
abstract class Shader

	# TODO add alternative init to load shaders from binary

	# Index of this shader in OpenGL
	private var gl_shader: GLShader is noinit

	# Latest error raised by operations of this shader
	var error: nullable Error = null

	# Source code of this shader
	var source: Text

	# Low-level type of this shader
	private fun gl_shader_type: GLShaderType is abstract

	# Compile this shader and report any errors in the attribute `error`
	fun compile
	do
		# Create
		var gl_shader = glCreateShader(gl_shader_type)
		if not glIsShader(gl_shader) then
			self.error = new Error("Shader creation failed: {glGetError}")
			return
		end
		self.gl_shader = gl_shader

		glShaderSource(gl_shader, source.to_cstring)

		# Compile
		glCompileShader gl_shader
		if not gl_shader.is_compiled then
			self.error = new Error("Shader compilation failed: {glGetShaderInfoLog(gl_shader)}")
			return
		end

		error = gammit_gl_error
	end

	# Has this shader been deleted?
	var deleted = false

	# Delete this shader and free its resources
	fun delete
	do
		if deleted then return

		glDeleteShader gl_shader
		deleted = true
	end
end

# Gamnit vertex shader
class VertexShader
	super Shader

	redef fun gl_shader_type do return gl_VERTEX_SHADER
end

# Gamnit fragment shader
class FragmentShader
	super Shader

	redef fun gl_shader_type do return gl_FRAGMENT_SHADER
end

# Gamnit graphical program
#
# Subclasses should implement both `vertex_shader` and `fragment_shader`.
abstract class GamnitProgram

	# Vertex shader to attach to this program
	fun vertex_shader: VertexShader is abstract

	# Fragment shader to attach to this program
	fun fragment_shader: FragmentShader is abstract

	# Index to the OpenGL ES program, set by `compile_and_link`
	private var gl_program: nullable GLProgram = null

	# Last error raised by `compile_and_link`
	var error: nullable Error = null is protected writable

	# Compile the shaders, and this program, then link and report any errors
	fun compile_and_link
	do
		# Get an index
		var gl_program = glCreateProgram
		if not glIsProgram(gl_program) then
			self.error = new Error("Program creation failed: {glGetError.to_s}")
			return
		end
		self.gl_program = gl_program

		# Vertex shader
		var vertex_shader = vertex_shader
		vertex_shader.compile
		if vertex_shader.error != null then
			self.error = vertex_shader.error
			return
		end

		# Fragment shader
		var fragment_shader = fragment_shader
		fragment_shader.compile
		if fragment_shader.error != null then
			self.error = fragment_shader.error
			return
		end

		# Attach shaders
		glAttachShader(gl_program, vertex_shader.gl_shader)
		glAttachShader(gl_program, fragment_shader.gl_shader)

		# Catch any errors up to here
		var error = gammit_gl_error
		if error != null then
			self.error = error
			return
		end

		# Link
		glLinkProgram gl_program
		if not gl_program.is_linked then
			self.error = new Error("Linking failed: {glGetProgramInfoLog(gl_program)}")
			return
		end

		# Fill the attribute and uniform lists
		var n_attribs = glGetProgramiv(gl_program, gl_ACTIVE_ATTRIBUTES)
		for a in [0..n_attribs[ do
			var name = gl_program.active_attrib_name(a)
			var size = gl_program.active_attrib_size(a)
			var typ = gl_program.active_attrib_type(a)
			var location = gl_program.attrib_location(name)

			# FIXME location may be invalid at this point because
			# attrib_location does not work with truncated names,
			# as returned by `active_attrib_name`.

			var attribute
			if typ == gl_FLOAT then
				attribute = new AttributeFloat(gl_program, name, location, size)
			else if typ == gl_FLOAT_VEC2 then
				attribute = new AttributeVec2(gl_program, name, location, size)
			else if typ == gl_FLOAT_VEC3 then
				attribute = new AttributeVec3(gl_program, name, location, size)
			else if typ == gl_FLOAT_VEC4 then
				attribute = new AttributeVec4(gl_program, name, location, size)
			else
				attribute = new Attribute(gl_program, name, location, size)
			end
			# TODO missing types
			attributes[name] = attribute
		end

		var n_uniforms = glGetProgramiv(gl_program, gl_ACTIVE_UNIFORMS)
		for a in [0..n_uniforms[ do

			var name = gl_program.active_uniform_name(a)
			var size = gl_program.active_uniform_size(a)
			var typ = gl_program.active_uniform_type(a)
			var location = gl_program.uniform_location(name)

			var uniform
			if typ == gl_BOOL then
				uniform = new UniformBool(gl_program, name, location, size)
			else if typ == gl_INT then
				uniform = new UniformInt(gl_program, name, location, size)
			else if typ == gl_SAMPLER_2D then
				uniform = new UniformSampler2D(gl_program, name, location, size)
			else if typ == gl_FLOAT then
				uniform = new UniformFloat(gl_program, name, location, size)
			else if typ == gl_FLOAT_VEC2 then
				uniform = new UniformVec2(gl_program, name, location, size)
			else if typ == gl_FLOAT_VEC3 then
				uniform = new UniformVec3(gl_program, name, location, size)
			else if typ == gl_FLOAT_VEC4 then
				uniform = new UniformVec4(gl_program, name, location, size)
			else if typ == gl_FLOAT_MAT4 then
				uniform = new UniformMat4(gl_program, name, location, size)
			else
				uniform = new Uniform(gl_program, name, location, size)
			end
			# TODO missing types
			uniforms[name] = uniform
		end
	end

	# Diagnose possible problems with the shaders of the program
	#
	# Lists to the console inactive uniforms and attributes.
	# These may not be problematic but they can help to debug the program.
	fun diagnose
	do
		if gl_program == null then compile_and_link

		print "# Diagnose {class_name}"
		for k,v in uniforms do
			if not v.is_active then print "* Uniform {v.name} is inactive"
		end
		for k,v in attributes do
			if not v.is_active then print "* Attribute {v.name} is inactive"
		end
	end

	# Attributes of this program organized by name
	#
	# Active attributes are gathered at `compile_and_link`.
	# Upon request, inactive attributes are returned as a new `InactiveAttribute`.
	var attributes = new AttributeMap(self)

	# Uniforms of this program organized by name
	#
	# Active uniforms are gathered at `compile_and_link`.
	# Upon request, inactive attributes are returned as a new `InactiveUniform`.
	var uniforms = new UniformMap(self)

	# Notify the GPU to use this program
	fun use
	do
		var gl_program = gl_program
		assert gl_program != null # TODO error not compiled, or compile it
		glUseProgram gl_program
	end

	# Has this program been deleted?
	var deleted = false

	# Delete this program if it has not already been deleted
	fun delete
	do
		if deleted then return

		var gl_program = gl_program
		if gl_program != null then glDeleteProgram gl_program

		deleted = true
	end
end

# Gamnit graphical program from the shaders source code
class GamnitProgramFromSource
	super GamnitProgram

	# Source code of the vertex shader
	fun vertex_shader_source: Text is abstract

	redef var vertex_shader = new VertexShader(vertex_shader_source) is lazy

	# Source code of the fragment shader
	fun fragment_shader_source: Text is abstract

	redef var fragment_shader = new FragmentShader(fragment_shader_source) is lazy
end

# Map to organize `ShaderVariable` instances by their name
abstract class ShaderVariableMap[A: ShaderVariable]
	super HashMap[String, A]

	private var program: GamnitProgram

	redef fun [](key)
	do
		# Alter the user specified name to fit the truncated name
		var max_len = max_name_length - 1
		if key isa Text and key.length > max_len then key = key.substring(0, max_len)
		return super(key)
	end

	private fun max_name_length: Int is abstract
end

# Map to organize `Attribute` instances by their name
class AttributeMap
	super ShaderVariableMap[Attribute]

	redef fun provide_default_value(key) do
		return new InactiveAttribute(program.gl_program.as(not null), "", -1, 0)
	end

	redef fun max_name_length do return glGetProgramiv(program.gl_program.as(not null), gl_ACTIVE_ATTRIBUTE_MAX_LENGTH)

	redef fun [](key)
	do
		# Update the location of this attribute from the user specified name
		var item = super
		if key isa Text then item.location = program.gl_program.attrib_location(key.to_s)
		return item
	end
end

# Map to organize `Uniform` instances by their name
class UniformMap
	super ShaderVariableMap[Uniform]

	redef fun provide_default_value(key) do
		return new InactiveUniform(program.gl_program.as(not null), "", -1, 0)
	end

	redef fun max_name_length do return glGetProgramiv(program.gl_program.as(not null), gl_ACTIVE_UNIFORM_MAX_LENGTH)

	redef fun [](key)
	do
		var item = super
		if key isa Text then item.location = program.gl_program.uniform_location(key.to_s)
		return item
	end
end

redef extern class NativeGLfloatArray

	# Allocate a new matrix
	new matrix `{ return malloc(4*4*sizeof(GLfloat)); `}

	# Overwrite this matrix with the identity matrix
	fun set_identity
	do
		for i in [0..4[ do
			for j in [0..4[ do
				matrix_set(i, j, if i == j then 1.0 else 0.0)
			end
		end
	end

	# Get the element at `x, y`
	fun matrix_get(x, y: Int): Float `{ return self[y*4+x]; `}

	# Set the element at `x, y`
	fun matrix_set(x, y: Int, val: Float) `{ self[y*4+x] = val; `}
end

redef class Matrix
	# Copy content of this matrix to a `NativeGLfloatArray`
	fun fill_native(native: NativeGLfloatArray)
	do
		for i in [0..width[ do
			for j in [0..height[ do
				native.matrix_set(i, j, self[i, j])
			end
		end
	end
end

private fun gammit_gl_error: nullable Error
do
	var gl_error = glGetError
	if gl_error == gl_NO_ERROR then return null
	return new Error("GL error: {gl_error}")
end
lib/gamnit/programs.nit:15,1--602,3