Skip to content

Commit 9ed419f

Browse files
committed
simplify workspace
1 parent 716b3c5 commit 9ed419f

File tree

2 files changed

+11
-16
lines changed

2 files changed

+11
-16
lines changed

src/stdlib_linalg_iterative_solvers.fypp

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -19,10 +19,8 @@ module stdlib_linalg_iterative_solvers
1919
#:endfor
2020

2121
#:for k, t, s in R_KINDS_TYPES
22-
type, abstract, public :: solver_workspace_${s}$
23-
end type
24-
type, public, extends(solver_workspace_${s}$) :: cg_workspace_${s}$
25-
${t}$, allocatable :: r(:), p(:), Ap(:)
22+
type, public :: solver_workspace_${s}$
23+
${t}$, allocatable :: tmp(:,:)
2624
end type
2725

2826
#:endfor
@@ -49,7 +47,7 @@ module stdlib_linalg_iterative_solvers
4947
${t}$, intent(in) :: b(:), tol
5048
${t}$, intent(inout) :: x(:)
5149
integer, intent(in) :: maxiter
52-
type(cg_workspace_${s}$), intent(inout) :: workspace
50+
type(solver_workspace_${s}$), intent(inout) :: workspace
5351
end subroutine
5452
#:endfor
5553
end interface
@@ -67,7 +65,7 @@ module stdlib_linalg_iterative_solvers
6765
${t}$, intent(in) :: b(:), tol
6866
${t}$, intent(inout) :: x(:)
6967
integer, intent(in), optional :: maxiter
70-
type(cg_workspace_${s}$), optional, intent(inout), target :: workspace
68+
type(solver_workspace_${s}$), optional, intent(inout), target :: workspace
7169
end subroutine
7270
#:endfor
7371
#:endfor

src/stdlib_linalg_iterative_solvers_cg.fypp

Lines changed: 7 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -20,14 +20,14 @@ contains
2020
${t}$, intent(in) :: b(:), tol
2121
${t}$, intent(inout) :: x(:)
2222
integer, intent(in) :: maxiter
23-
type(cg_workspace_${s}$), intent(inout) :: workspace
23+
type(solver_workspace_${s}$), intent(inout) :: workspace
2424
!-------------------------
2525
integer :: iter
2626
${t}$ :: rtr, rtrold, alpha, beta, norm0_sq
2727
!-------------------------
28-
associate( p => workspace%p, &
29-
r => workspace%r, &
30-
Ap => workspace%Ap)
28+
associate( p => workspace%tmp(:,1), &
29+
r => workspace%tmp(:,2), &
30+
Ap => workspace%tmp(:,3))
3131
x = zero_${s}$
3232
rtr = A%inner_product(r, r)
3333
norm0_sq = A%inner_product(b, b)
@@ -60,10 +60,10 @@ contains
6060
${t}$, intent(in) :: b(:), tol
6161
${t}$, intent(inout) :: x(:)
6262
integer, intent(in), optional :: maxiter
63-
type(cg_workspace_${s}$), optional, intent(inout), target :: workspace
63+
type(solver_workspace_${s}$), optional, intent(inout), target :: workspace
6464
!-------------------------
6565
type(linop_${s}$) :: op
66-
type(cg_workspace_${s}$), pointer :: workspace_
66+
type(solver_workspace_${s}$), pointer :: workspace_
6767
integer :: n, maxiter_
6868
!-------------------------
6969
n = size(b)
@@ -75,10 +75,7 @@ contains
7575
if(present(workspace)) then
7676
workspace_ => workspace
7777
else
78-
allocate( workspace_%r(n), &
79-
workspace_%p(n), &
80-
workspace_%Ap(n))
81-
78+
allocate( workspace_%tmp(n,3) )
8279
end if
8380
call solve_cg_generic(op,b,x,tol,maxiter_,workspace_)
8481
contains

0 commit comments

Comments
 (0)