Skip to content

Commit df4016a

Browse files
authored
Merge branch 'master' into qr
2 parents 6fc0e1d + d685294 commit df4016a

19 files changed

+709
-69
lines changed

doc/specs/stdlib_linalg.md

+95-1
Original file line numberDiff line numberDiff line change
@@ -1244,6 +1244,101 @@ Exceptions trigger an `error stop`, unless argument `err` is present.
12441244
{!example/linalg/example_svdvals.f90!}
12451245
```
12461246

1247+
1248+
## `cholesky` - Compute the Cholesky factorization of a rank-2 square array (matrix)
1249+
1250+
### Status
1251+
1252+
Experimental
1253+
1254+
### Description
1255+
1256+
This subroutine computes the Cholesky factorization of a `real` or `complex` rank-2 square array (matrix),
1257+
\( A = L \cdot L^T \), or \( A = U^T \cdot U \). \( A \) is symmetric or complex Hermitian, and \( L \),
1258+
\( U \) are lower- or upper-triangular, respectively.
1259+
The solver is based on LAPACK's `*POTRF` backends.
1260+
1261+
### Syntax
1262+
1263+
`call ` [[stdlib_linalg(module):cholesky(interface)]] `(a, c, lower [, other_zeroed] [, err])`
1264+
1265+
### Class
1266+
Subroutine
1267+
1268+
### Arguments
1269+
1270+
`a`: Shall be a rank-2 square `real` or `complex` array containing the coefficient matrix of size `[n,n]`. It is an `intent(inout)` argument, but returns unchanged if the argument `c` is present.
1271+
1272+
`c` (optional): Shall be a rank-2 square `real` or `complex` of the same size and kind as `a`. It is an `intent(out)` argument, that returns the triangular Cholesky matrix `L` or `U`.
1273+
1274+
`lower`: Shall be an input `logical` flag. If `.true.`, the lower triangular decomposition \( A = L \cdot L^T \) will be performed. If `.false.`, the upper decomposition \( A = U^T \cdot U \) will be performed.
1275+
1276+
`other_zeroed` (optional): Shall be an input `logical` flag. If `.true.`, the unused part of the output matrix will contain zeroes. Otherwise, it will not be accessed. This saves cpu time. By default, `other_zeroed=.true.`. It is an `intent(in)` argument.
1277+
1278+
`err` (optional): Shall be a `type(linalg_state_type)` value. It is an `intent(out)` argument.
1279+
1280+
### Return values
1281+
1282+
The factorized matrix is returned in-place overwriting `a` if no other arguments are provided.
1283+
Otherwise, it can be provided as a second argument `c`. In this case, `a` is not overwritten.
1284+
The `logical` flag `lower` determines whether the lower- or the upper-triangular factorization should be performed.
1285+
1286+
Results are returned on the applicable triangular region of the output matrix, while the unused triangular region
1287+
is filled by zeroes by default. Optional argument `other_zeroed`, if `.false.` allows the expert user to avoid zeroing the unused part;
1288+
however, in this case, the unused region of the matrix is not accessed and will usually contain invalid values.
1289+
1290+
Raises `LINALG_ERROR` if the underlying process did not converge.
1291+
Raises `LINALG_VALUE_ERROR` if the matrix or any of the output arrays invalid/incompatible sizes.
1292+
Exceptions trigger an `error stop`, unless argument `err` is present.
1293+
1294+
### Example
1295+
1296+
```fortran
1297+
{!example/linalg/example_cholesky.f90!}
1298+
```
1299+
1300+
## `chol` - Compute the Cholesky factorization of a rank-2 square array (matrix)
1301+
1302+
### Status
1303+
1304+
Experimental
1305+
1306+
### Description
1307+
1308+
This is a `pure` functional interface for the Cholesky factorization of a `real` or
1309+
`complex` rank-2 square array (matrix) computed as \( A = L \cdot L^T \), or \( A = U^T \cdot U \).
1310+
\( A \) is symmetric or complex Hermitian, and \( L \), \( U \) are lower- or upper-triangular, respectively.
1311+
The solver is based on LAPACK's `*POTRF` backends.
1312+
1313+
Result matrix `c` has the same size and kind as `a`, and returns the lower or upper triangular factor.
1314+
1315+
### Syntax
1316+
1317+
`c = ` [[stdlib_linalg(module):chol(interface)]] `(a, lower [, other_zeroed])`
1318+
1319+
### Arguments
1320+
1321+
`a`: Shall be a rank-2 square `real` or `complex` array containing the coefficient matrix of size `[n,n]`. It is an `intent(inout)` argument, but returns unchanged if argument `c` is present.
1322+
1323+
`lower`: Shall be an input `logical` flag. If `.true.`, the lower triangular decomposition \( A = L \cdot L^T \) will be performed. If `.false.`, the upper decomposition \( A = U^T \cdot U \) will be performed.
1324+
1325+
`other_zeroed` (optional): Shall be an input `logical` flag. If `.true.`, the unused part of the output matrix will contain zeroes. Otherwise, it will not be accessed. This saves cpu time. By default, `other_zeroed=.true.`. It is an `intent(in)` argument.
1326+
1327+
### Return values
1328+
1329+
Returns a rank-2 array `c` of the same size and kind as `a`, that contains the triangular Cholesky matrix `L` or `U`.
1330+
1331+
Raises `LINALG_ERROR` if the underlying process did not converge.
1332+
Raises `LINALG_VALUE_ERROR` if the matrix or any of the output arrays invalid/incompatible sizes.
1333+
Exceptions trigger an `error stop`, unless argument `err` is present.
1334+
1335+
### Example
1336+
1337+
```fortran
1338+
{!example/linalg/example_chol.f90!}
1339+
```
1340+
1341+
12471342
## `.inv.` - Inverse operator of a square matrix
12481343

12491344
### Status
@@ -1273,7 +1368,6 @@ If an exception occurred on input errors, or singular matrix, `NaN`s will be ret
12731368
For fine-grained error control in case of singular matrices prefer the `subroutine` and the `function`
12741369
interfaces.
12751370

1276-
12771371
### Example
12781372

12791373
```fortran

doc/specs/stdlib_math.md

+64
Original file line numberDiff line numberDiff line change
@@ -382,6 +382,70 @@ Notes: Although the angle of the complex number `0` is undefined, `argpi((0,0))`
382382
{!example/math/example_math_argpi.f90!}
383383
```
384384

385+
### `deg2rad`
386+
387+
#### Status
388+
389+
Experimental
390+
391+
#### Class
392+
393+
Elemenal function.
394+
395+
### Description
396+
397+
`deg2rad` converts phase angles from degrees to radians.
398+
399+
#### Syntax
400+
401+
`result = ` [[stdlib_math(module):deg2rad(interface)]] `(theta)`
402+
403+
#### Arguments
404+
405+
`theta`: Shall be a `real` scalar/array.
406+
407+
#### Return value
408+
409+
Returns the `real` phase angle in radians.
410+
411+
#### Example
412+
413+
```fortran
414+
{!example/math/example_math_deg2rad.f90!}
415+
```
416+
417+
### `rad2deg`
418+
419+
#### Status
420+
421+
Experimental
422+
423+
#### Class
424+
425+
Elemenal function.
426+
427+
### Description
428+
429+
`rad2deg` converts phase angles from radians to degrees.
430+
431+
#### Syntax
432+
433+
`result = ` [[stdlib_math(module):rad2deg(interface)]] `(theta)`
434+
435+
#### Arguments
436+
437+
`theta`: Shall be a `real` scalar/array.
438+
439+
#### Return value
440+
441+
Returns the `real` phase angle in degrees.
442+
443+
#### Example
444+
445+
```fortran
446+
{!example/math/example_math_rad2deg.f90!}
447+
```
448+
385449
### `is_close` function
386450

387451
#### Description

example/linalg/CMakeLists.txt

+2
Original file line numberDiff line numberDiff line change
@@ -37,3 +37,5 @@ ADD_EXAMPLE(determinant)
3737
ADD_EXAMPLE(determinant2)
3838
ADD_EXAMPLE(qr)
3939
ADD_EXAMPLE(qr_space)
40+
ADD_EXAMPLE(cholesky)
41+
ADD_EXAMPLE(chol)

example/linalg/example_chol.f90

+25
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,25 @@
1+
! Cholesky factorization: function interface
2+
program example_chol
3+
use stdlib_linalg, only: chol
4+
implicit none
5+
6+
real, allocatable, dimension(:,:) :: A,L,U
7+
8+
! Set real matrix
9+
A = reshape( [ [6, 15, 55], &
10+
[15, 55, 225], &
11+
[55, 225, 979] ], [3,3] )
12+
13+
! Decompose (lower)
14+
L = chol(A, lower=.true.)
15+
16+
! Compare decomposition
17+
print *, maxval(abs(A-matmul(L,transpose(L))))
18+
19+
! Decompose (upper)
20+
U = chol(A, lower=.false.)
21+
22+
! Compare decomposition
23+
print *, maxval(abs(A-matmul(transpose(U),U)))
24+
25+
end program example_chol

example/linalg/example_cholesky.f90

+25
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,25 @@
1+
! Cholesky factorization: subroutine interface
2+
program example_cholesky
3+
use stdlib_linalg, only: cholesky
4+
implicit none
5+
6+
real, dimension(3,3) :: A,L,U
7+
8+
! Set real matrix
9+
A = reshape( [ [6, 15, 55], &
10+
[15, 55, 225], &
11+
[55, 225, 979] ], [3,3] )
12+
13+
! Decompose (lower)
14+
call cholesky(A, L, lower=.true.)
15+
16+
! Compare decomposition
17+
print *, maxval(abs(A-matmul(L,transpose(L))))
18+
19+
! Decompose (upper)
20+
call cholesky(A, U, lower=.false.)
21+
22+
! Compare decomposition
23+
print *, maxval(abs(A-matmul(transpose(U),U)))
24+
25+
end program example_cholesky

example/math/CMakeLists.txt

+2
Original file line numberDiff line numberDiff line change
@@ -12,5 +12,7 @@ ADD_EXAMPLE(math_arange)
1212
ADD_EXAMPLE(math_argd)
1313
ADD_EXAMPLE(math_arg)
1414
ADD_EXAMPLE(math_argpi)
15+
ADD_EXAMPLE(math_deg2rad)
16+
ADD_EXAMPLE(math_rad2deg)
1517
ADD_EXAMPLE(math_is_close)
1618
ADD_EXAMPLE(meshgrid)

example/math/example_math_deg2rad.f90

+8
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
program example_math_deg2rad
2+
use stdlib_math, only: deg2rad
3+
implicit none
4+
print *, deg2rad(0.0) ! 0.0
5+
print *, deg2rad(90.0) ! 1.57508
6+
print *, deg2rad(-180.0) ! -3.1416
7+
8+
end program example_math_deg2rad

example/math/example_math_rad2deg.f90

+9
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
program example_math_rad2deg
2+
use stdlib_math, only: rad2deg
3+
use stdlib_constants, only: PI_sp
4+
implicit none
5+
print *, rad2deg(0.0) ! 0.0
6+
print *, rad2deg(PI_sp / 2.0) ! 90.0
7+
print *, rad2deg(-PI_sp) ! -3.1416
8+
9+
end program example_math_rad2deg

src/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,7 @@ set(fppFiles
3434
stdlib_linalg_inverse.fypp
3535
stdlib_linalg_state.fypp
3636
stdlib_linalg_svd.fypp
37+
stdlib_linalg_cholesky.fypp
3738
stdlib_optval.fypp
3839
stdlib_selection.fypp
3940
stdlib_sorting.fypp

src/stdlib_linalg.fypp

+81
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,8 @@ module stdlib_linalg
1616
implicit none
1717
private
1818

19+
public :: chol
20+
public :: cholesky
1921
public :: det
2022
public :: operator(.det.)
2123
public :: diag
@@ -51,6 +53,85 @@ module stdlib_linalg
5153
! Export linalg error handling
5254
public :: linalg_state_type, linalg_error_handling
5355

56+
interface chol
57+
!! version: experimental
58+
!!
59+
!! Computes the Cholesky factorization \( A = L \cdot L^T \), or \( A = U^T \cdot U \).
60+
!! ([Specification](../page/specs/stdlib_linalg.html#chol-compute-the-cholesky-factorization-of-a-rank-2-square-array-matrix))
61+
!!
62+
!!### Summary
63+
!! Pure function interface for computing the Cholesky triangular factors.
64+
!!
65+
!!### Description
66+
!!
67+
!! This interface provides methods for computing the lower- or upper- triangular matrix from the
68+
!! Cholesky factorization of a `real` symmetric or `complex` Hermitian matrix.
69+
!! Supported data types include `real` and `complex`.
70+
!!
71+
!!@note The solution is based on LAPACK's `*POTRF` methods.
72+
!!
73+
#:for rk,rt,ri in RC_KINDS_TYPES
74+
pure module function stdlib_linalg_${ri}$_cholesky_fun(a,lower,other_zeroed) result(c)
75+
!> Input matrix a[m,n]
76+
${rt}$, intent(in) :: a(:,:)
77+
!> [optional] is the lower or upper triangular factor required? Default = lower
78+
logical(lk), optional, intent(in) :: lower
79+
!> [optional] should the unused half of the return matrix be zeroed out? Default: yes
80+
logical(lk), optional, intent(in) :: other_zeroed
81+
!> Output matrix with Cholesky factors c[n,n]
82+
${rt}$ :: c(size(a,1),size(a,2))
83+
end function stdlib_linalg_${ri}$_cholesky_fun
84+
#:endfor
85+
end interface chol
86+
87+
interface cholesky
88+
!! version: experimental
89+
!!
90+
!! Computes the Cholesky factorization \( A = L \cdot L^T \), or \( A = U^T \cdot U \).
91+
!! ([Specification](../page/specs/stdlib_linalg.html#cholesky-compute-the-cholesky-factorization-of-a-rank-2-square-array-matrix))
92+
!!
93+
!!### Summary
94+
!! Pure subroutine interface for computing the Cholesky triangular factors.
95+
!!
96+
!!### Description
97+
!!
98+
!! This interface provides methods for computing the lower- or upper- triangular matrix from the
99+
!! Cholesky factorization of a `real` symmetric or `complex` Hermitian matrix.
100+
!! Supported data types include `real` and `complex`.
101+
!! The factorization is computed in-place if only one matrix argument is present; or returned into
102+
!! a second matrix argument, if present. The `lower` `logical` flag allows to select between upper or
103+
!! lower factorization; the `other_zeroed` optional `logical` flag allows to choose whether the unused
104+
!! part of the triangular matrix should be filled with zeroes.
105+
!!
106+
!!@note The solution is based on LAPACK's `*POTRF` methods.
107+
!!
108+
#:for rk,rt,ri in RC_KINDS_TYPES
109+
pure module subroutine stdlib_linalg_${ri}$_cholesky_inplace(a,lower,other_zeroed,err)
110+
!> Input matrix a[m,n]
111+
${rt}$, intent(inout), target :: a(:,:)
112+
!> [optional] is the lower or upper triangular factor required? Default = lower
113+
logical(lk), optional, intent(in) :: lower
114+
!> [optional] should the unused half of the return matrix be zeroed out? Default: yes
115+
logical(lk), optional, intent(in) :: other_zeroed
116+
!> [optional] state return flag. On error if not requested, the code will stop
117+
type(linalg_state_type), optional, intent(out) :: err
118+
end subroutine stdlib_linalg_${ri}$_cholesky_inplace
119+
120+
pure module subroutine stdlib_linalg_${ri}$_cholesky(a,c,lower,other_zeroed,err)
121+
!> Input matrix a[n,n]
122+
${rt}$, intent(in) :: a(:,:)
123+
!> Output matrix with Cholesky factors c[n,n]
124+
${rt}$, intent(out) :: c(:,:)
125+
!> [optional] is the lower or upper triangular factor required? Default = lower
126+
logical(lk), optional, intent(in) :: lower
127+
!> [optional] should the unused half of the return matrix be zeroed out? Default: yes
128+
logical(lk), optional, intent(in) :: other_zeroed
129+
!> [optional] state return flag. On error if not requested, the code will stop
130+
type(linalg_state_type), optional, intent(out) :: err
131+
end subroutine stdlib_linalg_${ri}$_cholesky
132+
#:endfor
133+
end interface cholesky
134+
54135
interface diag
55136
!! version: experimental
56137
!!

0 commit comments

Comments
 (0)