Load textures, create subtextures and manage their life-cycle

Introduced classes

class AbsoluteSubtexture

gamnit :: AbsoluteSubtexture

Subtexture created from pixel coordinates within parent
class CheckerTexture

gamnit :: CheckerTexture

Colorful small texture of 32x32 pixels by default
class CustomTexture

gamnit :: CustomTexture

Custom texture with pixel values filled programmatically
class RelativeSubtexture

gamnit :: RelativeSubtexture

Subtexture created from relative coordinates ([0..1]) out of the root texture
class RootTexture

gamnit :: RootTexture

Texture with its own pixel data
abstract class Subtexture

gamnit :: Subtexture

Texture derived from another texture, does not own its pixels
abstract class Texture

gamnit :: Texture

Texture composed of pixels, loaded from the assets folder by default
class TextureAsset

gamnit :: TextureAsset

Texture loaded from the assets folder
class TextureSet

gamnit :: TextureSet

Group of Texture

Redefined classes

redef extern class Pointer

gamnit :: textures $ Pointer

Pointer classes are used to manipulate extern C structures.
redef class Sys

gamnit :: textures $ Sys

The main class of the program.

All class definitions

class AbsoluteSubtexture

gamnit $ AbsoluteSubtexture

Subtexture created from pixel coordinates within parent
class CheckerTexture

gamnit $ CheckerTexture

Colorful small texture of 32x32 pixels by default
class CustomTexture

gamnit $ CustomTexture

Custom texture with pixel values filled programmatically
redef extern class Pointer

gamnit :: textures $ Pointer

Pointer classes are used to manipulate extern C structures.
class RelativeSubtexture

gamnit $ RelativeSubtexture

Subtexture created from relative coordinates ([0..1]) out of the root texture
class RootTexture

gamnit $ RootTexture

Texture with its own pixel data
abstract class Subtexture

gamnit $ Subtexture

Texture derived from another texture, does not own its pixels
redef class Sys

gamnit :: textures $ Sys

The main class of the program.
abstract class Texture

gamnit $ Texture

Texture composed of pixels, loaded from the assets folder by default
class TextureAsset

gamnit $ TextureAsset

Texture loaded from the assets folder
class TextureSet

gamnit $ TextureSet

Group of Texture
package_diagram gamnit::textures textures gamnit::display display gamnit::textures->gamnit::display glesv2 glesv2 gamnit::display->glesv2 mnit::input input gamnit::display->mnit::input ...glesv2 ... ...glesv2->glesv2 ...mnit::input ... ...mnit::input->mnit::input gamnit::gamnit gamnit gamnit::gamnit->gamnit::textures gamnit::display_android display_android gamnit::display_android->gamnit::textures gamnit::display_linux display_linux gamnit::display_linux->gamnit::textures gamnit::display_ios display_ios gamnit::display_ios->gamnit::textures gamnit::virtual_gamepad_spritesheet virtual_gamepad_spritesheet gamnit::virtual_gamepad_spritesheet->gamnit::textures gamnit::gamnit_android gamnit_android gamnit::gamnit_android->gamnit::gamnit gamnit::gamnit_android->gamnit::display_android 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_linux->gamnit::display_linux gamnit::gamnit_ios gamnit_ios gamnit::gamnit_ios->gamnit::gamnit gamnit::gamnit_ios->gamnit::display_ios 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 gamnit::virtual_gamepad virtual_gamepad gamnit::virtual_gamepad->gamnit::virtual_gamepad_spritesheet gamnit::virtual_gamepad... ... gamnit::virtual_gamepad...->gamnit::virtual_gamepad

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 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 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 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 native

core :: native

Native structures for text and bytes
module numeric

core :: numeric

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

Children

module display_android

gamnit :: display_android

Gamnit display implementation for Android
module display_ios

gamnit :: display_ios

Gamnit display implementation for iOS
module display_linux

gamnit :: display_linux

Gamnit display implementation for GNU/Linux using egl, sdl and x11
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
# Load textures, create subtextures and manage their life-cycle
module textures

import display

# Texture composed of pixels, loaded from the assets folder by default
#
# Most textures should be created with `App` (as attributes)
# for the method `create_scene` to load them.
#
# ~~~
# import gamnit::flat
#
# redef class App
#     # Create the texture object, it will be loaded automatically
#     var texture = new Texture("path/in/assets.png")
#
#     redef fun create_scene()
#     do
#         # Let `create_scene` load the texture
#         super
#
#         # Use the texture
#         var sprite = new Sprite(texture, new Point3d[Float](0.0, 0.0, 0.0))
#         app.sprites.add sprite
#     end
# end
# ~~~
#
# Otherwise, they can be loaded and error checked explicitly after `create_scene`.
#
# ~~~nitish
# var texture = new Texture("path/in/assets.png")
# texture.load
# var error = texture.error
# if error != null then print_error error
# ~~~
#
# A texture may also be created programmatically, like `CheckerTexture`,
# or derived from another texture, using `subtexture`.
# Textures with actual pixel data (not `Subtexture`) are `RootTexture`.
# Texture loaded from the assets folder may in the PNG or JPG formats.
abstract class Texture

	# Prepare a texture located at `path` within the `assets` folder
	new (path: Text) do return new TextureAsset(path.to_s)

	# Root texture from which `self` is derived
	fun root: RootTexture is abstract

	# Width in pixels of this texture
	var width = 0.0

	# Height in pixels of this texture
	var height = 0.0

	# Load this texture, force reloading it if `force`
	fun load(force: nullable Bool) do end

	# Last error on this texture
	var error: nullable Error = null

	# OpenGL handle to this texture
	fun gl_texture: Int do return root.gl_texture

	# Prepare a subtexture from this texture, from the given pixel offsets
	fun subtexture(left, top, width, height: Numeric): Subtexture
	do
		return new AbsoluteSubtexture(self, left.to_f, top.to_f, width.to_f, height.to_f)
	end

	# Offset of the left border on `root` from 0.0 to 1.0
	fun offset_left: Float do return 0.0

	# Offset of the top border on `root` from 0.0 to 1.0
	fun offset_top: Float do return 0.0

	# Offset of the right border on `root` from 0.0 to 1.0
	fun offset_right: Float do return 1.0

	# Offset of the bottom border on `root` from 0.0 to 1.0
	fun offset_bottom: Float do return 1.0

	# Should this texture be drawn pixelated when magnified? otherwise it is interpolated
	#
	# This setting affects all the textures based on the same pixel data, or `root`.
	#
	# Must be set after a successful call to `load`.
	fun pixelated=(pixelated: Bool)
	do
		if root.gl_texture == -1 then return

		# TODO do not modify `root` by using *sampler objects* in glesv3
		glBindTexture(gl_TEXTURE_2D, root.gl_texture)

		var param = if pixelated then gl_NEAREST else gl_LINEAR
		glTexParameteri(gl_TEXTURE_2D, gl_TEXTURE_MAG_FILTER, param)
	end
end

# Colorful small texture of 32x32 pixels by default
class CheckerTexture
	super RootTexture

	# Width and height in pixels, defaults to 32
	var size = 32 is optional

	redef fun load(force)
	do
		if gl_texture != -1 then return
		load_checker size
		loaded = true
	end
end

# Custom texture with pixel values filled programmatically
#
# At creation, the texture is composed of `width` by `height` (rounded down)
# transparent pixels. The pixels value can be set using `[]=`.
#
# ~~~
# # Build a texture with 4 colors
# var tex = new CustomTexture(2.0, 2.0)
# tex[0, 0] = [1.0, 0.0, 0.0] # Red
# tex[0, 1] = [0.0, 1.0, 0.0] # Green
# tex[1, 0] = [0.0, 0.0, 1.0] # Blue
# tex[1, 1] = [1.0, 1.0, 1.0, 0.5] # Transparent white
# tex.load
# ~~~
class CustomTexture
	super RootTexture

	redef var width
	redef var height

	private var cpixels = new CByteArray(4*width.to_i*height.to_i) is lazy

	# Set the `color` of the pixel at `x`, `y` (from the top-left corner)
	#
	# The argument `color` should be an array of up to 4 floats (RGBA).
	# If `color` has less than 4 items, the missing items are replaced by 1.0.
	#
	# Require: `x < width.to_i and y < height.to_i`
	fun []=(x, y: Int, color: Array[Float])
	do
		assert x < width.to_i and y < height.to_i else print_error "{class_name}::[] out of bounds"

		# Simple conversion from [0.0..1.0] to [0..255]
		var bytes = [for c in color do (c*255.0).round.to_i.clamp(0, 255).to_bytes.last]
		while bytes.length < 4 do bytes.add 255

		var offset = 4*(x + y*width.to_i)
		for i in [0..4[ do cpixels[offset+i] = bytes[i].to_b

		loaded = false
	end

	# Overwrite all pixels with `color`, return `self`
	#
	# The argument `color` should be an array of up to 4 floats (RGBA).
	# If `color` has less than 4 items, the missing items are replaced by 1.0.
	fun fill(color: Array[Float]): SELF
	do
		# Simple conversion from [0.0..1.0] to [0..255]
		var bytes = [for c in color do (c*255.0).round.to_i.clamp(0, 255).to_bytes.last]
		while bytes.length < 4 do bytes.add 255

		var i = 0
		for x in [0..width.to_i[ do
			for y in [0..height.to_i[ do
				for j in [0..4[ do cpixels[i+j] = bytes[j].to_b
				i += 4
			end
		end

		loaded = false
		return self
	end

	redef fun load(force)
	do
		force = force or else false
		if loaded and not force then return

		if force and glIsTexture(gl_texture) then
			# Was already loaded, free the previous GL name
			glDeleteTextures([gl_texture])
		end
		gl_texture = -1

		# Round down the desired dimension
		var width = width.to_i
		var height = height.to_i
		self.width = width.to_f
		self.height = height.to_f

		load_from_pixels(cpixels.native_array, width, height, gl_RGBA)

		loaded = true
	end
end

# Texture with its own pixel data
class RootTexture
	super Texture

	redef fun root do return self

	# Has this texture been loaded yet?
	var loaded = false

	redef var gl_texture = -1

	init do all_root_textures.add self

	# Should the pixels RGB values be premultiplied by their alpha value at loading?
	#
	# All gamnit textures must have premultiplied alpha, it provides a better
	# alpha blending, avoids artifacts and allows for additive blending.
	#
	# When at `true`, the default, pixels RGB values are premultiplied
	# at loading. Set to `false` if pixels RGB values are already
	# premultiplied in the source data.
	#
	# This value must be set before calling `load`.
	var premultiply_alpha = true is writable

	private fun load_from_pixels(pixels: Pointer, width, height: Int, format: GLPixelFormat)
	do
		var max_texture_size = glGetIntegerv(gl_MAX_TEXTURE_SIZE, 0)
		if width > max_texture_size then
			error = new Error("Texture width larger than gl_MAX_TEXTURE_SIZE ({max_texture_size}) in {self} at {width}")
			return
		else if height > max_texture_size then
			error = new Error("Texture height larger than gl_MAX_TEXTURE_SIZE ({max_texture_size}) in {self} at {height}")
			return
		end

		# Premultiply alpha?
		if premultiply_alpha and format == gl_RGBA then
			pixels.premultiply_alpha(width, height)
		end

		glPixelStorei(gl_UNPACK_ALIGNEMENT, 1)
		var tex = glGenTextures(1)[0]
		gl_texture = tex

		glBindTexture(gl_TEXTURE_2D, tex)
		glTexImage2D(gl_TEXTURE_2D, 0, format, width, height, 0, format, gl_UNSIGNED_BYTE, pixels)

		glHint(gl_GENERATE_MIPMAP_HINT, gl_NICEST)
		glGenerateMipmap(gl_TEXTURE_2D)
		glTexParameteri(gl_TEXTURE_2D, gl_TEXTURE_MIN_FILTER, gl_LINEAR_MIPMAP_LINEAR)

		glBindTexture(gl_TEXTURE_2D, 0)
	end

	private fun load_checker(size: Int)
	do
		var cpixels = new CByteArray(3*size*size)

		var i = 0
		for x in [0..size[ do
			var quadrant_x = if x < size/2 then 0 else 1
			for y in [0..size[ do
				var quadrant_y = if y < size/2 then 0 else 1
				var color = if quadrant_x == quadrant_y then
					[0u8, 0u8, 0u8, 255u8]
				else [255u8, 255u8, 255u8, 255u8]

				for j in [0..3[ do cpixels[i+j] = color[j]
				i += 3
			end
		end

		width = size.to_f
		height = size.to_f
		load_from_pixels(cpixels.native_array, size, size, gl_RGB)

		cpixels.destroy
	end

	# Has this resource been deleted?
	var deleted = false

	# Delete this texture and free all its resources
	#
	# Use caution with this service as the subtextures may rely on the deleted data.
	fun delete
	do
		if deleted or not loaded then return

		deleted = true
	end
end

# Texture loaded from the assets folder
class TextureAsset
	super RootTexture

	# Path to this texture within the `assets` folder
	var path: String

	redef fun load(force)
	do
		if loaded and force != true then return

		load_from_platform

		# If no pixel data was loaded, load the pixel default texture
		if gl_texture == -1 then load_checker 32

		loaded = true
	end

	# Partially load this texture from platform-specific features
	#
	# This method should fill `width`, `height` and `pixels`.
	private fun load_from_platform is abstract

	redef fun to_s do return "<{class_name} path:{path}>"
end

# Texture derived from another texture, does not own its pixels
abstract class Subtexture
	super Texture

	# Parent texture, from which this texture was created
	var parent: Texture

	redef fun root do return parent.root

	redef fun load(force) do root.load(force)
end

# Subtexture created from pixel coordinates within `parent`
class AbsoluteSubtexture
	super Subtexture

	# Left border of this texture relative to `parent`
	var left: Float

	# Top border of this texture relative to `parent`
	var top: Float

	private fun set_wh(width, height: Float)
	is autoinit do
		self.width = width
		self.height = height
	end

	redef var offset_left = parent.offset_left + left / root.width is lazy
	redef var offset_top = parent.offset_top + top / root.height is lazy
	redef var offset_right = offset_left + width / root.width is lazy
	redef var offset_bottom = offset_top + height / root.height is lazy
end

# Subtexture created from relative coordinates ([0..1]) out of the `root` texture
class RelativeSubtexture
	super Subtexture

	redef var offset_left
	redef var offset_top
	redef var offset_right
	redef var offset_bottom

	redef fun width do return root.width * (offset_right - offset_left)
	redef fun height do return root.height * (offset_bottom - offset_top)
end

redef class Sys
	# All declared root textures
	var all_root_textures = new TextureSet
end

# Group of `Texture`
class TextureSet
	super HashSet[Texture]

	# Load all texture of this set
	fun load_all do for t in self do t.load
end

redef class Pointer
	# Multiply RGB values by their alpha value
	private fun premultiply_alpha(width, height: Int) `{
		uint8_t *bytes = (uint8_t *)self;
		int x, y, i = 0;
		for(y = 0; y < height; y ++) {
			for(x = 0; x < width; x ++) {
				int a = bytes[i+3];
				bytes[i  ] = bytes[i  ] * a / 255;
				bytes[i+1] = bytes[i+1] * a / 255;
				bytes[i+2] = bytes[i+2] * a / 255;
				i += 4;
			}
		}
	`}
end
lib/gamnit/textures.nit:15,1--413,3