Skip to content

Commit 6abe7df

Browse files
committed
document svd and interface
1 parent 063b421 commit 6abe7df

File tree

2 files changed

+65
-7
lines changed

2 files changed

+65
-7
lines changed

src/stdlib_linalg.fypp

Lines changed: 45 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -458,24 +458,64 @@ module stdlib_linalg
458458
#:endfor
459459
end interface
460460

461-
! Singular value decomposition
462-
interface svd
461+
! Singular value decomposition
462+
interface svd
463463
!! version: experimental
464464
!!
465+
!! Computes the singular value decomposition of a `real` or `complex` 2d matrix.
466+
!!
467+
!!### Summary
468+
!! Interface for computing the singular value decomposition of a `real` or `complex` 2d matrix.
469+
!!
465470
!!### Description
466471
!!
472+
!! This interface provides methods for computing the singular value decomposition of a matrix.
473+
!! Supported data types include `real` and `complex`. The subroutine returns a `real` array of
474+
!! singular values, and optionally, left- and right- singular vector matrices, `U` and `V`.
475+
!! For a matrix `A` with size [m,n], full matrix storage for `U` and `V` should be [m,m] and [n,n].
476+
!! It is possible to use partial storage [m,k] and [k,n], `k=min(m,n)`, choosing `full_matrices=.false.`.
467477
!!
468-
478+
!!@note The solution is based on LAPACK's singular value decomposition `*GESDD` methods.
479+
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
480+
!!
481+
!!### Example
482+
!!
483+
!!```fortran
484+
!! real(sp) :: a(2,3), s(2), u(2,2), vt(3,3)
485+
!! a = reshape([3,2, 2,3, 2,-2],[2,3])
486+
!!
487+
!! call svd(A,s,u,v)
488+
!! print *, 'singular values = ',s
489+
!!```
490+
!!
469491
#:for rk,rt,ri in RC_KINDS_TYPES
470492
#:if rk!="xdp"
471493
module subroutine stdlib_linalg_svd_${ri}$(a,s,u,vt,overwrite_a,full_matrices,err)
494+
!!### Summary
495+
!! Compute singular value decomposition of a matrix \( A = U \cdot S \cdot \V^T \)
496+
!!
497+
!!### Description
498+
!!
499+
!! This function computes the singular value decomposition of a `real` or `complex` matrix \( A \),
500+
!! and returns the array of singular values, and optionally the left matrix \( U \) containing the
501+
!! left unitary singular vectors, and the right matrix \( V^T \), containing the right unitary
502+
!! singular vectors.
503+
!!
504+
!! param: a Input matrix of size [m,n].
505+
!! param: s Output `real` array of size [min(m,n)] returning a list of singular values.
506+
!! param: u [optional] Output left singular matrix of size [m,m] or [m,min(m,n)] (.not.full_matrices). Contains singular vectors as columns.
507+
!! param: vt [optional] Output right singular matrix of size [n,n] or [min(m,n),n] (.not.full_matrices). Contains singular vectors as rows.
508+
!! param: overwrite_a [optional] Flag indicating if the input matrix can be overwritten.
509+
!! param: full_matrices [optional] If `.true.` (default), matrices \( U \) and \( V^T \) have size [m,m], [n,n]. Otherwise, they are [m,k], [k,n] with `k=min(m,n)`.
510+
!! param: err [optional] State return flag.
511+
!!
472512
!> Input matrix A[m,n]
473513
${rt}$, intent(inout), target :: a(:,:)
474514
!> Array of singular values
475515
real(${rk}$), intent(out) :: s(:)
476-
!> The columns of U contain the eigenvectors of A A^T
516+
!> The columns of U contain the left singular vectors
477517
${rt}$, optional, intent(out), target :: u(:,:)
478-
!> The rows of V^T contain the eigenvectors of A^T A
518+
!> The rows of V^T contain the right singular vectors
479519
${rt}$, optional, intent(out), target :: vt(:,:)
480520
!> [optional] Can A data be overwritten and destroyed?
481521
logical(lk), optional, intent(in) :: overwrite_a

src/stdlib_linalg_svd.fypp

Lines changed: 20 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -91,13 +91,31 @@ submodule(stdlib_linalg) stdlib_linalg_svd
9191

9292
!> SVD of matrix A = U S V^T, returning S and optionally U and V^T
9393
module subroutine stdlib_linalg_svd_${ri}$(a,s,u,vt,overwrite_a,full_matrices,err)
94+
!!### Summary
95+
!! Compute singular value decomposition of a matrix \( A = U \cdot S \cdot \V^T \)
96+
!!
97+
!!### Description
98+
!!
99+
!! This function computes the singular value decomposition of a `real` or `complex` matrix \( A \),
100+
!! and returns the array of singular values, and optionally the left matrix \( U \) containing the
101+
!! left unitary singular vectors, and the right matrix \( V^T \), containing the right unitary
102+
!! singular vectors.
103+
!!
104+
!! param: a Input matrix of size [m,n].
105+
!! param: s Output `real` array of size [min(m,n)] returning a list of singular values.
106+
!! param: u [optional] Output left singular matrix of size [m,m] or [m,min(m,n)] (.not.full_matrices). Contains singular vectors as columns.
107+
!! param: vt [optional] Output right singular matrix of size [n,n] or [min(m,n),n] (.not.full_matrices). Contains singular vectors as rows.
108+
!! param: overwrite_a [optional] Flag indicating if the input matrix can be overwritten.
109+
!! param: full_matrices [optional] If `.true.` (default), matrices \( U \) and \( V^T \) have size [m,m], [n,n]. Otherwise, they are [m,k], [k,n] with `k=min(m,n)`.
110+
!! param: err [optional] State return flag.
111+
!!
94112
!> Input matrix A[m,n]
95113
${rt}$, intent(inout), target :: a(:,:)
96114
!> Array of singular values
97115
real(${rk}$), intent(out) :: s(:)
98-
!> The columns of U contain the eigenvectors of A A^T
116+
!> The columns of U contain the left singular vectors
99117
${rt}$, optional, intent(out), target :: u(:,:)
100-
!> The rows of V^T contain the eigenvectors of A^T A
118+
!> The rows of V^T contain the right singular vectors
101119
${rt}$, optional, intent(out), target :: vt(:,:)
102120
!> [optional] Can A data be overwritten and destroyed?
103121
logical(lk), optional, intent(in) :: overwrite_a

0 commit comments

Comments
 (0)