Gamnit graphical program

Subclasses should implement both vertex_shader and fragment_shader.

Introduced properties

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 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?
fun diagnose

gamnit :: GamnitProgram :: diagnose

Diagnose possible problems with the shaders of the program
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
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
abstract fun vertex_shader: VertexShader

gamnit :: GamnitProgram :: vertex_shader

Vertex shader to attach to this program

Redefined properties

redef type SELF: GamnitProgram

gamnit $ GamnitProgram :: SELF

Type of this instance, automatically specialized in every class

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 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
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 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?
fun diagnose

gamnit :: GamnitProgram :: diagnose

Diagnose possible problems with the shaders of the program
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
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.
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 serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
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 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
abstract fun vertex_shader: VertexShader

gamnit :: GamnitProgram :: vertex_shader

Vertex shader to attach to this program
package_diagram gamnit::GamnitProgram GamnitProgram core::Object Object gamnit::GamnitProgram->core::Object gamnit::GamnitProgramFromSource GamnitProgramFromSource gamnit::GamnitProgramFromSource->gamnit::GamnitProgram gamnit::BlinnPhongProgram BlinnPhongProgram gamnit::BlinnPhongProgram->gamnit::GamnitProgramFromSource gamnit::ShadowDepthProgram ShadowDepthProgram gamnit::ShadowDepthProgram->gamnit::GamnitProgramFromSource gamnit::ParticleProgram ParticleProgram gamnit::ParticleProgram->gamnit::GamnitProgramFromSource gamnit::SelectionProgram SelectionProgram gamnit::SelectionProgram->gamnit::GamnitProgramFromSource gamnit::BlinnPhongProgram... ... gamnit::BlinnPhongProgram...->gamnit::BlinnPhongProgram gamnit::ShadowDepthProgram... ... gamnit::ShadowDepthProgram...->gamnit::ShadowDepthProgram gamnit::ParticleProgram... ... gamnit::ParticleProgram...->gamnit::ParticleProgram gamnit::SelectionProgram... ... gamnit::SelectionProgram...->gamnit::SelectionProgram

Parents

interface Object

core :: Object

The root of the class hierarchy.

Children

class GamnitProgramFromSource

gamnit :: GamnitProgramFromSource

Gamnit graphical program from the shaders source code

Descendants

class BlinnPhongProgram

gamnit :: BlinnPhongProgram

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

gamnit :: ExplosionProgram

Graphics program to display blowing up particles
class NormalProgram

gamnit :: NormalProgram

Program to color objects from their normal vectors
class ParticleProgram

gamnit :: ParticleProgram

Particle drawing program using gl_POINTS
class SelectionProgram

gamnit :: SelectionProgram

Program to draw selection values
class ShadowDepthProgram

gamnit :: ShadowDepthProgram

Efficiently draw actors from the light view
class SmokeProgram

gamnit :: SmokeProgram

Graphics program to display particles slowly drifting upwards

Class definitions

gamnit $ GamnitProgram
# 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
lib/gamnit/programs.nit:319,1--492,3