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

Introduced properties

fun accept_scroll_and_zoom(event: InputEvent): Bool

gamnit :: EulerCamera :: accept_scroll_and_zoom

Zoom and scroll this camera from user input
fun camera_pan_mask: Int

gamnit :: EulerCamera :: camera_pan_mask

Scroll trigger button mask from SDL2 (1: left, 2: middle, 4: right)
fun camera_pan_mask=(camera_pan_mask: Int)

gamnit :: EulerCamera :: camera_pan_mask=

Scroll trigger button mask from SDL2 (1: left, 2: middle, 4: right)
fun camera_to_world(x: Numeric, y: Numeric, target_z: nullable Float): Point[Float]

gamnit :: EulerCamera :: camera_to_world

Convert the position x, y on screen, to world coordinates on the plane at target_z
fun camera_zoom_mod: Float

gamnit :: EulerCamera :: camera_zoom_mod

Zoom factor, default at 1.2, higher means more reactive zoom effect
fun camera_zoom_mod=(camera_zoom_mod: Float)

gamnit :: EulerCamera :: camera_zoom_mod=

Zoom factor, default at 1.2, higher means more reactive zoom effect
fun eye_separation: Float

gamnit :: EulerCamera :: eye_separation

Half of the distance between the eyes
protected fun eye_separation=(eye_separation: Float)

gamnit :: EulerCamera :: eye_separation=

Half of the distance between the eyes
fun far: Float

gamnit :: EulerCamera :: far

Clipping wall the farthest of the camera, in world dimensions
fun far=(far: Float)

gamnit :: EulerCamera :: far=

Clipping wall the farthest of the camera, in world dimensions
fun field_of_view_y: Float

gamnit :: EulerCamera :: field_of_view_y

Field of view in radians on the vertical axis of the screen
fun field_of_view_y=(field_of_view_y: Float)

gamnit :: EulerCamera :: field_of_view_y=

Field of view in radians on the vertical axis of the screen
fun look_at(x: Float, y: Float, z: Float)

gamnit :: EulerCamera :: look_at

Aim the camera at x, y, z
fun move(dx: Float, dy: Float, dz: Float)

gamnit :: EulerCamera :: move

Move the camera considering the current orientation
protected fun mvp_matrix=(mvp_matrix: Matrix)

gamnit :: EulerCamera :: mvp_matrix=

fun mvp_matrix_left: Matrix

gamnit :: EulerCamera :: mvp_matrix_left

MVP matrix for the left eye
fun mvp_matrix_right: Matrix

gamnit :: EulerCamera :: mvp_matrix_right

MVP matrix for the right eye
fun near: Float

gamnit :: EulerCamera :: near

Clipping wall near the camera, in world dimensions
fun near=(near: Float)

gamnit :: EulerCamera :: near=

Clipping wall near the camera, in world dimensions
fun pitch: Float

gamnit :: EulerCamera :: pitch

Rotation around the X axis (looking down or up)
fun pitch=(pitch: Float)

gamnit :: EulerCamera :: pitch=

Rotation around the X axis (looking down or up)
fun reset_height(height: nullable Float)

gamnit :: EulerCamera :: reset_height

Reset the camera position so that height world units are visible on the y axis at z=0
fun roll: Float

gamnit :: EulerCamera :: roll

Rotation around the Z axis
fun roll=(roll: Float)

gamnit :: EulerCamera :: roll=

Rotation around the Z axis
protected fun rotation_matrix: Matrix

gamnit :: EulerCamera :: rotation_matrix

Rotation matrix produced by the current rotation of the camera
protected fun rotation_matrix=(rotation_matrix: Matrix)

gamnit :: EulerCamera :: rotation_matrix=

Do not use yaw and pitch, the value will instead originate from the Cardboard API
fun sensitivity: Float

gamnit :: EulerCamera :: sensitivity

Look around sensitivity, used by turn
fun sensitivity=(sensitivity: Float)

gamnit :: EulerCamera :: sensitivity=

Look around sensitivity, used by turn
fun turn(dx: Float, dy: Float)

gamnit :: EulerCamera :: turn

Apply a mouse movement (or similar) to the camera
fun yaw: Float

gamnit :: EulerCamera :: yaw

Rotation around the Y axis (looking left or right)
fun yaw=(yaw: Float)

gamnit :: EulerCamera :: yaw=

Rotation around the Y axis (looking left or right)

Redefined properties

redef type SELF: EulerCamera

gamnit $ EulerCamera :: SELF

Type of this instance, automatically specialized in every class
redef fun accept_scroll_and_zoom(event: InputEvent): Bool

gamnit :: camera_control_android $ EulerCamera :: accept_scroll_and_zoom

Zoom and scroll this camera from user input
redef fun accept_scroll_and_zoom(event: InputEvent): Bool

gamnit :: camera_control_linux $ EulerCamera :: accept_scroll_and_zoom

Zoom and scroll this camera from user input
redef fun far=(value: Float)

gamnit :: cameras_cache $ EulerCamera :: far=

Clipping wall the farthest of the camera, in world dimensions
redef fun field_of_view_y=(value: Float)

gamnit :: cameras_cache $ EulerCamera :: field_of_view_y=

Field of view in radians on the vertical axis of the screen
redef fun mvp_matrix: Matrix

gamnit :: cameras_cache $ EulerCamera :: mvp_matrix

The returned matrix must not be modified as it is cached.
redef fun mvp_matrix: Matrix

gamnit $ EulerCamera :: mvp_matrix

The Model-View-Projection matrix created by this camera
redef fun mvp_matrix: Matrix

gamnit :: stereoscopic_view $ EulerCamera :: mvp_matrix

The Model-View-Projection matrix created by this camera
redef fun near=(value: Float)

gamnit :: cameras_cache $ EulerCamera :: near=

Clipping wall near the camera, in world dimensions
redef fun pitch: Float

gamnit :: cardboard $ EulerCamera :: pitch

Get the angle value from the rotation_matrix
redef fun pitch=(value: Float)

gamnit :: cameras_cache $ EulerCamera :: pitch=

Rotation around the X axis (looking down or up)
redef fun roll=(value: Float)

gamnit :: cameras_cache $ EulerCamera :: roll=

Rotation around the Z axis
redef fun rotation_matrix: Matrix

gamnit :: cardboard $ EulerCamera :: rotation_matrix

Do not use yaw and pitch, the value will instead originate from the Cardboard API
redef fun yaw: Float

gamnit :: cardboard $ EulerCamera :: yaw

Get the angle value from the rotation_matrix
redef fun yaw=(value: Float)

gamnit :: cameras_cache $ EulerCamera :: yaw=

Rotation around the Y axis (looking left or right)

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 accept_scroll_and_zoom(event: InputEvent): Bool

gamnit :: EulerCamera :: accept_scroll_and_zoom

Zoom and scroll this camera from user input
fun camera_pan_mask: Int

gamnit :: EulerCamera :: camera_pan_mask

Scroll trigger button mask from SDL2 (1: left, 2: middle, 4: right)
fun camera_pan_mask=(camera_pan_mask: Int)

gamnit :: EulerCamera :: camera_pan_mask=

Scroll trigger button mask from SDL2 (1: left, 2: middle, 4: right)
fun camera_to_world(x: Numeric, y: Numeric, target_z: nullable Float): Point[Float]

gamnit :: EulerCamera :: camera_to_world

Convert the position x, y on screen, to world coordinates on the plane at target_z
fun camera_zoom_mod: Float

gamnit :: EulerCamera :: camera_zoom_mod

Zoom factor, default at 1.2, higher means more reactive zoom effect
fun camera_zoom_mod=(camera_zoom_mod: Float)

gamnit :: EulerCamera :: camera_zoom_mod=

Zoom factor, default at 1.2, higher means more reactive zoom effect
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 display: GamnitDisplay

gamnit :: Camera :: display

The host GamnitDisplay
protected fun display=(display: GamnitDisplay)

gamnit :: Camera :: display=

The host GamnitDisplay
fun eye_separation: Float

gamnit :: EulerCamera :: eye_separation

Half of the distance between the eyes
protected fun eye_separation=(eye_separation: Float)

gamnit :: EulerCamera :: eye_separation=

Half of the distance between the eyes
fun far: Float

gamnit :: EulerCamera :: far

Clipping wall the farthest of the camera, in world dimensions
fun far=(far: Float)

gamnit :: EulerCamera :: far=

Clipping wall the farthest of the camera, in world dimensions
fun field_of_view_y: Float

gamnit :: EulerCamera :: field_of_view_y

Field of view in radians on the vertical axis of the screen
fun field_of_view_y=(field_of_view_y: Float)

gamnit :: EulerCamera :: field_of_view_y=

Field of view in radians on the vertical axis of the screen
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.
fun look_at(x: Float, y: Float, z: Float)

gamnit :: EulerCamera :: look_at

Aim the camera at x, y, z
fun move(dx: Float, dy: Float, dz: Float)

gamnit :: EulerCamera :: move

Move the camera considering the current orientation
abstract fun mvp_matrix: Matrix

gamnit :: Camera :: mvp_matrix

The Model-View-Projection matrix created by this camera
protected fun mvp_matrix=(mvp_matrix: Matrix)

gamnit :: EulerCamera :: mvp_matrix=

fun mvp_matrix_left: Matrix

gamnit :: EulerCamera :: mvp_matrix_left

MVP matrix for the left eye
fun mvp_matrix_right: Matrix

gamnit :: EulerCamera :: mvp_matrix_right

MVP matrix for the right eye
fun near: Float

gamnit :: EulerCamera :: near

Clipping wall near the camera, in world dimensions
fun near=(near: Float)

gamnit :: EulerCamera :: near=

Clipping wall near the camera, in world dimensions
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 pitch: Float

gamnit :: EulerCamera :: pitch

Rotation around the X axis (looking down or up)
fun pitch=(pitch: Float)

gamnit :: EulerCamera :: pitch=

Rotation around the X axis (looking down or up)
fun position: Point3d[Float]

gamnit :: Camera :: position

Position of this camera in world space
protected fun position=(position: Point3d[Float])

gamnit :: Camera :: position=

Position of this camera in world space
fun reset_height(height: nullable Float)

gamnit :: EulerCamera :: reset_height

Reset the camera position so that height world units are visible on the y axis at z=0
fun roll: Float

gamnit :: EulerCamera :: roll

Rotation around the Z axis
fun roll=(roll: Float)

gamnit :: EulerCamera :: roll=

Rotation around the Z axis
protected fun rotation_matrix: Matrix

gamnit :: EulerCamera :: rotation_matrix

Rotation matrix produced by the current rotation of the camera
protected fun rotation_matrix=(rotation_matrix: Matrix)

gamnit :: EulerCamera :: rotation_matrix=

Do not use yaw and pitch, the value will instead originate from the Cardboard API
fun sensitivity: Float

gamnit :: EulerCamera :: sensitivity

Look around sensitivity, used by turn
fun sensitivity=(sensitivity: Float)

gamnit :: EulerCamera :: sensitivity=

Look around sensitivity, used by turn
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 turn(dx: Float, dy: Float)

gamnit :: EulerCamera :: turn

Apply a mouse movement (or similar) to the camera
fun yaw: Float

gamnit :: EulerCamera :: yaw

Rotation around the Y axis (looking left or right)
fun yaw=(yaw: Float)

gamnit :: EulerCamera :: yaw=

Rotation around the Y axis (looking left or right)
package_diagram gamnit::EulerCamera EulerCamera gamnit::Camera Camera gamnit::EulerCamera->gamnit::Camera core::Object Object gamnit::Camera->core::Object ...core::Object ... ...core::Object->core::Object

Ancestors

interface Object

core :: Object

The root of the class hierarchy.

Parents

abstract class Camera

gamnit :: Camera

A camera with a point of view on the world

Class definitions

gamnit $ EulerCamera
# 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
lib/gamnit/cameras.nit:41,1--194,3

gamnit :: camera_control $ EulerCamera
redef class EulerCamera
	# Zoom and scroll this camera from user input
	#
	# Scrolling is accomplished by moving the camera on the XY plane and
	# zooming by moving it on the Z axis.
	#
	# This method has distinct implementations per platform.
	# On desktop computers, the mouse wheel changes the zoom level, and
	# holding down the middle mouse button scrolls the camera.
	# On Android, a two finger pinch and slide gesture zoom and scroll.
	#
	# Returns `true` if the event is used.
	#
	# Should be called from `App::accept_event` before accepting pointer events:
	#
	# ~~~nitish
	# redef class App
	#     redef fun accept_event(event)
	#     do
	#         if world_camera.accept_scroll_and_zoom(event) then return true
	#
	#         # Handle other events...
	#         return false
	#     end
	# end
	# ~~~
	fun accept_scroll_and_zoom(event: InputEvent): Bool do return false
end
lib/gamnit/camera_control.nit:24,1--51,3

gamnit :: cameras_cache $ EulerCamera
redef class EulerCamera
	# The returned matrix must not be modified as it is cached.
	redef fun mvp_matrix
	do
		var m = mvp_matrix_cache
		if m == null or check_position_changed then
			m = super
			mvp_matrix_cache = m
		end
		return m
	end

	redef fun pitch=(value)
	do
		super
		mvp_matrix_cache = null
	end

	redef fun yaw=(value)
	do
		super
		mvp_matrix_cache = null
	end

	redef fun roll=(value)
	do
		super
		mvp_matrix_cache = null
	end

	redef fun field_of_view_y=(value)
	do
		super
		mvp_matrix_cache = null
	end

	redef fun near=(value)
	do
		super
		mvp_matrix_cache = null
	end

	redef fun far=(value)
	do
		super
		mvp_matrix_cache = null
	end
end
lib/gamnit/cameras_cache.nit:40,1--87,3

gamnit :: camera_control_linux $ EulerCamera
redef class EulerCamera

	# Zoom factor, default at 1.2, higher means more reactive zoom effect
	var camera_zoom_mod = 1.2 is writable

	# Scroll trigger button mask from SDL2 (1: left, 2: middle, 4: right)
	#
	# Set to 0 to deactivate the scrolling feature.
	var camera_pan_mask = 2 is writable

	redef fun accept_scroll_and_zoom(event)
	do
		# Zoom
		if event isa GamnitMouseWheelEvent then
			var dy = event.y
			var mod = camera_zoom_mod
			if dy > 0.0 then
				# Zoom in when moving the wheel up
				mod = 1.0/mod
			else dy = -dy

			position.z *= dy * mod
			return true
		end

		# Scroll
		var but_mask = camera_pan_mask
		if but_mask != 0 and event isa GamnitPointerEvent then
			var native = event.native
			if native isa SDLMouseMotionEvent and native.state & but_mask == but_mask then
				var dx = native.xrel.to_f
				var dy = native.yrel.to_f

				var world_height = field_of_view_y.sin * position.z
				var mod = app.display.as(not null).height.to_f / world_height
				position.x -= dx / mod
				position.y += dy / mod # Y is inverted between the input and output
				return true
			end
		end

		return false
	end
end
lib/gamnit/camera_control_linux.nit:21,1--64,3

gamnit :: camera_control_android $ EulerCamera
redef class EulerCamera
	# Smoothened history of pointers in the current motion event
	private var last_motion_pointers = new HashMap[Int, Point[Float]] is lazy

	# Start time of the current motion event
	private var last_motion_start: Int = -1

	redef fun accept_scroll_and_zoom(event)
	do
		if not event isa AndroidMotionEvent then return false

		if event.pointers.length < 2 then
			# Intercept leftovers of the last motion
			return event.down_time == last_motion_start
		end

		# Collect active pointer and their world position
		var new_motion_pointers = new HashMap[Int, Point[Float]]
		var ids = new Array[Int]
		for pointer in event.pointers do
			var id = pointer.pointer_id
			ids.add id
			new_motion_pointers[id] = camera_to_world(pointer.x, pointer.y)
		end

		var last_motion_pointers = last_motion_pointers
		if last_motion_start == event.down_time and
		   last_motion_pointers.keys.has(ids[0]) and last_motion_pointers.keys.has(ids[1]) then
			# Continued motion event

			# Get new and old position for 2 fingers
			var new_motion_a = new_motion_pointers[ids[0]]
			var new_motion_b = new_motion_pointers[ids[1]]
			var prev_pos_a = last_motion_pointers[ids[0]]
			var prev_pos_b = last_motion_pointers[ids[1]]

			# Move camera
			var prev_middle_pos = prev_pos_a.lerp(prev_pos_b, 0.5)
			var new_middle_pos = new_motion_a.lerp(new_motion_b, 0.5)
			position.x -= new_middle_pos.x - prev_middle_pos.x
			position.y -= new_middle_pos.y - prev_middle_pos.y

			# Zoom camera
			var prev_dist = prev_pos_a.dist(prev_pos_b)
			var new_dist = new_motion_a.dist(new_motion_b)

			position.z = prev_dist * position.z / new_dist
		else
			# Prepare for a new motion event
			last_motion_pointers.clear
			last_motion_start = event.down_time
		end

		# Keep a smooth history
		for i in [0..1] do
			if last_motion_pointers.keys.has(ids[i]) then
				last_motion_pointers[ids[i]] = last_motion_pointers[ids[i]]*0.5 +
				                                new_motion_pointers[ids[i]]*0.5
			else last_motion_pointers[ids[i]] = new_motion_pointers[ids[i]]
		end

		return true
	end
end
lib/gamnit/camera_control_android.nit:21,1--84,3

gamnit :: stereoscopic_view $ EulerCamera
redef class EulerCamera
	redef var mvp_matrix = new Matrix.identity(4)

	# Half of the distance between the eyes
	var eye_separation: Float = 0.03125

	# MVP matrix for the left eye
	fun mvp_matrix_left: Matrix do return mvp_matrix_eye(eye_separation)

	# MVP matrix for the right eye
	fun mvp_matrix_right: Matrix do return mvp_matrix_eye(-eye_separation)

	# Get an MVP matrix for an eye at `diff` world unit from the center
	private fun mvp_matrix_eye(diff: Float): Matrix
	do
		var view = new Matrix.identity(4)

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

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

		# Apply eye transformation
		var translation = new Matrix.identity(4)
		translation.translate(diff, 0.0, 0.0)
		view = view * translation

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

		return view * projection
	end
end
lib/gamnit/depth/stereoscopic_view.nit:21,1--55,3

gamnit :: cardboard $ EulerCamera
redef class EulerCamera
	# Do not use `yaw` and `pitch`, the value will instead originate from the Cardboard API
	redef var rotation_matrix = new Matrix.identity(4)

	# Get the angle value from the `rotation_matrix`
	redef fun pitch
	do
		var a = rotation_matrix[0, 1]
		var b = rotation_matrix[1, 1]
		return -atan2(a, b)
	end

	# Get the angle value from the `rotation_matrix`
	redef fun yaw
	do
		var a = rotation_matrix[2, 0]
		var b = rotation_matrix[2, 2]
		return -atan2(a, b)
	end
end
lib/gamnit/depth/cardboard.nit:25,1--44,3