Skip to content

Commit cbaac2f

Browse files
committed
Move handle_potrf_info to the auxliary function module.
1 parent 089d316 commit cbaac2f

File tree

2 files changed

+33
-25
lines changed

2 files changed

+33
-25
lines changed

src/lapack/stdlib_linalg_lapack_aux.fypp

Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1275,4 +1275,36 @@ module stdlib_linalg_lapack_aux
12751275

12761276
#:endfor
12771277

1278+
!----------------------------------------------------------------------------
1279+
!----- -----
1280+
!----- AUXILIARY INFO HANDLING FUNCTIONS FOR LAPACK SUBROUTINES -----
1281+
!----- -----
1282+
!----------------------------------------------------------------------------
1283+
1284+
elemental subroutine handle_potrf_info(info,triangle,lda,n,err)
1285+
character, intent(in) :: triangle
1286+
integer(ilp), intent(in) :: info,lda,n
1287+
type(linalg_state_type), intent(out) :: err
1288+
1289+
! Process output
1290+
select case (info)
1291+
case (0)
1292+
! Success
1293+
case (-1)
1294+
err = linalg_state_type(this,LINALG_INTERNAL_ERROR,'invalid triangle selection: ', &
1295+
triangle,'. should be U/L')
1296+
case (-2)
1297+
err = linalg_state_type(this,LINALG_VALUE_ERROR,'invalid matrix size n=',n)
1298+
case (-4)
1299+
err = linalg_state_type(this,LINALG_VALUE_ERROR,'invalid lda=',lda,': is < n = ',n)
1300+
case (1:)
1301+
err = linalg_state_type(this,LINALG_ERROR,'cannot complete factorization:',info, &
1302+
'-th order leading minor is not positive definite')
1303+
case default
1304+
err = linalg_state_type(this,LINALG_INTERNAL_ERROR,'catastrophic error')
1305+
end select
1306+
1307+
end subroutine handle_potrf_info
1308+
1309+
12781310
end module stdlib_linalg_lapack_aux

src/stdlib_linalg_cholesky.fypp

Lines changed: 1 addition & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
submodule (stdlib_linalg) stdlib_linalg_cholesky
55
use stdlib_linalg_constants
66
use stdlib_linalg_lapack, only: potrf
7+
use stdlib_linalg_lapack_aux, only: handle_potrf_info
78
use stdlib_linalg_state, only: linalg_state_type, linalg_error_handling, LINALG_ERROR, &
89
LINALG_INTERNAL_ERROR, LINALG_VALUE_ERROR
910
implicit none
@@ -13,31 +14,6 @@ submodule (stdlib_linalg) stdlib_linalg_cholesky
1314

1415
contains
1516

16-
elemental subroutine handle_potrf_info(info,triangle,lda,n,err)
17-
character, intent(in) :: triangle
18-
integer(ilp), intent(in) :: info,lda,n
19-
type(linalg_state_type), intent(out) :: err
20-
21-
! Process output
22-
select case (info)
23-
case (0)
24-
! Success
25-
case (-1)
26-
err = linalg_state_type(this,LINALG_INTERNAL_ERROR,'invalid triangle selection: ', &
27-
triangle,'. should be U/L')
28-
case (-2)
29-
err = linalg_state_type(this,LINALG_VALUE_ERROR,'invalid matrix size n=',n)
30-
case (-4)
31-
err = linalg_state_type(this,LINALG_VALUE_ERROR,'invalid lda=',lda,': is < n = ',n)
32-
case (1:)
33-
err = linalg_state_type(this,LINALG_ERROR,'cannot complete factorization:',info, &
34-
'-th order leading minor is not positive definite')
35-
case default
36-
err = linalg_state_type(this,LINALG_INTERNAL_ERROR,'catastrophic error')
37-
end select
38-
39-
end subroutine handle_potrf_info
40-
4117
#:for rk,rt,ri in RC_KINDS_TYPES
4218

4319
! Compute the Cholesky factorization of a symmetric / Hermitian matrix, A = L*L^T = U^T*U.

0 commit comments

Comments
 (0)