27 logical,
save :: async_matvec_flg = .false.
42 real(kind=
kreal),
intent(in) :: x(:)
43 real(kind=
kreal),
intent(out) :: y(:)
44 real(kind=
kreal),
intent(inout) :: time_ax
45 real(kind=
kreal),
intent(inout),
optional :: commtime
47 real(kind=
kreal) :: tcomm
48 real(kind=
kreal),
allocatable :: wk(:)
53 allocate(wk(hecmat%NP * hecmat%NDOF))
57 call hecmw_matvec_nn_inner(hecmesh, hecmat, x, y, time_ax, tcomm)
60 if (
present(commtime)) commtime = commtime + tcomm
122 subroutine hecmw_matvec_nn_inner (hecMESH, hecMAT, X, Y, time_Ax, COMMtime)
133 real(kind=
kreal),
intent(in) :: x(:)
134 real(kind=
kreal),
intent(out) :: y(:)
135 real(kind=
kreal),
intent(inout) :: time_ax
136 real(kind=
kreal),
intent(inout),
optional :: commtime
138 real(kind=
kreal) :: start_time, end_time, tcomm
139 integer(kind=kint) :: i, j, k, l, js, je, in
140 real(kind=
kreal) :: yv(hecmat%NDOF), xv(hecmat%NDOF)
142 integer(kind=kint) :: n, np, ndof, ndof2
143 integer(kind=kint),
pointer :: indexl(:), iteml(:), indexu(:), itemu(:)
144 real(kind=
kreal),
pointer :: al(:), au(:), d(:)
147 integer,
parameter :: numofblockperthread = 100
148 logical,
save :: isfirst = .true.
149 integer,
save :: numofthread = 1
150 integer,
save,
allocatable :: startpos(:), endpos(:)
151 integer(kind=kint),
save :: sectorcachesize0, sectorcachesize1
152 integer(kind=kint) :: threadnum, blocknum, numofblock
153 integer(kind=kint) :: numofelement, elementcount, blockindex
154 real(kind=
kreal) :: numofelementperblock
162 time_ax = time_ax + end_time - start_time - tcomm
163 if (
present(commtime)) commtime = commtime + tcomm
168 indexl => hecmat%indexL
169 indexu => hecmat%indexU
170 iteml => hecmat%itemL
171 itemu => hecmat%itemU
179 if (.not. isfirst)
then
180 numofblock = numofthread * numofblockperthread
181 if (endpos(numofblock-1) .ne. n-1)
then
182 deallocate(startpos, endpos)
188 numofblock = numofthread * numofblockperthread
189 allocate (startpos(0 : numofblock - 1), endpos(0 : numofblock - 1))
190 numofelement = n + indexl(n) + indexu(n)
191 numofelementperblock = dble(numofelement) / numofblock
194 startpos(blocknum) = 1
196 elementcount = elementcount + 1
197 elementcount = elementcount + (indexl(i) - indexl(i-1))
198 elementcount = elementcount + (indexu(i) - indexu(i-1))
199 if (elementcount > (blocknum + 1) * numofelementperblock)
then
203 blocknum = blocknum + 1
204 startpos(blocknum) = i + 1
205 if (blocknum == (numofblock - 1))
exit
212 do i= blocknum+1, numofblock-1
220 sectorcachesize0, sectorcachesize1)
233 if (
present(commtime)) commtime = commtime + end_time - start_time
248 do blocknum = 0 , numofblockperthread - 1
249 blockindex = blocknum * numofthread + threadnum
250 do i = startpos(blockindex), endpos(blockindex)
252 xv(k) = x(ndof*(i-1)+k)
257 yv(k)=yv(k)+d(ndof2*(i-1)+(k-1)*ndof+l)*xv(l)
265 xv(k) = x(ndof*(in-1)+k)
269 yv(k)=yv(k)+al(ndof2*(j-1)+(k-1)*ndof+l)*xv(l)
279 xv(k) = x(ndof*(in-1)+k)
283 yv(k)=yv(k)+au(ndof2*(j-1)+(k-1)*ndof+l)*xv(l)
288 y(ndof*(i-1)+k) = yv(k)
301 time_ax = time_ax + end_time - start_time
304 end subroutine hecmw_matvec_nn_inner
318 real(kind=
kreal),
intent(in) :: x(:), b(:)
319 real(kind=
kreal),
intent(out) :: r(:)
320 real(kind=
kreal),
intent(inout) :: time_ax
321 real(kind=
kreal),
intent(inout),
optional :: commtime
323 integer(kind=kint) :: i
324 real(kind=
kreal) :: tcomm
328 if (
present(commtime)) commtime = commtime + tcomm
331 do i = 1, hecmat%N * hecmat%NDOF
350 real(kind=
kreal),
intent(inout) :: time_ax
351 real(kind=
kreal),
intent(inout),
optional :: commtime
353 real(kind=
kreal),
allocatable :: r(:)
354 real(kind=
kreal) :: bnorm2, rnorm2
355 real(kind=
kreal) :: tcomm
357 allocate(r(hecmat%NDOF*hecmat%NP))
361 hecmat%B, hecmat%B, bnorm2, tcomm)
362 if (bnorm2 == 0.d0)
then
369 if (
present(commtime)) commtime = commtime + tcomm
384 integer(kind=kint),
intent(in) :: ndof
385 real(kind=
kreal),
intent(in) :: x(:)
386 real(kind=
kreal),
intent(out) :: y(:)
387 real(kind=
kreal),
intent(inout) :: commtime
389 real(kind=
kreal) :: start_time, end_time
390 integer(kind=kint) :: i, j, jj, k, kk
395 commtime = commtime + end_time - start_time
399 do i= 1, hecmesh%nn_internal * ndof
405 outer:
do i= 1, hecmesh%mpc%n_mpc
406 do j= hecmesh%mpc%mpc_index(i-1) + 1, hecmesh%mpc%mpc_index(i)
407 if (hecmesh%mpc%mpc_dof(j) > ndof) cycle outer
409 k = hecmesh%mpc%mpc_index(i-1) + 1
410 kk = ndof * (hecmesh%mpc%mpc_item(k) - 1) + hecmesh%mpc%mpc_dof(k)
412 do j= hecmesh%mpc%mpc_index(i-1) + 2, hecmesh%mpc%mpc_index(i)
413 jj = ndof * (hecmesh%mpc%mpc_item(j) - 1) + hecmesh%mpc%mpc_dof(j)
414 y(kk) = y(kk) - hecmesh%mpc%mpc_val(j) * x(jj)
432 integer(kind=kint),
intent(in) :: ndof
433 real(kind=
kreal),
intent(in) :: x(:)
434 real(kind=
kreal),
intent(out) :: y(:)
435 real(kind=
kreal),
intent(inout) :: commtime
437 real(kind=
kreal) :: start_time, end_time
438 integer(kind=kint) :: i, j, jj, k, kk
443 commtime = commtime + end_time - start_time
447 do i= 1, hecmesh%nn_internal * ndof
453 outer:
do i= 1, hecmesh%mpc%n_mpc
454 do j= hecmesh%mpc%mpc_index(i-1) + 1, hecmesh%mpc%mpc_index(i)
455 if (hecmesh%mpc%mpc_dof(j) > ndof) cycle outer
457 k = hecmesh%mpc%mpc_index(i-1) + 1
458 kk = ndof * (hecmesh%mpc%mpc_item(k) - 1) + hecmesh%mpc%mpc_dof(k)
460 do j= hecmesh%mpc%mpc_index(i-1) + 2, hecmesh%mpc%mpc_index(i)
461 jj = ndof * (hecmesh%mpc%mpc_item(j) - 1) + hecmesh%mpc%mpc_dof(j)
463 y(jj) = y(jj) - hecmesh%mpc%mpc_val(j) * x(kk)
482 real(kind=
kreal),
intent(in) :: x(:)
483 real(kind=
kreal),
intent(out) :: y(:), w(:)
484 real(kind=
kreal),
intent(inout) :: time_ax
485 real(kind=
kreal),
intent(inout) :: commtime
488 call hecmw_matvec_nn_inner(hecmesh, hecmat, y, w, time_ax, commtime)
504 real(kind=
kreal),
intent(inout),
optional :: commtime
505 real(kind=
kreal),
allocatable :: w(:,:)
506 real(kind=
kreal),
pointer :: d(:)
507 integer(kind=kint) :: ip, ndof, i, j
508 real(kind=
kreal) :: start_time, end_time
510 allocate(w(ndof*hecmat%NP,ndof))
515 w(ndof*(ip-1)+i,j) = d(ndof*ndof*(ip-1)+(i-1)*ndof+j)
524 if (
present(commtime)) commtime = commtime + end_time - start_time
525 do ip= hecmat%N+1, hecmat%NP
528 d(ndof*ndof*(ip-1)+(i-1)*ndof+j) = w(ndof*(ip-1)+i,j)
539 integer(kind=kint) :: i
541 do i = 1, hecmat1%NP*hecmat1%NDOF*hecmat1%NDOF
542 hecmat3%D(i) = hecmat1%D(i) + hecmat2%D(i)
545 do i = 1, hecmat1%NPU*hecmat1%NDOF*hecmat1%NDOF
546 hecmat3%AU(i) = hecmat1%AU(i) + hecmat2%AU(i)
549 do i = 1, hecmat1%NPL*hecmat1%NDOF*hecmat1%NDOF
550 hecmat3%AL(i) = hecmat1%AL(i) + hecmat2%AL(i)
558 real(kind=
kreal),
intent(in) :: alpha
559 integer(kind=kint) :: i
561 do i = 1, hecmat%NP*hecmat%NDOF*hecmat%NDOF
562 hecmat%D(i) = alpha*hecmat%D(i)
565 do i = 1, hecmat%NPU*hecmat%NDOF*hecmat%NDOF
566 hecmat%AU(i) = alpha*hecmat%AU(i)
569 do i = 1, hecmat%NPL*hecmat%NDOF*hecmat%NDOF
570 hecmat%AL(i) = alpha*hecmat%AL(i)