Skip to content

Commit 84f4bc9

Browse files
committed
make default inner_product point to a default dot_product add enum for workspace sizes
1 parent 85a70ba commit 84f4bc9

File tree

3 files changed

+28
-18
lines changed

3 files changed

+28
-18
lines changed

src/stdlib_linalg_iterative_solvers.fypp

Lines changed: 24 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,11 +10,17 @@ module stdlib_linalg_iterative_solvers
1010
implicit none
1111
private
1212

13+
enum, bind(c)
14+
enumerator :: size_wksp_cg = 3
15+
enumerator :: size_wksp_pccg = 4
16+
end enum
17+
public :: size_wksp_cg, size_wksp_pccg
18+
1319
#:for k, t, s in R_KINDS_TYPES
1420
type, public :: linop_${s}$
1521
procedure(vector_sub_${s}$), nopass, pointer :: matvec => null()
1622
procedure(vector_sub_${s}$), nopass, pointer :: preconditionner => null()
17-
procedure(reduction_sub_${s}$), nopass, pointer :: inner_product => null()
23+
procedure(reduction_sub_${s}$), nopass, pointer :: inner_product => default_dot_${s}$
1824
end type
1925
#:endfor
2026

@@ -114,6 +120,22 @@ module stdlib_linalg_iterative_solvers
114120
#:endfor
115121
#:endfor
116122
end interface
117-
public :: solve_pccg
123+
public :: solve_pccg
124+
125+
126+
contains
127+
128+
!------------------------------------------------------------------
129+
! defaults
130+
!------------------------------------------------------------------
131+
#:for k, t, s in R_KINDS_TYPES
132+
pure ${t}$ function default_dot_${s}$(x,y) result(r)
133+
use stdlib_intrinsics, only: stdlib_dot_product
134+
${t}$, intent(in) :: x(:)
135+
${t}$, intent(in) :: y(:)
136+
r = stdlib_dot_product(x,y)
137+
end function
138+
139+
#:endfor
118140

119141
end module stdlib_linalg_iterative_solvers

src/stdlib_linalg_iterative_solvers_cg.fypp

Lines changed: 2 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@ submodule(stdlib_linalg_iterative_solvers) stdlib_linalg_iterative_cg
88
use stdlib_kinds
99
use stdlib_sparse
1010
use stdlib_constants
11-
use stdlib_intrinsics, only: dot_product => stdlib_dot_product
1211
use stdlib_linalg_iterative_solvers
1312
implicit none
1413

@@ -100,7 +99,7 @@ contains
10099
!-------------------------
101100
! internal memory setup
102101
op%matvec => default_matvec
103-
op%inner_product => default_dot
102+
! op%inner_product => default_dot
104103
if(present(di))then
105104
di_ => di
106105
else
@@ -112,7 +111,7 @@ contains
112111
else
113112
allocate( workspace_ )
114113
end if
115-
if(.not.allocated(workspace_%tmp)) allocate( workspace_%tmp(n,3), source = zero_${s}$ )
114+
if(.not.allocated(workspace_%tmp)) allocate( workspace_%tmp(n,size_wksp_cg), source = zero_${s}$ )
116115
!-------------------------
117116
! main call to the solver
118117
call solve_cg_generic(op,b,x,di_,tol_,maxiter_,restart_,workspace_)
@@ -138,11 +137,6 @@ contains
138137
call spmv( A , x, y )
139138
#:endif
140139
end subroutine
141-
pure ${t}$ function default_dot(x,y) result(r)
142-
${t}$, intent(in) :: x(:)
143-
${t}$, intent(in) :: y(:)
144-
r = dot_product(x,y)
145-
end function
146140
end subroutine
147141

148142
#:endfor

src/stdlib_linalg_iterative_solvers_pccg.fypp

Lines changed: 2 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@ submodule(stdlib_linalg_iterative_solvers) stdlib_linalg_iterative_pccg
88
use stdlib_kinds
99
use stdlib_sparse
1010
use stdlib_constants
11-
use stdlib_intrinsics, only: dot_product => stdlib_dot_product
1211
use stdlib_linalg_iterative_solvers
1312
implicit none
1413

@@ -110,7 +109,7 @@ contains
110109
!-------------------------
111110
! internal memory setup
112111
op%matvec => default_matvec
113-
op%inner_product => default_dot
112+
! op%inner_product => default_dot
114113
op%preconditionner => default_preconditionner
115114
if(present(di))then
116115
di_ => di
@@ -123,7 +122,7 @@ contains
123122
else
124123
allocate( workspace_ )
125124
end if
126-
if(.not.allocated(workspace_%tmp)) allocate( workspace_%tmp(n,4) , source = zero_${s}$ )
125+
if(.not.allocated(workspace_%tmp)) allocate( workspace_%tmp(n,size_wksp_pccg) , source = zero_${s}$ )
127126
!-------------------------
128127
! main call to the solver
129128
call solve_pccg_generic(op,b,x,di_,tol_,maxiter_,restart_,workspace_)
@@ -154,11 +153,6 @@ contains
154153
${t}$, intent(inout) :: y(:)
155154
y = x
156155
end subroutine
157-
pure ${t}$ function default_dot(x,y) result(r)
158-
${t}$, intent(in) :: x(:)
159-
${t}$, intent(in) :: y(:)
160-
r = dot_product(x,y)
161-
end function
162156
end subroutine
163157

164158
#:endfor

0 commit comments

Comments
 (0)