Property definitions

gamnit $ SpriteContext :: defaultinit
# Context for calls to `glDrawElements`
#
# Each context has only one `texture` and `usage`, but many sprites.
private class SpriteContext

	# ---
	# Context config and state

	# Only root texture drawn by this context
	var texture: nullable RootTexture

	# Only animation texture drawn by this context
	var animation_texture: nullable RootTexture

	# OpenGL ES usage of `buffer_array` and `buffer_element`
	var usage: GLBufferUsage

	# Draw order shared by all `sprites`
	var draw_order: Int

	# Sprites drawn by this context
	var sprites = new GroupedSprites

	# Sprites to update since last `draw`
	var sprites_to_update = new Set[Sprite]

	# Cache of the last `Sprite` added to `sprites_to_update` since the last call to `draw`
	var last_sprite_to_update: nullable Sprite = null

	# Sprites that have been update and for which `needs_update` can be set to false
	var updated_sprites = new Array[Sprite]

	# Buffer size to preallocate at `resize`, multiplied by `sprites.length`
	#
	# Require: `resize_ratio >= 1.0`
	var resize_ratio = 1.2

	# ---
	# OpenGL ES data

	# OpenGL ES buffer name for vertex data
	var buffer_array: Int = -1

	# OpenGL ES buffer name for indices
	var buffer_element: Int = -1

	# Current capacity, in sprites, of `buffer_array` and `buffer_element`
	var buffer_capacity = 0

	# C buffers used to pass the data of a single sprite
	var local_data_buffer = new GLfloatArray(float_per_vertex*4) is lazy
	var local_indices_buffer = new CUInt16Array(indices_per_sprite) is lazy

	# ---
	# Constants

	# Number of GL_FLOAT per vertex of `Simple2dProgram`
	var float_per_vertex: Int is lazy do
		return 4 + 4 + 4 +   # vec4 translation, vec4 color, vec4 coord,
		       1 + 2 + 4*4 + # float scale, vec2 tex_coord, vec4 rotation_row*,
		       1 + 1 +       # float a_fps, float a_n_frames,
		       2 + 2 + 2 +   # vec2 a_coord, vec2 a_tex_coord, vec2 a_tex_diff,
		       1 + 1         # float a_start, float a_loops
	end

	# Number of bytes per vertex of `Simple2dProgram`
	var bytes_per_vertex: Int is lazy do
		var fs = 4 # sizeof(GL_FLOAT)
		return fs * float_per_vertex
	end

	# Number of bytes per sprite
	var bytes_per_sprite: Int is lazy do return bytes_per_vertex * 4

	# Number of vertex indices per sprite draw call (2 triangles)
	var indices_per_sprite = 6

	# ---
	# Main services

	# Allocate `buffer_array` and `buffer_element`
	fun prepare
	do
		var bufs = glGenBuffers(2)
		buffer_array = bufs[0]
		buffer_element = bufs[1]

		assert glGetError == gl_NO_ERROR
	end

	# Destroy `buffer_array` and `buffer_element`
	fun destroy
	do
		glDeleteBuffers([buffer_array, buffer_element])
		assert glGetError == gl_NO_ERROR

		buffer_array = -1
		buffer_element = -1
	end

	# Resize `buffer_array` and `buffer_element` to fit all `sprites` (and more)
	fun resize
	do
		app.perf_clock_sprites.lapse

		# Allocate a bit more space
		var capacity = (sprites.capacity.to_f * resize_ratio).to_i

		var array_bytes = capacity * bytes_per_sprite
		glBindBuffer(gl_ARRAY_BUFFER, buffer_array)
		assert glIsBuffer(buffer_array)
		glBufferData(gl_ARRAY_BUFFER, array_bytes, new Pointer.nul, usage)
		assert glGetError == gl_NO_ERROR

		# GL_TRIANGLES 6 vertices * sprite
		var n_indices = capacity * indices_per_sprite
		var ius = 2 # sizeof(GL_UNSIGNED_SHORT)
		var element_bytes = n_indices * ius
		glBindBuffer(gl_ELEMENT_ARRAY_BUFFER, buffer_element)
		assert glIsBuffer(buffer_element)
		glBufferData(gl_ELEMENT_ARRAY_BUFFER, element_bytes, new Pointer.nul, usage)
		assert glGetError == gl_NO_ERROR

		buffer_capacity = capacity

		sys.perfs["gamnit flat gpu resize"].add app.perf_clock_sprites.lapse
	end

	# Update GPU data of `sprite`
	fun update_sprite(sprite: Sprite)
	do
		var context = sprite.context
		if context != self then return

		var sprite_index = sprite.context_index
		assert sprite_index != -1

		# Vertices data

		var data = local_data_buffer
		var o = 0
		for v in [0..4[ do
			# vec4 translation
			data[o+ 0] = sprite.center.x
			data[o+ 1] = sprite.center.y
			data[o+ 2] = sprite.center.z
			data[o+ 3] = 0.0

			# vec4 color
			data[o+ 4] = sprite.tint[0]
			data[o+ 5] = sprite.tint[1]
			data[o+ 6] = sprite.tint[2]
			data[o+ 7] = sprite.tint[3]

			# float scale
			data[o+ 8] = sprite.scale

			# vec4 coord
			data[o+ 9] = sprite.texture.vertices[v*3+0]
			data[o+10] = sprite.texture.vertices[v*3+1]
			data[o+11] = sprite.texture.vertices[v*3+2]
			data[o+12] = 0.0

			# vec2 tex_coord
			var texture = texture
			if texture != null then
				var tc = if sprite.invert_x then
						sprite.texture.texture_coords_invert_x
					else sprite.texture.texture_coords
				data[o+13] = tc[v*2+0]
				data[o+14] = tc[v*2+1]
			end

			# mat4 rotation
			var rot
			if sprite.rotation == 0.0 then
				# Cache the matrix at no rotation
				rot = once new Matrix.identity(4)
			else
				rot = new Matrix.rotation(sprite.rotation, 0.0, 0.0, 1.0)
			end
			data.fill_from_matrix(rot, o+15)

			var animation = sprite.animation
			if animation == null then
				for i in [31..40] do data[o+i] = 0.0
			else
				# a_fps
				data[o+31] = animation.fps

				# a_n_frames
				data[o+32] = animation.frames.length.to_f

				# a_coord
				data[o+33] = animation.frames.first.vertices[v*3+0]
				data[o+34] = animation.frames.first.vertices[v*3+1]

				# a_tex_coord
				var tc = if sprite.invert_x then
						animation.frames.first.texture_coords_invert_x
					else animation.frames.first.texture_coords
				data[o+35] = tc[v*2]
				data[o+36] = tc[v*2+1]

				# a_tex_diff
				var dx = 0.0
				var dy = 0.0
				if animation.frames.length > 1 then
					dx = animation.frames[1].texture_coords[0] - animation.frames[0].texture_coords[0]
					dy = animation.frames[1].texture_coords[1] - animation.frames[0].texture_coords[1]
				end
				data[o+37] = dx
				data[o+38] = dy

				# a_start
				data[o+39] = sprite.animation_start

				# a_loops
				data[o+40] = sprite.animation_loops
			end

			o += float_per_vertex
		end

		glBindBuffer(gl_ARRAY_BUFFER, buffer_array)
		glBufferSubData(gl_ARRAY_BUFFER, sprite_index*bytes_per_sprite, bytes_per_sprite, data.native_array)

		var gl_error = glGetError
		assert gl_error == gl_NO_ERROR else print_error gl_error

		# Element / indices
		#
		# 0--1
		# | /|
		# |/ |
		# 2--3

		var indices = local_indices_buffer
		var io = sprite_index*4
		indices[0] = io+0
		indices[1] = io+2
		indices[2] = io+1
		indices[3] = io+1
		indices[4] = io+2
		indices[5] = io+3

		glBindBuffer(gl_ELEMENT_ARRAY_BUFFER, buffer_element)
		glBufferSubData(gl_ELEMENT_ARRAY_BUFFER, sprite_index*6*2, 6*2, indices.native_array)

		assert glGetError == gl_NO_ERROR
	end

	# Draw all `sprites`
	#
	# Call `resize` and `update_sprite` as needed before actual draw operation.
	#
	# Require: `app.simple_2d_program` and `mvp` must be bound on the GPU
	fun draw
	do
		if buffer_array == -1 then prepare

		assert buffer_array > 0 and buffer_element > 0 else
			print_error "Internal error: {self} was destroyed"
		end

		# Setup
		glBindBuffer(gl_ARRAY_BUFFER, buffer_array)
		glBindBuffer(gl_ELEMENT_ARRAY_BUFFER, buffer_element)

		# Resize GPU buffers?
		var update_everything = false
		if sprites.capacity > buffer_capacity then
			# Try to defragment first
			var moved = sprites.defragment

			if sprites.capacity > buffer_capacity then
				# Defragmentation wasn't enough, grow
				resize

				# We must update everything
				update_everything = true
				for s in sprites.items do if s != null then sprites_to_update.add s
			else
				# Just update the moved sprites
				for s in moved do sprites_to_update.add s
			end
		else if sprites.available.not_empty then
			# Defragment a bit anyway
			# TODO defrag only when there's time left on a frame
			var moved = sprites.defragment(1)
			for s in moved do sprites_to_update.add s
		end

		# Update GPU sprites data
		if sprites_to_update.not_empty or update_everything then
			app.perf_clock_sprites.lapse

			if update_everything then
				for sprite in sprites.items do if sprite != null then
					update_sprite(sprite)
				end
			else
				for sprite in sprites_to_update do update_sprite(sprite)
			end

			sprites_to_update.clear
			last_sprite_to_update = null

			sys.perfs["gamnit flat gpu update"].add app.perf_clock_sprites.lapse
		end

		# Update uniforms specific to this context
		var texture = texture
		app.simple_2d_program.use_texture.uniform texture != null
		if texture != null then
			glActiveTexture gl_TEXTURE0
			glBindTexture(gl_TEXTURE_2D, texture.gl_texture)
			app.simple_2d_program.texture.uniform 0
		end
		assert glGetError == gl_NO_ERROR

		var animation = animation_texture
		if animation != null then
			glActiveTexture gl_TEXTURE1
			glBindTexture(gl_TEXTURE_2D, animation.gl_texture)
			app.simple_2d_program.animation_texture.uniform 1
		end
		assert glGetError == gl_NO_ERROR

		# Configure attributes, in order:
		# vec4 translation, vec4 color, float scale, vec4 coord, vec2 tex_coord, vec4 rotation_row*,
		# a_fps, a_n_frames, a_coord, a_tex_coord, a_tex_diff, a_start, a_loops

		var offset = 0
		var p = app.simple_2d_program
		var sizeof_gl_float = 4 # sizeof(GL_FLOAT)

		var size = 4 # Number of floats
		glEnableVertexAttribArray p.translation.location
		glVertexAttribPointeri(p.translation.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
		offset += size * sizeof_gl_float
		assert glGetError == gl_NO_ERROR

		size = 4
		glEnableVertexAttribArray p.color.location
		glVertexAttribPointeri(p.color.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
		offset += size * sizeof_gl_float
		assert glGetError == gl_NO_ERROR

		size = 1
		glEnableVertexAttribArray p.scale.location
		glVertexAttribPointeri(p.scale.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
		offset += size * sizeof_gl_float
		assert glGetError == gl_NO_ERROR

		size = 4
		glEnableVertexAttribArray p.coord.location
		glVertexAttribPointeri(p.coord.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
		offset += size * sizeof_gl_float
		assert glGetError == gl_NO_ERROR

		size = 2
		glEnableVertexAttribArray p.tex_coord.location
		glVertexAttribPointeri(p.tex_coord.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
		offset += size * sizeof_gl_float
		assert glGetError == gl_NO_ERROR

		size = 4
		for r in [p.rotation_row0, p.rotation_row1, p.rotation_row2, p.rotation_row3] do
			if r.is_active then
				glEnableVertexAttribArray r.location
				glVertexAttribPointeri(r.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
			end
			offset += size * sizeof_gl_float
			assert glGetError == gl_NO_ERROR
		end

		size = 1
		glEnableVertexAttribArray p.animation_fps.location
		glVertexAttribPointeri(p.animation_fps.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
		offset += size * sizeof_gl_float
		assert glGetError == gl_NO_ERROR

		size = 1
		glEnableVertexAttribArray p.animation_n_frames.location
		glVertexAttribPointeri(p.animation_n_frames.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
		offset += size * sizeof_gl_float
		assert glGetError == gl_NO_ERROR

		size = 2
		glEnableVertexAttribArray p.animation_coord.location
		glVertexAttribPointeri(p.animation_coord.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
		offset += size * sizeof_gl_float
		assert glGetError == gl_NO_ERROR

		size = 2
		glEnableVertexAttribArray p.animation_tex_coord.location
		glVertexAttribPointeri(p.animation_tex_coord.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
		offset += size * sizeof_gl_float
		assert glGetError == gl_NO_ERROR

		size = 2
		glEnableVertexAttribArray p.animation_tex_diff.location
		glVertexAttribPointeri(p.animation_tex_diff.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
		offset += size * sizeof_gl_float
		assert glGetError == gl_NO_ERROR

		size = 1
		glEnableVertexAttribArray p.animation_start.location
		glVertexAttribPointeri(p.animation_start.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
		offset += size * sizeof_gl_float
		assert glGetError == gl_NO_ERROR

		size = 1
		glEnableVertexAttribArray p.animation_loops.location
		glVertexAttribPointeri(p.animation_loops.location, size, gl_FLOAT, false, bytes_per_vertex, offset)
		offset += size * sizeof_gl_float
		assert glGetError == gl_NO_ERROR

		# Actual draw
		for s in sprites.starts, e in sprites.ends do
			var l = e-s
			glDrawElementsi(gl_TRIANGLES, l*indices_per_sprite, gl_UNSIGNED_SHORT, 2*s*indices_per_sprite)
			assert glGetError == gl_NO_ERROR
		end

		# Take down
		for attr in [p.translation, p.color, p.scale, p.coord, p.tex_coord,
		             p.rotation_row0, p.rotation_row1, p.rotation_row2, p.rotation_row3: Attribute] do
			if not attr.is_active then continue
			glDisableVertexAttribArray(attr.location)
			assert glGetError == gl_NO_ERROR
		end

		glBindBuffer(gl_ARRAY_BUFFER, 0)
		glBindBuffer(gl_ELEMENT_ARRAY_BUFFER, 0)
		assert glGetError == gl_NO_ERROR
	end
end
lib/gamnit/flat/flat_core.nit:1040,1--1478,3