!!$ !!$ Parallel Sparse BLAS v2.0 !!$ (C) Copyright 2006 Salvatore Filippone University of Rome Tor Vergata !!$ Alfredo Buttari University of Rome Tor Vergata !!$ !!$ Redistribution and use in source and binary forms, with or without !!$ modification, are permitted provided that the following conditions !!$ are met: !!$ 1. Redistributions of source code must retain the above copyright !!$ notice, this list of conditions and the following disclaimer. !!$ 2. Redistributions in binary form must reproduce the above copyright !!$ notice, this list of conditions, and the following disclaimer in the !!$ documentation and/or other materials provided with the distribution. !!$ 3. The name of the PSBLAS group or the names of its contributors may !!$ not be used to endorse or promote products derived from this !!$ software without specific written permission. !!$ !!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS !!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED !!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR !!$ PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS !!$ BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR !!$ CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF !!$ SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS !!$ INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN !!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) !!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE !!$ POSSIBILITY OF SUCH DAMAGE. !!$ !!$ ! File: psb_zneigh.f90 ! Subroutine: ! Parameters: subroutine psb_zneigh(a,idx,neigh,n,info,lev) use psb_realloc_mod use psb_const_mod use psb_spmat_type implicit none type(psb_zspmat_type), intent(in) :: a ! the sparse matrix integer, intent(in) :: idx ! the index whose neighbours we want to find integer, intent(out) :: n, info ! the number of neighbours and the info integer, allocatable :: neigh(:) ! the neighbours integer, optional :: lev ! level of neighbours to find integer, allocatable :: tmpn(:) integer :: level, dim, i, j, k, r, c, brow,& & elem_pt, ii, n1, col_idx, ne, err_act, nn, nidx character(len=20) :: name, ch_err name='psb_zneigh' info = 0 call psb_erractionsave(err_act) n = 0 info = 0 if(present(lev)) then if(lev.le.2) then level=lev else write(0,'("Too many levels!!!")') return endif else level=1 end if call psb_zneigh1l(a,idx,neigh,n) if(level.eq.2) then n1=n allocate(tmpn(max(10,2*n))) if (size(neigh) 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 i=0 dim=0 blkfnd: do i=i+1 if(ia1(i).eq.iidx) then blk=i dim=dim+ia3(i)-ia2(i) ipx = ia1(i) ! the first row index of the block rb = iidx-ipx ! the row offset within the block row = ia3(i)+rb dim = dim+ja(row+1)-ja(row) exit blkfnd else if(ia1(i).gt.iidx) then blk=i-1 dim=dim+ia3(i-1)-ia2(i-1) ipx = ia1(i-1) ! the first row index of the block rb = iidx-ipx ! the row offset within the block row = ia3(i-1)+rb dim = dim+ja(row+1)-ja(row) exit blkfnd end if end do blkfnd if(dim.gt.size(neigh)) call psb_realloc(dim,neigh,info) 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 = iidx-ipx ! the row offset within the block npg = ja(k_pt+1)-ja(k_pt) ! the number of rows in the block k=0 do col = ia2(blk), ia3(blk)-1 k=k+1 neigh(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 neigh(k) = ka(j) end do n=k end subroutine jad_zneigh1l subroutine psb_zneigh1l(a,idx,neigh,n) use psb_realloc_mod use psb_const_mod use psb_spmat_type use psb_string_mod implicit none type(psb_zspmat_type), intent(in) :: a ! the sparse matrix integer, intent(in) :: idx ! the index whose neighbours we want to find integer, intent(out) :: n ! the number of neighbours and the info integer, allocatable :: neigh(:) ! the neighbours select case(toupper(a%fida(1:3))) case('CSR') call csr_zneigh1l(a,idx,neigh,n) case('COO') call coo_zneigh1l(a,idx,neigh,n) case('JAD') call jad_zneigh1l(a,idx,neigh,n) end select end subroutine psb_zneigh1l end subroutine psb_zneigh