|
|
|
@ -71,10 +71,8 @@ subroutine psb_dspgtrow(irw,a,b,info,append,iren,lrw)
|
|
|
|
|
call coo_dspgtrow(irw_,a,b,append_,iren_,lrw_)
|
|
|
|
|
|
|
|
|
|
else if (a%fida == 'JAD') then
|
|
|
|
|
info=135
|
|
|
|
|
ch_err=a%fida(1:3)
|
|
|
|
|
call psb_errpush(info,name,a_err=ch_err)
|
|
|
|
|
goto 9999
|
|
|
|
|
call jad_dspgtrow(irw_,a,b,append_,iren_,lrw_)
|
|
|
|
|
|
|
|
|
|
else
|
|
|
|
|
info=136
|
|
|
|
|
ch_err=a%fida(1:3)
|
|
|
|
@ -109,32 +107,70 @@ contains
|
|
|
|
|
integer, pointer :: iren(:)
|
|
|
|
|
integer :: lrw
|
|
|
|
|
|
|
|
|
|
integer :: idx,i,j ,nr,nz,nzb
|
|
|
|
|
integer :: idx,i,j ,nr,nz,nzb, row_idx
|
|
|
|
|
integer, pointer :: indices(:)
|
|
|
|
|
|
|
|
|
|
if (append) then
|
|
|
|
|
nzb = b%infoa(psb_nnz_)
|
|
|
|
|
else
|
|
|
|
|
nzb = 0
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
if (a%pl(1) /= 0) then
|
|
|
|
|
write(0,*) 'Fatal error in SPGTROW: do not feed a permuted mat so far!',&
|
|
|
|
|
& a%pl(1)
|
|
|
|
|
idx = -1
|
|
|
|
|
|
|
|
|
|
nr = lrw - irw + 1
|
|
|
|
|
allocate(indices(nr))
|
|
|
|
|
do i=1,nr
|
|
|
|
|
indices(i)=a%pl(irw+i-1)
|
|
|
|
|
nz=nz+a%ia2(indices(i)+1)-a%ia2(indices(i))
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
if (min(size(b%ia1),size(b%ia2),size(b%aspk)) < nzb+nz) then
|
|
|
|
|
call psb_spreall(b,nzb+nz,iret)
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
k=0
|
|
|
|
|
if(associated(iren)) then
|
|
|
|
|
do i=1,nr
|
|
|
|
|
row_idx=indices(i)
|
|
|
|
|
do j=a%ia2(row_idx),a%ia2(row_idx+1)-1
|
|
|
|
|
k = k + 1
|
|
|
|
|
b%aspk(nzb+k) = a%aspk(j)
|
|
|
|
|
b%ia1(nzb+k) = iren(row_idx)
|
|
|
|
|
b%ia2(nzb+k) = iren(a%ia1(j))
|
|
|
|
|
end do
|
|
|
|
|
end do
|
|
|
|
|
else
|
|
|
|
|
idx = irw
|
|
|
|
|
do i=1,nr
|
|
|
|
|
row_idx=indices(i)
|
|
|
|
|
do j=a%ia2(row_idx),a%ia2(row_idx+1)-1
|
|
|
|
|
k = k + 1
|
|
|
|
|
b%aspk(nzb+k) = a%aspk(j)
|
|
|
|
|
b%ia1(nzb+k) = row_idx
|
|
|
|
|
b%ia2(nzb+k) = a%ia1(j)
|
|
|
|
|
end do
|
|
|
|
|
end do
|
|
|
|
|
end if
|
|
|
|
|
!!$ write(0,*) 'csr_gtrow: ',irw,lrw,a%pl(1),idx
|
|
|
|
|
|
|
|
|
|
b%infoa(psb_nnz_) = nzb+k
|
|
|
|
|
b%m = b%m+nr
|
|
|
|
|
b%k = max(b%k,a%k)
|
|
|
|
|
|
|
|
|
|
else
|
|
|
|
|
idx = irw
|
|
|
|
|
|
|
|
|
|
if (idx<0) then
|
|
|
|
|
write(0,*) ' spgtrow Error : idx no good ',idx
|
|
|
|
|
return
|
|
|
|
|
end if
|
|
|
|
|
nr = lrw - irw + 1
|
|
|
|
|
nz = a%ia2(idx+nr) - a%ia2(idx)
|
|
|
|
|
if (append) then
|
|
|
|
|
nzb = b%infoa(psb_nnz_)
|
|
|
|
|
else
|
|
|
|
|
nzb = 0
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
if (min(size(b%ia1),size(b%ia2),size(b%aspk)) < nzb+nz) then
|
|
|
|
|
call psb_spreall(b,nzb+nz,iret)
|
|
|
|
|
endif
|
|
|
|
|
b%fida='COO'
|
|
|
|
|
!!$ write(0,*) 'csr_gtrow: ',out_,b%fida,nzb
|
|
|
|
|
|
|
|
|
|
if (associated(iren)) then
|
|
|
|
|
k=0
|
|
|
|
|
do i=irw,lrw
|
|
|
|
@ -147,9 +183,9 @@ contains
|
|
|
|
|
enddo
|
|
|
|
|
else
|
|
|
|
|
k=0
|
|
|
|
|
!!$ write(0,*) 'csr_gtrow: ilp',irw,lrw
|
|
|
|
|
|
|
|
|
|
do i=irw,lrw
|
|
|
|
|
!!$ write(0,*) 'csr_gtrow: jlp',a%ia2(i),a%ia2(i+1)-1
|
|
|
|
|
|
|
|
|
|
do j=a%ia2(i),a%ia2(i+1)-1
|
|
|
|
|
k = k + 1
|
|
|
|
|
b%aspk(nzb+k) = a%aspk(j)
|
|
|
|
@ -166,6 +202,8 @@ contains
|
|
|
|
|
b%m = b%m+lrw-irw+1
|
|
|
|
|
b%k = max(b%k,a%k)
|
|
|
|
|
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
end subroutine csr_dspgtrow
|
|
|
|
|
|
|
|
|
|
subroutine coo_dspgtrow(irw,a,b,append,iren,lrw)
|
|
|
|
@ -309,5 +347,124 @@ contains
|
|
|
|
|
b%k = max(b%k,a%k)
|
|
|
|
|
end subroutine coo_dspgtrow
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
subroutine jad_dspgtrow(irw,a,b,append,iren,lrw)
|
|
|
|
|
|
|
|
|
|
type(psb_dspmat_type), intent(in) :: a
|
|
|
|
|
integer :: irw
|
|
|
|
|
type(psb_dspmat_type), intent(inout) :: b
|
|
|
|
|
logical, intent(in) :: append
|
|
|
|
|
integer, pointer :: iren(:)
|
|
|
|
|
integer :: lrw
|
|
|
|
|
|
|
|
|
|
integer, pointer :: ia1(:), ia2(:), ia3(:),&
|
|
|
|
|
& ja(:), ka(:), indices(:), blks(:)
|
|
|
|
|
integer :: png, pia, pja, ipx, blk, rb, row, k_pt, npg, col, ng
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
png = a%ia2(1) ! points to the number of blocks
|
|
|
|
|
pia = a%ia2(2) ! points to the beginning of ia(3,png)
|
|
|
|
|
pja = a%ia2(3) ! points to the beginning of ja(:)
|
|
|
|
|
|
|
|
|
|
ng = a%ia2(png) ! the number of blocks
|
|
|
|
|
ja => a%ia2(pja:) ! the array containing the pointers to ka and aspk
|
|
|
|
|
ka => a%ia1(:) ! the array containing the column indices
|
|
|
|
|
ia1 => a%ia2(pia:pja-1:3) ! the array containing the first row index of each block
|
|
|
|
|
ia2 => a%ia2(pia+1:pja-1:3) ! the array containing a pointer to the pos. in ja to the first jad column
|
|
|
|
|
ia3 => a%ia2(pia+2:pja-1:3) ! the array containing a pointer to the pos. in ja to the first csr column
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
if (append) then
|
|
|
|
|
nzb = b%infoa(psb_nnz_)
|
|
|
|
|
else
|
|
|
|
|
nzb = 0
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
if (a%pl(1) /= 0) then
|
|
|
|
|
|
|
|
|
|
nr = lrw - irw + 1
|
|
|
|
|
allocate(indices(nr),blks(nr))
|
|
|
|
|
nz = 0
|
|
|
|
|
|
|
|
|
|
do i=1,nr
|
|
|
|
|
indices(i)=a%pl(irw+i-1)
|
|
|
|
|
j=0
|
|
|
|
|
blkfnd: do
|
|
|
|
|
j=j+1
|
|
|
|
|
if(ia1(j).eq.indices(i)) then
|
|
|
|
|
blks(i)=j
|
|
|
|
|
nz=nz+ia3(j)-ia2(j)
|
|
|
|
|
ipx = ia1(j) ! the first row index of the block
|
|
|
|
|
rb = indices(i)-ipx ! the row offset within the block
|
|
|
|
|
row = ia3(j)+rb
|
|
|
|
|
nz = nz+ja(row+1)-ja(row)
|
|
|
|
|
exit blkfnd
|
|
|
|
|
else if(ia1(j).gt.indices(i)) then
|
|
|
|
|
blks(i)=j-1
|
|
|
|
|
nz=nz+ia3(j-1)-ia2(j-1)
|
|
|
|
|
ipx = ia1(j-1) ! the first row index of the block
|
|
|
|
|
rb = indices(i)-ipx ! the row offset within the block
|
|
|
|
|
row = ia3(j-1)+rb
|
|
|
|
|
nz = nz+ja(row+1)-ja(row)
|
|
|
|
|
exit blkfnd
|
|
|
|
|
end if
|
|
|
|
|
end do blkfnd
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
if (size(b%ia1) < nzb+nz) then
|
|
|
|
|
call psb_spreall(b,nzb+nz,iret)
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
k=0
|
|
|
|
|
! cycle over rows
|
|
|
|
|
do i=1,nr
|
|
|
|
|
|
|
|
|
|
! find which block the row belongs to
|
|
|
|
|
blk = blks(i)
|
|
|
|
|
|
|
|
|
|
! extract first part of the row from the jad block
|
|
|
|
|
ipx = ia1(blk) ! the first row index of the block
|
|
|
|
|
k_pt= ia2(blk) ! the pointer to the beginning of a column in ja
|
|
|
|
|
rb = indices(i)-ipx ! the row offset within the block
|
|
|
|
|
npg = ja(k_pt+1)-ja(k_pt) ! the number of rows in the block
|
|
|
|
|
|
|
|
|
|
do col = ia2(blk), ia3(blk)-1
|
|
|
|
|
k=k+1
|
|
|
|
|
b%aspk(nzb+k) = a%aspk(ja(col)+rb)
|
|
|
|
|
b%ia1(nzb+k) = irw+i-1
|
|
|
|
|
b%ia2(nzb+k) = ka(ja(col)+rb)
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
! extract second part of the row from the csr tail
|
|
|
|
|
row=ia3(blk)+rb
|
|
|
|
|
do j=ja(row), ja(row+1)-1
|
|
|
|
|
k=k+1
|
|
|
|
|
b%aspk(nzb+k) = a%aspk(j)
|
|
|
|
|
b%ia1(nzb+k) = irw+i-1
|
|
|
|
|
b%ia2(nzb+k) = ka(j)
|
|
|
|
|
end do
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
b%infoa(psb_nnz_) = nzb+k
|
|
|
|
|
b%m = b%m+lrw-irw+1
|
|
|
|
|
b%k = max(b%k,a%k)
|
|
|
|
|
b%fida='COO'
|
|
|
|
|
|
|
|
|
|
else
|
|
|
|
|
! There might be some problems
|
|
|
|
|
info=134
|
|
|
|
|
ch_err=a%fida(1:3)
|
|
|
|
|
call psb_errpush(info,name,a_err=ch_err)
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
end subroutine jad_dspgtrow
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
end subroutine psb_dspgtrow
|
|
|
|
|
|
|
|
|
|