A rectangular array of Float

Require: width > 0 and height > 0

Introduced properties

fun *(other: Matrix): Matrix

matrix :: Matrix :: *

Matrix product (×)
fun [](y: Int, x: Int): Float

matrix :: Matrix :: []

Get the value at column y and row x
fun []=(y: Int, x: Int, value: Float)

matrix :: Matrix :: []=

Set the value at row y and column x
init defaultinit(width: Int, height: Int)

matrix :: Matrix :: defaultinit

fun fill_native(native: NativeGLfloatArray)

matrix :: Matrix :: fill_native

Copy content of this matrix to a NativeGLfloatArray
init from(items: SequenceRead[SequenceRead[Float]])

matrix :: Matrix :: from

Create a matrix from nested sequences
init from_array(width: Int, height: Int, array: SequenceRead[Float])

matrix :: Matrix :: from_array

Create a matrix from an Array[Float] composed of rows after rows
init frustum(left: Float, right: Float, bottom: Float, top: Float, near: Float, far: Float): Matrix

matrix :: Matrix :: frustum

Create a frustum transformation matrix
init gamnit_euler_rotation(pitch: Float, yaw: Float, roll: Float): Matrix

matrix :: Matrix :: gamnit_euler_rotation

Rotation matrix from Euler angles pitch, yaw and roll in radians
fun height: Int

matrix :: Matrix :: height

Number of rows
protected fun height=(height: Int)

matrix :: Matrix :: height=

Number of rows
init identity(size: Int): Matrix

matrix :: Matrix :: identity

Create an identity matrix
fun iterator: MapIterator[MatrixCoordinate, Float]

matrix :: Matrix :: iterator

Iterate over the values in this matrix
init orthogonal(left: Float, right: Float, bottom: Float, top: Float, near: Float, far: Float): Matrix

matrix :: Matrix :: orthogonal

Create an orthogonal projection matrix
init perspective(field_of_view_y: Float, aspect_ratio: Float, near: Float, far: Float): Matrix

matrix :: Matrix :: perspective

Create a perspective transformation matrix
fun rotate(angle: Float, x: Float, y: Float, z: Float)

matrix :: Matrix :: rotate

Apply a rotation of angle radians around the vector x, y, z
init rotation(angle: Float, x: Float, y: Float, z: Float): Matrix

matrix :: Matrix :: rotation

Create a rotation matrix by angle around the vector defined by x, y, z
fun scale(x: Float, y: Float, z: Float)

matrix :: Matrix :: scale

Apply scaling on x, y, z to this matrix
fun to_a: Array[Array[Float]]

matrix :: Matrix :: to_a

Get each row of this matrix in nested arrays
fun translate(x: Float, y: Float, z: Float)

matrix :: Matrix :: translate

Apply a translation by x, y, z to this matrix
fun transposed: Matrix

matrix :: Matrix :: transposed

Get the transpose of this matrix
fun width: Int

matrix :: Matrix :: width

Number of columns
protected fun width=(width: Int)

matrix :: Matrix :: width=

Number of columns

Redefined properties

redef fun ==(other: nullable Object): Bool

matrix $ Matrix :: ==

Have self and other the same value?
redef type SELF: Matrix

matrix $ Matrix :: SELF

Type of this instance, automatically specialized in every class
redef fun clone: SELF

matrix $ Matrix :: clone

Create a new clone of this matrix
redef fun hash: Int

matrix $ Matrix :: hash

The hash code of the object.
redef fun to_s: String

matrix $ Matrix :: to_s

User readable representation of self.

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
fun *(other: Matrix): Matrix

matrix :: Matrix :: *

Matrix product (×)
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 [](y: Int, x: Int): Float

matrix :: Matrix :: []

Get the value at column y and row x
fun []=(y: Int, x: Int, value: Float)

matrix :: Matrix :: []=

Set the value at row y and column x
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.
abstract fun clone: SELF

core :: Cloneable :: clone

Duplicate self
init defaultinit(width: Int, height: Int)

matrix :: Matrix :: defaultinit

fun fill_native(native: NativeGLfloatArray)

matrix :: Matrix :: fill_native

Copy content of this matrix to a NativeGLfloatArray
init from(items: SequenceRead[SequenceRead[Float]])

matrix :: Matrix :: from

Create a matrix from nested sequences
init from_array(width: Int, height: Int, array: SequenceRead[Float])

matrix :: Matrix :: from_array

Create a matrix from an Array[Float] composed of rows after rows
init frustum(left: Float, right: Float, bottom: Float, top: Float, near: Float, far: Float): Matrix

matrix :: Matrix :: frustum

Create a frustum transformation matrix
init gamnit_euler_rotation(pitch: Float, yaw: Float, roll: Float): Matrix

matrix :: Matrix :: gamnit_euler_rotation

Rotation matrix from Euler angles pitch, yaw and roll in radians
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.
fun height: Int

matrix :: Matrix :: height

Number of rows
protected fun height=(height: Int)

matrix :: Matrix :: height=

Number of rows
init identity(size: Int): Matrix

matrix :: Matrix :: identity

Create an identity matrix
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 iterator: MapIterator[MatrixCoordinate, Float]

matrix :: Matrix :: iterator

Iterate over the values in this matrix
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
init orthogonal(left: Float, right: Float, bottom: Float, top: Float, near: Float, far: Float): Matrix

matrix :: Matrix :: orthogonal

Create an orthogonal projection matrix
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).
init perspective(field_of_view_y: Float, aspect_ratio: Float, near: Float, far: Float): Matrix

matrix :: Matrix :: perspective

Create a perspective transformation matrix
fun rotate(angle: Float, x: Float, y: Float, z: Float)

matrix :: Matrix :: rotate

Apply a rotation of angle radians around the vector x, y, z
init rotation(angle: Float, x: Float, y: Float, z: Float): Matrix

matrix :: Matrix :: rotation

Create a rotation matrix by angle around the vector defined by x, y, z
fun scale(x: Float, y: Float, z: Float)

matrix :: Matrix :: scale

Apply scaling on x, y, z to this matrix
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.
fun to_a: Array[Array[Float]]

matrix :: Matrix :: to_a

Get each row of this matrix in nested arrays
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 translate(x: Float, y: Float, z: Float)

matrix :: Matrix :: translate

Apply a translation by x, y, z to this matrix
fun transposed: Matrix

matrix :: Matrix :: transposed

Get the transpose of this matrix
fun width: Int

matrix :: Matrix :: width

Number of columns
protected fun width=(width: Int)

matrix :: Matrix :: width=

Number of columns
package_diagram matrix::Matrix Matrix core::Cloneable Cloneable matrix::Matrix->core::Cloneable core::Object Object core::Cloneable->core::Object ...core::Object ... ...core::Object->core::Object

Ancestors

interface Object

core :: Object

The root of the class hierarchy.

Parents

interface Cloneable

core :: Cloneable

Something that can be cloned

Class definitions

matrix $ Matrix
# A rectangular array of `Float`
#
# Require: `width > 0 and height > 0`
class Matrix
	super Cloneable

	# Number of columns
	var width: Int

	# Number of rows
	var height: Int

	# Items of this matrix, rows by rows
	private var items = new NativeDoubleArray(width*height) is lazy

	# Create a matrix from nested sequences
	#
	# Require: all rows are of the same length
	#
	# ~~~
	# var matrix = new Matrix.from([[1.0, 2.0],
	#                               [3.0, 4.0]])
	# assert matrix.to_s == """
	# 1.0 2.0
	# 3.0 4.0"""
	# ~~~
	init from(items: SequenceRead[SequenceRead[Float]])
	do
		if items.is_empty then
			init(0, 0)
			return
		end

		init(items.first.length, items.length)

		for j in height.times do assert items[j].length == width

		for j in [0..height[ do
			for i in [0..width[ do
				self[j, i] = items[j][i]
			end
		end
	end

	# Get each row of this matrix in nested arrays
	#
	# ~~~
	# var items = [[1.0, 2.0],
	#              [3.0, 4.0]]
	# var matrix = new Matrix.from(items)
	# assert matrix.to_a == items
	# ~~~
	fun to_a: Array[Array[Float]]
	do
		var a = new Array[Array[Float]]
		for j in height.times do
			var row = new Array[Float]
			for i in width.times do
				row.add self[j, i]
			end
			a.add row
		end
		return a
	end

	# Create a matrix from an `Array[Float]` composed of rows after rows
	#
	# Require: `width > 0 and height > 0`
	# Require: `array.length >= width*height`
	#
	# ~~~
	# var matrix = new Matrix.from_array(2, 2, [1.0, 2.0,
	#                                           3.0, 4.0])
	# assert matrix.to_s == """
	# 1.0 2.0
	# 3.0 4.0"""
	# ~~~
	init from_array(width, height: Int, array: SequenceRead[Float])
	do
		assert width > 0
		assert height > 0
		assert array.length >= width*height

		init(width, height)

		for i in height.times do
			for j in width.times do
				self[j, i] = array[i + j*width]
			end
		end
	end

	# Create an identity matrix
	#
	# Require: `size >= 0`
	#
	# ~~~
	# var i = new Matrix.identity(3)
	# assert i.to_s == """
	# 1.0 0.0 0.0
	# 0.0 1.0 0.0
	# 0.0 0.0 1.0"""
	# ~~~
	new identity(size: Int)
	do
		assert size >= 0

		var matrix = new Matrix(size, size)
		for i in [0..size[ do
			for j in [0..size[ do
				matrix[j, i] = if i == j then 1.0 else 0.0
			end
		end
		return matrix
	end

	# Create a new clone of this matrix
	redef fun clone
	do
		var c = new Matrix(width, height)
		for i in [0..width*height[ do c.items[i] = items[i]
		return c
	end

	# Get the value at column `y` and row `x`
	#
	# Require: `x >= 0 and x <= width and y >= 0 and y <= height`
	#
	# ~~~
	# var matrix = new Matrix.from([[0.0, 0.1],
	#                               [1.0, 1.1]])
	#
	# assert matrix[0, 0] == 0.0
	# assert matrix[0, 1] == 0.1
	# assert matrix[1, 0] == 1.0
	# assert matrix[1, 1] == 1.1
	# ~~~
	fun [](y, x: Int): Float
	do
		assert x >= 0 and x < width
		assert y >= 0 and y < height

		return items[x + y*width]
	end

	# Set the `value` at row `y` and column `x`
	#
	# Require: `x >= 0 and x <= width and y >= 0 and y <= height`
	#
	# ~~~
	# var matrix = new Matrix.identity(2)
	#
	# matrix[0, 0] = 0.0
	# matrix[0, 1] = 0.1
	# matrix[1, 0] = 1.0
	# matrix[1, 1] = 1.1
	#
	# assert matrix.to_s == """
	# 0.0 0.1
	# 1.0 1.1"""
	# ~~~
	fun []=(y, x: Int, value: Float)
	do
		assert x >= 0 and x < width
		assert y >= 0 and y < height

		items[x + y*width] = value
	end

	# Matrix product (×)
	#
	# Require: `self.width == other.height`
	#
	# ~~~
	# var m = new Matrix.from([[3.0, 4.0],
	#                          [5.0, 6.0]])
	# var i = new Matrix.identity(2)
	#
	# assert m * i == m
	# assert (m * m).to_s == """
	# 29.0 36.0
	# 45.0 56.0"""
	#
	# var a = new Matrix.from([[1.0, 2.0, 3.0],
	#                          [4.0, 5.0, 6.0]])
	# var b = new Matrix.from([[1.0],
	#                          [2.0],
	#                          [3.0]])
	# var c = a * b
	# assert c.to_s == """
	# 14.0
	# 32.0"""
	# ~~~
	fun *(other: Matrix): Matrix
	do
		assert self.width == other.height

		var out = new Matrix(other.width, self.height)
		out.items.mul(items, other.items, self.width, self.height, other.width)
		return out
	end

	# Get the transpose of this matrix
	#
	# ~~~
	# var matrix = new Matrix.from([[1.0, 2.0, 3.0],
	#                               [4.0, 5.0, 6.0]])
	# assert matrix.transposed.to_a == [[1.0, 4.0],
	#                                   [2.0, 5.0],
	#                                   [3.0, 6.0]]
	#
	# var i = new Matrix.identity(3)
	# assert i.transposed == i
	# ~~~
	fun transposed: Matrix
	do
		var out = new Matrix(height, width)
		for k, v in self do out[k.x, k.y] = v
		return out
	end

	# Iterate over the values in this matrix
	fun iterator: MapIterator[MatrixCoordinate, Float] do return new MatrixIndexIterator(self)

	redef fun to_s
	do
		var s = new FlatBuffer
		for y in [0..height[ do
			for x in [0..width[ do
				s.append items[y*width+x].to_s
				if x < width-1 then s.add ' '
			end
			if y < height-1 then s.add '\n'
		end
		return s.to_s
	end

	redef fun ==(other) do return other isa Matrix and
		width == other.width and height == other.height and
		items.equal_items(items, width*height)

	redef fun hash do return items.hash_items(width*height)
end
lib/matrix/matrix.nit:18,1--260,3

matrix :: projection $ Matrix
redef class Matrix

	# Create an orthogonal projection matrix
	#
	# `left, right, bottom, top, near, far` defines the world clip planes.
	new orthogonal(left, right, bottom, top, near, far: Float)
	do
		var dx = right - left
		var dy = top - bottom
		var dz = far - near

		assert dx != 0.0 and dy != 0.0 and dz != 0.0

		var mat = new Matrix.identity(4)
		mat[0, 0] = 2.0 / dx
		mat[3, 0] = -(right + left) / dx
		mat[1, 1] = 2.0 / dy
		mat[3, 1] = -(top + bottom) / dy
		mat[2, 2] = 2.0 / dz
		mat[3, 2] = -(near + far) / dz
		return mat
	end

	# Create a perspective transformation matrix
	#
	# Using the given vertical `field_of_view_y` in radians, the `aspect_ratio`
	# and the `near`/`far` world distances.
	new perspective(field_of_view_y, aspect_ratio, near, far: Float)
	do
		var frustum_height = (field_of_view_y/2.0).tan * near
		var frustum_width = frustum_height * aspect_ratio

		return new Matrix.frustum(-frustum_width, frustum_width,
		                          -frustum_height, frustum_height,
		                          near, far)
	end

	# Create a frustum transformation matrix
	#
	# `left, right, bottom, top, near, far` defines the world clip planes.
	new frustum(left, right, bottom, top, near, far: Float)
	do
		var dx = right - left
		var dy = top - bottom
		var dz = far - near

		assert near > 0.0
		assert far > 0.0
		assert dx > 0.0
		assert dy > 0.0
		assert dz > 0.0

		var mat = new Matrix(4, 4)

		mat[0, 0] = 2.0 * near / dx
		mat[0, 1] = 0.0
		mat[0, 2] = 0.0
		mat[0, 3] = 0.0

		mat[1, 0] = 0.0
		mat[1, 1] = 2.0 * near / dy
		mat[1, 2] = 0.0
		mat[1, 3] = 0.0

		mat[2, 0] = (right + left) / dx
		mat[2, 1] = (top + bottom) / dy
		mat[2, 2] = -(near + far) / dz
		mat[2, 3] = -1.0

		mat[3, 0] = 0.0
		mat[3, 1] = 0.0
		mat[3, 2] = -2.0 * near * far / dz
		mat[3, 3] = 0.0

		return mat
	end

	# Apply a translation by `x, y, z` to this matrix
	fun translate(x, y, z: Float)
	do
		for i in [0..3] do
			self[3, i] = self[3,i] + self[0, i] * x + self[1, i] * y + self[2, i] * z
		end
	end

	# Apply scaling on `x, y, z` to this matrix
	fun scale(x, y, z: Float)
	do
		for i in [0..3] do
			self[0, i] = self[0, i] * x
			self[1, i] = self[1, i] * y
			self[2, i] = self[2, i] * z
		end
	end

	# Create a rotation matrix by `angle` around the vector defined by `x, y, z`
	new rotation(angle, x, y, z: Float)
	do
		var mat = new Matrix.identity(4)

		var mag = (x*x + y*y + z*z).sqrt
		var sin = angle.sin
		var cos = angle.cos

		if mag > 0.0 then
			x = x / mag
			y = y / mag
			z = z / mag

			var inv_cos = 1.0 - cos

			mat[0, 0] = inv_cos*x*x + cos
			mat[0, 1] = inv_cos*x*y - z*sin
			mat[0, 2] = inv_cos*z*x + y*sin

			mat[1, 0] = inv_cos*x*y + z*sin
			mat[1, 1] = inv_cos*y*y + cos
			mat[1, 2] = inv_cos*y*z - x*sin

			mat[2, 0] = inv_cos*z*x - y*sin
			mat[2, 1] = inv_cos*y*z + x*sin
			mat[2, 2] = inv_cos*z*z + cos
		end
		return mat
	end

	# Apply a rotation of `angle` radians around the vector `x, y, z`
	fun rotate(angle, x, y, z: Float)
	do
		var rotation = new Matrix.rotation(angle, x, y, z)
		var rotated = self * rotation
		self.items = rotated.items
	end

	# Rotation matrix from Euler angles `pitch`, `yaw` and `roll` in radians
	#
	# Apply a composition of intrinsic rotations around the axes x-y'-z''.
	# Or `pitch` around the X axis, `yaw` around Y and `roll` around Z,
	# applied successively. All rotations follow the right hand rule.
	#
	# This service aims to respect the world axes and logic of `gamnit`,
	# it may not correspond to all needs.
	#
	# The returned `Matrix` may be cached, it must not be modified.
	new gamnit_euler_rotation(pitch, yaw, roll: Float)
	do
		if pitch == 0.0 and yaw == 0.0 and roll == 0.0 then
			return once new Matrix.identity(4)
		end

		if rotation_pitch == pitch and rotation_yaw == yaw and rotation_roll == roll then
			var rot = rotation_matrix_cache
			if rot != null then return rot
		end

		var c1 = pitch.cos
		var s1 = pitch.sin
		var c2 = yaw.cos
		var s2 = yaw.sin
		var c3 = roll.cos
		var s3 = roll.sin

		var rot = new Matrix(4, 4)
		rot.items.mat4_set(
			          c2*c3,          -c2*s3,   -s2, 0.0,
			 c1*s3+c3*s1*s2,  c1*c3-s1*s2*s3, c2*s1, 0.0,
			-s1*s3+c1*c3*s2, -c3*s1-c1*s2*s3, c1*c2, 0.0,
			            0.0,             0.0,   0.0, 1.0)

		rotation_matrix_cache = rot
		rotation_pitch = pitch
		rotation_yaw = yaw
		rotation_roll = roll
		return rot
	end
end
lib/matrix/projection.nit:20,1--195,3

gamnit :: programs $ Matrix
redef class Matrix
	# Copy content of this matrix to a `NativeGLfloatArray`
	fun fill_native(native: NativeGLfloatArray)
	do
		for i in [0..width[ do
			for j in [0..height[ do
				native.matrix_set(i, j, self[i, j])
			end
		end
	end
end
lib/gamnit/programs.nit:585,1--595,3