SML3d
3d graphics for Standard ML

The SML3d Basic Types

The SML3d library defines a large collection of basic types that are used to represent the information passed to the GL. These include types to represent 2D, 3D, and 4D vectors, small matrix types, and colors (scalar types are defined in the Raw Data library. The type definitions are collected into the module SML3dTypes; in addtion, there are utility modules that support standard operations on the various types.

SML3d vector types

The SML3d library provides support for standard OpenGL vector types.

Floating-point vector types

SML3d supports 2D, 3D, and 4D vectors in both single and double-precision floating point formats.

Common vector operations

signature VEC_BASE =
  sig

  (* underlying scalar type of elements *)
    structure Scalar : SCALAR

    type scalar = Scalar.t
    type vec

  (* the number of elements in a vector (2, 3, or 4) *)
    val arity : int

  (* get i'th element (zero-based); raise Size if index is out of range *)
    val nth : vec * int -> scalar

  (* set i'th element (zero-based); raise Size if index is out of range *)
    val setNth : vec * int * scalar -> vec

  (* printable representation *)
    val toString : vec -> string

  (* zero vector *)
    val zero : vec

  (* vector arithmetic *)
    val negate : vec -> vec
    val add : (vec * vec) -> vec
    val sub : (vec * vec) -> vec
    val mul : (vec * vec) -> vec

    val scale : (scalar * vec) -> vec

  (* adds (u, s, v) = u + s*v *)
    val adds : (vec * scalar * vec) -> vec

  (* per-element operations *)
    val abs : vec -> vec
    val min : vec * vec -> vec
    val max : vec * vec -> vec

  (* lerp (u, t, v) = (1-t)*u + t*v; we assume that 0 <= t <= 1 *)
    val lerp : (vec * scalar * vec) -> vec

    val dot : (vec * vec) -> scalar
    val normalize : vec -> vec
    val length : vec -> scalar
    val lengthSq : vec -> scalar
    val lengthAndDir : vec -> (scalar * vec)
    val distance : (vec * vec) -> scalar
    val distanceSq : (vec * vec) -> scalar
    val clipLength : (vec * scalar) -> vec
    val clamp : vec -> vec

  (* return the parallel and perpendicular components of a vector v
   * relative to a unit basis vector.
   *)
    val parallelComponent : {basis : vec, v : vec} -> vec
    val perpendicularComponent : {basis : vec, v : vec} -> vec

  end
Substructures

Each vector module contains one substructure, which a reference to the underlying scalar element type.

  • structure Scalar : SCALAR

Types
  • scalar

    The type of scalar elements in a vector.

  • vec

    The vector type supported by the module.

Values
  • arity

    specifies the number of elements in this vector type (will be 2, 3, or 4).

  • nth (v, i)

    returns the i th element of the vector v. It will raise the Size exception if i < 0 or arity <= i.

Note
the nth function uses zero-based indexing in keeping with other SML sequence types, but we use one-based indexing other parts of the vector API.
  • setNth (v, i, x)

    returns a vector that is the same as v except that its i th component has been replaced by x. It will raise the Size exception if i < 0 or arity <= i.

Note
the setNth function uses zero-based indexing in keeping with other SML sequence types, but we use one-based indexing other parts of the vector API.
  • toString v

    returns a string representation of the vector v.

  • zero

    the length-zero vector.

  • negate v

    returns the negation of the vector v.

  • add (u, v)

    returns the vector-sum of vectors u and v (i.e., u + v).

  • sub (u, v)

    returns the vector-difference of vectors u and v (i.e., u - v).

  • mul (u, v)

    returns the element-wise product of vectors u and v.

  • scale (s, v)

    returns the vector-difference of vectors u and v (i.e., u - v).

  • adds (u, s, v)

    is equivalent to sum(u, scale(s, v)).

  • abs v

    returns a vector where is component is the absolute value of the corresponding component in v.

  • min (u, v)

    returns a vector where is component is the minimum value of the corresponding components of u and v.

  • max (u, v)

    returns a vector where is component is the maximum value of the corresponding components of u and v.

  • lerp (u, t, v)

    returns the linear interpolation of the vectors u and v for 0 <= t <= 1. It is equivalent to adds(u, t, sub(v, u)).

  • dot (u, v)

    returns the dot (or inner) product of the vectors u and v.

  • normalize v

    returns a unit length vector that has the same direction as v. If v is close to zero length, then zero is returned.

  • length v

    returns the length of v.

  • lengthSq v

    returns the square of the length of v (i.e., dot(v, v)).

  • lengthAndDir v

    returns the pair (l, n), where l is the length of v and n is the unit vector in the direction of v. If v is close to zero length, then (0.0, zero) is returned.

  • distance (p, q)

    returns the distance between two points. It is equivalent to length(sub(p, q)).

  • distanceSq (p, q)

    returns the square of the distance between two points. It is equivalent to lengthSq(sub(p, q)).

  • clipLength (l, v)

    returns a vector with length no greater than l that points in the same direction as v.

  • clamp v

    clamps the components of v to be in the range 0..1.

  • parallelComponent {basis, v}

    returns the component of v that is parallel to the unit vector basis. If basis does not have unit length, then the result is scaled by the length of basis.

  • perpendicularComponent {basis, v}

    returns the component of v that is perpendicular to the unit vector basis. If basis does not have unit length, then the result is scaled by the length of basis.

2D vectors

The VEC2 signature extends the VEC_BASE signature with additional operations that are specific to 2D vectors, which are represented by pairs of scalars.

signature VEC2 =
  sig

    include VEC_BASE

  (* create a 2D vector *)
    val vec : {x : scalar, y : scalar} -> vec

  (* standard basis vectors *)
    val e1 : vec
    val e2 : vec

  (* get vector components by name *)
    val getX : vec -> scalar
    val getY : vec -> scalar

  (* functional update *)
    val setX : vec * scalar -> vec
    val setY : vec * scalar -> vec

  (* conversions from other vector types *)
    val fromVec3 : scalar SML3dTypes.vec3 -> vec	(* drop z component *)
    val fromVec4 : scalar SML3dTypes.vec4 -> vec	(* drop z and w components *)

  (* lift a 2D vector into 3D homogeneous space *)
    val vector : vec -> scalar SML3dTypes.vec3
    val point : vec -> scalar SML3dTypes.vec3

  (* spherical interpolation between unit vectors *)
    val slerp : (vec * scalar * vec) -> vec

  (* iterators *)
    val app  : (scalar -> unit) -> vec -> unit
    val map  : (scalar -> 'a) -> vec -> ('a * 'a)
    val map2 : (scalar * scalar -> 'a) -> (vec * vec) -> ('a * 'a)

  end
Values
  • vec {x, y}

    returns a vector with the given components.

  • e1

    the canonical basis vector in the positive X direction (i.e., (1, 0)).

  • e2

    the canonical basis vector in the positive Y direction (i.e., (0, 1)).

  • getX v

    returns the first component of the vector v. It is equivalent to #1(v).

  • getY v

    returns the second component of the vector v. It is equivalent to #2(v).

  • setX (v, x)

    returns a vector that is the same as v except that its first component has been replaced by x. It is equivalent to setNth(v, 0, x).

  • setY (v, y)

    returns a vector that is the same as v except that its second component has been replaced by y. It is equivalent to setNth(v, 1, y).

  • fromVec3 v

    converts a 3D vector to 2D by dropping the third (Z) component.

  • fromVec4 v

    converts a 3D vector to 2D by dropping the third (Z) and fourth (W) components.

  • vector v

    converts a 2D vector to its homogenous representation as a 3D vector (i.e., by adding 0 as its third component).

  • point v

    converts a 2D point to its homogenous representation as a 3D vector (i.e., by adding 1 as its third component).

  • slerp (u, t, v)

    returns the spherical-linear interpolation between unit vectors u and v for 0 <= t <= 1.

  • app f v

    applies the function f to the elements of v in left-to-right order.

  • map f v

    maps the function f over the elements of v in left-to-right order, returning a pair of results.

  • map2 f (u, v)

    maps the function f over the paired elements of u and v in left-to-right order, returning a pair of results.

Instances

The SML3d Library provides two implementations of the VEC2 signature; one for IEEE single-precision numbers and one for IEEE double-precision numbers:

structure Vec2f : VEC2 where type scalar = Float.t
structure Vec2d : VEC2 where type scalar = Double.t

3D vectors

The VEC3 signature extends the VEC_BASE signature with additional operations that are specific to 3D vectors, which are represented as triples of scalars.

signature VEC3 =
  sig

    include VEC_BASE

  (* create a 3D vector *)
    val vec : {x : scalar, y : scalar, z : scalar} -> vec

  (* standard basis vectors *)
    val e1 : vec
    val e2 : vec
    val e3 : vec

  (* get vector components by name *)
    val getX : vec -> scalar
    val getY : vec -> scalar
    val getZ : vec -> scalar

  (* functional update *)
    val setX : vec * scalar -> vec
    val setY : vec * scalar -> vec
    val setZ : vec * scalar -> vec

  (* conversions from other vector types *)
    val fromVec2 : scalar SML3dTypes.vec2 -> vec	(* zero-extend *)
    val fromVec4 : scalar SML3dTypes.vec4 -> vec	(* drop w component *)

  (* lift a 3D vector into 4D homogeneous space *)
    val vector : vec -> scalar SML3dTypes.vec4
    val point : vec -> scalar SML3dTypes.vec4

  (* cross product *)
    val cross : vec * vec -> vec

  (* spherical interpolation between unit vectors *)
    val slerp : (vec * scalar * vec) -> vec

  (* iterators *)
    val app  : (scalar -> unit) -> vec -> unit
    val map  : (scalar -> 'a) -> vec -> ('a * 'a * 'a)
    val map2 : (scalar * scalar -> 'a) -> (vec * vec) -> ('a * 'a * 'a)

  end
Values
  • vec {x, y, z}

    returns a vector with the given components.

  • e1

    the canonical basis vector in the positive X direction (i.e., (1, 0, 0)).

  • e2

    the canonical basis vector in the positive Y direction (i.e., (0, 1, 0)).

  • e3

    the canonical basis vector in the positive Z direction (i.e., (0, 0, 1)).

  • getX v

    returns the first component of the vector v. It is equivalent to #1(v).

  • getY v

    returns the second component of the vector v. It is equivalent to #2(v).

  • getZ v

    returns the third component of the vector v. It is equivalent to #3(v).

  • setX (v, x)

    returns a vector that is the same as v except that its first component has been replaced by x. It is equivalent to setNth(v, 0, x).

  • setY (v, y)

    returns a vector that is the same as v except that its second component has been replaced by y. It is equivalent to setNth(v, 1, y).

  • setZ (v, z)

    returns a vector that is the same as v except that its third component has been replaced by z. It is equivalent to setNth(v, 2, z).

  • fromVec2 v

    converts a 2D vector to 3D by adding 0 as the third (Z) component.

  • fromVec4 v

    converts a 4D vector to 3D by dropping the third (Z) component.

  • vector v

    converts a 3D vector to its homogenous representation as a 4D vector (i.e., by adding 0 as its fourth component).

  • point v

    converts a 3D point to its homogenous representation as a 4D vector (i.e., by adding 1 as its fourth component).

  • cross (u, v)

    returns the cross product of the vectors u and v.

  • slerp (u, t, v)

    returns the spherical-linear interpolation between unit vectors u and v for 0 <= t <= 1.

  • app f v

    applies the function f to the elements of v in left-to-right order.

  • map f v

    maps the function f over the elements of v in left-to-right order, returning a pair of results.

  • map2 f (u, v)

    maps the function f over the paired elements of u and v in left-to-right order, returning a pair of results.

Instances

The SML3d Library provides two implementations of the VEC3 signature; one for IEEE single-precision numbers and one for IEEE double-precision numbers:

structure Vec3f : VEC3 where type scalar = Float.t
structure Vec3d : VEC3 where type scalar = Double.t

4D vectors

signature VEC4 =
  sig

    include VEC_BASE

  (* create a 4D vector *)
    val vec : {x : scalar, y : scalar, z : scalar, w : scalar} -> vec

  (* standard basis vectors *)
    val e1 : vec
    val e2 : vec
    val e3 : vec
    val e4 : vec

  (* get vector components by name *)
    val getX : vec -> scalar
    val getY : vec -> scalar
    val getZ : vec -> scalar
    val getW : vec -> scalar

  (* functional update *)
    val setX : vec * scalar -> vec
    val setY : vec * scalar -> vec
    val setZ : vec * scalar -> vec
    val setW : vec * scalar -> vec

  (* conversions from other vector types *)
    val fromVec2 : scalar SML3dTypes.vec2 -> vec	(* zero-extend *)
    val fromVec3 : scalar SML3dTypes.vec3 -> vec	(* zero-extend *)

  (* iterators *)
    val app  : (scalar -> unit) -> vec -> unit
    val map  : (scalar -> 'a) -> vec -> ('a * 'a * 'a * 'a)
    val map2 : (scalar * scalar -> 'a) -> (vec * vec) -> ('a * 'a * 'a * 'a)

  end
Values
  • vec {x, y, z, w}

    returns a vector with the given components.

  • e1

    the canonical basis vector in the positive X direction (i.e., (1, 0, 0, 0)).

  • e2

    the canonical basis vector in the positive Y direction (i.e., (0, 1, 0, 0)).

  • e3

    the canonical basis vector in the positive Z direction (i.e., (0, 0, 1, 0)).

  • e3

    the canonical basis vector in the positive W direction (i.e., (0, 0, 0, 1)).

  • getX v

    returns the first component of the vector v. It is equivalent to #1(v).

  • getY v

    returns the second component of the vector v. It is equivalent to #2(v).

  • getZ v

    returns the third component of the vector v. It is equivalent to #3(v).

  • getW v

    returns the fourth component of the vector v. It is equivalent to #4(v).

  • setX (v, x)

    returns a vector that is the same as v except that its first component has been replaced by x. It is equivalent to setNth(v, 0, x).

  • setY (v, y)

    returns a vector that is the same as v except that its second component has been replaced by y. It is equivalent to setNth(v, 1, y).

  • setZ (v, z)

    returns a vector that is the same as v except that its third component has been replaced by z. It is equivalent to setNth(v, 2, z).

  • setW (v, w)

    returns a vector that is the same as v except that its third component has been replaced by w. It is equivalent to setNth(v, 3, w).

  • fromVec2 v

    converts a 2D vector to 4D by adding 0 as the third (Z) and fourth components.

  • fromVec3 v

    converts a 3D vector to 4D by adding 0 the fourth (Z) component.

  • app f v

    applies the function f to the elements of v in left-to-right order.

  • map f v

    maps the function f over the elements of v in left-to-right order, returning a pair of results.

  • map2 f (u, v)

    maps the function f over the paired elements of u and v in left-to-right order, returning a pair of results.

Instances

The SML3d Library provides two implementations of the VEC4 signature; one for IEEE single-precision numbers and one for IEEE double-precision numbers:

structure Vec4f : VEC4 where type scalar = Float.t
structure Vec4d : VEC4 where type scalar = Double.t

Integer-vector types

OpenGL also allows data to be specified as vectors of 8-bit, 16-bit, and 32-bit signed and unsigned numbers. The SML3d library provides type definitions for these as well, but does not provide any linear-algebra operations for these types.

SML3d matrix types

The SML3d library currently provides support for the OpenGL square matrix types (2x2, 3x3, and 4x4 matricies).

Note
eventually SML3d will also support the non-square matrix types, such as 3x4.

Common matrix operations

Matrix operations that are common across all of the matrix modules are captured by the MATRIX_BASE signature:

signature MATRIX_BASE =
  sig

    structure Scalar : SCALAR

    type scalar	= Scalar.t
    type vec
    type mat

    val dim : (int * int)

    val outer : vec * vec -> mat

    val fromVector  : scalar Vector.vector -> mat
    val fromVectorT : scalar Vector.vector -> mat

    val toVector  : mat -> scalar Vector.vector
    val toVectorT : mat -> scalar Vector.vector

    val identity : mat

    val negate : mat -> mat
    val add : mat * mat -> mat
    val sub : mat * mat -> mat

    val sxm : scalar * mat -> mat
    val mxv : mat * vec -> vec
    val vxm : vec * mat -> vec
    val mxm : mat * mat -> mat

    val transpose : mat -> mat

    val det : mat -> scalar

    val trace : mat -> scalar

    val inverse : mat -> mat option

    val app           : (scalar -> unit) -> mat -> unit
    val map           : (scalar -> scalar) -> mat -> mat
    val mapToVector   : (scalar -> 'a) -> mat -> 'a Vector.vector
    val mapFromVector : ('a -> scalar) -> 'a Vector.vector -> mat

  end

Substructures

Each matrix module contains a Scalar substructure that provides a reference to the scalar types

  • structure Scalar : SCALAR

Types

  • scalar

    The type of scalar elements in a vector.

  • vec

    The vector type supported by the module.

Values

  • dim

    a pair of the number of rows and columns in the matrix.

  • outer (u, v)

    constructs a matrix from the outer produce of vectors u and v.

  • fromVector

    returns an SML vector of the matrix elements in row-major order (OpenGL’s default representation).

  • fromVectorT

    returns an SML vector of the matrix elements in column-major order.

  • toVector

    creates a matrix from an SML vector of the elements in row-major order.

  • toVectorT

    creates a matrix from an SML vector of the elements in column-major order.

  • identityMat

    the identity matrix.

  • negate mat

    element-wise negation of the matrix mat.

  • add (mat1, mat2)

    element-wise addition of the matrices m1 and m2.

  • sub (mat1, mat2)

    element-wise subtraction of the matrices m1 and m2.

  • sxm (s, mat)

    returns the result of multiplying the components of mat by the scalar s.

  • mxv (mat, v)

    returns the result of multiplying the matrix mat times the column-vector v.

  • vxm (v, mat)

    returns the result of multiplying the row-vector v times matrix mat.

  • mxm (mat1, mat2)

    returns the product of multiplying the matrix mat1 times the matrix mat2.

  • transpose mat

    returns the transpose of the matrix mat.

  • det mat

    returns the determinant of the matrix mat.

  • trace mat

    returns the trace of the matrix mat.

  • inverse mat

    returns SOME matInv, where matInv is the inverse of mat; if the mat is not invertable, it returns NONE.

  • app f mat

    applies the function f to the elements of the matrix mat in row-major order.

  • map f mat

    maps the function f over the elements of the matrix mat, producing an SML vector of results in row-major order.

2x2 matrices

signature MATRIX2 =
  sig

    structure Vec : VEC2

    include MATRIX_BASE where type vec = Vec.vec

    val mat : {
	    m11 : scalar, m12 : scalar,
	    m21 : scalar, m22 : scalar
	  } -> mat

  (* create a matrix from two column vectors *)
    val fromCols : (vec * vec) -> mat
  (* create a matrix from two row vectors *)
    val fromRows : (vec * vec) -> mat

  (* return the columns of the matrix *)
    val toCols : mat -> (vec * vec)
  (* return the rows of the matrix *)
    val toRows : mat -> (vec * vec)

  (* project specific columns/rows *)
    val col1 : mat -> vec
    val col2 : mat -> vec
    val row1 : mat -> vec
    val row2 : mat -> vec

  (* standard 2D transformation matrices *)
    val isoscaleMat : scalar -> mat
    val scaleMat    : vec -> mat
    val rotateMat   : scalar -> mat	(* CCW rotation around origin (in degrees) *)
    val reflectXMat : mat		(* X-axis reflection *)
    val reflectYMat : mat		(* Y-axis reflection *)
    val reflectMat  : vec -> mat	(* reflection across the given axis *)
    val perpMat     : mat		(* maps vectors to CCW perp *)

  end

Values

  • isoscaleMat s

    returns the isotropic-scaling transformation matrix.

  • scaleMat v

    returns the anisotropic-scaling transformation matrix.

3x3 matrices

signature MATRIX3 =
  sig

    structure Vec : VEC3

    include MATRIX_BASE
      where type scalar = Vec.scalar
      where type vec = Vec.vec

    val mat : {
	    m11 : scalar, m12 : scalar, m13 : scalar,
	    m21 : scalar, m22 : scalar, m23 : scalar,
	    m31 : scalar, m32 : scalar, m33 : scalar
	  } -> mat

  (* create a matrix from three column vectors *)
    val fromCols : (vec * vec * vec) -> mat
  (* create a matrix from three row vectors *)
    val fromRows : (vec * vec * vec) -> mat

  (* return the columns of the matrix *)
    val toCols : mat -> (vec * vec * vec)
  (* return the rows of the matrix *)
    val toRows : mat -> (vec * vec * vec)

  (* project specific columns/rows *)
    val col1 : mat -> vec
    val col2 : mat -> vec
    val col3 : mat -> vec
    val row1 : mat -> vec
    val row2 : mat -> vec
    val row3 : mat -> vec

  (* standard 3D transformation matrices *)
    val isoscaleMat : scalar -> mat
    val scaleMat    : vec -> mat
    val rotateXMat  : scalar -> mat		(* rotation around X axis (in degrees) *)
    val rotateYMat  : scalar -> mat		(* rotation around Y axis (in degrees) *)
    val rotateZMat  : scalar -> mat		(* rotation around Z axis (in degrees) *)
    val rotateMat   : scalar * vec -> mat	(* rotation around an axis (in degrees) *)

  (* matrix transformations; these correspond to post-multiplication by the transform matrix *)
    val isoscale : mat * scalar -> mat
    val scale    : mat * vec -> mat
    val rotateX  : mat * scalar -> mat
    val rotateY  : mat * scalar -> mat
    val rotateZ  : mat * scalar -> mat
    val rotate   : mat * scalar * scalar SML3dTypes.vec3 -> mat

  (* the inverse transpose matrix, which is used to tranform normals and planes *)
    val normal : mat -> mat option

  end

Values

  • isoscaleMat s

    returns the isotropic-scaling transformation matrix.

  • scaleMat v

    returns the anisotropic-scaling transformation matrix.

  • isoscale (mat, s)

    transforms the matrix by multiplying it times the isotropic scaling matrix isoscaleMat s. This expression evaluates to the same matrix as sxm(s, mat).

  • scale (mat, v)+

    transforms the matrix by multiplying it times the anisotropic scaling matrix scaleMat v.

4x4 matrices

signature MATRIX4 =
  sig

    structure Vec : VEC4

    include MATRIX_BASE
      where type scalar = Vec.scalar
      where type vec = Vec.vec

    type vec3 = scalar SML3dTypes.vec3
    type mat3

    val mat : {
	    m11 : scalar, m12 : scalar, m13 : scalar, m14 : scalar,
	    m21 : scalar, m22 : scalar, m23 : scalar, m24 : scalar,
	    m31 : scalar, m32 : scalar, m33 : scalar, m34 : scalar,
	    m41 : scalar, m42 : scalar, m43 : scalar, m44 : scalar
	  } -> mat

  (* create a matrix from three column vectors *)
    val fromCols : (vec * vec * vec * vec) -> mat
  (* create a matrix from three row vectors *)
    val fromRows : (vec * vec * vec * vec) -> mat

  (* return the columns of the matrix *)
    val toCols : mat -> (vec * vec * vec * vec)
  (* return the rows of the matrix *)
    val toRows : mat -> (vec * vec * vec * vec)

  (* project specific columns/rows *)
    val col1 : mat -> vec
    val col2 : mat -> vec
    val col3 : mat -> vec
    val col4 : mat -> vec
    val row1 : mat -> vec
    val row2 : mat -> vec
    val row3 : mat -> vec
    val row4 : mat -> vec

  (* standard homogeneous-coordinate transformation matrices *)
    val isoscaleMat  : scalar -> mat
    val scaleMat     : vec3 -> mat
    val rotateXMat   : scalar -> mat			(* rotation around X axis (in degrees) *)
    val rotateYMat   : scalar -> mat			(* rotation around Y axis (in degrees) *)
    val rotateZMat   : scalar -> mat			(* rotation around Z axis (in degrees) *)
    val rotateMat    : scalar * scalar SML3dTypes.vec3 -> mat	(* rotation around an axis (in degrees) *)
    val translateMat : scalar SML3dTypes.vec3 -> mat	(* translation matrix *)

  (* transform matrices; these correspond to post-multiplication by the transform matrix *)
    val isoscale  : mat * scalar -> mat
    val scale     : mat * vec3 -> mat
    val rotateX   : mat * scalar -> mat
    val rotateY   : mat * scalar -> mat
    val rotateZ   : mat * scalar -> mat
    val rotate    : mat * scalar * scalar SML3dTypes.vec3 -> mat
    val translate : mat * scalar SML3dTypes.vec3 -> mat

  (* view-matrix *)
    val lookAtMat : {eye : vec3, center : vec3, up : vec3} -> mat

  (* orthographic projection matrices *)
    val orthoMat : {left : scalar, right : scalar, top : scalar, bottom : scalar, near : scalar, far : scalar} -> mat
    val ortho2DMat : {left : scalar, right : scalar, top : scalar, bottom : scalar} -> mat

  (* perspective projection matrices *)
    val frustumMat : {left : scalar, right : scalar, top : scalar, bottom : scalar, near : scalar, far : scalar} -> mat
    val perspectiveMat : {fov : scalar, aspect : scalar, near : scalar, far : scalar} -> mat

  (* homogeneous transforms *)
    val mxpt : mat * scalar SML3dTypes.vec3 -> scalar SML3dTypes.vec3		(* matrix times point (i.e., w = 0) *)
    val mxvec : mat * scalar SML3dTypes.vec3 -> scalar SML3dTypes.vec3	(* matrix times vector (i.e., w = 1) *)

  (* the inverse transpose matrix, which is used to tranform normals and planes *)
    val normal : mat -> mat3 option

  end

some stuff

Values

  • isoscaleMat s

    returns the isotropic-scaling transformation matrix.

  • scaleMat v

    returns the anisotropic-scaling transformation matrix.

  • isoscale (mat, s)

    transforms the matrix by multiplying it times the isotropic scaling matrix isoscaleMat s. This expression evaluates to the same matrix as sxm(s, mat).

  • scale (mat, v)+

    transforms the matrix by multiplying it times the anisotropic scaling matrix scaleMat v.

SML3d drawing commands

signature GL32_DRAW =
  sig

  (* controlling the provoking vertex (Section 2.18) *)
    eqtype provoke_mode
    val FIRST_VERTEX_CONVENTION : provoke_mode
    val LAST_VERTEX_CONVENTION : provoke_mode
    val provokingVertex : provoke_mode -> unit
    val getProvokingVertex : unit -> provoke_mode

  (* primitive restart control (Section 2.8.1) *)
    val enableRestart : bool -> unit
    val restartIndex : Word32.word -> unit

  (* drawing modes *)
    type prim = PrimitiveType.t
(*
    eqtype prim
    val POINTS : prim
    val LINES : prim
    val LINE_LOOP : prim
    val LINE_STRIP : prim
    val TRIANGLES : prim
    val TRIANGLE_STRIP : prim
    val TRIANGLE_FAN : prim
    val LINES_ADJACENCY : prim
    val LINE_STRIP_ADJACENCY : prim
    val TRIANGLES_ADJACENCY : prim
    val TRIANGLE_STRIP_ADJACENCY : prim
*)

  (* render primitives from the currently enabled arrays [glDrawArrays] *)
    val arrays : prim * {first : int, count : int} -> unit

  (* render multiple sets of primitives from the currently enabled arrays *)
    val multiArrays : prim * {first : int, count : int} list -> unit

  (* render multiple instances of primitives from the currently enabled arrays *)
    val arraysInstanced : prim * {first : int, count : int} * int -> unit

  (* render primitives using the given indices and the currently enabled arrays;
   * the indices can be specified as vectors, arrays, or data buffers of
   * 8, 16, or 32-bit words.  There are also versions that use the whole sequence
   * and versions that specify a count of the elements.  If the count is greater
   * than the number of elements, then the Size exception is raised.
   *)
    val elementsVecb  : prim * Word8.word vector -> unit
    val elementsArrb  : prim * Word8.word array -> unit
    val elementsBufb  : prim * Word8.word DataBuffer.buffer -> unit
    val elementsVecb' : prim * int * Word8.word vector -> unit
    val elementsArrb' : prim * int * Word8.word array -> unit
    val elementsBufb' : prim * int * Word8.word DataBuffer.buffer -> unit
    val elementsVecs  : prim * Word16.word vector -> unit
    val elementsArrs  : prim * Word16.word array -> unit
    val elementsBufs  : prim * Word16.word DataBuffer.buffer -> unit
    val elementsVecs' : prim * int * Word16.word vector -> unit
    val elementsArrs' : prim * int * Word16.word array -> unit
    val elementsBufs' : prim * int * Word16.word DataBuffer.buffer -> unit
    val elementsVeci  : prim * Word32.word vector -> unit
    val elementsArri  : prim * Word32.word array -> unit
    val elementsBufi  : prim * Word32.word DataBuffer.buffer -> unit
    val elementsVeci' : prim * int * Word32.word vector -> unit
    val elementsArri' : prim * int * Word32.word array -> unit
    val elementsBufi' : prim * int * Word32.word DataBuffer.buffer -> unit

  (* render primitives using the given indices, offset, and the currently enabled arrays *)
    val elementsBaseVertexVecub : {mode : prim, count : int, buf : Word8.word vector, base : int} -> unit
    val elementsBaseVertexArrub : {mode : prim, count : int, buf : Word8.word array, base : int} -> unit
    val elementsBaseVertexBufub : {mode : prim, count : int, buf : Word8.word DataBuffer.buffer, base : int} -> unit
    val elementsBaseVertexVecus : {mode : prim, count : int, buf : Word16.word vector, base : int} -> unit
    val elementsBaseVertexArrus : {mode : prim, count : int, buf : Word16.word array, base : int} -> unit
    val elementsBaseVertexBufus : {mode : prim, count : int, buf : Word16.word DataBuffer.buffer, base : int} -> unit
    val elementsBaseVertexVecui : {mode : prim, count : int, buf : Word32.word vector, base : int} -> unit
    val elementsBaseVertexArrui : {mode : prim, count : int, buf : Word32.word array, base : int} -> unit
    val elementsBaseVertexBufui : {mode : prim, count : int, buf : Word32.word DataBuffer.buffer, base : int} -> unit

  (* render primitives using the given indices and the currently enabled arrays.  These
   * functions are similar to the elements* function above, except that the minimum and
   * maximum index values are specified.
   *)
    val rangeElementsVecub : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word8.word vector} -> unit
    val rangeElementsArrub : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word8.word array} -> unit
    val rangeElementsBufub : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word8.word DataBuffer.buffer} -> unit
    val rangeElementsVecus : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word16.word vector} -> unit
    val rangeElementsArrus : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word16.word array} -> unit
    val rangeElementsBufus : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word16.word DataBuffer.buffer} -> unit
    val rangeElementsVecui : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word32.word vector} -> unit
    val rangeElementsArrui : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word32.word array} -> unit
    val rangeElementsBufui : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word32.word DataBuffer.buffer} -> unit

  (* render primitives using the given indices and the currently enabled arrays.  These
   * functions are similar to the elementsBaseVertex* functions above, except that the
   * minimum and maximum index values are specified.
   *)
    val rangeElementsBaseVertexVecub : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word8.word vector, base : int} -> unit
    val rangeElementsBaseVertexArrub : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word8.word array, base : int} -> unit
    val rangeElementsBaseVertexBufub : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word8.word DataBuffer.buffer, base : int} -> unit
    val rangeElementsBaseVertexVecus : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word16.word vector, base : int} -> unit
    val rangeElementsBaseVertexArrus : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word16.word array, base : int} -> unit
    val rangeElementsBaseVertexBufus : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word16.word DataBuffer.buffer, base : int} -> unit
    val rangeElementsBaseVertexVecui : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word32.word vector, base : int} -> unit
    val rangeElementsBaseVertexArrui : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word32.word array, base : int} -> unit
    val rangeElementsBaseVertexBufui : {mode : prim, min : GLuint.word, max : GLuint.word, count : int, buf : Word32.word DataBuffer.buffer, base : int} -> unit

  (* render multiple instances of primitives using the given indices and the currently
   * enabled arrays
   *)
    val elementsInstancedVecub : {mode : prim, count : int, buf : Word8.word vector, primCount : int} -> unit
    val elementsInstancedArrub : {mode : prim, count : int, buf : Word8.word array, primCount : int} -> unit
    val elementsInstancedBufub : {mode : prim, count : int, buf : Word8.word DataBuffer.buffer, primCount : int} -> unit
    val elementsInstancedVecus : {mode : prim, count : int, buf : Word16.word vector, primCount : int} -> unit
    val elementsInstancedArrus : {mode : prim, count : int, buf : Word16.word array, primCount : int} -> unit
    val elementsInstancedBufus : {mode : prim, count : int, buf : Word16.word DataBuffer.buffer, primCount : int} -> unit
    val elementsInstancedVecui : {mode : prim, count : int, buf : Word32.word vector, primCount : int} -> unit
    val elementsInstancedArrui : {mode : prim, count : int, buf : Word32.word array, primCount : int} -> unit
    val elementsInstancedBufui : {mode : prim, count : int, buf : Word32.word DataBuffer.buffer, primCount : int} -> unit

  (* render multiple instances of primitives using the given indices, offset, and the currently
   * enabled arrays
   *)
    val elementsInstancedBaseVertexVecub : {mode : prim, count : int, buf : Word8.word vector, primCount : int, base : int} -> unit
    val elementsInstancedBaseVertexArrub : {mode : prim, count : int, buf : Word8.word array, primCount : int, base : int} -> unit
    val elementsInstancedBaseVertexBufub : {mode : prim, count : int, buf : Word8.word DataBuffer.buffer, primCount : int, base : int} -> unit
    val elementsInstancedBaseVertexVecus : {mode : prim, count : int, buf : Word16.word vector, primCount : int, base : int} -> unit
    val elementsInstancedBaseVertexArrus : {mode : prim, count : int, buf : Word16.word array, primCount : int, base : int} -> unit
    val elementsInstancedBaseVertexBufus : {mode : prim, count : int, buf : Word16.word DataBuffer.buffer, primCount : int, base : int} -> unit
    val elementsInstancedBaseVertexVecui : {mode : prim, count : int, buf : Word32.word vector, primCount : int, base : int} -> unit
    val elementsInstancedBaseVertexArrui : {mode : prim, count : int, buf : Word32.word array, primCount : int, base : int} -> unit
    val elementsInstancedBaseVertexBufui : {mode : prim, count : int, buf : Word32.word DataBuffer.buffer, primCount : int, base : int} -> unit

  end