Skip to content

Commit b23c811

Browse files
authored
Merge branch 'master' into matrix_inverse
2 parents e2159bc + c0c0647 commit b23c811

18 files changed

+1066
-140
lines changed

doc/specs/stdlib_linalg.md

Lines changed: 92 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -777,7 +777,8 @@ Result vector `x` returns the approximate solution that minimizes the 2-norm \(
777777

778778
`cond` (optional): Shall be a scalar `real` value cut-off threshold for rank evaluation: `s_i >= cond*maxval(s), i=1:rank`. Shall be a scalar, `intent(in)` argument.
779779

780-
`singvals` (optional): Shall be a `real` rank-1 array of the same kind `a` and size at least `minval(shape(a))`, returning the list of singular values `s(i)>=cond*maxval(s)`, in descending order of magnitude. It is an `intent(out)` argument.
780+
`singvals` (optional): Shall be a `real` rank-1 array of the same kind `a` and size at least `m
781+
al(shape(a))`, returning the list of singular values `s(i)>=cond*maxval(s)`, in descending order of magnitude. It is an `intent(out)` argument.
781782

782783
`overwrite_a` (optional): Shall be an input `logical` flag. If `.true.`, input matrix `A` will be used as temporary storage and overwritten. This avoids internal data allocation. This is an `intent(in)` argument.
783784

@@ -899,6 +900,96 @@ Exceptions trigger an `error stop`.
899900
{!example/linalg/example_determinant2.f90!}
900901
```
901902

903+
## `svd` - Compute the singular value decomposition of a rank-2 array (matrix).
904+
905+
### Status
906+
907+
Experimental
908+
909+
### Description
910+
911+
This subroutine computes the singular value decomposition of a `real` or `complex` rank-2 array (matrix) \( A = U \cdot S \cdot \V^T \).
912+
The solver is based on LAPACK's `*GESDD` backends.
913+
914+
Result vector `s` returns the array of singular values on the diagonal of \( S \).
915+
If requested, `u` contains the left singular vectors, as columns of \( U \).
916+
If requested, `vt` contains the right singular vectors, as rows of \( V^T \).
917+
918+
### Syntax
919+
920+
`call ` [[stdlib_linalg(module):svd(interface)]] `(a, s, [, u, vt, overwrite_a, full_matrices, err])`
921+
922+
### Class
923+
Subroutine
924+
925+
### Arguments
926+
927+
`a`: Shall be a rank-2 `real` or `complex` array containing the coefficient matrix of size `[m,n]`. It is an `intent(inout)` argument, but returns unchanged unless `overwrite_a=.true.`.
928+
929+
`s`: Shall be a rank-1 `real` array, returning the list of `k = min(m,n)` singular values. It is an `intent(out)` argument.
930+
931+
`u` (optional): Shall be a rank-2 array of same kind as `a`, returning the left singular vectors of `a` as columns. Its size should be `[m,m]` unless `full_matrices=.false.`, in which case, it can be `[m,min(m,n)]`. It is an `intent(out)` argument.
932+
933+
`vt` (optional): Shall be a rank-2 array of same kind as `a`, returning the right singular vectors of `a` as rows. Its size should be `[n,n]` unless `full_matrices=.false.`, in which case, it can be `[min(m,n),n]`. It is an `intent(out)` argument.
934+
935+
`overwrite_a` (optional): Shall be an input `logical` flag. If `.true.`, input matrix `A` will be used as temporary storage and overwritten. This avoids internal data allocation. By default, `overwrite_a=.false.`. It is an `intent(in)` argument.
936+
937+
`full_matrices` (optional): Shall be an input `logical` flag. If `.true.` (default), matrices `u` and `vt` shall be full-sized. Otherwise, their secondary dimension can be resized to `min(m,n)`. See `u`, `v` for details.
938+
939+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
940+
941+
### Return values
942+
943+
Returns an array `s` that contains the list of singular values of matrix `a`.
944+
If requested, returns a rank-2 array `u` that contains the left singular vectors of `a` along its columns.
945+
If requested, returns a rank-2 array `vt` that contains the right singular vectors of `a` along its rows.
946+
947+
Raises `LINALG_ERROR` if the underlying Singular Value Decomposition process did not converge.
948+
Raises `LINALG_VALUE_ERROR` if the matrix or any of the output arrays invalid/incompatible sizes.
949+
Exceptions trigger an `error stop`, unless argument `err` is present.
950+
951+
### Example
952+
953+
```fortran
954+
{!example/linalg/example_svd.f90!}
955+
```
956+
957+
## `svdvals` - Compute the singular values of a rank-2 array (matrix).
958+
959+
### Status
960+
961+
Experimental
962+
963+
### Description
964+
965+
This subroutine computes the singular values of a `real` or `complex` rank-2 array (matrix) from its singular
966+
value decomposition \( A = U \cdot S \cdot \V^T \). The solver is based on LAPACK's `*GESDD` backends.
967+
968+
Result vector `s` returns the array of singular values on the diagonal of \( S \).
969+
970+
### Syntax
971+
972+
`s = ` [[stdlib_linalg(module):svdvals(interface)]] `(a [, err])`
973+
974+
### Arguments
975+
976+
`a`: Shall be a rank-2 `real` or `complex` array containing the coefficient matrix of size `[m,n]`. It is an `intent(in)` argument.
977+
978+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
979+
980+
### Return values
981+
982+
Returns an array `s` that contains the list of singular values of matrix `a`.
983+
984+
Raises `LINALG_ERROR` if the underlying Singular Value Decomposition process did not converge.
985+
Raises `LINALG_VALUE_ERROR` if the matrix or any of the output arrays invalid/incompatible sizes.
986+
Exceptions trigger an `error stop`, unless argument `err` is present.
987+
988+
### Example
989+
990+
```fortran
991+
{!example/linalg/example_svdvals.f90!}
992+
```
902993
## `.inv.` - Inverse operator of a square matrix
903994

904995
### Status

doc/specs/stdlib_sorting.md

Lines changed: 17 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -24,17 +24,18 @@ module's `string_type` type.
2424

2525
## Overview of the module
2626

27-
The module `stdlib_sorting` defines several public entities, one
28-
default integer parameter, `int_index`, and four overloaded
27+
The module `stdlib_sorting` defines several public entities, two
28+
default integer parameters, `int_index` and `int_index_low`, and four overloaded
2929
subroutines: `ORD_SORT`, `SORT`, `RADIX_SORT` and `SORT_INDEX`. The
3030
overloaded subroutines also each have several specific names for
3131
versions corresponding to different types of array arguments.
3232

33-
### The `int_index` parameter
33+
### The parameters `int_index` and `int_index_low`
3434

35-
The `int_index` parameter is used to specify the kind of integer used
36-
in indexing the various arrays. Currently the module sets `int_index`
37-
to the value of `int64` from the `stdlib_kinds` module.
35+
The parameters `int_index` and `int_index_low` are used to specify the kind of integer used
36+
in indexing the various arrays. Currently the module sets `int_index` and
37+
`int_index_low`
38+
to the value of `int64` and `int32` from the `stdlib_kinds` module, respectively.
3839

3940
### The module subroutines
4041

@@ -414,7 +415,7 @@ It is an `intent(inout)` argument. On input it
414415
will be an array whose sorting indices are to be determined. On return
415416
it will be the sorted array.
416417

417-
`index`: shall be a rank one integer array of kind `int_index` and of
418+
`index`: shall be a rank one integer array of kind `int_index` or `int_index_low` and of
418419
the size of `array`. It is an `intent(out)` argument. On return it
419420
shall have values that are the indices needed to sort the original
420421
array in the desired direction.
@@ -426,8 +427,8 @@ memory for internal record keeping. If associated with an array in
426427
static storage, its use can significantly reduce the stack memory
427428
requirements for the code. Its contents on return are undefined.
428429

429-
`iwork` (optional): shall be a rank one integer array of kind
430-
`int_index`, and shall have at least `size(array)/2` elements. It
430+
`iwork` (optional): shall be a rank one integer array of the same kind
431+
of the array `index`, and shall have at least `size(array)/2` elements. It
431432
is an `intent(out)` argument. It is intended to be used as "scratch"
432433
memory for internal record keeping. If associated with an array in
433434
static storage, its use can significantly reduce the stack memory
@@ -457,6 +458,12 @@ different on return
457458

458459
##### Examples
459460

461+
Sorting a rank one array with `sort_index`:
462+
463+
```Fortran
464+
{!example/sorting/example_sort_index.f90!}
465+
```
466+
460467
Sorting a related rank one array:
461468

462469
```Fortran
@@ -504,7 +511,7 @@ Sorting an array of a derived type based on the data in one component
504511

505512
```fortran
506513
subroutine sort_a_data( a_data, a, work, index, iwork )
507-
! Sort `a_data` in terms or its component `a`
514+
! Sort `a_data` in terms of its component `a`
508515
type(a_type), intent(inout) :: a_data(:)
509516
integer(int32), intent(inout) :: a(:)
510517
integer(int32), intent(out) :: work(:)

example/linalg/CMakeLists.txt

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -26,5 +26,7 @@ ADD_EXAMPLE(lstsq2)
2626
ADD_EXAMPLE(solve1)
2727
ADD_EXAMPLE(solve2)
2828
ADD_EXAMPLE(solve3)
29+
ADD_EXAMPLE(svd)
30+
ADD_EXAMPLE(svdvals)
2931
ADD_EXAMPLE(determinant)
3032
ADD_EXAMPLE(determinant2)

example/linalg/example_svd.f90

Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,50 @@
1+
! Singular Value Decomposition
2+
program example_svd
3+
use stdlib_linalg_constants, only: dp
4+
use stdlib_linalg, only: svd
5+
implicit none
6+
7+
real(dp), allocatable :: A(:,:),s(:),u(:,:),vt(:,:)
8+
character(*), parameter :: fmt = "(a,*(1x,f12.8))"
9+
10+
! We want to find the singular value decomposition of matrix:
11+
!
12+
! A = [ 3 2 2]
13+
! [ 2 3 -2]
14+
!
15+
A = transpose(reshape([ 3, 2, 2, &
16+
2, 3,-2], [3,2]))
17+
18+
! Prepare arrays
19+
allocate(s(2),u(2,2),vt(3,3))
20+
21+
! Get singular value decomposition
22+
call svd(A,s,u,vt)
23+
24+
! Singular values: [5, 3]
25+
print fmt, ' '
26+
print fmt, 'S = ',s
27+
print fmt, ' '
28+
29+
! Left vectors (may be flipped):
30+
! [Ã2/2 Ã2/2]
31+
! U = [Ã2/2 -Ã2/2]
32+
!
33+
print fmt, ' '
34+
print fmt, 'U = ',u(1,:)
35+
print fmt, ' ',u(2,:)
36+
37+
38+
! Right vectors (may be flipped):
39+
! [Ã2/2 Ã2/2 0]
40+
! V = [1/Ã18 -1/Ã18 4/Ã18]
41+
! [ 2/3 -2/3 -1/3]
42+
!
43+
print fmt, ' '
44+
print fmt, ' ',vt(1,:)
45+
print fmt, 'VT= ',vt(2,:)
46+
print fmt, ' ',vt(3,:)
47+
print fmt, ' '
48+
49+
50+
end program example_svd

example/linalg/example_svdvals.f90

Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
! Singular Values
2+
program example_svdvals
3+
use stdlib_linalg_constants, only: dp
4+
use stdlib_linalg, only: svdvals
5+
implicit none
6+
7+
real(dp), allocatable :: A(:,:),s(:)
8+
character(*), parameter :: fmt="(a,*(1x,f12.8))"
9+
10+
! We want to find the singular values of matrix:
11+
!
12+
! A = [ 3 2 2]
13+
! [ 2 3 -2]
14+
!
15+
A = transpose(reshape([ 3, 2, 2, &
16+
2, 3,-2], [3,2]))
17+
18+
! Get singular values
19+
s = svdvals(A)
20+
21+
! Singular values: [5, 3]
22+
print fmt, ' '
23+
print fmt, 'S = ',s
24+
print fmt, ' '
25+
26+
end program example_svdvals

example/sorting/CMakeLists.txt

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
ADD_EXAMPLE(ord_sort)
22
ADD_EXAMPLE(sort)
3+
ADD_EXAMPLE(sort_index)
34
ADD_EXAMPLE(radix_sort)
4-
ADD_EXAMPLE(sort_bitset)
5+
ADD_EXAMPLE(sort_bitset)
Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
program example_sort_index
2+
use stdlib_sorting, only: sort_index
3+
implicit none
4+
integer, allocatable :: array(:)
5+
integer, allocatable :: index(:)
6+
7+
array = [5, 4, 3, 1, 10, 4, 9]
8+
allocate(index, mold=array)
9+
10+
call sort_index(array, index)
11+
12+
print *, array !print [1, 3, 4, 4, 5, 9, 10]
13+
print *, index !print [4, 3, 2, 6, 1, 7, 5]
14+
15+
end program example_sort_index

src/CMakeLists.txt

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,8 @@ set(fppFiles
3030
stdlib_linalg_solve.fypp
3131
stdlib_linalg_determinant.fypp
3232
stdlib_linalg_inverse.fypp
33-
stdlib_linalg_state.fypp
33+
stdlib_linalg_state.fypp
34+
stdlib_linalg_svd.fypp
3435
stdlib_optval.fypp
3536
stdlib_selection.fypp
3637
stdlib_sorting.fypp

0 commit comments

Comments
 (0)