Skip to content

Commit 6627f4c

Browse files
committed
clean docstrings
1 parent 463259b commit 6627f4c

4 files changed

+22
-23
lines changed

src/stdlib_linalg_iterative_aux.fypp

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -63,7 +63,7 @@ contains
6363
aux = zero_${s}$
6464
do m = L%rowptr(i), L%rowptr(i+1)-1
6565
j = L%col(m)
66-
if(j>i) cycle !> skip upper part of the matrix
66+
if(j>i) cycle ! skip upper part of the matrix
6767
aux = aux + L%data(m)*x(j)
6868
end do
6969
x(i) = b(i) - aux
@@ -77,7 +77,7 @@ contains
7777
end do
7878
x(i) = b(i) - aux
7979
end do
80-
case(sparse_upper) !> treates as lower triangular (thus transpose)
80+
case(sparse_upper) ! treates as lower triangular (thus transpose)
8181
do i = 1, L%nrows
8282
x(i) = b(i)
8383
do m = L%rowptr(i)+1, L%rowptr(i+1)-1
@@ -104,7 +104,7 @@ contains
104104
x(i) = b(i) - baux(i)
105105
do m = Lt%rowptr(i), Lt%rowptr(i+1)-1
106106
j = Lt%col(m)
107-
if(j<i) cycle !> skip lower part of the matrix
107+
if(j<i) cycle ! skip lower part of the matrix
108108
baux(j) = baux(j) + Lt%data(m)*x(i)
109109
end do
110110
end do
@@ -199,8 +199,8 @@ contains
199199

200200
#:endfor
201201

202-
!> Bunch-Kaufman factorization of a symmetric positive definite matrix A.
203-
!> The matrix A is assumed to be symmetric and positive definite.
202+
!! Bunch-Kaufman factorization of a symmetric positive definite matrix A.
203+
!! The matrix A is assumed to be symmetric and positive definite.
204204
#:for k, t, s in R_KINDS_TYPES
205205
module subroutine ldlt_dense_${s}$(A, L, D)
206206
${t}$, intent(in) :: A(:,:)

src/stdlib_linalg_iterative_solvers.fypp

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -11,8 +11,7 @@ module stdlib_linalg_iterative_solvers
1111
implicit none
1212
private
1313

14-
!> brief workspace size for the iterative solvers
15-
!> details The size of the workspace is defined by the number of vectors used in the iterative solver.
14+
!! workspace sizes: defined by the number of vectors used by the iterative solver.
1615
enum, bind(c)
1716
enumerator :: size_wksp_cg = 3
1817
enumerator :: size_wksp_pcg = 4
@@ -150,7 +149,7 @@ module stdlib_linalg_iterative_solvers
150149
public :: solve_pcg
151150

152151
interface solve_forward_triangular
153-
!> Solve the system L x = b, where L is a strictly lower triangular matrix (diagonal assumed = 1).
152+
! Solve the system L x = b, where L is a strictly lower triangular matrix (diagonal assumed = 1).
154153
#:for k, t, s in R_KINDS_TYPES
155154
module subroutine solve_forward_triangular_dense_${s}$(L,b,x)
156155
${t}$, intent(in) :: L(:,:)
@@ -168,7 +167,7 @@ module stdlib_linalg_iterative_solvers
168167

169168

170169
interface solve_backward_triangular
171-
!> Solve the system U x = b, where U is a strictly upper triangular matrix (diagonal assumed = 1).
170+
! Solve the system U x = b, where U is a strictly upper triangular matrix (diagonal assumed = 1).
172171
#:for k, t, s in R_KINDS_TYPES
173172
module subroutine solve_backward_triangular_dense_${s}$(Lt,b,x)
174173
${t}$, intent(in) :: Lt(:,:)

src/stdlib_linalg_iterative_solvers_cg.fypp

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ contains
3434
if(associated(workspace%callback)) call workspace%callback(x, norm_sq0, iter)
3535

3636
R = B
37-
call A%apply(X, R, alpha= -one_${s}$, beta=one_${s}$) !> R = B - A*X
37+
call A%apply(X, R, alpha= -one_${s}$, beta=one_${s}$) ! R = B - A*X
3838
norm_sq = A%inner_product(R, R)
3939

4040
P = R
@@ -43,7 +43,7 @@ contains
4343
beta = zero_${s}$
4444
if(associated(workspace%callback)) call workspace%callback(x, norm_sq, iter)
4545
do while( norm_sq > tolsq * norm_sq0 .and. iter < maxiter)
46-
call A%apply(P,Ap, alpha= one_${s}$, beta=zero_${s}$) !> Ap = A*P
46+
call A%apply(P,Ap, alpha= one_${s}$, beta=zero_${s}$) ! Ap = A*P
4747

4848
alpha = norm_sq / A%inner_product(P, Ap)
4949

@@ -111,7 +111,7 @@ contains
111111
!-------------------------
112112
! main call to the solver
113113
if(restart_) x = zero_${s}$
114-
x = merge( b, x, di_ ) !> copy dirichlet load conditions encoded in B and indicated by di
114+
x = merge( b, x, di_ ) ! copy dirichlet load conditions encoded in B and indicated by di
115115
call solve_cg_kernel(op,b,x,tol_,maxiter_,workspace_)
116116

117117
!-------------------------

src/stdlib_linalg_iterative_solvers_pcg.fypp

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -45,25 +45,25 @@ contains
4545
if ( norm_sq0 > zero_${s}$ ) then
4646

4747
R = B
48-
call A%apply(X, R, alpha= -one_${s}$, beta=one_${s}$) !> R = B - A*X
48+
call A%apply(X, R, alpha= -one_${s}$, beta=one_${s}$) ! R = B - A*X
4949

50-
call M%apply(R,P, alpha= one_${s}$, beta=zero_${s}$) !> P = M^{-1}*R
50+
call M%apply(R,P, alpha= one_${s}$, beta=zero_${s}$) ! P = M^{-1}*R
5151

5252
tolsq = tol*tol
5353

5454
zr1 = zero_${s}$
5555
zr2 = one_${s}$
5656
do while ( (iter < maxiter) .AND. (norm_sq > tolsq * norm_sq0) )
5757

58-
call M%apply(R,S, alpha= one_${s}$, beta=zero_${s}$) !> S = M^{-1}*R
58+
call M%apply(R,S, alpha= one_${s}$, beta=zero_${s}$) ! S = M^{-1}*R
5959
zr2 = A%inner_product( R, S )
6060

6161
if (iter>0) then
6262
beta = zr2 / zr1
6363
P = S + beta * P
6464
end if
6565

66-
call A%apply(P, Q, alpha= one_${s}$, beta=zero_${s}$) !> Q = A*P
66+
call A%apply(P, Q, alpha= one_${s}$, beta=zero_${s}$) ! Q = A*P
6767
zv2 = A%inner_product( P, Q )
6868

6969
alpha = zr2 / zv2
@@ -114,9 +114,9 @@ contains
114114
integer :: precond_
115115
${t}$, allocatable :: diagonal(:)
116116
#:if matrix == "dense"
117-
${t}$, allocatable:: L(:,:) !> lower triangular
117+
${t}$, allocatable:: L(:,:) ! lower triangular
118118
#:else
119-
type(${matrix}$_${s}$_type) :: L !> lower triangular
119+
type(${matrix}$_${s}$_type) :: L ! lower triangular
120120
#:endif
121121
!-------------------------
122122
n = size(b)
@@ -147,11 +147,11 @@ contains
147147
#:else
148148
call diag(A,diagonal)
149149
#:endif
150-
L = A !> copy A structure to L
150+
L = A ! copy A structure to L
151151
call ssor( A , one_${s}$ , L, diagonal )
152152
M_%apply => precond_ldlt
153153
case(pc_ldlt)
154-
L = A !> copy A structure to L
154+
L = A ! copy A structure to L
155155
call ldlt( A , L, diagonal )
156156
M_%apply => precond_ldlt
157157
case default
@@ -179,7 +179,7 @@ contains
179179
!-------------------------
180180
! main call to the solver
181181
if(restart_) x = zero_${s}$
182-
x = merge( b, x, di_ ) !> copy dirichlet load conditions encoded in B and indicated by di
182+
x = merge( b, x, di_ ) ! copy dirichlet load conditions encoded in B and indicated by di
183183
call solve_pcg_kernel(op,M_,b,x,tol_,maxiter_,workspace_)
184184

185185
!-------------------------
@@ -220,15 +220,15 @@ contains
220220
${t}$, intent(inout) :: y(:)
221221
${t}$, intent(in) :: alpha
222222
${t}$, intent(in) :: beta
223-
y = merge( zero_${s}$, diagonal * x, di_ ) !> inverted diagonal
223+
y = merge( zero_${s}$, diagonal * x, di_ ) ! inverted diagonal
224224
end subroutine
225225
subroutine precond_ldlt(x,y,alpha,beta)
226226
${t}$, intent(in) :: x(:)
227227
${t}$, intent(inout) :: y(:)
228228
${t}$, intent(in) :: alpha
229229
${t}$, intent(in) :: beta
230230
call solve_forward_triangular( L , x , y )
231-
y = merge( zero_${s}$, diagonal * y, di_ ) !> inverted diagonal
231+
y = merge( zero_${s}$, diagonal * y, di_ ) ! inverted diagonal
232232
call solve_backward_triangular( L , y , y )
233233
end subroutine
234234
end subroutine

0 commit comments

Comments
 (0)