pitch, yaw, roll)gamnit :: EulerCamera :: accept_scroll_and_zoom
Zoom and scroll this camera from user inputgamnit :: EulerCamera :: camera_pan_mask
Scroll trigger button mask from SDL2 (1: left, 2: middle, 4: right)gamnit :: EulerCamera :: camera_pan_mask=
Scroll trigger button mask from SDL2 (1: left, 2: middle, 4: right)gamnit :: EulerCamera :: camera_to_world
Convert the positionx, y on screen, to world coordinates on the plane at target_z
			gamnit :: EulerCamera :: camera_zoom_mod
Zoom factor, default at 1.2, higher means more reactive zoom effectgamnit :: EulerCamera :: camera_zoom_mod=
Zoom factor, default at 1.2, higher means more reactive zoom effectgamnit :: EulerCamera :: defaultinit
gamnit :: EulerCamera :: eye_separation
Half of the distance between the eyesgamnit :: EulerCamera :: eye_separation=
Half of the distance between the eyesgamnit :: EulerCamera :: far
Clipping wall the farthest of the camera, in world dimensionsgamnit :: EulerCamera :: far=
Clipping wall the farthest of the camera, in world dimensionsgamnit :: EulerCamera :: field_of_view_y
Field of view in radians on the vertical axis of the screengamnit :: EulerCamera :: field_of_view_y=
Field of view in radians on the vertical axis of the screengamnit :: EulerCamera :: mvp_matrix=
gamnit :: EulerCamera :: near=
Clipping wall near the camera, in world dimensionsgamnit :: EulerCamera :: pitch=
Rotation around the X axis (looking down or up)gamnit :: EulerCamera :: reset_height
Reset the camera position so thatheight world units are visible on the y axis at z=0
			gamnit :: EulerCamera :: rotation_matrix
Rotation matrix produced by the current rotation of the cameragamnit :: EulerCamera :: rotation_matrix=
Do not useyaw and pitch, the value will instead originate from the Cardboard API
			gamnit :: EulerCamera :: sensitivity=
Look around sensitivity, used byturn
			gamnit :: EulerCamera :: yaw=
Rotation around the Y axis (looking left or right)gamnit $ EulerCamera :: SELF
Type of this instance, automatically specialized in every classgamnit :: camera_control_android $ EulerCamera :: accept_scroll_and_zoom
Zoom and scroll this camera from user inputgamnit :: camera_control_linux $ EulerCamera :: accept_scroll_and_zoom
Zoom and scroll this camera from user inputgamnit :: cameras_cache $ EulerCamera :: far=
Clipping wall the farthest of the camera, in world dimensionsgamnit :: cameras_cache $ EulerCamera :: field_of_view_y=
Field of view in radians on the vertical axis of the screengamnit :: cameras_cache $ EulerCamera :: mvp_matrix
The returned matrix must not be modified as it is cached.gamnit $ EulerCamera :: mvp_matrix
The Model-View-Projection matrix created by this cameragamnit :: stereoscopic_view $ EulerCamera :: mvp_matrix
The Model-View-Projection matrix created by this cameragamnit :: cameras_cache $ EulerCamera :: near=
Clipping wall near the camera, in world dimensionsgamnit :: cameras_cache $ EulerCamera :: pitch=
Rotation around the X axis (looking down or up)gamnit :: cameras_cache $ EulerCamera :: roll=
Rotation around the Z axisgamnit :: cardboard $ EulerCamera :: rotation_matrix
Do not useyaw and pitch, the value will instead originate from the Cardboard API
			gamnit :: cameras_cache $ EulerCamera :: yaw=
Rotation around the Y axis (looking left or right)gamnit :: EulerCamera :: accept_scroll_and_zoom
Zoom and scroll this camera from user inputgamnit :: EulerCamera :: camera_pan_mask
Scroll trigger button mask from SDL2 (1: left, 2: middle, 4: right)gamnit :: EulerCamera :: camera_pan_mask=
Scroll trigger button mask from SDL2 (1: left, 2: middle, 4: right)gamnit :: EulerCamera :: camera_to_world
Convert the positionx, y on screen, to world coordinates on the plane at target_z
			gamnit :: EulerCamera :: camera_zoom_mod
Zoom factor, default at 1.2, higher means more reactive zoom effectgamnit :: EulerCamera :: camera_zoom_mod=
Zoom factor, default at 1.2, higher means more reactive zoom effectcore :: Object :: class_factory
Implementation used byget_class to create the specific class.
			gamnit :: Camera :: defaultinit
core :: Object :: defaultinit
gamnit :: EulerCamera :: defaultinit
gamnit :: EulerCamera :: eye_separation
Half of the distance between the eyesgamnit :: EulerCamera :: eye_separation=
Half of the distance between the eyesgamnit :: EulerCamera :: far
Clipping wall the farthest of the camera, in world dimensionsgamnit :: EulerCamera :: far=
Clipping wall the farthest of the camera, in world dimensionsgamnit :: EulerCamera :: field_of_view_y
Field of view in radians on the vertical axis of the screengamnit :: EulerCamera :: field_of_view_y=
Field of view in radians on the vertical axis of the screencore :: Object :: is_same_instance
Return true ifself and other are the same instance (i.e. same identity).
			core :: Object :: is_same_serialized
Isself the same as other in a serialization context?
			core :: Object :: is_same_type
Return true ifself and other have the same dynamic type.
			gamnit :: Camera :: mvp_matrix
The Model-View-Projection matrix created by this cameragamnit :: EulerCamera :: mvp_matrix=
gamnit :: EulerCamera :: near=
Clipping wall near the camera, in world dimensionscore :: Object :: output_class_name
Display class name on stdout (debug only).gamnit :: EulerCamera :: pitch=
Rotation around the X axis (looking down or up)gamnit :: EulerCamera :: reset_height
Reset the camera position so thatheight world units are visible on the y axis at z=0
			gamnit :: EulerCamera :: rotation_matrix
Rotation matrix produced by the current rotation of the cameragamnit :: EulerCamera :: rotation_matrix=
Do not useyaw and pitch, the value will instead originate from the Cardboard API
			gamnit :: EulerCamera :: sensitivity=
Look around sensitivity, used byturn
			gamnit :: EulerCamera :: yaw=
Rotation around the Y axis (looking left or right)
# 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
				
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
				
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
				
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
				
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
				
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
				
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