55 real(kind=
rp),
allocatable :: w1(:)
56 real(kind=
rp),
allocatable :: w2(:)
57 real(kind=
rp),
allocatable :: w3(:)
58 real(kind=
rp),
allocatable :: r1(:)
59 real(kind=
rp),
allocatable :: r2(:)
60 real(kind=
rp),
allocatable :: r3(:)
61 real(kind=
rp),
allocatable :: p1(:)
62 real(kind=
rp),
allocatable :: p2(:)
63 real(kind=
rp),
allocatable :: p3(:)
64 real(kind=
rp),
allocatable :: z1(:)
65 real(kind=
rp),
allocatable :: z2(:)
66 real(kind=
rp),
allocatable :: z3(:)
67 real(kind=
rp),
allocatable :: tmp(:)
70 type(c_ptr) :: w1_d = c_null_ptr
71 type(c_ptr) :: w2_d = c_null_ptr
72 type(c_ptr) :: w3_d = c_null_ptr
74 type(c_ptr) :: r1_d = c_null_ptr
75 type(c_ptr) :: r2_d = c_null_ptr
76 type(c_ptr) :: r3_d = c_null_ptr
78 type(c_ptr) :: p1_d = c_null_ptr
79 type(c_ptr) :: p2_d = c_null_ptr
80 type(c_ptr) :: p3_d = c_null_ptr
82 type(c_ptr) :: z1_d = c_null_ptr
83 type(c_ptr) :: z2_d = c_null_ptr
84 type(c_ptr) :: z3_d = c_null_ptr
86 type(c_ptr) :: tmp_d = c_null_ptr
88 type(c_ptr) :: gs_event = c_null_ptr
101 class(
pc_t),
optional,
intent(in),
target :: M
102 integer,
intent(in) :: n
103 integer,
intent(in) :: max_iter
104 real(kind=
rp),
optional,
intent(in) :: rel_tol
105 real(kind=
rp),
optional,
intent(in) :: abs_tol
106 logical,
optional,
intent(in) :: monitor
122 allocate(this%tmp(n))
142 if (
present(rel_tol) .and.
present(abs_tol) .and.
present(monitor))
then
143 call this%ksp_init(max_iter, rel_tol, abs_tol, monitor = monitor)
144 else if (
present(rel_tol) .and.
present(abs_tol))
then
145 call this%ksp_init(max_iter, rel_tol, abs_tol)
146 else if (
present(monitor) .and.
present(abs_tol))
then
147 call this%ksp_init(max_iter, abs_tol = abs_tol, monitor = monitor)
148 else if (
present(rel_tol) .and.
present(monitor))
then
149 call this%ksp_init(max_iter, rel_tol, monitor = monitor)
150 else if (
present(rel_tol))
then
151 call this%ksp_init(max_iter, rel_tol = rel_tol)
152 else if (
present(abs_tol))
then
153 call this%ksp_init(max_iter, abs_tol = abs_tol)
154 else if (
present(monitor))
then
155 call this%ksp_init(max_iter, monitor = monitor)
157 call this%ksp_init(max_iter)
169 if (
allocated(this%w1))
then
173 if (
allocated(this%w2))
then
177 if (
allocated(this%w3))
then
181 if (
allocated(this%r1))
then
185 if (
allocated(this%r2))
then
189 if (
allocated(this%r3))
then
193 if (
allocated(this%p1))
then
197 if (
allocated(this%p2))
then
201 if (
allocated(this%p3))
then
205 if (
allocated(this%z1))
then
209 if (
allocated(this%z2))
then
213 if (
allocated(this%z3))
then
217 if (
allocated(this%tmp))
then
223 if (c_associated(this%w1_d))
then
227 if (c_associated(this%w2_d))
then
231 if (c_associated(this%w3_d))
then
235 if (c_associated(this%r1_d))
then
239 if (c_associated(this%r2_d))
then
243 if (c_associated(this%r3_d))
then
247 if (c_associated(this%p1_d))
then
251 if (c_associated(this%p2_d))
then
255 if (c_associated(this%p3_d))
then
259 if (c_associated(this%z1_d))
then
263 if (c_associated(this%z2_d))
then
267 if (c_associated(this%z3_d))
then
271 if (c_associated(this%tmp_d))
then
275 if (c_associated(this%gs_event))
then
303 n, coef, blstx, blsty, blstz, gs_h, niter)
result(ksp_results)
305 class(
ax_t),
intent(in) :: ax
306 type(
field_t),
intent(inout) :: x
307 type(
field_t),
intent(inout) :: y
308 type(
field_t),
intent(inout) :: z
309 integer,
intent(in) :: n
310 real(kind=
rp),
dimension(n),
intent(in) :: fx
311 real(kind=
rp),
dimension(n),
intent(in) :: fy
312 real(kind=
rp),
dimension(n),
intent(in) :: fz
313 type(
coef_t),
intent(inout) :: coef
317 type(
gs_t),
intent(inout) :: gs_h
319 integer,
optional,
intent(in) :: niter
320 integer :: i, iter, max_iter
321 real(kind=
rp) :: rnorm, rtr, rtr0, rtz2, rtz1
322 real(kind=
rp) :: beta, pap, alpha, alphm, norm_fac
323 integer,
parameter :: gdim = 3
332 if (
present(niter))
then
335 max_iter = this%max_iter
337 norm_fac = 1.0_rp / coef%volume
339 associate(p1_d => this%p1_d, p2_d => this%p2_d, p3_d => this%p3_d, &
340 z1_d => this%z1_d, z2_d => this%z2_d, z3_d => this%z3_d, &
341 r1_d => this%r1_d, r2_d => this%r2_d, r3_d => this%r3_d, &
342 w1_d => this%w1_d, w2_d => this%w2_d, w3_d => this%w3_d, &
358 call device_vdot3(tmp_d, r1_d, r2_d, r3_d, r1_d, r2_d, r3_d, n)
362 rnorm = sqrt(rtr)*norm_fac
363 ksp_results%res_start = rnorm
364 ksp_results%res_final = rnorm
366 if(
abscmp(rnorm, 0.0_rp))
then
367 ksp_results%converged = .true.
371 call this%monitor_start(
'device_cpldCG')
372 do iter = 1, max_iter
373 call this%M%solve(this%z1, this%r1, n)
374 call this%M%solve(this%z2, this%r2, n)
375 call this%M%solve(this%z3, this%r3, n)
378 call device_vdot3(tmp_d, z1_d, z2_d, z3_d, r1_d, r2_d, r3_d, n)
383 if (iter .eq. 1) beta = 0.0_rp
388 call ax%compute_vector(this%w1, this%w2, this%w3, &
389 this%p1, this%p2, this%p3, coef, x%msh, x%Xh)
391 call rotate_cyc(this%w1, this%w2, this%w3, 1, coef)
392 call gs_h%op(this%w1, n, gs_op_add, this%gs_event)
394 call gs_h%op(this%w2, n, gs_op_add, this%gs_event)
396 call gs_h%op(this%w3, n, gs_op_add, this%gs_event)
398 call rotate_cyc(this%w1, this%w2, this%w3, 0, coef)
400 call blstx%apply(this%w1, n)
401 call blsty%apply(this%w2, n)
402 call blstz%apply(this%w3, n)
404 call device_vdot3(tmp_d, w1_d, w2_d, w3_d, p1_d, p2_d, p3_d, n)
411 p1_d, p2_d, p3_d, alpha, n, gdim)
413 w1_d, w2_d, w3_d, alphm, n, gdim)
414 call device_vdot3(tmp_d, r1_d, r2_d, r3_d, r1_d, r2_d, r3_d, n)
417 if (iter .eq. 1) rtr0 = rtr
418 rnorm = sqrt(rtr) * norm_fac
419 call this%monitor_iter(iter, rnorm)
420 if (rnorm .lt. this%abs_tol)
then
425 call this%monitor_stop()
426 ksp_results%res_final = rnorm
427 ksp_results%iter = iter
428 ksp_results%converged = this%is_converged(iter, rnorm)