Camera services producing Model-View-Projection matrices

Introduced classes

abstract class Camera

gamnit :: Camera

A camera with a point of view on the world
class EulerCamera

gamnit :: EulerCamera

Simple camera with perspective oriented with Euler angles (pitch, yaw, roll)
class UICamera

gamnit :: UICamera

Orthogonal camera to draw UI objects with services to work with screens of different sizes

All class definitions

abstract class Camera

gamnit $ Camera

A camera with a point of view on the world
class EulerCamera

gamnit $ EulerCamera

Simple camera with perspective oriented with Euler angles (pitch, yaw, roll)
class UICamera

gamnit $ UICamera

Orthogonal camera to draw UI objects with services to work with screens of different sizes
package_diagram gamnit::cameras cameras geometry geometry gamnit::cameras->geometry matrix::projection projection gamnit::cameras->matrix::projection gamnit::display display gamnit::cameras->gamnit::display serialization serialization geometry->serialization pipeline pipeline geometry->pipeline matrix matrix matrix::projection->matrix glesv2 glesv2 gamnit::display->glesv2 mnit::input input gamnit::display->mnit::input ...serialization ... ...serialization->serialization ...pipeline ... ...pipeline->pipeline ...matrix ... ...matrix->matrix ...glesv2 ... ...glesv2->glesv2 ...mnit::input ... ...mnit::input->mnit::input gamnit::cameras_cache cameras_cache gamnit::cameras_cache->gamnit::cameras gamnit::camera_control camera_control gamnit::camera_control->gamnit::cameras gamnit::flat_core flat_core gamnit::flat_core->gamnit::cameras_cache gamnit::flat_core... ... gamnit::flat_core...->gamnit::flat_core gamnit::camera_control_android camera_control_android gamnit::camera_control_android->gamnit::camera_control gamnit::camera_control_linux camera_control_linux gamnit::camera_control_linux->gamnit::camera_control gamnit::flat flat gamnit::flat->gamnit::camera_control gamnit::camera_control_android... ... gamnit::camera_control_android...->gamnit::camera_control_android gamnit::camera_control_linux... ... gamnit::camera_control_linux...->gamnit::camera_control_linux gamnit::flat... ... gamnit::flat...->gamnit::flat

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 angles

geometry :: angles

Angle related service using Float to represent an angle in radians
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 boxes

geometry :: boxes

Provides interfaces and classes to represent basic geometry needs.
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 matrix

matrix :: matrix

Services for matrices of Float values
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 points_and_lines

geometry :: points_and_lines

Interfaces and classes to represent basic geometry needs.
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 geometry

geometry :: geometry

Provides interfaces and classes to represent basic geometry needs.
module projection

matrix :: projection

Services on Matrix to transform and project 3D coordinates

Children

module camera_control

gamnit :: camera_control

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

gamnit :: cameras_cache

Cache the Matrix produced by Camera::mvp_matrix

Descendants

module a_star-m

a_star-m

module bmfont

gamnit :: bmfont

Parse Angel Code BMFont format and draw text
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 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 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 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
# Camera services producing Model-View-Projection matrices
module cameras

import geometry
import matrix::projection

import display

# A camera with a point of view on the world
abstract class Camera

	# TODO make this a physical object in the world

	# The host `GamnitDisplay`
	var display: GamnitDisplay

	# Position of this camera in world space
	var position = new Point3d[Float](0.0, 0.0, 0.0)

	# The Model-View-Projection matrix created by this camera
	#
	# This method should only be called by the display at the moment
	# of drawing to the screen.
	fun mvp_matrix: Matrix is abstract
end

# Simple camera with perspective oriented with Euler angles (`pitch, yaw, roll`)
class EulerCamera
	super Camera

	# Rotation around the X axis (looking down or up)
	var pitch = 0.0 is writable

	# Rotation around the Y axis (looking left or right)
	var yaw = 0.0 is writable

	# Rotation around the Z axis
	var roll = 0.0 is writable

	# Field of view in radians on the vertical axis of the screen
	#
	# Default at `0.8`
	var field_of_view_y = 0.8 is writable

	# Clipping wall near the camera, in world dimensions
	#
	# Default at `0.01`.
	var near = 0.01 is writable

	# Clipping wall the farthest of the camera, in world dimensions
	#
	# Default at `10000.0` but this one should be adapted to each context.
	var far = 10000.0 is writable

	# Look around sensitivity, used by `turn`
	var sensitivity = 0.005 is writable

	# Apply a mouse movement (or similar) to the camera
	#
	# `dx` and `dy` are relative mouse movements in pixels.
	fun turn(dx, dy: Float)
	do
		# Moving on x, turn around the y axis
		yaw -= dx*sensitivity
		pitch -= dy*sensitivity

		# Protect rotation around then x axis for not falling on your back
		pitch = pitch.min(pi/2.0)
		pitch = pitch.max(-pi/2.0)
	end

	# Move the camera considering the current orientation
	fun move(dx, dy, dz: Float)
	do
		# +dz move forward
		position.x -= yaw.sin*dz
		position.z -= yaw.cos*dz

		# +dx strafe to the right
		position.x += yaw.cos*dx
		position.z -= yaw.sin*dx

		# +dz move towards the sky
		position.y += dy
	end

	# Aim the camera at `x, y, z`
	fun look_at(x, y, z: Float)
	do
		var dx = position.x
		var dy = position.y
		var dz = position.z

		yaw = atan2(dx, dz)
		pitch = atan2(-dy, dz)
	end

	# Rotation matrix produced by the current rotation of the camera
	protected fun rotation_matrix: Matrix
	do
		var view = new Matrix.identity(4)

		# Rotate the camera, first by looking left or right, then up or down
		view.rotate(yaw,   0.0, 1.0, 0.0)
		view.rotate(pitch, 1.0, 0.0, 0.0)
		view.rotate(roll,  0.0, 0.0, 1.0)

		return view
	end

	redef fun mvp_matrix
	do
		var view = new Matrix.identity(4)

		# Translate the world away from the camera
		view.translate(-position.x, -position.y, -position.z)

		# Rotate the camera, first by looking left or right, then up or down
		view = view * rotation_matrix

		# Use a projection matrix with a depth
		var projection = new Matrix.perspective(field_of_view_y,
			display.aspect_ratio, near, far)

		return view * projection
	end

	# Reset the camera position so that `height` world units are visible on the y axis at z=0
	#
	# By default, `height` is set to `display.height`.
	#
	# After the reset, the camera sits on the Z axis and rotation values are reset to 0.
	# The X axis is horizontal on the screen and the Y axis is vertical.
	# Higher values on the Z axis are closer to the camera.
	fun reset_height(height: nullable Float)
	do
		if height == null then height = display.height.to_f

		var opp = height / 2.0
		var angle = field_of_view_y / 2.0
		var adj = opp / angle.tan

		position.x = 0.0
		position.y = 0.0
		position.z = adj

		pitch = 0.0
		yaw = 0.0
		roll = 0.0
	end

	# Convert the position `x, y` on screen, to world coordinates on the plane at `target_z`
	#
	# `target_z` defaults to `0.0` and specifies the Z coordinates of the plane
	# on which to project the screen position `x, y`.
	#
	# This method assumes that the camera is looking along the Z axis towards higher values.
	# Using it in a different orientation can be useful, but won't result in valid
	# world coordinates.
	fun camera_to_world(x, y: Numeric, target_z: nullable Float): Point[Float]
	do
		# TODO, this method could be tweaked to support projecting the 2D point,
		# on the near plane (x,y) onto a given distance no matter to orientation
		# of the camera.

		target_z = target_z or else 0.0

		# Convert from pixel units / window resolution to
		# units on the near clipping wall to
		# units on the target wall at Z = 0
		var near_height = (field_of_view_y/2.0).tan * near
		var cross_screen_to_near = near_height / (display.height.to_f/2.0)
		var cross_near_to_target = (position.z - target_z) / near
		var mod = cross_screen_to_near * cross_near_to_target

		var wx = position.x + (x.to_f-display.width.to_f/2.0) * mod
		var wy = position.y - (y.to_f-display.height.to_f/2.0) * mod
		return new Point[Float](wx, wy)
	end
end

# Orthogonal camera to draw UI objects with services to work with screens of different sizes
#
# X axis: left to right of the screen, from `position.x` to `position.x + width`
# Y axis: top to bottom of the screen, from `position.y` to `position.y + height`
# Z axis: far to near the camera (usually when values are higher), from `far` to `near`
class UICamera
	super Camera

	# Clipping wall near the camera, defaults to 100.0
	var near = 100.0 is writable

	# Clipping wall the farthest of the camera, defaults to -100.0
	var far: Float = -100.0 is writable

	# Width in world units, calculated from `height` and the screen aspect ratio
	fun width: Float do return height * display.aspect_ratio

	# Height in world units, defaults to 1080.0
	#
	# Set this value using `reset_height`.
	var height = 1080.0

	# Reset the camera position so that `height` world units are visible on the Y axis
	#
	# This can be used to set standardized UI units independently from the screen resolution.
	fun reset_height(height: nullable Float)
	do
		if height == null then height = display.height.to_f
		self.height = height
	end

	# Convert the position `x, y` on screen, to UI coordinates
	fun camera_to_ui(x, y: Numeric): Point3d[Float]
	do
		# FIXME this kind of method should use something like a canvas
		# instead of being hard coded on the display.

		var wx = x.to_f * width / display.width.to_f - position.x
		var wy = y.to_f * height / display.height.to_f - position.y
		return new Point3d[Float](wx, -wy, 0.0)
	end

	# Center of the screen, from the point of view of the camera, at z = 0
	var center: IPoint3d[Float] = new CameraAnchor(self, 0.5, -0.5)

	# Center of the top of the screen, at z = 0
	var top: IPoint3d[Float] = new CameraAnchor(self, 0.5, 0.0)

	# Center of the bottom of the screen, at z = 0
	var bottom: IPoint3d[Float] = new CameraAnchor(self, 0.5, -1.0)

	# Center of the left border of the screen, at z = 0
	var left: IPoint3d[Float] = new CameraAnchor(self, 0.0, -0.5)

	# Center of the right border of the screen, at z = 0
	var right: IPoint3d[Float] = new CameraAnchor(self, 1.0, -0.5)

	# Top left corner of the screen, at z = 0
	var top_left: IPoint3d[Float] = new CameraAnchor(self, 0.0, 0.0)

	# Top right corner of the screen, at z = 0
	var top_right: IPoint3d[Float] = new CameraAnchor(self, 1.0, 0.0)

	# Bottom left corner of the screen, at z = 0
	var bottom_left: IPoint3d[Float] = new CameraAnchor(self, 0.0, -1.0)

	# Bottom right corner of the screen, at z = 0
	var bottom_right: IPoint3d[Float] = new CameraAnchor(self, 1.0, -1.0)

	redef fun mvp_matrix
	do
		var view = new Matrix.identity(4)

		# Translate the world away from the camera
		view.translate(-position.x, -position.y, -position.z)

		# Use a projection matrix with a depth
		var projection = new Matrix.orthogonal(0.0, width, -height, 0.0, near, far)

		return view * projection
	end
end

# Immutable relative anchors for reference points on `camera`
private class CameraAnchor
	super IPoint3d[Float]

	# Reference camera
	var camera: UICamera

	# Reference position, the top left of the screen
	var ref: Point3d[Float] = camera.position is lazy

	# X position as proportion of the screen width
	var relative_x: Float

	# Y position as proportion of the screen height
	var relative_y: Float

	redef fun x do return ref.x + relative_x*camera.width
	redef fun y do return ref.y + relative_y*camera.height
	redef fun z do return ref.z

	redef fun offset(x, y, z) do return new OffsetPoint3d(self, x.to_f, y.to_f, z.to_f)
end

# Position relative to another point or usually a `CameraAnchor`
private class OffsetPoint3d
	super Point3d[Float]

	autoinit ref, offset_x, offset_y, offset_z

	# Reference point to which the offsets are applied
	var ref: IPoint3d[Float]

	# Difference on the X axis
	var offset_x: Float

	# Difference on the X axis
	var offset_y: Float

	# Difference on the X axis
	var offset_z: Float

	redef fun x do return ref.x + offset_x
	redef fun y do return ref.y + offset_y
	redef fun z do return ref.z + offset_z

	redef fun x=(value) do if value != null then offset_x += value - x
	redef fun y=(value) do if value != null then offset_y += value - y
	redef fun z=(value) do if value != null then offset_z += value - z

	redef fun offset(x, y, z) do return new OffsetPoint3d(self, x.to_f, y.to_f, z.to_f)
end
lib/gamnit/cameras.nit:15,1--329,3