Skip to content

Commit ea7d35e

Browse files
committed
shorten factorization procedures names
1 parent 5cb2ad7 commit ea7d35e

File tree

4 files changed

+24
-25
lines changed

4 files changed

+24
-25
lines changed

src/stdlib_linalg_iterative_aux.fypp

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -134,7 +134,7 @@ contains
134134
! Factorization for preconditioners
135135
!==============================================================
136136
#:for k, t, s in R_KINDS_TYPES
137-
module subroutine factorize_ssor_dense_${s}$(A, w, L, D)
137+
module subroutine ssor_dense_${s}$(A, w, L, D)
138138
${t}$, intent(in) :: A(:,:)
139139
${t}$, intent(in) :: w
140140
${t}$, intent(inout) :: L(:,:)
@@ -161,7 +161,7 @@ contains
161161
#:endfor
162162

163163
#:for k, t, s in R_KINDS_TYPES
164-
module subroutine factorize_ssor_csr_${s}$(A, w, L, D)
164+
module subroutine ssor_csr_${s}$(A, w, L, D)
165165
type(CSR_${s}$_type), intent(in) :: A
166166
${t}$, intent(in) :: w
167167
type(CSR_${s}$_type), intent(inout) :: L
@@ -202,7 +202,7 @@ contains
202202
!> Bunch-Kaufman factorization of a symmetric positive definite matrix A.
203203
!> The matrix A is assumed to be symmetric and positive definite.
204204
#:for k, t, s in R_KINDS_TYPES
205-
module subroutine factorize_ldlt_dense_${s}$(A, L, D)
205+
module subroutine ldlt_dense_${s}$(A, L, D)
206206
${t}$, intent(in) :: A(:,:)
207207
${t}$, intent(inout) :: L(:,:)
208208
${t}$, intent(inout) :: D(:)
@@ -242,7 +242,7 @@ contains
242242
#:endfor
243243

244244
#:for k, t, s in R_KINDS_TYPES
245-
module subroutine factorize_ldlt_csr_${s}$(A, L, D)
245+
module subroutine ldlt_csr_${s}$(A, L, D)
246246
type(CSR_${s}$_type), intent(in) :: A
247247
type(CSR_${s}$_type), intent(inout) :: L
248248
${t}$, intent(inout) :: D(:)

src/stdlib_linalg_iterative_solvers.fypp

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -167,39 +167,39 @@ module stdlib_linalg_iterative_solvers
167167
end interface
168168
public :: solve_backward_triangular
169169

170-
interface factorize_ldlt
170+
interface ldlt
171171
#:for k, t, s in R_KINDS_TYPES
172-
module subroutine factorize_ldlt_dense_${s}$(A, L, D)
172+
module subroutine ldlt_dense_${s}$(A, L, D)
173173
${t}$, intent(in) :: A(:,:)
174174
${t}$, intent(inout) :: L(:,:)
175175
${t}$, intent(inout) :: D(:)
176176
end subroutine
177-
module subroutine factorize_ldlt_csr_${s}$(A, L, D)
177+
module subroutine ldlt_csr_${s}$(A, L, D)
178178
type(CSR_${s}$_type), intent(in) :: A
179179
type(CSR_${s}$_type), intent(inout) :: L
180180
${t}$, intent(inout) :: D(:)
181181
end subroutine
182182
#:endfor
183183
end interface
184-
public :: factorize_ldlt
184+
public :: ldlt
185185

186-
interface factorize_ssor
186+
interface ssor
187187
#:for k, t, s in R_KINDS_TYPES
188-
module subroutine factorize_ssor_dense_${s}$(A, w, L, D)
188+
module subroutine ssor_dense_${s}$(A, w, L, D)
189189
${t}$, intent(in) :: A(:,:)
190190
${t}$, intent(in) :: w
191191
${t}$, intent(inout) :: L(:,:)
192192
${t}$, intent(inout) :: D(:)
193193
end subroutine
194-
module subroutine factorize_ssor_csr_${s}$(A, w, L, D)
194+
module subroutine ssor_csr_${s}$(A, w, L, D)
195195
type(CSR_${s}$_type), intent(in) :: A
196196
${t}$, intent(in) :: w
197197
type(CSR_${s}$_type), intent(inout) :: L
198198
${t}$, intent(inout) :: D(:)
199199
end subroutine
200200
#:endfor
201201
end interface
202-
public :: factorize_ssor
202+
public :: ssor
203203

204204

205205
contains

src/stdlib_linalg_iterative_solvers_pccg.fypp

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -12,10 +12,10 @@ submodule(stdlib_linalg_iterative_solvers) stdlib_linalg_iterative_pccg
1212
implicit none
1313

1414
enum, bind(c)
15-
enumerator :: none = 0
16-
enumerator :: jacobi
17-
enumerator :: ssor
18-
enumerator :: ldlt
15+
enumerator :: pc_none = 0
16+
enumerator :: pc_jacobi
17+
enumerator :: pc_ssor
18+
enumerator :: pc_ldlt
1919
end enum
2020

2121
contains
@@ -123,7 +123,7 @@ contains
123123
maxiter_ = n; if(present(maxiter)) maxiter_ = maxiter
124124
restart_ = .true.; if(present(restart)) restart_ = restart
125125
tol_ = 1.e-4_${s}$; if(present(tol)) tol_ = tol
126-
precond_ = none ; if(present(precond)) precond_ = precond
126+
precond_ = pc_none; if(present(precond)) precond_ = precond
127127
!-------------------------
128128
! internal memory setup
129129
! Preconditionner
@@ -134,25 +134,25 @@ contains
134134
allocate(diagonal(n),source=zero_${s}$)
135135

136136
select case(precond_)
137-
case(jacobi)
137+
case(pc_jacobi)
138138
#:if matrix == "dense"
139139
diagonal = diag(A)
140140
#:else
141141
call diag(A,diagonal)
142142
#:endif
143143
M_%apply => precond_jacobi
144-
case(ssor)
144+
case(pc_ssor)
145145
#:if matrix == "dense"
146146
diagonal = diag(A)
147147
#:else
148148
call diag(A,diagonal)
149149
#:endif
150150
L = A !> copy A structure to L
151-
call factorize_ssor( A , one_${s}$ , L, diagonal )
151+
call ssor( A , one_${s}$ , L, diagonal )
152152
M_%apply => precond_ldl
153-
case(ldlt)
153+
case(pc_ldlt)
154154
L = A !> copy A structure to L
155-
call factorize_ldlt( A , L, diagonal )
155+
call ldlt( A , L, diagonal )
156156
M_%apply => precond_ldl
157157
case default
158158
M_%apply => precond_none

test/linalg/test_linalg_solve_iterative.fypp

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -49,13 +49,12 @@ module test_linalg_solve_iterative
4949

5050
${t}$ :: L(5,5), D(5)
5151

52-
call factorize_ldlt(A, L, D)
52+
call ldlt(A, L, D)
5353

5454
call check(error, all(abs(L-Lref)<tol), 'LDLt factorization L doesnt match')
5555
if (allocated(error)) return
5656
call check(error, all(abs(D-Dref)<tol), 'LDLt factorization D doesnt match')
5757
if (allocated(error)) return
58-
5958
end block
6059

6160
#:endfor
@@ -76,7 +75,7 @@ module test_linalg_solve_iterative
7675
${t}$ :: Dref(3) = [${t}$ :: 4, 1, 9]
7776
${t}$ :: L(3,3), D(3), b(3), x(3), res(3)
7877

79-
call factorize_ldlt(A, L, D)
78+
call ldlt(A, L, D)
8079

8180
call check(error, all(abs(L-Lref)<tol), 'LDLt factorization L doesnt match')
8281
if (allocated(error)) return

0 commit comments

Comments
 (0)