54 real(kind=
rp),
allocatable :: w1(:)
55 real(kind=
rp),
allocatable :: w2(:)
56 real(kind=
rp),
allocatable :: w3(:)
57 real(kind=
rp),
allocatable :: r1(:)
58 real(kind=
rp),
allocatable :: r2(:)
59 real(kind=
rp),
allocatable :: r3(:)
60 real(kind=
rp),
allocatable :: p1(:)
61 real(kind=
rp),
allocatable :: p2(:)
62 real(kind=
rp),
allocatable :: p3(:)
63 real(kind=
rp),
allocatable :: z1(:)
64 real(kind=
rp),
allocatable :: z2(:)
65 real(kind=
rp),
allocatable :: z3(:)
66 real(kind=
rp),
allocatable :: tmp(:)
69 type(c_ptr) :: w1_d = c_null_ptr
70 type(c_ptr) :: w2_d = c_null_ptr
71 type(c_ptr) :: w3_d = c_null_ptr
73 type(c_ptr) :: r1_d = c_null_ptr
74 type(c_ptr) :: r2_d = c_null_ptr
75 type(c_ptr) :: r3_d = c_null_ptr
77 type(c_ptr) :: p1_d = c_null_ptr
78 type(c_ptr) :: p2_d = c_null_ptr
79 type(c_ptr) :: p3_d = c_null_ptr
81 type(c_ptr) :: z1_d = c_null_ptr
82 type(c_ptr) :: z2_d = c_null_ptr
83 type(c_ptr) :: z3_d = c_null_ptr
85 type(c_ptr) :: tmp_d = c_null_ptr
87 type(c_ptr) :: gs_event = c_null_ptr
100 class(
pc_t),
optional,
intent(in),
target :: M
101 integer,
intent(in) :: n
102 integer,
intent(in) :: max_iter
103 real(kind=
rp),
optional,
intent(in) :: rel_tol
104 real(kind=
rp),
optional,
intent(in) :: abs_tol
105 logical,
optional,
intent(in) :: monitor
121 allocate(this%tmp(n))
141 if (
present(rel_tol) .and.
present(abs_tol) .and.
present(monitor))
then
142 call this%ksp_init(max_iter, rel_tol, abs_tol, monitor = monitor)
143 else if (
present(rel_tol) .and.
present(abs_tol))
then
144 call this%ksp_init(max_iter, rel_tol, abs_tol)
145 else if (
present(monitor) .and.
present(abs_tol))
then
146 call this%ksp_init(max_iter, abs_tol = abs_tol, monitor = monitor)
147 else if (
present(rel_tol) .and.
present(monitor))
then
148 call this%ksp_init(max_iter, rel_tol, monitor = monitor)
149 else if (
present(rel_tol))
then
150 call this%ksp_init(max_iter, rel_tol = rel_tol)
151 else if (
present(abs_tol))
then
152 call this%ksp_init(max_iter, abs_tol = abs_tol)
153 else if (
present(monitor))
then
154 call this%ksp_init(max_iter, monitor = monitor)
156 call this%ksp_init(max_iter)
168 if (
allocated(this%w1))
then
172 if (
allocated(this%w2))
then
176 if (
allocated(this%w3))
then
180 if (
allocated(this%r1))
then
184 if (
allocated(this%r2))
then
188 if (
allocated(this%r3))
then
192 if (
allocated(this%p1))
then
196 if (
allocated(this%p2))
then
200 if (
allocated(this%p3))
then
204 if (
allocated(this%z1))
then
208 if (
allocated(this%z2))
then
212 if (
allocated(this%z3))
then
216 if (
allocated(this%tmp))
then
222 if (c_associated(this%w1_d))
then
226 if (c_associated(this%w2_d))
then
230 if (c_associated(this%w3_d))
then
234 if (c_associated(this%r1_d))
then
238 if (c_associated(this%r2_d))
then
242 if (c_associated(this%r3_d))
then
246 if (c_associated(this%p1_d))
then
250 if (c_associated(this%p2_d))
then
254 if (c_associated(this%p3_d))
then
258 if (c_associated(this%z1_d))
then
262 if (c_associated(this%z2_d))
then
266 if (c_associated(this%z3_d))
then
270 if (c_associated(this%tmp_d))
then
274 if (c_associated(this%gs_event))
then
302 n, coef, blstx, blsty, blstz, gs_h, niter)
result(ksp_results)
304 class(
ax_t),
intent(in) :: ax
305 type(
field_t),
intent(inout) :: x
306 type(
field_t),
intent(inout) :: y
307 type(
field_t),
intent(inout) :: z
308 integer,
intent(in) :: n
309 real(kind=
rp),
dimension(n),
intent(in) :: fx
310 real(kind=
rp),
dimension(n),
intent(in) :: fy
311 real(kind=
rp),
dimension(n),
intent(in) :: fz
312 type(
coef_t),
intent(inout) :: coef
316 type(
gs_t),
intent(inout) :: gs_h
318 integer,
optional,
intent(in) :: niter
319 integer :: i, iter, max_iter
320 real(kind=
rp) :: rnorm, rtr, rtr0, rtz2, rtz1
321 real(kind=
rp) :: beta, pap, alpha, alphm, norm_fac
322 integer,
parameter :: gdim = 3
331 if (
present(niter))
then
334 max_iter = this%max_iter
336 norm_fac = 1.0_rp / coef%volume
338 associate(p1_d => this%p1_d, p2_d => this%p2_d, p3_d => this%p3_d, &
339 z1_d => this%z1_d, z2_d => this%z2_d, z3_d => this%z3_d, &
340 r1_d => this%r1_d, r2_d => this%r2_d, r3_d => this%r3_d, &
341 w1_d => this%w1_d, w2_d => this%w2_d, w3_d => this%w3_d, &
357 call device_vdot3(tmp_d, r1_d, r2_d, r3_d, r1_d, r2_d, r3_d, n)
361 rnorm = sqrt(rtr)*norm_fac
362 ksp_results%res_start = rnorm
363 ksp_results%res_final = rnorm
365 if(
abscmp(rnorm, 0.0_rp))
then
366 ksp_results%converged = .true.
370 call this%monitor_start(
'device_cpldCG')
371 do iter = 1, max_iter
372 call this%M%solve(this%z1, this%r1, n)
373 call this%M%solve(this%z2, this%r2, n)
374 call this%M%solve(this%z3, this%r3, n)
377 call device_vdot3(tmp_d, z1_d, z2_d, z3_d, r1_d, r2_d, r3_d, n)
382 if (iter .eq. 1) beta = 0.0_rp
387 call ax%compute_vector(this%w1, this%w2, this%w3, &
388 this%p1, this%p2, this%p3, coef, x%msh, x%Xh)
389 call gs_h%op(this%w1, n, gs_op_add, this%gs_event)
391 call gs_h%op(this%w2, n, gs_op_add, this%gs_event)
393 call gs_h%op(this%w3, n, gs_op_add, this%gs_event)
396 call blstx%apply(this%w1, n)
397 call blsty%apply(this%w2, n)
398 call blstz%apply(this%w3, n)
400 call device_vdot3(tmp_d, w1_d, w2_d, w3_d, p1_d, p2_d, p3_d, n)
407 p1_d, p2_d, p3_d, alpha, n, gdim)
409 w1_d, w2_d, w3_d, alphm, n, gdim)
410 call device_vdot3(tmp_d, r1_d, r2_d, r3_d, r1_d, r2_d, r3_d, n)
413 if (iter .eq. 1) rtr0 = rtr
414 rnorm = sqrt(rtr) * norm_fac
415 call this%monitor_iter(iter, rnorm)
416 if (rnorm .lt. this%abs_tol)
then
421 call this%monitor_stop()
422 ksp_results%res_final = rnorm
423 ksp_results%iter = iter
424 ksp_results%converged = this%is_converged(iter, rnorm)
type(ksp_monitor_t) function, dimension(3) cg_cpld_device_solve(this, ax, x, y, z, fx, fy, fz, n, coef, blstx, blsty, blstz, gs_h, niter)
Standard PCG solve.