package lacaml

  1. Overview
  2. Docs

Single precision real BLAS and LAPACK functions.

This module Lacaml.S contains linear algebra routines for real numbers (precision: float32). It is recommended to use this module by writing

open Lacaml.S

at the top of your file.

type prec = Stdlib.Bigarray.float32_elt
type num_type = float
type vec = (float, Stdlib.Bigarray.float32_elt, Stdlib.Bigarray.fortran_layout) Stdlib.Bigarray.Array1.t

Vectors (precision: float32).

type rvec = vec
type mat = (float, Stdlib.Bigarray.float32_elt, Stdlib.Bigarray.fortran_layout) Stdlib.Bigarray.Array2.t

Matrices (precision: float32).

type trans3 = [
  1. | `N
  2. | `T
]

Transpose parameter (normal or transposed). For complex matrices, conjugate transpose is also offered, hence the name.

val prec : (float, Stdlib.Bigarray.float32_elt) Stdlib.Bigarray.kind

Precision for this submodule S. Allows to write precision independent code.

module Vec : sig ... end
module Mat : sig ... end
val pp_num : Stdlib.Format.formatter -> float -> unit

pp_num ppf el is equivalent to fprintf ppf "%G" el.

val pp_vec : (float, 'a) Io.pp_vec

Pretty-printer for column vectors.

val pp_mat : (float, 'a) Io.pp_mat

Pretty-printer for matrices.

BLAS-1 interface
val dot : ?n:int -> ?ofsx:int -> ?incx:int -> vec -> ?ofsy:int -> ?incy:int -> vec -> float

dot ?n ?ofsx ?incx x ?ofsy ?incy y see BLAS documentation!

  • parameter n

    default = greater n s.t. ofsx+(n-1)(abs incx) <= dim x

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

  • parameter ofsy

    default = 1

  • parameter incy

    default = 1

val asum : ?n:int -> ?ofsx:int -> ?incx:int -> vec -> float

asum ?n ?ofsx ?incx x see BLAS documentation!

  • parameter n

    default = greater n s.t. ofsx+(n-1)(abs incx) <= dim x

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

BLAS-2 interface
val sbmv : ?n:int -> ?k:int -> ?ofsy:int -> ?incy:int -> ?y:vec -> ?ar:int -> ?ac:int -> mat -> ?up:bool -> ?alpha:float -> ?beta:float -> ?ofsx:int -> ?incx:int -> vec -> vec

sbmv ?n ?k ?ofsy ?incy ?y ?ar ?ac a ?up ?alpha ?beta ?ofsx ?incx x see BLAS documentation!

  • returns

    vector y, which is overwritten.

  • parameter n

    default = number of available columns to the right of ac.

  • parameter k

    default = number of available rows in matrix a - 1

  • parameter ofsy

    default = 1

  • parameter incy

    default = 1

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter y

    default = uninitialized vector of minimal length (see BLAS)

  • parameter up

    default = true i.e., upper band of a is supplied

  • parameter alpha

    default = 1.0

  • parameter beta

    default = 0.0

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

val ger : ?m:int -> ?n:int -> ?alpha:float -> ?ofsx:int -> ?incx:int -> vec -> ?ofsy:int -> ?incy:int -> vec -> ?ar:int -> ?ac:int -> mat -> unit

ger ?m ?n ?alpha ?ofsx ?incx x ?ofsy ?incy y n ?ar ?ac a see BLAS documentation!

  • parameter m

    default = number of rows of a

  • parameter n

    default = number of columns of a

  • parameter alpha

    default = 1.0

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

  • parameter ofsy

    default = 1

  • parameter incy

    default = 1

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val syr : ?n:int -> ?alpha:float -> ?up:bool -> ?ofsx:int -> ?incx:int -> vec -> ?ar:int -> ?ac:int -> mat -> unit

syr ?n ?alpha ?up ?ofsx ?incx x ?ar ?ac a see BLAS documentation!

  • parameter n

    default = number of rows of a

  • parameter alpha

    default = 1.0

  • parameter up

    default = true i.e., upper triangle of a is supplied

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

  • parameter ar

    default = 1

  • parameter ac

    default = 1

LAPACK interface
Auxiliary routines
val lansy_min_lwork : int -> Common.norm4 -> int

lansy_min_lwork m norm

  • returns

    the minimum length of the work array used by the lansy-function.

  • parameter norm

    type of norm that will be computed by lansy

  • parameter n

    the number of columns (and rows) in the matrix

val lansy : ?n:int -> ?up:bool -> ?norm:Common.norm4 -> ?work:vec -> ?ar:int -> ?ac:int -> mat -> float

lansy ?norm ?up ?n ?ar ?ac ?work a see LAPACK documentation!

  • parameter norm

    default = `O

  • parameter up

    default = true (reference upper triangular part of a)

  • parameter n

    default = number of columns of matrix a

  • parameter work

    default = allocated work space for norm `I

val lamch : [ `E | `S | `B | `P | `N | `R | `M | `U | `L | `O ] -> float

lamch cmach see LAPACK documentation!

Linear equations (computational routines)
val orgqr_min_lwork : n:int -> int

orgqr_min_lwork ~n

  • returns

    the minimum length of the work-array used by the orgqr-function if the matrix has n columns.

val orgqr_opt_lwork : ?m:int -> ?n:int -> ?k:int -> tau:vec -> ?ar:int -> ?ac:int -> mat -> int

orgqr_opt_lwork ?m ?n ?k ~tau ?ar ?ac a

  • returns

    the optimum length of the work-array used by the orgqr-function given matrix a, optionally its logical dimensions m and n, and the number of reflectors k.

  • parameter m

    default = available number of rows in matrix a

  • parameter n

    default = available number of columns in matrix a

  • parameter k

    default = available number of elements in vector tau

val orgqr : ?m:int -> ?n:int -> ?k:int -> ?work:vec -> tau:vec -> ?ar:int -> ?ac:int -> mat -> unit

orgqr ?m ?n ?k ?work ~tau ?ar ?ac a see LAPACK documentation!

  • parameter m

    default = available number of rows in matrix a

  • parameter n

    default = available number of columns in matrix a

  • parameter k

    default = available number of elements in vector tau

val ormqr_opt_lwork : ?side:Common.side -> ?trans:Common.trans2 -> ?m:int -> ?n:int -> ?k:int -> tau:vec -> ?ar:int -> ?ac:int -> mat -> ?cr:int -> ?cc:int -> mat -> int

ormqr_opt_lwork ?side ?trans ?m ?n ?k ~tau ?ar ?ac a ?cr ?cc c

  • returns

    the optimum length of the work-array used by the ormqr-function given matrix a and b, optionally its logical dimensions m and n, and the number of reflectors k.

  • parameter m

    default = available number of rows in matrix a

  • parameter n

    default = available number of columns in matrix a

  • parameter k

    default = available number of elements in vector tau

val ormqr : ?side:Common.side -> ?trans:Common.trans2 -> ?m:int -> ?n:int -> ?k:int -> ?work:vec -> tau:vec -> ?ar:int -> ?ac:int -> mat -> ?cr:int -> ?cc:int -> mat -> unit

ormqr ?side ?trans ?m ?n ?k ?work ~tau ?ar ?ac a ?cr ?cc c see LAPACK documentation!

  • parameter side

    default = `L

  • parameter trans

    default = `N

  • parameter m

    default = available number of rows in matrix a

  • parameter n

    default = available number of columns in matrix a

  • parameter k

    default = available number of elements in vector tau

val gecon_min_lwork : int -> int

gecon_min_lwork n

  • returns

    the minimum length of the work array used by the gecon-function.

  • parameter n

    the logical dimensions of the matrix given to the gecon-function

val gecon_min_liwork : int -> int

gecon_min_liwork n

  • returns

    the minimum length of the iwork array used by the gecon-function.

  • parameter n

    the logical dimensions of the matrix given to gecon-function

val gecon : ?n:int -> ?norm:Common.norm2 -> ?anorm:float -> ?work:vec -> ?iwork:Common.int32_vec -> ?ar:int -> ?ac:int -> mat -> float

gecon ?n ?norm ?anorm ?work ?rwork ?ar ?ac a

  • returns

    estimate of the reciprocal of the condition number of matrix a

  • parameter n

    default = available number of columns of matrix a

  • parameter norm

    default = 1-norm

  • parameter anorm

    default = norm of the matrix a as returned by lange

  • parameter work

    default = automatically allocated workspace

  • parameter iwork

    default = automatically allocated workspace

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val sycon_min_lwork : int -> int

sycon_min_lwork n

  • returns

    the minimum length of the work array used by the sycon-function.

  • parameter n

    the logical dimensions of the matrix given to the sycon-function

val sycon_min_liwork : int -> int

sycon_min_liwork n

  • returns

    the minimum length of the iwork array used by the sycon-function.

  • parameter n

    the logical dimensions of the matrix given to sycon-function

val sycon : ?n:int -> ?up:bool -> ?ipiv:Common.int32_vec -> ?anorm:float -> ?work:vec -> ?iwork:Common.int32_vec -> ?ar:int -> ?ac:int -> mat -> float

sycon ?n ?up ?ipiv ?anorm ?work ?iwork ?ar ?ac a

  • returns

    estimate of the reciprocal of the condition number of symmetric matrix a

  • parameter n

    default = available number of columns of matrix a

  • parameter up

    default = upper triangle of the factorization of a is stored

  • parameter ipiv

    default = vec of length n

  • parameter anorm

    default = 1-norm of the matrix a as returned by lange

  • parameter work

    default = automatically allocated workspace

  • parameter iwork

    default = automatically allocated workspace

val pocon_min_lwork : int -> int

pocon_min_lwork n

  • returns

    the minimum length of the work array used by the pocon-function.

  • parameter n

    the logical dimensions of the matrix given to the pocon-function

val pocon_min_liwork : int -> int

pocon_min_liwork n

  • returns

    the minimum length of the iwork array used by the pocon-function.

  • parameter n

    the logical dimensions of the matrix given to pocon-function

val pocon : ?n:int -> ?up:bool -> ?anorm:float -> ?work:vec -> ?iwork:Common.int32_vec -> ?ar:int -> ?ac:int -> mat -> float

pocon ?n ?up ?anorm ?work ?iwork ?ar ?ac a

  • returns

    estimate of the reciprocal of the condition number of symmetric positive definite matrix a

  • parameter n

    default = available number of columns of matrix a

  • parameter up

    default = upper triangle of Cholesky factorization of a is stored

  • parameter work

    default = automatically allocated workspace

  • parameter iwork

    default = automatically allocated workspace

  • parameter anorm

    default = 1-norm of the matrix a as returned by lange

Least squares (expert drivers)
val gelsy_min_lwork : m:int -> n:int -> nrhs:int -> int

gelsy_min_lwork ~m ~n ~nrhs

  • returns

    the minimum length of the work-array used by the gelsy-function if the logical dimensions of the matrix are m rows and n columns and if there are nrhs right hand side vectors.

val gelsy_opt_lwork : ?m:int -> ?n:int -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> int

gelsy_opt_lwork ?m ?n ?ar ?ac a ?nrhs ?br ?bc b

  • returns

    the optimum length of the work-array used by the gelsy-function given matrix a, optionally its logical dimensions m and n and given right hand side matrix b with an optional number nrhs of vectors.

  • parameter m

    default = available number of rows in matrix a

  • parameter n

    default = available number of columns in matrix a

  • parameter nrhs

    default = available number of columns in matrix b

val gelsy : ?m:int -> ?n:int -> ?ar:int -> ?ac:int -> mat -> ?rcond:float -> ?jpvt:Common.int32_vec -> ?work:vec -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> int

gelsy ?m ?n ?ar ?ac a ?rcond ?jpvt ?ofswork ?work ?nrhs b see LAPACK documentation!

  • returns

    the effective rank of a.

  • parameter m

    default = available number of rows in matrix a

  • parameter n

    default = available number of columns of matrix a

  • parameter rcond

    default = (-1) => machine precision

  • parameter jpvt

    default = vec of length n

  • parameter work

    default = vec of optimum length (-> gelsy_opt_lwork)

  • parameter nrhs

    default = available number of columns in matrix b

val gelsd_min_lwork : m:int -> n:int -> nrhs:int -> int

gelsd_min_lwork ~m ~n ~nrhs

  • returns

    the minimum length of the work-array used by the gelsd-function if the logical dimensions of the matrix are m and n and if there are nrhs right hand side vectors.

val gelsd_opt_lwork : ?m:int -> ?n:int -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> int

gelsd_opt_lwork ?m ?n ?ar ?ac a ?nrhs b

  • returns

    the optimum length of the work-array used by the gelsd-function given matrix a, optionally its logical dimensions m and n and given right hand side matrix b with an optional number nrhs of vectors.

  • parameter m

    default = available number of rows in matrix a

  • parameter n

    default = available number of columns in matrix a

  • parameter nrhs

    default = available number of columns in matrix b

val gelsd_min_iwork : int -> int -> int

gelsd_min_iwork m n

  • returns

    the minimum (= optimum) length of the iwork-array used by the gelsd-function if the logical dimensions of the matrix are m and n.

val gelsd : ?m:int -> ?n:int -> ?rcond:float -> ?ofss:int -> ?s:vec -> ?work:vec -> ?iwork:vec -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> int

gelsd ?m ?n ?rcond ?ofss ?s ?ofswork ?work ?ar ?ac a ?nrhs b see LAPACK documentation!

  • returns

    the effective rank of a.

  • raises Failure

    if the function fails to converge.

  • parameter m

    default = available number of rows in matrix a

  • parameter n

    default = available number of columns of matrix a

  • parameter rcond

    default = (-1) => machine precision

  • parameter ofss

    default = 1 or ignored if s is not given

  • parameter s

    default = vec of length min rows cols

  • parameter work

    default = vec of optimum length (-> gelsd_opt_lwork)

  • parameter iwork

    default = vec of optimum (= minimum) length

  • parameter nrhs

    default = available number of columns in matrix b

val gelss_min_lwork : m:int -> n:int -> nrhs:int -> int

gelss_min_lwork ~m ~n ~nrhs

  • returns

    the minimum length of the work-array used by the gelss-function if the logical dimensions of the matrix are m rows and n columns and if there are nrhs right hand side vectors.

val gelss_opt_lwork : ?ar:int -> ?ac:int -> mat -> ?m:int -> ?n:int -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> int

gelss_opt_lwork ?ar ?ac a ?m ?n ?nrhs ?br ?bc b

  • returns

    the optimum length of the work-array used by the gelss-function given matrix a, optionally its logical dimensions m and n and given right hand side matrix b with an optional number nrhs of vectors.

  • parameter m

    default = available number of rows in matrix a

  • parameter n

    default = available number of columns in matrix a

  • parameter nrhs

    default = available number of columns in matrix b

val gelss : ?m:int -> ?n:int -> ?rcond:float -> ?ofss:int -> ?s:vec -> ?work:vec -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> int

gelss ?m ?n ?rcond ?ofss ?s ?ofswork ?work ?ar ?ac a ?nrhs ?br ?bc b see LAPACK documentation!

  • returns

    the effective rank of a.

  • raises Failure

    if the function fails to converge.

  • parameter m

    default = available number of rows in matrix a

  • parameter n

    default = available number of columns of matrix a

  • parameter rcond

    default = (-1) => machine precision

  • parameter ofss

    default = 1 or ignored if s is not given

  • parameter s

    default = vec of length min m n

  • parameter work

    default = vec of optimum length (-> gelss_opt_lwork)

  • parameter nrhs

    default = available number of columns in matrix b

General Schur factorization
val gees : ?n:int -> ?jobvs:Common.schur_vectors -> ?sort:Common.eigen_value_sort -> ?wr:vec -> ?wi:vec -> ?vsr:int -> ?vsc:int -> ?vs:mat -> ?work:vec -> ?ar:int -> ?ac:int -> mat -> int * vec * vec * mat

gees ?n ?jobvs ?sort ?w ?vsr ?vsc ?vs ?work ?ar ?ac a See gees-function for details about arguments.

  • returns

    (sdim, wr, wi, vs)

General SVD routines
val gesvd_min_lwork : m:int -> n:int -> int

gesvd_min_lwork ~m ~n

  • returns

    the minimum length of the work array used by the gesvd-function for matrices with m rows and n columns.

val gesvd_opt_lwork : ?m:int -> ?n:int -> ?jobu:Common.svd_job -> ?jobvt:Common.svd_job -> ?s:vec -> ?ur:int -> ?uc:int -> ?u:mat -> ?vtr:int -> ?vtc:int -> ?vt:mat -> ?ar:int -> ?ac:int -> mat -> int
val gesvd : ?m:int -> ?n:int -> ?jobu:Common.svd_job -> ?jobvt:Common.svd_job -> ?s:vec -> ?ur:int -> ?uc:int -> ?u:mat -> ?vtr:int -> ?vtc:int -> ?vt:mat -> ?work:vec -> ?ar:int -> ?ac:int -> mat -> vec * mat * mat
val gesdd_liwork : m:int -> n:int -> int
val gesdd_min_lwork : ?jobz:Common.svd_job -> m:int -> n:int -> unit -> int

gesdd_min_lwork ?jobz ~m ~n

  • returns

    the minimum length of the work array used by the gesdd-function for matrices with m rows and n columns for SVD-job jobz.

val gesdd_opt_lwork : ?m:int -> ?n:int -> ?jobz:Common.svd_job -> ?s:vec -> ?ur:int -> ?uc:int -> ?u:mat -> ?vtr:int -> ?vtc:int -> ?vt:mat -> ?iwork:Common.int32_vec -> ?ar:int -> ?ac:int -> mat -> int
val gesdd : ?m:int -> ?n:int -> ?jobz:Common.svd_job -> ?s:vec -> ?ur:int -> ?uc:int -> ?u:mat -> ?vtr:int -> ?vtc:int -> ?vt:mat -> ?work:vec -> ?iwork:Common.int32_vec -> ?ar:int -> ?ac:int -> mat -> vec * mat * mat
General eigenvalue problem (simple drivers)
val geev_min_lwork : ?vectors:bool -> int -> int

geev_min_lwork vectors n

  • returns

    the minimum length of the work array used by the geev-function. vectors indicates whether eigenvectors are supposed to be computed.

  • parameter n

    the logical dimensions of the matrix given to geev-function

  • parameter vectors

    default = true

val geev_opt_lwork : ?n:int -> ?vlr:int -> ?vlc:int -> ?vl:mat option -> ?vrr:int -> ?vrc:int -> ?vr:mat option -> ?ofswr:int -> ?wr:vec -> ?ofswi:int -> ?wi:vec -> ?ar:int -> ?ac:int -> mat -> int

geev_opt_lwork ?n ?vlr ?vlc ?vl ?vrr ?vrc ?vr ?ofswr wr ?ofswi wi ?ar ?ac a See geev-function for details about arguments.

  • returns

    "optimal" size of work array.

val geev : ?n:int -> ?work:vec -> ?vlr:int -> ?vlc:int -> ?vl:mat option -> ?vrr:int -> ?vrc:int -> ?vr:mat option -> ?ofswr:int -> ?wr:vec -> ?ofswi:int -> ?wi:vec -> ?ar:int -> ?ac:int -> mat -> mat * vec * vec * mat

geev ?work ?n ?vlr ?vlc ?vl ?vrr ?vrc ?vr ?ofswr ?wr ?ofswi ?wi ?ar ?ac a

  • returns

    (lv, wr, wi, rv), where wr and wv are the real and imaginary components of the eigenvalues, and lv and rv are the left and right eigenvectors. lv (rv) is the empty matrix if vl (vr) is set to None.

  • raises Failure

    if the function fails to converge

  • parameter n

    default = available number of columns of matrix a

  • parameter work

    default = automatically allocated workspace

  • parameter vl

    default = Automatically allocated left eigenvectors. Pass None if you do not want to compute them, Some lv if you want to provide the storage. You can set vlr, vlc in the last case. (See LAPACK GEEV docs for details about storage of complex eigenvectors)

  • parameter vr

    default = Automatically allocated right eigenvectors. Pass None if you do not want to compute them, Some rv if you want to provide the storage. You can set vrr, vrc in the last case.

  • parameter wr

    default = vector of size n; real components of the eigenvalues

  • parameter wi

    default = vector of size n; imaginary components of the eigenvalues

  • parameter a

    the matrix whose eigensystem is computed

Symmetric-matrix eigenvalue and singular value problems (simple drivers)
val syev_min_lwork : int -> int

syev_min_lwork n

  • returns

    the minimum length of the work-array used by the syev-function if the logical dimensions of the matrix are n.

val syev_opt_lwork : ?n:int -> ?vectors:bool -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> int

syev_opt_lwork ?n ?vectors ?up ?ar ?ac a

  • returns

    the optimum length of the work-array used by the syev-function given matrix a, optionally its logical dimension n and whether the eigenvectors must be computed (vectors).

  • parameter n

    default = available number of columns of matrix a

  • parameter vectors

    default = false, i.e. eigenvectors are not computed

  • parameter up

    default = true, i.e. upper triangle of a is stored

val syev : ?n:int -> ?vectors:bool -> ?up:bool -> ?work:vec -> ?ofsw:int -> ?w:vec -> ?ar:int -> ?ac:int -> mat -> vec

syev ?n ?vectors ?up ?ofswork ?work ?ofsw ?w ?ar ?ac a computes all eigenvalues and, optionally, eigenvectors of the real symmetric matrix a.

  • returns

    the vector w of eigenvalues in ascending order.

  • raises Failure

    if the function fails to converge.

  • parameter n

    default = available number of columns of matrix a

  • parameter vectors

    default = false i.e, eigenvectors are not computed

  • parameter up

    default = true i.e., upper triangle of a is stored

  • parameter ofsw

    default = 1 or ignored if w is not given

  • parameter w

    default = vec of length n

val syevd_min_lwork : vectors:bool -> int -> int

syevd_min_lwork vectors n

  • returns

    the minimum length of the work-array used by the syevd-function if the logical dimensions of the matrix are n and given whether eigenvectors should be computed (vectors).

val syevd_min_liwork : vectors:bool -> int -> int

syevd_min_liwork vectors n

  • returns

    the minimum length of the iwork-array used by the syevd-function if the logical dimensions of the matrix are n and given whether eigenvectors should be computed (vectors).

val syevd_opt_lwork : ?n:int -> ?vectors:bool -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> int

syevd_opt_lwork ?n ?vectors ?up ?ar ?ac a

  • returns

    the optimum length of the work-array used by the syevd-function given matrix a, optionally its logical dimension n and whether the eigenvectors must be computed (vectors).

  • parameter n

    default = available number of columns of matrix a

  • parameter vectors

    default = false, i.e. eigenvectors are not computed

  • parameter up

    default = true, i.e. upper triangle of a is stored

val syevd_opt_liwork : ?n:int -> ?vectors:bool -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> int

syevd_opt_liwork ?n ?vectors ?up ?ar ?ac a

  • returns

    the optimum length of the iwork-array used by the syevd-function given matrix a, optionally its logical dimension n and whether the eigenvectors must be computed (vectors).

  • parameter n

    default = available number of columns of matrix a

  • parameter vectors

    default = false, i.e. eigenvectors are not computed

  • parameter up

    default = true, i.e. upper triangle of a is stored

val syevd_opt_l_li_work : ?n:int -> ?vectors:bool -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> int * int

syevd_opt_l_li_iwork ?n ?vectors ?up ?ar ?ac a

  • returns

    the tuple of optimum lengths of the work- and iwork-arrays respectively, used by the syevd-function given matrix a, optionally its logical dimension n and whether the eigenvectors must be computed (vectors).

  • parameter n

    default = available number of columns of matrix a

  • parameter vectors

    default = false, i.e. eigenvectors are not computed

  • parameter up

    default = true, i.e. upper triangle of a is stored

val syevd : ?n:int -> ?vectors:bool -> ?up:bool -> ?work:vec -> ?iwork:Common.int32_vec -> ?ofsw:int -> ?w:vec -> ?ar:int -> ?ac:int -> mat -> vec

syevd ?n ?vectors ?up ?ofswork ?work ?iwork ?ofsw ?w ?ar ?ac a computes all eigenvalues and, optionally, eigenvectors of the real symmetric matrix a. If eigenvectors are desired, it uses a divide and conquer algorithm.

  • returns

    the vector w of eigenvalues in ascending order.

  • raises Failure

    if the function fails to converge.

  • parameter n

    default = available number of columns of matrix a

  • parameter vectors

    default = false i.e, eigenvectors are not computed

  • parameter up

    default = true i.e., upper triangle of a is stored

  • parameter ofsw

    default = 1 or ignored if w is not given

  • parameter w

    default = vec of length n

val sbev_min_lwork : int -> int

sbev_min_lwork n

  • returns

    the minimum length of the work-array used by the sbev-function if the logical dimensions of the matrix are n.

val sbev : ?n:int -> ?kd:int -> ?zr:int -> ?zc:int -> ?z:mat -> ?up:bool -> ?work:vec -> ?ofsw:int -> ?w:vec -> ?abr:int -> ?abc:int -> mat -> vec

sbev ?n ?vectors ?zr ?zc ?z ?up ?ofswork ?work ?ofsw ?w ?abr ?abc ab computes all the eigenvalues and, optionally, eigenvectors of the real symmetric band matrix ab.

  • raises Failure

    if the function fails to converge.

  • returns

    the vector w of eigenvalues in ascending order.

  • raises Failure

    if the function fails to converge.

  • parameter n

    default = available number of columns of matrix ab

  • parameter z

    matrix to contain the orthonormal eigenvectors of ab, the i-th column of z holding the eigenvector associated with w.{i}. default = None i.e, eigenvectors are not computed

  • parameter kd

    default = number of rows in matrix ab - 1

  • parameter up

    default = true i.e., upper triangle of the matrix is stored

  • parameter ofsw

    default = 1 or ignored if w is not given

  • parameter w

    default = vec of length n

  • parameter abr

    default = 1

  • parameter abc

    default = 1

Symmetric-matrix eigenvalue and singular value problems (expert & RRR drivers)
val syevr_min_lwork : int -> int

syevr_min_lwork n

  • returns

    the minimum length of the work-array used by the syevr-function if the logical dimensions of the matrix are n.

val syevr_min_liwork : int -> int

syevr_min_liwork n

  • returns

    the minimum length of the iwork-array used by the syevr-function if the logical dimensions of the matrix are n.

val syevr_opt_lwork : ?n:int -> ?vectors:bool -> ?range:[ `A | `V of float * float | `I of int * int ] -> ?up:bool -> ?abstol:float -> ?ar:int -> ?ac:int -> mat -> int

syevr_opt_lwork ?n ?vectors ?range ?up ?abstol ?ar ?ac a

  • returns

    the optimum length of the work-array used by the syevr-function given matrix a, optionally its logical dimension n and whether the eigenvectors must be computed (vectors).

  • parameter n

    default = available number of columns of matrix a

  • parameter vectors

    default = false, i.e. eigenvectors are not computed

  • parameter up

    default = true, i.e. upper triangle of a is stored

val syevr_opt_liwork : ?n:int -> ?vectors:bool -> ?range:[ `A | `V of float * float | `I of int * int ] -> ?up:bool -> ?abstol:float -> ?ar:int -> ?ac:int -> mat -> int

syevr_opt_liwork ?n ?vectors ?range ?up ?abstol ?ar ?ac a

  • returns

    the optimum length of the iwork-array used by the syevr-function given matrix a, optionally its logical dimension n and whether the eigenvectors must be computed (vectors).

  • parameter n

    default = available number of columns of matrix a

  • parameter vectors

    default = false, i.e. eigenvectors are not computed

  • parameter up

    default = true, i.e. upper triangle of a is stored

val syevr_opt_l_li_work : ?n:int -> ?vectors:bool -> ?range:[ `A | `V of float * float | `I of int * int ] -> ?up:bool -> ?abstol:float -> ?ar:int -> ?ac:int -> mat -> int * int

syevr_opt_l_li_iwork ?n ?vectors ?range ?up ?abstol ?ar ?ac a

  • returns

    the tuple of optimum lengths of the work- and iwork-arrays respectively, used by the syevr-function given matrix a, optionally its logical dimension n and whether the eigenvectors must be computed (vectors).

  • parameter n

    default = available number of columns of matrix a

  • parameter vectors

    default = false, i.e. eigenvectors are not computed

  • parameter up

    default = true, i.e. upper triangle of a is stored

val syevr : ?n:int -> ?vectors:bool -> ?range:[ `A | `V of float * float | `I of int * int ] -> ?up:bool -> ?abstol:float -> ?work:vec -> ?iwork:Common.int32_vec -> ?ofsw:int -> ?w:vec -> ?zr:int -> ?zc:int -> ?z:mat -> ?isuppz:Common.int32_vec -> ?ar:int -> ?ac:int -> mat -> int * vec * mat * Common.int32_vec

syevr ?n ?vectors ?range ?up ?abstol ?work ?iwork ?ofsw ?w ?zr ?zc ?z ?isuppz ?ar ?ac a range is either `A for computing all eigenpairs, `V (vl, vu) defines the lower and upper range of computed eigenvalues, `I (il, iu) defines the indexes of the computed eigenpairs, which are sorted in ascending order.

  • returns

    the tuple (m, w, z, isuppz), where m is the number of computed eigenpairs, vector w contains the computed eigenvalues in ascending order, z contains the computed eigenvectors in same order, and isuppz indicates the nonzero elements in z.

  • parameter n

    default = available number of columns of matrix a

  • parameter vectors

    default = false i.e, eigenvectors are not computed

  • parameter range

    default = `A

  • parameter up

    default = true i.e., upper triangle of a is stored

  • parameter abstol

    default = result of calling lamch `S

  • parameter ofsw

    default = 1 or ignored if w is not given

  • parameter w

    default = vec of length n

  • parameter zr

    default = 1

  • parameter zc

    default = 1

  • parameter z

    default = matrix with minimal required dimension

  • parameter isuppz

    default = int32_vec with minimal required dimension

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val sygv_opt_lwork : ?n:int -> ?vectors:bool -> ?up:bool -> ?itype:[ `A_B | `AB | `BA ] -> ?ar:int -> ?ac:int -> mat -> ?br:int -> ?bc:int -> mat -> int

sygv_opt_lwork ?n ?vectors ?up ?ar ?ac a ?br ?bc b

  • returns

    the optimum length of the work-array used by the sygv-function for the given matrices a and b, optionally their logical dimension n and whether the eigenvectors must be computed (vectors).

  • parameter n

    default = available number of columns of matrix a

  • parameter vectors

    default = false, i.e. eigenvectors are not computed

  • parameter up

    default = true, i.e. upper triangle of a is stored

  • parameter itype

    specifies the problem type to be solved:

    • `A_B (default): a*x = (lambda)*a*x
    • `AB: a*b*x = (lambda)*x
    • `BA: b*a*x = (lambda)*x
val sygv : ?n:int -> ?vectors:bool -> ?up:bool -> ?work:vec -> ?ofsw:int -> ?w:vec -> ?itype:[ `A_B | `AB | `BA ] -> ?ar:int -> ?ac:int -> mat -> ?br:int -> ?bc:int -> mat -> vec

sygv ?n ?vectors ?up ?ofswork ?work ?ofsw ?w ?ar ?ac a ?br ?bc b computes all the eigenvalues, and optionally, the eigenvectors of a real generalized symmetric-definite eigenproblem, of the form a*x=(lambda)*b*x, a*b*x=(lambda)*x, or b*a*x=(lambda)*x. Here a and b are assumed to be symmetric and b is also positive definite.

  • returns

    the vector w of eigenvalues in ascending order.

  • raises Failure

    if the function fails to converge.

  • parameter n

    default = available number of columns of matrix a

  • parameter vectors

    default = false i.e, eigenvectors are not computed

  • parameter up

    default = true i.e., upper triangle of a is stored

  • parameter ofsw

    default = 1 or ignored if w is not given

  • parameter w

    default = vec of length n

  • parameter itype

    specifies the problem type to be solved:

    • `A_B (default): a*x = (lambda)*a*x
    • `AB: a*b*x = (lambda)*x
    • `BA: b*a*x = (lambda)*x
val sbgv : ?n:int -> ?ka:int -> ?kb:int -> ?zr:int -> ?zc:int -> ?z:mat -> ?up:bool -> ?work:vec -> ?ofsw:int -> ?w:vec -> ?ar:int -> ?ac:int -> mat -> ?br:int -> ?bc:int -> mat -> vec

sbgv ?n ?ka ?kb ?zr ?zc ?z ?up ?work ?ofsw ?w ?ar ?ac a ?br ?bc b computes all the eigenvalues, and optionally, the eigenvectors of a real generalized symmetric-definite banded eigenproblem, of the form a*x=(lambda)*b*x. Here a and b are assumed to be symmetric and banded, and b is also positive definite.

  • returns

    the vector w of eigenvalues in ascending order.

  • raises Failure

    if the function fails to converge.

  • parameter n

    default = available number of columns of matrix a

  • parameter ka

    the number of superdiagonals (or subdiagonals if up = false) of the matrix a. Default = dim1 a - ar.

  • parameter kb

    same as ka but for the matrix b.

  • parameter z

    default = None i.e, eigenvectors are not computed

  • parameter up

    default = true i.e., upper triangle of a is stored

  • parameter work

    default = vec of optimum length (3 * n)

  • parameter ofsw

    default = 1 or ignored if w is not given

  • parameter w

    default = vec of length n

BLAS-1 interface
val swap : ?n:int -> ?ofsx:int -> ?incx:int -> vec -> ?ofsy:int -> ?incy:int -> vec -> unit

swap ?n ?ofsx ?incx x ?ofsy ?incy y see BLAS documentation!

  • parameter n

    default = greater n s.t. ofsx+(n-1)(abs incx) <= dim x

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

  • parameter ofsy

    default = 1

  • parameter incy

    default = 1

val scal : ?n:int -> float -> ?ofsx:int -> ?incx:int -> vec -> unit

scal ?n alpha ?ofsx ?incx x see BLAS documentation!

  • parameter n

    default = greater n s.t. ofsx+(n-1)(abs incx) <= dim x

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

val copy : ?n:int -> ?ofsy:int -> ?incy:int -> ?y:vec -> ?ofsx:int -> ?incx:int -> vec -> vec

copy ?n ?ofsy ?incy ?y ?ofsx ?incx x see BLAS documentation!

  • returns

    vector y, which is overwritten.

  • parameter n

    default = greater n s.t. ofsx+(n-1)(abs incx) <= dim x

  • parameter ofsy

    default = 1

  • parameter incy

    default = 1

  • parameter y

    default = new vector with ofsy+(n-1)(abs incy) rows

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

val nrm2 : ?n:int -> ?ofsx:int -> ?incx:int -> vec -> float

nrm2 ?n ?ofsx ?incx x see BLAS documentation!

  • parameter n

    default = greater n s.t. ofsx+(n-1)(abs incx) <= dim x

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

val axpy : ?alpha:float -> ?n:int -> ?ofsx:int -> ?incx:int -> vec -> ?ofsy:int -> ?incy:int -> vec -> unit

axpy ?alpha ?n ?ofsx ?incx x ?ofsy ?incy y see BLAS documentation!

  • parameter alpha

    default = { re = 1.; im = 0. }

  • parameter n

    default = greater n s.t. ofsx+(n-1)(abs incx) <= dim x

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

  • parameter ofsy

    default = 1

  • parameter incy

    default = 1

val iamax : ?n:int -> ?ofsx:int -> ?incx:int -> vec -> int

iamax ?n ?ofsx ?incx x see BLAS documentation!

  • parameter n

    default = greater n s.t. ofsx+(n-1)(abs incx) <= dim x

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

val amax : ?n:int -> ?ofsx:int -> ?incx:int -> vec -> float

amax ?n ?ofsx ?incx x

  • returns

    the greater of the absolute values of the elements of the vector x.

  • parameter n

    default = greater n s.t. ofsx+(n-1)(abs incx) <= dim x

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

BLAS-2 interface
val gemv : ?m:int -> ?n:int -> ?beta:float -> ?ofsy:int -> ?incy:int -> ?y:vec -> ?trans:trans3 -> ?alpha:float -> ?ar:int -> ?ac:int -> mat -> ?ofsx:int -> ?incx:int -> vec -> vec

gemv ?m ?n ?beta ?ofsy ?incy ?y ?trans ?alpha ?ar ?ac a ?ofsx ?incx x performs the operation y := alpha * op(a) * x + beta * y where op(a) = a or aᵀ according to the value of trans. See BLAS documentation for more information. BEWARE that the 1988 BLAS-2 specification mandates that this function has no effect when n=0 while the mathematically expected behavior is y ← beta * y.

  • returns

    vector y, which is overwritten.

  • parameter m

    default = number of available rows in matrix a

  • parameter n

    default = available columns in matrix a

  • parameter beta

    default = { re = 0.; im = 0. }

  • parameter ofsy

    default = 1

  • parameter incy

    default = 1

  • parameter y

    default = vector with minimal required length (see BLAS)

  • parameter trans

    default = `N

  • parameter alpha

    default = { re = 1.; im = 0. }

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

val gbmv : ?m:int -> ?n:int -> ?beta:float -> ?ofsy:int -> ?incy:int -> ?y:vec -> ?trans:trans3 -> ?alpha:float -> ?ar:int -> ?ac:int -> mat -> int -> int -> ?ofsx:int -> ?incx:int -> vec -> vec

gbmv ?m ?n ?beta ?ofsy ?incy ?y ?trans ?alpha ?ar ?ac a kl ku ?ofsx ?incx x see BLAS documentation!

  • returns

    vector y, which is overwritten.

  • parameter m

    default = same as n (i.e., a is a square matrix)

  • parameter n

    default = available number of columns in matrix a

  • parameter beta

    default = { re = 0.; im = 0. }

  • parameter ofsy

    default = 1

  • parameter incy

    default = 1

  • parameter y

    default = vector with minimal required length (see BLAS)

  • parameter trans

    default = `N

  • parameter alpha

    default = { re = 1.; im = 0. }

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

val symv : ?n:int -> ?beta:float -> ?ofsy:int -> ?incy:int -> ?y:vec -> ?up:bool -> ?alpha:float -> ?ar:int -> ?ac:int -> mat -> ?ofsx:int -> ?incx:int -> vec -> vec

symv ?n ?beta ?ofsy ?incy ?y ?up ?alpha ?ar ?ac a ?ofsx ?incx x see BLAS documentation!

  • returns

    vector y, which is overwritten.

  • parameter n

    default = dimension of symmetric matrix a

  • parameter beta

    default = { re = 0.; im = 0. }

  • parameter ofsy

    default = 1

  • parameter incy

    default = 1

  • parameter y

    default = vector with minimal required length (see BLAS)

  • parameter up

    default = true (upper triangular portion of a is accessed)

  • parameter alpha

    default = { re = 1.; im = 0. }

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

val trmv : ?n:int -> ?trans:trans3 -> ?diag:Common.diag -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> ?ofsx:int -> ?incx:int -> vec -> unit

trmv ?n ?trans ?diag ?up ?ar ?ac a ?ofsx ?incx x see BLAS documentation!

  • parameter n

    default = dimension of triangular matrix a

  • parameter trans

    default = `N

  • parameter diag

    default = false (not a unit triangular matrix)

  • parameter up

    default = true (upper triangular portion of a is accessed)

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

val trsv : ?n:int -> ?trans:trans3 -> ?diag:Common.diag -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> ?ofsx:int -> ?incx:int -> vec -> unit

trsv ?n ?trans ?diag ?up ?ar ?ac a ?ofsx ?incx x see BLAS documentation!

  • parameter n

    default = dimension of triangular matrix a

  • parameter trans

    default = `N

  • parameter diag

    default = false (not a unit triangular matrix)

  • parameter up

    default = true (upper triangular portion of a is accessed)

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

val tpmv : ?n:int -> ?trans:trans3 -> ?diag:Common.diag -> ?up:bool -> ?ofsap:int -> vec -> ?ofsx:int -> ?incx:int -> vec -> unit

tpmv ?n ?trans ?diag ?up ?ofsap ap ?ofsx ?incx x see BLAS documentation!

  • parameter n

    default = dimension of packed triangular matrix ap

  • parameter trans

    default = `N

  • parameter diag

    default = false (not a unit triangular matrix)

  • parameter up

    default = true (upper triangular portion of ap is accessed)

  • parameter ofsap

    default = 1

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

val tpsv : ?n:int -> ?trans:trans3 -> ?diag:Common.diag -> ?up:bool -> ?ofsap:int -> vec -> ?ofsx:int -> ?incx:int -> vec -> unit

tpsv ?n ?trans ?diag ?up ?ofsap ap ?ofsx ?incx x see BLAS documentation!

  • parameter n

    default = dimension of packed triangular matrix ap

  • parameter trans

    default = `N

  • parameter diag

    default = false (not a unit triangular matrix)

  • parameter up

    default = true (upper triangular portion of ap is accessed)

  • parameter ofsap

    default = 1

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

BLAS-3 interface
val gemm : ?m:int -> ?n:int -> ?k:int -> ?beta:float -> ?cr:int -> ?cc:int -> ?c:mat -> ?transa:trans3 -> ?alpha:float -> ?ar:int -> ?ac:int -> mat -> ?transb:trans3 -> ?br:int -> ?bc:int -> mat -> mat

gemm ?m ?n ?k ?beta ?cr ?cc ?c ?transa ?alpha ?ar ?ac a ?transb ?br ?bc b performs the operation c := alpha * op(a) * op(b) + beta * c where op(x) = x or xᵀ depending on transx. See BLAS documentation for more information.

  • returns

    matrix c, which is overwritten.

  • parameter m

    default = number of rows of a (or tr a) and c

  • parameter n

    default = number of columns of b (or tr b) and c

  • parameter k

    default = number of columns of a (or tr a) and number of rows of b (or tr b)

  • parameter beta

    default = { re = 0.; im = 0. }

  • parameter cr

    default = 1

  • parameter cc

    default = 1

  • parameter c

    default = matrix with minimal required dimension

  • parameter transa

    default = `N

  • parameter alpha

    default = { re = 1.; im = 0. }

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter transb

    default = `N

  • parameter br

    default = 1

  • parameter bc

    default = 1

val symm : ?m:int -> ?n:int -> ?side:Common.side -> ?up:bool -> ?beta:float -> ?cr:int -> ?cc:int -> ?c:mat -> ?alpha:float -> ?ar:int -> ?ac:int -> mat -> ?br:int -> ?bc:int -> mat -> mat

symm ?m ?n ?side ?up ?beta ?cr ?cc ?c ?alpha ?ar ?ac a ?br ?bc b see BLAS documentation!

  • returns

    matrix c, which is overwritten.

  • parameter m

    default = number of rows of c

  • parameter n

    default = number of columns of c

  • parameter side

    default = `L (left - multiplication is ab)

  • parameter up

    default = true (upper triangular portion of a is accessed)

  • parameter beta

    default = { re = 0.; im = 0. }

  • parameter cr

    default = 1

  • parameter cc

    default = 1

  • parameter c

    default = matrix with minimal required dimension

  • parameter alpha

    default = { re = 1.; im = 0. }

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter br

    default = 1

  • parameter bc

    default = 1

val trmm : ?m:int -> ?n:int -> ?side:Common.side -> ?up:bool -> ?transa:trans3 -> ?diag:Common.diag -> ?alpha:float -> ?ar:int -> ?ac:int -> mat -> ?br:int -> ?bc:int -> mat -> unit

trmm ?m ?n ?side ?up ?transa ?diag ?alpha ?ar ?ac a ?br ?bc b see BLAS documentation!

  • parameter m

    default = number of rows of b

  • parameter n

    default = number of columns of b

  • parameter side

    default = `L (left - multiplication is ab)

  • parameter up

    default = true (upper triangular portion of a is accessed)

  • parameter transa

    default = `N

  • parameter diag

    default = `N (non-unit)

  • parameter alpha

    default = { re = 1.; im = 0. }

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter br

    default = 1

  • parameter bc

    default = 1

val trsm : ?m:int -> ?n:int -> ?side:Common.side -> ?up:bool -> ?transa:trans3 -> ?diag:Common.diag -> ?alpha:float -> ?ar:int -> ?ac:int -> mat -> ?br:int -> ?bc:int -> mat -> unit

trsm ?m ?n ?side ?up ?transa ?diag ?alpha ?ar ?ac ~a ?br ?bc b see BLAS documentation!

  • returns

    matrix b, which is overwritten.

  • parameter m

    default = number of rows of b

  • parameter n

    default = number of columns of b

  • parameter side

    default = `L (left - multiplication is ab)

  • parameter up

    default = true (upper triangular portion of a is accessed)

  • parameter transa

    default = `N

  • parameter diag

    default = `N (non-unit)

  • parameter alpha

    default = { re = 1.; im = 0. }

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter br

    default = 1

  • parameter bc

    default = 1

val syrk : ?n:int -> ?k:int -> ?up:bool -> ?beta:float -> ?cr:int -> ?cc:int -> ?c:mat -> ?trans:Common.trans2 -> ?alpha:float -> ?ar:int -> ?ac:int -> mat -> mat

syrk ?n ?k ?up ?beta ?cr ?cc ?c ?trans ?alpha ?ar ?ac a see BLAS documentation!

  • returns

    matrix c, which is overwritten.

  • parameter n

    default = number of rows of a (or a'), c

  • parameter k

    default = number of columns of a (or a')

  • parameter up

    default = true (upper triangular portion of c is accessed)

  • parameter beta

    default = { re = 0.; im = 0. }

  • parameter cr

    default = 1

  • parameter cc

    default = 1

  • parameter c

    default = matrix with minimal required dimension

  • parameter trans

    default = `N

  • parameter alpha

    default = { re = 1.; im = 0. }

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val syr2k : ?n:int -> ?k:int -> ?up:bool -> ?beta:float -> ?cr:int -> ?cc:int -> ?c:mat -> ?trans:Common.trans2 -> ?alpha:float -> ?ar:int -> ?ac:int -> mat -> ?br:int -> ?bc:int -> mat -> mat

syr2k ?n ?k ?up ?beta ?cr ?cc ?c ?trans ?alpha ?ar ?ac a ?br ?bc b see BLAS documentation!

  • returns

    matrix c, which is overwritten.

  • parameter n

    default = number of rows of a (or a'), c

  • parameter k

    default = number of columns of a (or a')

  • parameter up

    default = true (upper triangular portion of c is accessed)

  • parameter beta

    default = { re = 0.; im = 0. }

  • parameter cr

    default = 1

  • parameter cc

    default = 1

  • parameter c

    default = matrix with minimal required dimension

  • parameter trans

    default = `N

  • parameter alpha

    default = { re = 1.; im = 0. }

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter br

    default = 1

  • parameter bc

    default = 1

LAPACK interface
Auxiliary routines
val lacpy : ?uplo:[ `U | `L ] -> ?patt:Common.Types.Mat.patt -> ?m:int -> ?n:int -> ?br:int -> ?bc:int -> ?b:mat -> ?ar:int -> ?ac:int -> mat -> mat

lacpy ?patt ?uplo ?m ?n ?br ?bc ?b ?ar ?ac a copy the (triangular) (sub-)matrix a (to an optional (sub-)matrix b) and return it. patt is more general than uplo and should be used in its place whenever strict BLAS conformance is not required. Only one of patt and uplo can be specified at a time.

  • raises Failure

    if both patt and uplo are specified simultaneously

  • parameter patt

    default = `Full

  • parameter uplo

    default = whole matrix

  • parameter b

    The target matrix. By default a fresh matrix to accommodate the sizes m and n and the offsets br and bc is created.

val laswp : ?n:int -> ?ar:int -> ?ac:int -> mat -> ?k1:int -> ?k2:int -> ?incx:int -> Common.int32_vec -> unit

laswp ?n ?ar ?ac a ?k1 ?k2 ?incx ipiv swap rows of a according to ipiv. See LAPACK-documentation for details!

  • parameter n

    default = number of columns of matrix

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter k1

    default = 1

  • parameter k2

    default = dimension of ipiv

  • parameter incx

    default = 1

  • parameter ipiv

    is a vector of sequential row interchanges.

val lapmt : ?forward:bool -> ?m:int -> ?n:int -> ?ar:int -> ?ac:int -> mat -> Common.int32_vec -> unit

lapmt ?forward ?n ?m ?ar ?ac a k swap columns of a according to the permutations in k. See LAPACK-documentation for details!

  • parameter forward

    default = true

  • parameter m

    default = number of rows of matrix

  • parameter n

    default = number of columns of matrix

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter k

    is vector of column permutations and must be of length n. Note that checking for duplicates in k is not performed and this could lead to undefined behavior. Furthermore, LAPACK uses k as a workspace and restore it upon completion, sharing this permutation array is not thread safe.

val lassq : ?n:int -> ?scale:float -> ?sumsq:float -> ?ofsx:int -> ?incx:int -> vec -> float * float

lassq ?n ?ofsx ?incx ?scale ?sumsq

  • returns

    (scl, ssq), where scl is a scaling factor and ssq the sum of squares of vector x starting at ofs and using increment incx and initial scale and sumsq. The following equality holds: scl**2. *. ssq = x.{1}**2. +. ... +. x.{n}**2. +. scale**2. *. sumsq. See LAPACK-documentation for details!

  • parameter n

    default = greater n s.t. ofsx+(n-1)(abs incx) <= dim x

  • parameter ofsx

    default = 1

  • parameter incx

    default = 1

  • parameter scale

    default = 0.

  • parameter sumsq

    default = 1.

val larnv : ?idist:[ `Uniform0 | `Uniform1 | `Normal ] -> ?iseed:Common.int32_vec -> ?n:int -> ?ofsx:int -> ?x:vec -> unit -> vec

larnv ?idist ?iseed ?n ?ofsx ?x ()

  • returns

    a random vector with random distribution as specifified by idist, random seed iseed, vector offset ofsx and optional vector x.

  • parameter idist

    default = `Normal

  • parameter iseed

    default = integer vector of size 4 with all ones.

  • parameter n

    default = dim x - ofsx + 1 if x is provided, 1 otherwise.

  • parameter ofsx

    default = 1

  • parameter x

    default = vector of length ofsx - 1 + n if n is provided.

val lange_min_lwork : int -> Common.norm4 -> int

lange_min_lwork m norm

  • returns

    the minimum length of the work array used by the lange-function.

  • parameter m

    the number of rows in the matrix

  • parameter norm

    type of norm that will be computed by lange

val lange : ?m:int -> ?n:int -> ?norm:Common.norm4 -> ?work:rvec -> ?ar:int -> ?ac:int -> mat -> float

lange ?m ?n ?norm ?work ?ar ?ac a

  • returns

    the value of the one norm (norm = `O), or the Frobenius norm (norm = `F), or the infinity norm (norm = `I), or the element of largest absolute value (norm = `M) of a real matrix a.

  • parameter m

    default = number of rows of matrix a

  • parameter n

    default = number of columns of matrix a

  • parameter norm

    default = `O

  • parameter work

    default = allocated work space for norm `I

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val lauum : ?n:int -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> unit

lauum ?n ?up ?ar ?ac a computes the product U * U**T or L**T * L, where the triangular factor U or L is stored in the upper or lower triangular part of the array a. The upper or lower part of a is overwritten.

  • parameter n

    default = minimum of available number of rows/columns in matrix a

  • parameter up

    default = true

  • parameter ar

    default = 1

  • parameter ac

    default = 1

Linear equations (computational routines)
val getrf : ?m:int -> ?n:int -> ?ipiv:Common.int32_vec -> ?ar:int -> ?ac:int -> mat -> Common.int32_vec

getrf ?m ?n ?ipiv ?ar ?ac a computes an LU factorization of a general m-by-n matrix a using partial pivoting with row interchanges. See LAPACK documentation.

  • returns

    ipiv, the pivot indices.

  • raises Failure

    if the matrix is singular.

  • parameter m

    default = number of rows in matrix a

  • parameter n

    default = number of columns in matrix a

  • parameter ipiv

    = vec of length min(m, n)

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val getrs : ?n:int -> ?ipiv:Common.int32_vec -> ?trans:trans3 -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

getrs ?n ?ipiv ?trans ?ar ?ac a ?nrhs ?br ?bc b solves a system of linear equations a * X = b or a' * X = b with a general n-by-n matrix a using the LU factorization computed by getrf. Note that matrix a will be passed to getrf if ipiv was not provided.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = number of columns in matrix a

  • parameter ipiv

    default = result from getrf applied to a

  • parameter trans

    default = `N

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val getri_min_lwork : int -> int

getri_min_lwork n

  • returns

    the minimum length of the work array used by the getri-function if the matrix has n columns.

val getri_opt_lwork : ?n:int -> ?ar:int -> ?ac:int -> mat -> int

getri_opt_lwork ?n ?ar ?ac a

  • returns

    the optimal size of the work array used by the getri-function.

  • parameter n

    default = number of columns of matrix a

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val getri : ?n:int -> ?ipiv:Common.int32_vec -> ?work:vec -> ?ar:int -> ?ac:int -> mat -> unit

getri ?n ?ipiv ?work ?ar ?ac a computes the inverse of a matrix using the LU factorization computed by getrf. Note that matrix a will be passed to getrf if ipiv was not provided.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = number of columns in matrix a

  • parameter ipiv

    default = vec of length m from getri

  • parameter work

    default = vec of optimum length

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val sytrf_min_lwork : unit -> int

sytrf_min_lwork ()

  • returns

    the minimum length of the work array used by the sytrf-function.

val sytrf_opt_lwork : ?n:int -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> int

sytrf_opt_lwork ?n ?up ?ar ?ac a

  • returns

    the optimal size of the work array used by the sytrf-function.

  • parameter n

    default = number of columns of matrix a

  • parameter up

    default = true (store upper triangle in a)

  • parameter a

    the matrix a

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val sytrf : ?n:int -> ?up:bool -> ?ipiv:Common.int32_vec -> ?work:vec -> ?ar:int -> ?ac:int -> mat -> Common.int32_vec

sytrf ?n ?up ?ipiv ?work ?ar ?ac a computes the factorization of the real symmetric matrix a using the Bunch-Kaufman diagonal pivoting method.

  • raises Failure

    if D in a = U*D*U' or L*D*L' is singular.

  • parameter n

    default = number of columns in matrix a

  • parameter up

    default = true (store upper triangle in a)

  • parameter ipiv

    = vec of length n

  • parameter work

    default = vec of optimum length

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val sytrs : ?n:int -> ?up:bool -> ?ipiv:Common.int32_vec -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

sytrs ?n ?up ?ipiv ?ar ?ac a ?nrhs ?br ?bc b solves a system of linear equations a*X = b with a real symmetric matrix a using the factorization a = U*D*U**T or a = L*D*L**T computed by sytrf. Note that matrix a will be passed to sytrf if ipiv was not provided.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = number of columns in matrix a

  • parameter up

    default = true (store upper triangle in a)

  • parameter ipiv

    default = vec of length n

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val sytri_min_lwork : int -> int

sytri_min_lwork n

  • returns

    the minimum length of the work array used by the sytri-function if the matrix has n columns.

val sytri : ?n:int -> ?up:bool -> ?ipiv:Common.int32_vec -> ?work:vec -> ?ar:int -> ?ac:int -> mat -> unit

sytri ?n ?up ?ipiv ?work ?ar ?ac a computes the inverse of the real symmetric indefinite matrix a using the factorization a = U*D*U**T or a = L*D*L**T computed by sytrf. Note that matrix a will be passed to sytrf if ipiv was not provided.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = number of columns in matrix a

  • parameter up

    default = true (store upper triangle in a)

  • parameter ipiv

    default = vec of length n from sytrf

  • parameter work

    default = vec of optimum length

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val potrf : ?n:int -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> unit

potrf ?n ?up ?ar ?ac a factorizes symmetric positive definite matrix a (or the designated submatrix) using Cholesky factorization.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = number of columns in matrix a

  • parameter up

    default = true (store upper triangle in a)

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val potrs : ?n:int -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

potrs ?n ?up ?ar ?ac a ?nrhs ?br ?bc b solves a system of linear equations a*X = b, where a is symmetric positive definite matrix, using the Cholesky factorization a = U**T*U or a = L*L**T computed by potrf.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = number of columns in matrix a

  • parameter up

    default = true

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val potri : ?n:int -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> unit

potri ?n ?up ?ar ?ac a computes the inverse of the real symmetric positive definite matrix a using the Cholesky factorization a = U**T*U or a = L*L**T computed by potrf.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = number of columns in matrix a

  • parameter up

    default = true (upper triangle stored in a)

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val trtrs : ?n:int -> ?up:bool -> ?trans:trans3 -> ?diag:Common.diag -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

trtrs ?n ?up ?trans ?diag ?ar ?ac a ?nrhs ?br ?bc b solves a triangular system of the form a * X = b or a**T * X = n, where a is a triangular matrix of order n, and b is an n-by-nrhs matrix.

  • raises Failure

    if the matrix a is singular.

  • parameter n

    default = number of columns in matrix a

  • parameter up

    default = true

  • parameter trans

    default = `N

  • parameter diag

    default = `N

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val tbtrs : ?n:int -> ?kd:int -> ?up:bool -> ?trans:trans3 -> ?diag:Common.diag -> ?abr:int -> ?abc:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

tbtrs ?n ?kd ?up ?trans ?diag ?abr ?abc ab ?nrhs ?br ?bc b solves a triangular system of the form a * X = b or a**T * X = b, where a is a triangular band matrix of order n, and b is an n-by-nrhs matrix.

  • raises Failure

    if the matrix a is singular.

  • parameter n

    default = number of columns in matrix ab

  • parameter kd

    default = number of rows in matrix ab - 1

  • parameter up

    default = true

  • parameter trans

    default = `N

  • parameter diag

    default = `N

  • parameter abr

    default = 1

  • parameter abc

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val trtri : ?n:int -> ?up:bool -> ?diag:Common.diag -> ?ar:int -> ?ac:int -> mat -> unit

trtri ?n ?up ?diag ?ar ?ac a computes the inverse of a real upper or lower triangular matrix a.

  • raises Failure

    if the matrix a is singular.

  • parameter n

    default = number of columns in matrix a

  • parameter up

    default = true (upper triangle stored in a)

  • parameter diag

    default = `N

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val geqrf_opt_lwork : ?m:int -> ?n:int -> ?ar:int -> ?ac:int -> mat -> int

geqrf_opt_lwork ?m ?n ?ar ?ac a

  • returns

    the optimum length of the work-array used by the geqrf-function given matrix a and optionally its logical dimensions m and n.

  • parameter m

    default = number of rows in matrix a

  • parameter n

    default = number of columns in matrix a

  • parameter ar

    default = 1

  • parameter ac

    default = 1

val geqrf_min_lwork : n:int -> int

geqrf_min_lwork ~n

  • returns

    the minimum length of the work-array used by the geqrf-function if the matrix has n columns.

val geqrf : ?m:int -> ?n:int -> ?work:vec -> ?tau:vec -> ?ar:int -> ?ac:int -> mat -> vec

geqrf ?m ?n ?work ?tau ?ar ?ac a computes a QR factorization of a real m-by-n matrix a. See LAPACK documentation.

  • returns

    tau, the scalar factors of the elementary reflectors.

  • parameter m

    default = number of rows in matrix a

  • parameter n

    default = number of columns in matrix a

  • parameter work

    default = vec of optimum length

  • parameter tau

    default = vec of required length

  • parameter ar

    default = 1

  • parameter ac

    default = 1

Linear equations (simple drivers)
val gesv : ?n:int -> ?ipiv:Common.int32_vec -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

gesv ?n ?ipiv ?ar ?ac a ?nrhs ?br ?bc b computes the solution to a real system of linear equations a * X = b, where a is an n-by-n matrix and X and b are n-by-nrhs matrices. The LU decomposition with partial pivoting and row interchanges is used to factor a as a = P * L * U, where P is a permutation matrix, L is unit lower triangular, and U is upper triangular. The factored form of a is then used to solve the system of equations a * X = b. On exit, b contains the solution matrix X.

  • raises Failure

    if the matrix a is singular.

  • parameter n

    default = available number of columns in matrix a

  • parameter ipiv

    default = vec of length n

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val gbsv : ?n:int -> ?ipiv:Common.int32_vec -> ?abr:int -> ?abc:int -> mat -> int -> int -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

gbsv ?n ?ipiv ?abr ?abc ab kl ku ?nrhs ?br ?bc b computes the solution to a real system of linear equations a * X = b, where a is a band matrix of order n with kl subdiagonals and ku superdiagonals, and X and b are n-by-nrhs matrices. The LU decomposition with partial pivoting and row interchanges is used to factor a as a = L * U, where L is a product of permutation and unit lower triangular matrices with kl subdiagonals, and U is upper triangular with kl+ku superdiagonals. The factored form of a is then used to solve the system of equations a * X = b.

  • raises Failure

    if the matrix a is singular.

  • parameter n

    default = available number of columns in matrix ab

  • parameter ipiv

    default = vec of length n

  • parameter abr

    default = 1

  • parameter abc

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val gtsv : ?n:int -> ?ofsdl:int -> vec -> ?ofsd:int -> vec -> ?ofsdu:int -> vec -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

gtsv ?n ?ofsdl dl ?ofsd d ?ofsdu du ?nrhs ?br ?bc b solves the equation a * X = b where a is an n-by-n tridiagonal matrix, by Gaussian elimination with partial pivoting. Note that the equation A'*X = b may be solved by interchanging the order of the arguments du and dl.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = available length of vector d

  • parameter ofsdl

    default = 1

  • parameter ofsd

    default = 1

  • parameter ofsdu

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val posv : ?n:int -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

posv ?n ?up ?ar ?ac a ?nrhs ?br ?bc b computes the solution to a real system of linear equations a * X = b, where a is an n-by-n symmetric positive definite matrix and X and b are n-by-nrhs matrices. The Cholesky decomposition is used to factor a as a = U**T * U, if up = true, or a = L * L**T, if up = false, where U is an upper triangular matrix and L is a lower triangular matrix. The factored form of a is then used to solve the system of equations a * X = b.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = available number of columns in matrix a

  • parameter up

    default = true i.e., upper triangle of a is stored

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val ppsv : ?n:int -> ?up:bool -> ?ofsap:int -> vec -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

ppsv ?n ?up ?ofsap ap ?nrhs ?br ?bc b computes the solution to the real system of linear equations a * X = b, where a is an n-by-n symmetric positive definite matrix stored in packed format and X and b are n-by-nrhs matrices. The Cholesky decomposition is used to factor a as a = U**T * U, if up = true, or a = L * L**T, if up = false, where U is an upper triangular matrix and L is a lower triangular matrix. The factored form of a is then used to solve the system of equations a * X = b.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = the greater n s.t. n(n+1)/2 <= Vec.dim ap

  • parameter up

    default = true i.e., upper triangle of ap is stored

  • parameter ofsap

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val pbsv : ?n:int -> ?up:bool -> ?kd:int -> ?abr:int -> ?abc:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

pbsv ?n ?up ?kd ?abr ?abc ab ?nrhs ?br ?bc b computes the solution to a real system of linear equations a * X = b, where a is an n-by-n symmetric positive definite band matrix and X and b are n-by-nrhs matrices. The Cholesky decomposition is used to factor a as a = U**T * U, if up = true, or a = L * L**T, if up = false, where U is an upper triangular band matrix, and L is a lower triangular band matrix, with the same number of superdiagonals or subdiagonals as a. The factored form of a is then used to solve the system of equations a * X = b.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = available number of columns in matrix ab

  • parameter up

    default = true i.e., upper triangle of ab is stored

  • parameter kd

    default = available number of rows in matrix ab - 1

  • parameter abr

    default = 1

  • parameter abc

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val ptsv : ?n:int -> ?ofsd:int -> rvec -> ?ofse:int -> vec -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

ptsv ?n ?ofsd d ?ofse e ?nrhs ?br ?bc b computes the solution to the real system of linear equations a*X = b, where a is an n-by-n symmetric positive definite tridiagonal matrix, and X and b are n-by-nrhs matrices. A is factored as a = L*D*L**T, and the factored form of a is then used to solve the system of equations.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = available length of vector d

  • parameter ofsd

    default = 1

  • parameter ofse

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val sysv_opt_lwork : ?n:int -> ?up:bool -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> int

sysv_opt_lwork ?n ?up ?ar ?ac a ?nrhs ?br ?bc b

  • returns

    the optimum length of the work-array used by the sysv-function given matrix a, optionally its logical dimension n and given right hand side matrix b with an optional number nrhs of vectors.

  • parameter n

    default = available number of columns in matrix a

  • parameter up

    default = true i.e., upper triangle of a is stored

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val sysv : ?n:int -> ?up:bool -> ?ipiv:Common.int32_vec -> ?work:vec -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

sysv ?n ?up ?ipiv ?work ?ar ?ac a ?nrhs ?br ?bc b computes the solution to a real system of linear equations a * X = b, where a is an N-by-N symmetric matrix and X and b are n-by-nrhs matrices. The diagonal pivoting method is used to factor a as a = U * D * U**T, if up = true, or a = L * D * L**T, if up = false, where U (or L) is a product of permutation and unit upper (lower) triangular matrices, and D is symmetric and block diagonal with 1-by-1 and 2-by-2 diagonal blocks. The factored form of a is then used to solve the system of equations a * X = b.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = available number of columns in matrix a

  • parameter up

    default = true i.e., upper triangle of a is stored

  • parameter ipiv

    default = vec of length n

  • parameter work

    default = vec of optimum length (-> sysv_opt_lwork)

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val spsv : ?n:int -> ?up:bool -> ?ipiv:Common.int32_vec -> ?ofsap:int -> vec -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

spsv ?n ?up ?ipiv ?ofsap ap ?nrhs ?br ?bc b computes the solution to the real system of linear equations a * X = b, where a is an n-by-n symmetric matrix stored in packed format and X and b are n-by-nrhs matrices. The diagonal pivoting method is used to factor a as a = U * D * U**T, if up = true, or a = L * D * L**T, if up = false, where U (or L) is a product of permutation and unit upper (lower) triangular matrices, D is symmetric and block diagonal with 1-by-1 and 2-by-2 diagonal blocks. The factored form of a is then used to solve the system of equations a * X = b.

  • raises Failure

    if the matrix is singular.

  • parameter n

    default = the greater n s.t. n(n+1)/2 <= Vec.dim ap

  • parameter up

    default = true i.e., upper triangle of ap is stored

  • parameter ipiv

    default = vec of length n

  • parameter ofsap

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

Least squares (simple drivers)
val gels_min_lwork : m:int -> n:int -> nrhs:int -> int

gels_min_lwork ~m ~n ~nrhs

  • returns

    the minimum length of the work-array used by the gels-function if the logical dimensions of the matrix are m rows and n columns and if there are nrhs right hand side vectors.

val gels_opt_lwork : ?m:int -> ?n:int -> ?trans:Common.trans2 -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> int

gels_opt_lwork ?m ?n ?trans ?ar ?ac a ?nrhs ?br ?bc b

  • returns

    the optimum length of the work-array used by the gels-function given matrix a, optionally its logical dimensions m and n and given right hand side matrix b with an optional number nrhs of vectors.

  • parameter m

    default = available number of rows in matrix a

  • parameter n

    default = available number of columns in matrix a

  • parameter trans

    default = `N

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1

val gels : ?m:int -> ?n:int -> ?work:vec -> ?trans:Common.trans2 -> ?ar:int -> ?ac:int -> mat -> ?nrhs:int -> ?br:int -> ?bc:int -> mat -> unit

gels ?m ?n ?work ?trans ?ar ?ac a ?nrhs ?br ?bc b see LAPACK documentation!

  • parameter m

    default = available number of rows in matrix a

  • parameter n

    default = available number of columns of matrix a

  • parameter trans

    default = `N

  • parameter ar

    default = 1

  • parameter ac

    default = 1

  • parameter nrhs

    default = available number of columns in matrix b

  • parameter br

    default = 1

  • parameter bc

    default = 1