Use of EGL to implement Gamnit on GNU/Linux and Android

Redefined classes

redef class GamnitDisplay

gamnit :: egl $ GamnitDisplay

General display class, is sized and drawable

All class definitions

redef class GamnitDisplay

gamnit :: egl $ GamnitDisplay

General display class, is sized and drawable
package_diagram gamnit::egl egl egl egl gamnit::egl->egl gamnit::display display gamnit::egl->gamnit::display android android egl->android glesv2 glesv2 gamnit::display->glesv2 mnit::input input gamnit::display->mnit::input ...android ... ...android->android ...glesv2 ... ...glesv2->glesv2 ...mnit::input ... ...mnit::input->mnit::input gamnit::display_android display_android gamnit::display_android->gamnit::egl gamnit::display_linux display_linux gamnit::display_linux->gamnit::egl gamnit::gamnit_android gamnit_android gamnit::gamnit_android->gamnit::display_android gamnit::gamnit_android... ... gamnit::gamnit_android...->gamnit::gamnit_android gamnit::gamnit_linux gamnit_linux gamnit::gamnit_linux->gamnit::display_linux gamnit::gamnit_linux... ... gamnit::gamnit_linux...->gamnit::gamnit_linux

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
module egl

egl :: egl

Interface between rendering APIs (OpenGL, OpenGL ES, etc.) and the native windowing system.

Children

module display_android

gamnit :: display_android

Gamnit display implementation for Android
module display_linux

gamnit :: display_linux

Gamnit display implementation for GNU/Linux using egl, sdl and x11

Descendants

module a_star-m

a_star-m

module android19

gamnit :: android19

Variation using features from Android API 19
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 gamnit_android

gamnit :: gamnit_android

Support services for Gamnit on Android
module gamnit_linux

gamnit :: gamnit_linux

Support services for Gamnit on GNU/Linux
module sensors

android :: sensors

Access Android sensors
# Use of EGL to implement Gamnit on GNU/Linux and Android
module egl

import ::egl

import gamnit::display

redef class GamnitDisplay

	# The EGL display
	var egl_display: EGLDisplay is noautoinit

	# The EGL context
	var egl_context: EGLContext is noautoinit

	# The EGL surface for the window
	var window_surface: EGLSurface is noautoinit

	# The selected EGL configuration
	var egl_config: EGLConfig is noautoinit

	# Setup the EGL display for the given `native_display`
	protected fun setup_egl_display(native_display: Pointer)
	do
		var egl_display = new EGLDisplay(native_display)
		assert egl_display.is_valid else print "new EGL display is not valid"

		egl_display.initialize
		assert egl_display.is_valid else print "EGL initialize error: {egl_display.error}"

		self.egl_display = egl_display
	end

	# Select an EGL config
	protected fun select_egl_config(red, green, blue, alpha, depth, stencil: Int)
	do
		var config_chooser = new EGLConfigChooser
		config_chooser.renderable_type_egl
		config_chooser.surface_type_egl
		config_chooser.red_size = red
		config_chooser.green_size = green
		config_chooser.blue_size = blue
		if alpha > 0 then config_chooser.alpha_size = alpha
		if depth > 0 then config_chooser.depth_size = depth
		if stencil > 0 then config_chooser.stencil_size = stencil

		config_chooser.sample_buffers = 1
		config_chooser.samples = 4

		config_chooser.close

		var configs = config_chooser.choose(egl_display)
		assert configs != null else print "Choosing EGL config failed: {egl_display.error}"
		assert not configs.is_empty else print "Found no EGL config"

		if debug_gamnit then
			print "EGL available configurations:"
			for config in configs do
				var attribs = config.attribs(egl_display)
				print "* Conformant to: {attribs.conformant}"
				print "  Caveats: {attribs.caveat}"
				print "  Size of RGBA: {attribs.red_size} {attribs.green_size} {attribs.blue_size} {attribs.alpha_size}"
				print "  Buffer, depth, stencil: {attribs.buffer_size} {attribs.depth_size} {attribs.stencil_size}"
				print "  Sample buffers, samples: {attribs.sample_buffers} {attribs.samples}"
			end
		end

		# We use the first one, it is recommended
		self.egl_config = configs.first
	end

	# Setup the EGL context for the given `native_window`
	protected fun setup_egl_context(native_window: Pointer)
	do
		var window_surface = egl_display.create_window_surface(egl_config, native_window, [0])
		assert window_surface.is_ok else print "Creating EGL window surface failed: {egl_display.error}"
		self.window_surface = window_surface

		egl_context = egl_display.create_context(egl_config)
		assert egl_context.is_ok else print "Creating EGL context failed: {egl_display.error}"

		var make_current_res = egl_display.make_current(window_surface, window_surface, egl_context)
		assert make_current_res else print "Creating EGL make current failed: {egl_display.error}"

		# TODO make the API selection configurable per platform
		assert egl_bind_opengl_es_api else print "EGL bind API failed: {egl_display.error}"
	end

	# Check if the current configuration of `native_window` is still valid
	#
	# There is two return values:
	# * Returns `true` if the Gamnit services should be recreated.
	# * Sets `native_window_is_invalid` if the system provided window handle is invalid.
	#   We should wait until we are provided a valid window handle.
	fun check_egl_context(native_window: Pointer): Bool
	do
		native_window_is_invalid = false

		if not egl_context.is_ok then
			# Needs recreating
			egl_context = egl_display.create_context(egl_config)
			assert egl_context.is_ok else print "Creating EGL context failed: {egl_display.error}"
		end

		var success = egl_display.make_current(window_surface, window_surface, egl_context)
		if not success then
			var error = egl_display.error
			print "check_egl_context make_current: {error}"


			if error.is_bad_native_window then
				# native_window is invalid
				native_window_is_invalid = true
				return true

			else if not error.is_success then
				# The context is now invalid, rebuild it
				setup_egl_context native_window
				return true
			end
		end
		return false
	end

	# Return value from `check_egl_context`, the current native window is invalid
	#
	# We should wait until we are provided a valid window handle.
	var native_window_is_invalid = false

	redef fun width do return window_surface.attribs(egl_display).width

	redef fun height do return window_surface.attribs(egl_display).height

	# Close the EGL context
	fun close_egl
	do
		egl_display.make_current(new EGLSurface.none, new EGLSurface.none, new EGLContext.none)
		egl_display.destroy_context(egl_context)
		egl_display.destroy_surface(window_surface)
	end

	redef fun flip
	do
		assert glGetError == gl_NO_ERROR

		assert egl_display.is_valid

		egl_display.swap_buffers(window_surface)
	end
end
lib/gamnit/egl.nit:15,1--164,3