Fixed in-line docs.

psblas3-type-indexed
Salvatore Filippone 17 years ago
parent 0911703866
commit 3297eb7d04

@ -33,7 +33,7 @@
! Subroutine: psb_dgatherm
! This subroutine gathers pieces of a distributed dense matrix into a local one.
!
! Parameters:
! Arguments:
! globx - real,dimension(:,:). The local matrix into which gather
! the distributed pieces.
! locx - real,dimension(:,:). The local piece of the distributed
@ -204,7 +204,7 @@ end subroutine psb_dgatherm
! Subroutine: psb_dgatherv
! This subroutine gathers pieces of a distributed dense vector into a local one.
!
! Parameters:
! Arguments:
! globx - real,dimension(:). The local vector into which gather the
! distributed pieces.
! locx - real,dimension(:). The local piece of the ditributed

@ -34,7 +34,7 @@
! This subroutine performs the exchange of the halo elements in a
! distributed dense matrix between all the processes.
!
! Parameters:
! Arguments:
! x - real,dimension(:,:). The local part of the dense matrix.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -250,7 +250,7 @@ end subroutine psb_dhalom
! This subroutine performs the exchange of the halo elements in a
! distributed dense vector between all the processes.
!
! Parameters:
! Arguments:
! x - real,dimension(:). The local part of the dense vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.

@ -34,7 +34,7 @@
! This subroutine performs the exchange of the overlap elements in a
! distributed dense matrix between all the processes.
!
! Parameters:
! Arguments:
! x - real,dimension(:,:). The local part of the dense matrix.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. A return code.
@ -254,7 +254,7 @@ end subroutine psb_dovrlm
! This subroutine performs the exchange of the overlap elements in a
! distributed dense vector between all the processes.
!
! Parameters:
! Arguments:
! x - real,dimension(:). The local part of the dense vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.

@ -34,7 +34,7 @@
! This subroutine scatters a global matrix locally owned by one process
! into pieces that are local to alle the processes.
!
! Parameters:
! Arguments:
! globx - real,dimension(:,:). The global matrix to scatter.
! locx - real,dimension(:,:). The local piece of the ditributed matrix.
! desc_a - type(<psb_desc_type>). The communication descriptor.
@ -263,7 +263,7 @@ end subroutine psb_dscatterm
! This subroutine scatters a global vector locally owned by one process
! into pieces that are local to alle the processes.
!
! Parameters:
! Arguments:
! globx - real,dimension(:). The global vector to scatter.
! locx - real,dimension(:). The local piece of the ditributed vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.

@ -33,7 +33,7 @@
! Subroutine: psb_igatherm
! This subroutine gathers pieces of a distributed dense matrix into a local one.
!
! Parameters:
! Arguments:
! globx - integer,dimension(:,:). The local matrix into which gather
! the distributed pieces.
! locx - integer,dimension(:,:). The local piece of the distributed
@ -204,7 +204,7 @@ end subroutine psb_igatherm
! Subroutine: psb_igatherv
! This subroutine gathers pieces of a distributed dense vector into a local one.
!
! Parameters:
! Arguments:
! globx - integer,dimension(:). The local vector into which gather the
! distributed pieces.
! locx - integer,dimension(:). The local piece of the ditributed

@ -35,7 +35,7 @@
! This subroutine performs the exchange of the halo elements in a
! distributed dense matrix between all the processes.
!
! Parameters:
! Arguments:
! x - integer,dimension(:,:). The local part of the dense matrix.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -252,7 +252,7 @@ end subroutine psb_ihalom
! This subroutine performs the exchange of the halo elements in a
! distributed dense matrix between all the processes.
!
! Parameters:
! Arguments:
! x - integer,dimension(:). The local part of the dense matrix.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.

@ -34,7 +34,7 @@
! This subroutine scatters a global matrix locally owned by one process
! into pieces that are local to alle the processes.
!
! Parameters:
! Arguments:
! globx - integer,dimension(:,:). The global matrix to scatter.
! locx - integer,dimension(:,:). The local piece of the ditributed matrix.
! desc_a - type(<psb_desc_type>). The communication descriptor.
@ -261,7 +261,7 @@ end subroutine psb_iscatterm
! This subroutine scatters a global vector locally owned by one process
! into pieces that are local to alle the processes.
!
! Parameters:
! Arguments:
! globx - integer,dimension(:). The global vector to scatter.
! locx - integer,dimension(:). The local piece of the ditributed vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.

@ -33,7 +33,7 @@
! Subroutine: psb_zgatherm
! This subroutine gathers pieces of a distributed dense matrix into a local one.
!
! Parameters:
! Arguments:
! globx - cplx,dimension(:,:). The local matrix into which gather
! the distributed pieces.
! locx - cplx,dimension(:,:). The local piece of the distributed
@ -206,7 +206,7 @@ end subroutine psb_zgatherm
! Subroutine: psb_zgatherv
! This subroutine gathers pieces of a distributed dense vector into a local one.
!
! Parameters:
! Arguments:
! globx - cplx,dimension(:). The local vector into which gather
! the distributed pieces.
! locx - cplx,dimension(:). The local piece of the distributed

@ -34,7 +34,7 @@
! This subroutine performs the exchange of the halo elements in a
! distributed dense matrix between all the processes.
!
! Parameters:
! Arguments:
! x - real,dimension(:,:). The local part of the dense matrix.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -249,7 +249,7 @@ end subroutine psb_zhalom
! This subroutine performs the exchange of the halo elements in a
! distributed dense vector between all the processes.
!
! Parameters:
! Arguments:
! x - real,dimension(:). The local part of the dense vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.

@ -34,7 +34,7 @@
! This subroutine performs the exchange of the overlap elements in a
! distributed dense matrix between all the processes.
!
! Parameters:
! Arguments:
! x - real,dimension(:,:). The local part of the dense matrix.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Returns an output code.
@ -254,7 +254,7 @@ end subroutine psb_zovrlm
! This subroutine performs the exchange of the overlap elements in a
! distributed dense vector between all the processes.
!
! Parameters:
! Arguments:
! x - real,dimension(:). The local part of the dense vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.

@ -34,7 +34,7 @@
! This subroutine scatters a global matrix locally owned by one process
! into pieces that are local to alle the processes.
!
! Parameters:
! Arguments:
! globx - complex,dimension(:,:). The global matrix to scatter.
! locx - complex,dimension(:,:). The local piece of the ditributed matrix.
! desc_a - type(<psb_desc_type>). The communication descriptor.
@ -265,7 +265,7 @@ end subroutine psb_zscatterm
! This subroutine scatters a global vector locally owned by one process
! into pieces that are local to alle the processes.
!
! Parameters:
! Arguments:
! globx - complex,dimension(:). The global vector to scatter.
! locx - complex,dimension(:). The local piece of the ditributed vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.

@ -37,7 +37,7 @@
! otherwise its size is equal to the number of boundary indices on the
! current (calling) process.
!
! Parameters:
! Arguments:
! bndel(:) - integer, allocatable Array containing the output list
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. return code.

@ -36,7 +36,7 @@
! Converts a list of data exchanges from build format to assembled format.
! See below for a description of the formats.
!
! Parameters:
! Arguments:
! desc_a - type(psb_desc_type) The descriptor; in this context only the index
! mapping parts are used.
! index_in(:) - integer The index list, build format

@ -36,7 +36,7 @@
! the number of processes sharing it (minimum: 2). List is ended by -1.
! See also description in base/modules/psb_desc_type.f90
!
! Parameters:
! Arguments:
! ovr_elem(:) - integer, allocatable Array containing the output list
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. return code.

@ -36,7 +36,7 @@
! then process j should depend on i (even if the data to be sent in one of the
! directions happens to be empty)
!
! Parameters:
! Arguments:
! dep_list(:,:) - integer Initial dependency lists
! dl_lda - integer Allocated size of dep_list
! np - integer Total number of processes.

@ -28,6 +28,58 @@
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_Xswapdata.F90
!
! Subroutine: psi_Xswapdatam
! Does the data exchange among processes. Essentially this is doing
! a variable all-to-all data exchange (ALLTOALLV in MPI parlance), but
! it is capable of pruning empty exchanges, which are very likely in out
! application environment. All the variants have the same structure
! In all these subroutines X may be: I Integer
! D real(kind(1.d0))
! Z complex(kind(1.d0))
! Basically the operation is as follows: on each process, we identify
! sections SND(Y) and RCV(Y); then we do a SEND(PACK(SND(Y)));
! then we receive, and we do an update with Y = UNPACK(RCV(Y)) + BETA * Y
! but only on the elements involved in the UNPACK operation.
! Thus: for halo data exchange, the receive section is confined in the
! halo indices, and BETA=0, whereas for overlap exchange the receive section
! is scattered in the owned indices, and BETA=1.
!
! Arguments:
! flag - integer Choose the algorithm for data exchange:
! this is chosen through bit fields.
! swap_mpi = iand(flag,psb_swap_mpi_) /= 0
! swap_sync = iand(flag,psb_swap_sync_) /= 0
! swap_send = iand(flag,psb_swap_send_) /= 0
! swap_recv = iand(flag,psb_swap_recv_) /= 0
! if (swap_mpi): use underlying MPI_ALLTOALLV.
! if (swap_sync): use PSB_SND and PSB_RCV in
! synchronized pairs
! if (swap_send .and. swap_recv): use mpi_irecv
! and mpi_send
! if (swap_send): use psb_snd (but need another
! call with swap_recv to complete)
! if (swap_recv): use psb_rcv (completing a
! previous call with swap_send)
!
!
! n - integer Number of columns in Y
! beta - X Choose overwrite or sum.
! y(:,:) - X The data area
! desc_a - type(<psb_desc_type>). The communication descriptor.
! work(:) - X Buffer space. If not sufficient, will do
! our own internal allocation.
! info - integer. return code.
! data - integer which list is to be used to exchange data
! default psb_comm_halo_
! psb_comm_halo_ use halo_index
! psb_comm_ext_ use ext_index
! psb_comm_ovrl_ use ovrl_index
!
!
!
subroutine psi_dswapdatam(flag,n,beta,y,desc_a,work,info,data)
use psi_mod, psb_protect_name => psi_dswapdatam
@ -451,6 +503,57 @@ end subroutine psi_dswapdatam
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_Xswapdata.F90
!
! Subroutine: psi_Xswapdatav
! Does the data exchange among processes. Essentially this is doing
! a variable all-to-all data exchange (ALLTOALLV in MPI parlance), but
! it is capable of pruning empty exchanges, which are very likely in out
! application environment. All the variants have the same structure
! In all these subroutines X may be: I Integer
! D real(kind(1.d0))
! Z complex(kind(1.d0))
! Basically the operation is as follows: on each process, we identify
! sections SND(Y) and RCV(Y); then we do a SEND(PACK(SND(Y)));
! then we receive, and we do an update with Y = UNPACK(RCV(Y)) + BETA * Y
! but only on the elements involved in the UNPACK operation.
! Thus: for halo data exchange, the receive section is confined in the
! halo indices, and BETA=0, whereas for overlap exchange the receive section
! is scattered in the owned indices, and BETA=1.
!
! Arguments:
! flag - integer Choose the algorithm for data exchange:
! this is chosen through bit fields.
! swap_mpi = iand(flag,psb_swap_mpi_) /= 0
! swap_sync = iand(flag,psb_swap_sync_) /= 0
! swap_send = iand(flag,psb_swap_send_) /= 0
! swap_recv = iand(flag,psb_swap_recv_) /= 0
! if (swap_mpi): use underlying MPI_ALLTOALLV.
! if (swap_sync): use PSB_SND and PSB_RCV in
! synchronized pairs
! if (swap_send .and. swap_recv): use mpi_irecv
! and mpi_send
! if (swap_send): use psb_snd (but need another
! call with swap_recv to complete)
! if (swap_recv): use psb_rcv (completing a
! previous call with swap_send)
!
!
! n - integer Number of columns in Y
! beta - X Choose overwrite or sum.
! y(:) - X The data area
! desc_a - type(<psb_desc_type>). The communication descriptor.
! work(:) - X Buffer space. If not sufficient, will do
! our own internal allocation.
! info - integer. return code.
! data - integer which list is to be used to exchange data
! default psb_comm_halo_
! psb_comm_halo_ use halo_index
! psb_comm_ext_ use ext_index
! psb_comm_ovrl_ use ovrl_index
!
!
subroutine psi_dswapdatav(flag,beta,y,desc_a,work,info,data)
use psi_mod, psb_protect_name => psi_dswapdatav

@ -28,6 +28,61 @@
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_Xswaptran.F90
!
! Subroutine: psi_Xswaptranm
! Does the data exchange among processes. This is similar to Xswapdata, but
! the list is read "in reverse", i.e. indices that are normally SENT are used
! for the RECEIVE part and vice-versa. This is the basic data exchange operation
! for doing the product of a sparse matrix by a vector.
! Essentially this is doing a variable all-to-all data exchange
! (ALLTOALLV in MPI parlance), but
! it is capable of pruning empty exchanges, which are very likely in out
! application environment. All the variants have the same structure
! In all these subroutines X may be: I Integer
! D real(kind(1.d0))
! Z complex(kind(1.d0))
! Basically the operation is as follows: on each process, we identify
! sections SND(Y) and RCV(Y); then we do a SEND(PACK(SND(Y)));
! then we receive, and we do an update with Y = UNPACK(RCV(Y)) + BETA * Y
! but only on the elements involved in the UNPACK operation.
! Thus: for halo data exchange, the receive section is confined in the
! halo indices, and BETA=0, whereas for overlap exchange the receive section
! is scattered in the owned indices, and BETA=1.
!
! Arguments:
! flag - integer Choose the algorithm for data exchange:
! this is chosen through bit fields.
! swap_mpi = iand(flag,psb_swap_mpi_) /= 0
! swap_sync = iand(flag,psb_swap_sync_) /= 0
! swap_send = iand(flag,psb_swap_send_) /= 0
! swap_recv = iand(flag,psb_swap_recv_) /= 0
! if (swap_mpi): use underlying MPI_ALLTOALLV.
! if (swap_sync): use PSB_SND and PSB_RCV in
! synchronized pairs
! if (swap_send .and. swap_recv): use mpi_irecv
! and mpi_send
! if (swap_send): use psb_snd (but need another
! call with swap_recv to complete)
! if (swap_recv): use psb_rcv (completing a
! previous call with swap_send)
!
!
! n - integer Number of columns in Y
! beta - X Choose overwrite or sum.
! y(:,:) - X The data area
! desc_a - type(<psb_desc_type>). The communication descriptor.
! work(:) - X Buffer space. If not sufficient, will do
! our own internal allocation.
! info - integer. return code.
! data - integer which list is to be used to exchange data
! default psb_comm_halo_
! psb_comm_halo_ use halo_index
! psb_comm_ext_ use ext_index
! psb_comm_ovrl_ use ovrl_index
!
!
subroutine psi_dswaptranm(flag,n,beta,y,desc_a,work,info,data)
use psi_mod, psb_protect_name => psi_dswaptranm
@ -442,6 +497,61 @@ end subroutine psi_dswaptranm
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_Xswaptran.F90
!
! Subroutine: psi_Xswaptranv
! Does the data exchange among processes. This is similar to Xswapdata, but
! the list is read "in reverse", i.e. indices that are normally SENT are used
! for the RECEIVE part and vice-versa. This is the basic data exchange operation
! for doing the product of a sparse matrix by a vector.
! Essentially this is doing a variable all-to-all data exchange
! (ALLTOALLV in MPI parlance), but
! it is capable of pruning empty exchanges, which are very likely in out
! application environment. All the variants have the same structure
! In all these subroutines X may be: I Integer
! D real(kind(1.d0))
! Z complex(kind(1.d0))
! Basically the operation is as follows: on each process, we identify
! sections SND(Y) and RCV(Y); then we do a SEND(PACK(SND(Y)));
! then we receive, and we do an update with Y = UNPACK(RCV(Y)) + BETA * Y
! but only on the elements involved in the UNPACK operation.
! Thus: for halo data exchange, the receive section is confined in the
! halo indices, and BETA=0, whereas for overlap exchange the receive section
! is scattered in the owned indices, and BETA=1.
!
! Arguments:
! flag - integer Choose the algorithm for data exchange:
! this is chosen through bit fields.
! swap_mpi = iand(flag,psb_swap_mpi_) /= 0
! swap_sync = iand(flag,psb_swap_sync_) /= 0
! swap_send = iand(flag,psb_swap_send_) /= 0
! swap_recv = iand(flag,psb_swap_recv_) /= 0
! if (swap_mpi): use underlying MPI_ALLTOALLV.
! if (swap_sync): use PSB_SND and PSB_RCV in
! synchronized pairs
! if (swap_send .and. swap_recv): use mpi_irecv
! and mpi_send
! if (swap_send): use psb_snd (but need another
! call with swap_recv to complete)
! if (swap_recv): use psb_rcv (completing a
! previous call with swap_send)
!
!
! n - integer Number of columns in Y
! beta - X Choose overwrite or sum.
! y(:) - X The data area
! desc_a - type(<psb_desc_type>). The communication descriptor.
! work(:) - X Buffer space. If not sufficient, will do
! our own internal allocation.
! info - integer. return code.
! data - integer which list is to be used to exchange data
! default psb_comm_halo_
! psb_comm_halo_ use halo_index
! psb_comm_ext_ use ext_index
! psb_comm_ovrl_ use ovrl_index
!
!
subroutine psi_dswaptranv(flag,beta,y,desc_a,work,info,data)
use psi_mod, psb_protect_name => psi_dswaptranv

@ -27,7 +27,22 @@
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!!$
!
! File: psi_fnd_owner.f90
!
! Subroutine: psi_fnd_owner
! Figure out who owns global indices.
!
! Arguments:
! nv - integer Number of indices required on the calling
! process
! idx(:) - integer Required indices on the calling process
! iprc(:) - integer, allocatable Output: process identifiers for the corresponding
! indices
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. return code.
!
subroutine psi_fnd_owner(nv,idx,iprc,desc,info)
use psb_descriptor_type
use psb_serial_mod
@ -80,10 +95,20 @@ subroutine psi_fnd_owner(nv,idx,iprc,desc,info)
write(0,*) 'Invalid input descriptor in psi_fnd_owner'
end if
!
! The basic idea is very simple.
! First we figure out the total number of requests.
! Second we build the aggregate list of requests (with psb_amx)
! Third, we figure out locally whether we own the indices (whoever is
! asking for them) and build our part of the reply (we shift process
! indices so that they're 1-based)
! Fourth, we do a psb_amx on the replies so that we have everybody's answers
! Fifth, we extract the answers for our local query, and shift back the
! process indices to 0-based.
Allocate(hidx(np+1),hsz(np),stat=info)
if (info /= 0) then
call psb_errpush(4010,name,a_err='Allocate')
call psb_errpush(4010,name,a_err='Allocate')
goto 9999
end if
hsz = 0

@ -28,6 +28,20 @@
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_idx_cnv.f90
!
! Subroutine: psi_idx_cnv1
! Converts a bunch of indices from global to local numbering.
!
!
! Arguments:
! nv - integer Number of indices required
! idxin(:) - integer Required indices, overwritten on output.
! desc - type(<psb_desc_type>). The communication descriptor.
! info - integer. return code.
! mask(:) - logical, optional Only do the conversion for specific indices.
! owned - logical,optional Restrict to local indices, no halo (default false)
subroutine psi_idx_cnv1(nv,idxin,desc,info,mask,owned)
use psb_descriptor_type
use psb_serial_mod
@ -167,7 +181,21 @@ end subroutine psi_idx_cnv1
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_idx_cnv.f90
!
! Subroutine: psi_idx_cnv2
! Converts a bunch of indices from global to local numbering.
!
!
! Arguments:
! nv - integer Number of indices required
! idxin(:) - integer Required indices
! idxout(:) - integer Output values, negative for invalid input.
! desc - type(<psb_desc_type>). The communication descriptor.
! info - integer. return code.
! mask(:) - logical, optional Only do the conversion for specific indices.
! owned - logical,optional Restrict to local indices, no halo (default false)
subroutine psi_idx_cnv2(nv,idxin,idxout,desc,info,mask,owned)
use psb_descriptor_type
use psb_serial_mod
@ -251,9 +279,19 @@ subroutine psi_idx_cnv2(nv,idxin,idxout,desc,info,mask,owned)
owned_ = .false.
endif
!
! The input descriptor may be in any state
!
if (psb_is_large_desc(desc)) then
!
! Large descriptor: the size of the index space is such that
! we decided not to allocate the glob_to_loc(:) map.
!
if (psb_is_bld_desc(desc)) then
!
! During the build phase of a large descriptor the indices
! are kept in an AVL tree.
!
do i = 1, nv
if (mask_(i)) then
ip = idxin(i)
@ -274,6 +312,12 @@ subroutine psi_idx_cnv2(nv,idxin,idxout,desc,info,mask,owned)
end if
enddo
else if (psb_is_asb_desc(desc)) then
!
! When a large descriptor is assembled the indices
! are kept in a (hashed) list of ordered lists,
! hence psi_inner_cnv does the hashing and binary search.
!
if (.not.allocated(desc%hashv)) then
write(0,*) 'Inconsistent input to inner_cnv'
end if
@ -283,6 +327,10 @@ subroutine psi_idx_cnv2(nv,idxin,idxout,desc,info,mask,owned)
else
!
! Not a large descriptor, so we have the glob_to_loc(:) map
! available.
!
do i = 1, nv
if (mask_(i)) then
ip = idxin(i)
@ -355,6 +403,20 @@ end subroutine psi_idx_cnv2
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_idx_cnv.f90
!
! Subroutine: psi_idx_cnvs
! Converts an index from global to local numbering.
!
!
! Arguments:
! idxin - integer Required index
! idxout - integer Output value, negative for invalid input.
! desc - type(<psb_desc_type>). The communication descriptor.
! info - integer. return code.
! mask - logical, optional Only do the conversion if true.
! owned - logical,optional Restrict to local indices, no halo (default false)
subroutine psi_idx_cnvs(idxin,idxout,desc,info,mask,owned)
use psi_mod, psb_protect_name => psi_idx_cnvs

@ -28,6 +28,25 @@
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_idx_ins_cnv.f90
!
! Subroutine: psi_idx_ins_cnv1
! Converts a bunch of indices from global to local numbering.
! This routine is called while the descriptor is in the build state;
! the idea is that if an index is not yet marked as local, it is a new
! connection to another process, i.e. a new entry into the halo.
! But we still need the mask, because we have to take out the column indices
! corresponding to row indices we do not own (see psb_cdins for how this is used).
!
! Arguments:
! nv - integer Number of indices required
! idxin(:) - integer Required indices, overwritten on output
! output is negative for masked entries
! desc - type(<psb_desc_type>). The communication descriptor.
! info - integer. return code.
! mask(:) - logical, optional Only do the conversion for specific indices.
!
subroutine psi_idx_ins_cnv1(nv,idxin,desc,info,mask)
use psi_mod, psb_protect_name => psi_idx_ins_cnv1
use psb_descriptor_type
@ -159,7 +178,25 @@ end subroutine psi_idx_ins_cnv1
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_idx_ins_cnv.f90
!
! Subroutine: psi_idx_ins_cnv2
! Converts a bunch of indices from global to local numbering.
! This routine is called while the descriptor is in the build state;
! the idea is that if an index is not yet marked as local, it is a new
! connection to another process, i.e. a new entry into the halo.
! But we still need the mask, because we have to take out the column indices
! corresponding to row indices we do not own (see psb_cdins for how this is used).
!
! Arguments:
! nv - integer Number of indices required
! idxin(:) - integer Required indices
! idxout(:) - integer Output values (negative for masked entries)
! desc - type(<psb_desc_type>). The communication descriptor.
! info - integer. return code.
! mask(:) - logical, optional Only do the conversion for specific indices.
!
subroutine psi_idx_ins_cnv2(nv,idxin,idxout,desc,info,mask)
use psi_mod, psb_protect_name => psi_idx_ins_cnv2
use psb_descriptor_type
@ -399,6 +436,24 @@ end subroutine psi_idx_ins_cnv2
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_idx_ins_cnv.f90
!
! Subroutine: psi_idx_ins_cnvs
! Converts an index from global to local numbering.
! This routine is called while the descriptor is in the build state;
! the idea is that if an index is not yet marked as local, it is a new
! connection to another process, i.e. a new entry into the halo.
! But we still need the mask, because we have to take out the column indices
! corresponding to row indices we do not own (see psb_cdins for how this is used).
!
! Arguments:
! idxin - integer Required index s
! idxout - integer Output value (negative for masked entries)
! desc - type(<psb_desc_type>). The communication descriptor.
! info - integer. return code.
! mask - logical, optional Only do the conversion for specific indices.
!
subroutine psi_idx_ins_cnvs(idxin,idxout,desc,info,mask)
use psi_mod, psb_protect_name => psi_idx_ins_cnvs
use psb_descriptor_type

@ -28,6 +28,57 @@
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_Xswapdata.F90
!
! Subroutine: psi_Xswapdatam
! Does the data exchange among processes. Essentially this is doing
! a variable all-to-all data exchange (ALLTOALLV in MPI parlance), but
! it is capable of pruning empty exchanges, which are very likely in out
! application environment. All the variants have the same structure
! In all these subroutines X may be: I Integer
! D real(kind(1.d0))
! Z complex(kind(1.d0))
! Basically the operation is as follows: on each process, we identify
! sections SND(Y) and RCV(Y); then we do a SEND(PACK(SND(Y)));
! then we receive, and we do an update with Y = UNPACK(RCV(Y)) + BETA * Y
! but only on the elements involved in the UNPACK operation.
! Thus: for halo data exchange, the receive section is confined in the
! halo indices, and BETA=0, whereas for overlap exchange the receive section
! is scattered in the owned indices, and BETA=1.
!
! Arguments:
! flag - integer Choose the algorithm for data exchange:
! this is chosen through bit fields.
! swap_mpi = iand(flag,psb_swap_mpi_) /= 0
! swap_sync = iand(flag,psb_swap_sync_) /= 0
! swap_send = iand(flag,psb_swap_send_) /= 0
! swap_recv = iand(flag,psb_swap_recv_) /= 0
! if (swap_mpi): use underlying MPI_ALLTOALLV.
! if (swap_sync): use PSB_SND and PSB_RCV in
! synchronized pairs
! if (swap_send .and. swap_recv): use mpi_irecv
! and mpi_send
! if (swap_send): use psb_snd (but need another
! call with swap_recv to complete)
! if (swap_recv): use psb_rcv (completing a
! previous call with swap_send)
!
!
! n - integer Number of columns in Y
! beta - X Choose overwrite or sum.
! y(:,:) - X The data area
! desc_a - type(<psb_desc_type>). The communication descriptor.
! work(:) - X Buffer space. If not sufficient, will do
! our own internal allocation.
! info - integer. return code.
! data - integer which list is to be used to exchange data
! default psb_comm_halo_
! psb_comm_halo_ use halo_index
! psb_comm_ext_ use ext_index
! psb_comm_ovrl_ use ovrl_index
!
!
subroutine psi_iswapdatam(flag,n,beta,y,desc_a,work,info,data)
use psi_mod, psb_protect_name => psi_iswapdatam
@ -451,6 +502,57 @@ end subroutine psi_iswapdatam
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_Xswapdata.F90
!
! Subroutine: psi_Xswapdatav
! Does the data exchange among processes. Essentially this is doing
! a variable all-to-all data exchange (ALLTOALLV in MPI parlance), but
! it is capable of pruning empty exchanges, which are very likely in out
! application environment. All the variants have the same structure
! In all these subroutines X may be: I Integer
! D real(kind(1.d0))
! Z complex(kind(1.d0))
! Basically the operation is as follows: on each process, we identify
! sections SND(Y) and RCV(Y); then we do a SEND(PACK(SND(Y)));
! then we receive, and we do an update with Y = UNPACK(RCV(Y)) + BETA * Y
! but only on the elements involved in the UNPACK operation.
! Thus: for halo data exchange, the receive section is confined in the
! halo indices, and BETA=0, whereas for overlap exchange the receive section
! is scattered in the owned indices, and BETA=1.
!
! Arguments:
! flag - integer Choose the algorithm for data exchange:
! this is chosen through bit fields.
! swap_mpi = iand(flag,psb_swap_mpi_) /= 0
! swap_sync = iand(flag,psb_swap_sync_) /= 0
! swap_send = iand(flag,psb_swap_send_) /= 0
! swap_recv = iand(flag,psb_swap_recv_) /= 0
! if (swap_mpi): use underlying MPI_ALLTOALLV.
! if (swap_sync): use PSB_SND and PSB_RCV in
! synchronized pairs
! if (swap_send .and. swap_recv): use mpi_irecv
! and mpi_send
! if (swap_send): use psb_snd (but need another
! call with swap_recv to complete)
! if (swap_recv): use psb_rcv (completing a
! previous call with swap_send)
!
!
! n - integer Number of columns in Y
! beta - X Choose overwrite or sum.
! y(:) - X The data area
! desc_a - type(<psb_desc_type>). The communication descriptor.
! work(:) - X Buffer space. If not sufficient, will do
! our own internal allocation.
! info - integer. return code.
! data - integer which list is to be used to exchange data
! default psb_comm_halo_
! psb_comm_halo_ use halo_index
! psb_comm_ext_ use ext_index
! psb_comm_ovrl_ use ovrl_index
!
!
subroutine psi_iswapdatav(flag,beta,y,desc_a,work,info,data)
use psi_mod, psb_protect_name => psi_iswapdatav

@ -28,6 +28,61 @@
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_Xswaptran.F90
!
! Subroutine: psi_Xswaptranm
! Does the data exchange among processes. This is similar to Xswapdata, but
! the list is read "in reverse", i.e. indices that are normally SENT are used
! for the RECEIVE part and vice-versa. This is the basic data exchange operation
! for doing the product of a sparse matrix by a vector.
! Essentially this is doing a variable all-to-all data exchange
! (ALLTOALLV in MPI parlance), but
! it is capable of pruning empty exchanges, which are very likely in out
! application environment. All the variants have the same structure
! In all these subroutines X may be: I Integer
! D real(kind(1.d0))
! Z complex(kind(1.d0))
! Basically the operation is as follows: on each process, we identify
! sections SND(Y) and RCV(Y); then we do a SEND(PACK(SND(Y)));
! then we receive, and we do an update with Y = UNPACK(RCV(Y)) + BETA * Y
! but only on the elements involved in the UNPACK operation.
! Thus: for halo data exchange, the receive section is confined in the
! halo indices, and BETA=0, whereas for overlap exchange the receive section
! is scattered in the owned indices, and BETA=1.
!
! Arguments:
! flag - integer Choose the algorithm for data exchange:
! this is chosen through bit fields.
! swap_mpi = iand(flag,psb_swap_mpi_) /= 0
! swap_sync = iand(flag,psb_swap_sync_) /= 0
! swap_send = iand(flag,psb_swap_send_) /= 0
! swap_recv = iand(flag,psb_swap_recv_) /= 0
! if (swap_mpi): use underlying MPI_ALLTOALLV.
! if (swap_sync): use PSB_SND and PSB_RCV in
! synchronized pairs
! if (swap_send .and. swap_recv): use mpi_irecv
! and mpi_send
! if (swap_send): use psb_snd (but need another
! call with swap_recv to complete)
! if (swap_recv): use psb_rcv (completing a
! previous call with swap_send)
!
!
! n - integer Number of columns in Y
! beta - X Choose overwrite or sum.
! y(:,:) - X The data area
! desc_a - type(<psb_desc_type>). The communication descriptor.
! work(:) - X Buffer space. If not sufficient, will do
! our own internal allocation.
! info - integer. return code.
! data - integer which list is to be used to exchange data
! default psb_comm_halo_
! psb_comm_halo_ use halo_index
! psb_comm_ext_ use ext_index
! psb_comm_ovrl_ use ovrl_index
!
!
subroutine psi_iswaptranm(flag,n,beta,y,desc_a,work,info,data)
use psi_mod, psb_protect_name => psi_iswaptranm
@ -441,6 +496,61 @@ end subroutine psi_iswaptranm
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_Xswaptran.F90
!
! Subroutine: psi_Xswaptranv
! Does the data exchange among processes. This is similar to Xswapdata, but
! the list is read "in reverse", i.e. indices that are normally SENT are used
! for the RECEIVE part and vice-versa. This is the basic data exchange operation
! for doing the product of a sparse matrix by a vector.
! Essentially this is doing a variable all-to-all data exchange
! (ALLTOALLV in MPI parlance), but
! it is capable of pruning empty exchanges, which are very likely in out
! application environment. All the variants have the same structure
! In all these subroutines X may be: I Integer
! D real(kind(1.d0))
! Z complex(kind(1.d0))
! Basically the operation is as follows: on each process, we identify
! sections SND(Y) and RCV(Y); then we do a SEND(PACK(SND(Y)));
! then we receive, and we do an update with Y = UNPACK(RCV(Y)) + BETA * Y
! but only on the elements involved in the UNPACK operation.
! Thus: for halo data exchange, the receive section is confined in the
! halo indices, and BETA=0, whereas for overlap exchange the receive section
! is scattered in the owned indices, and BETA=1.
!
! Arguments:
! flag - integer Choose the algorithm for data exchange:
! this is chosen through bit fields.
! swap_mpi = iand(flag,psb_swap_mpi_) /= 0
! swap_sync = iand(flag,psb_swap_sync_) /= 0
! swap_send = iand(flag,psb_swap_send_) /= 0
! swap_recv = iand(flag,psb_swap_recv_) /= 0
! if (swap_mpi): use underlying MPI_ALLTOALLV.
! if (swap_sync): use PSB_SND and PSB_RCV in
! synchronized pairs
! if (swap_send .and. swap_recv): use mpi_irecv
! and mpi_send
! if (swap_send): use psb_snd (but need another
! call with swap_recv to complete)
! if (swap_recv): use psb_rcv (completing a
! previous call with swap_send)
!
!
! n - integer Number of columns in Y
! beta - X Choose overwrite or sum.
! y(:) - X The data area
! desc_a - type(<psb_desc_type>). The communication descriptor.
! work(:) - X Buffer space. If not sufficient, will do
! our own internal allocation.
! info - integer. return code.
! data - integer which list is to be used to exchange data
! default psb_comm_halo_
! psb_comm_halo_ use halo_index
! psb_comm_ext_ use ext_index
! psb_comm_ovrl_ use ovrl_index
!
!
subroutine psi_iswaptranv(flag,beta,y,desc_a,work,info,data)
use psi_mod, psb_protect_name => psi_iswaptranv

@ -28,6 +28,57 @@
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_Xswapdata.F90
!
! Subroutine: psi_Xswapdatam
! Does the data exchange among processes. Essentially this is doing
! a variable all-to-all data exchange (ALLTOALLV in MPI parlance), but
! it is capable of pruning empty exchanges, which are very likely in out
! application environment. All the variants have the same structure
! In all these subroutines X may be: I Integer
! D real(kind(1.d0))
! Z complex(kind(1.d0))
! Basically the operation is as follows: on each process, we identify
! sections SND(Y) and RCV(Y); then we do a SEND(PACK(SND(Y)));
! then we receive, and we do an update with Y = UNPACK(RCV(Y)) + BETA * Y
! but only on the elements involved in the UNPACK operation.
! Thus: for halo data exchange, the receive section is confined in the
! halo indices, and BETA=0, whereas for overlap exchange the receive section
! is scattered in the owned indices, and BETA=1.
!
! Arguments:
! flag - integer Choose the algorithm for data exchange:
! this is chosen through bit fields.
! swap_mpi = iand(flag,psb_swap_mpi_) /= 0
! swap_sync = iand(flag,psb_swap_sync_) /= 0
! swap_send = iand(flag,psb_swap_send_) /= 0
! swap_recv = iand(flag,psb_swap_recv_) /= 0
! if (swap_mpi): use underlying MPI_ALLTOALLV.
! if (swap_sync): use PSB_SND and PSB_RCV in
! synchronized pairs
! if (swap_send .and. swap_recv): use mpi_irecv
! and mpi_send
! if (swap_send): use psb_snd (but need another
! call with swap_recv to complete)
! if (swap_recv): use psb_rcv (completing a
! previous call with swap_send)
!
!
! n - integer Number of columns in Y
! beta - X Choose overwrite or sum.
! y(:,:) - X The data area
! desc_a - type(<psb_desc_type>). The communication descriptor.
! work(:) - X Buffer space. If not sufficient, will do
! our own internal allocation.
! info - integer. return code.
! data - integer which list is to be used to exchange data
! default psb_comm_halo_
! psb_comm_halo_ use halo_index
! psb_comm_ext_ use ext_index
! psb_comm_ovrl_ use ovrl_index
!
!
subroutine psi_zswapdatam(flag,n,beta,y,desc_a,work,info,data)
use psi_mod, psb_protect_name => psi_zswapdatam
@ -451,6 +502,57 @@ end subroutine psi_zswapdatam
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_Xswapdata.F90
!
! Subroutine: psi_Xswapdatav
! Does the data exchange among processes. Essentially this is doing
! a variable all-to-all data exchange (ALLTOALLV in MPI parlance), but
! it is capable of pruning empty exchanges, which are very likely in out
! application environment. All the variants have the same structure
! In all these subroutines X may be: I Integer
! D real(kind(1.d0))
! Z complex(kind(1.d0))
! Basically the operation is as follows: on each process, we identify
! sections SND(Y) and RCV(Y); then we do a SEND(PACK(SND(Y)));
! then we receive, and we do an update with Y = UNPACK(RCV(Y)) + BETA * Y
! but only on the elements involved in the UNPACK operation.
! Thus: for halo data exchange, the receive section is confined in the
! halo indices, and BETA=0, whereas for overlap exchange the receive section
! is scattered in the owned indices, and BETA=1.
!
! Arguments:
! flag - integer Choose the algorithm for data exchange:
! this is chosen through bit fields.
! swap_mpi = iand(flag,psb_swap_mpi_) /= 0
! swap_sync = iand(flag,psb_swap_sync_) /= 0
! swap_send = iand(flag,psb_swap_send_) /= 0
! swap_recv = iand(flag,psb_swap_recv_) /= 0
! if (swap_mpi): use underlying MPI_ALLTOALLV.
! if (swap_sync): use PSB_SND and PSB_RCV in
! synchronized pairs
! if (swap_send .and. swap_recv): use mpi_irecv
! and mpi_send
! if (swap_send): use psb_snd (but need another
! call with swap_recv to complete)
! if (swap_recv): use psb_rcv (completing a
! previous call with swap_send)
!
!
! n - integer Number of columns in Y
! beta - X Choose overwrite or sum.
! y(:) - X The data area
! desc_a - type(<psb_desc_type>). The communication descriptor.
! work(:) - X Buffer space. If not sufficient, will do
! our own internal allocation.
! info - integer. return code.
! data - integer which list is to be used to exchange data
! default psb_comm_halo_
! psb_comm_halo_ use halo_index
! psb_comm_ext_ use ext_index
! psb_comm_ovrl_ use ovrl_index
!
!
subroutine psi_zswapdatav(flag,beta,y,desc_a,work,info,data)
use psi_mod, psb_protect_name => psi_zswapdatav

@ -28,6 +28,61 @@
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_Xswaptran.F90
!
! Subroutine: psi_Xswaptranm
! Does the data exchange among processes. This is similar to Xswapdata, but
! the list is read "in reverse", i.e. indices that are normally SENT are used
! for the RECEIVE part and vice-versa. This is the basic data exchange operation
! for doing the product of a sparse matrix by a vector.
! Essentially this is doing a variable all-to-all data exchange
! (ALLTOALLV in MPI parlance), but
! it is capable of pruning empty exchanges, which are very likely in out
! application environment. All the variants have the same structure
! In all these subroutines X may be: I Integer
! D real(kind(1.d0))
! Z complex(kind(1.d0))
! Basically the operation is as follows: on each process, we identify
! sections SND(Y) and RCV(Y); then we do a SEND(PACK(SND(Y)));
! then we receive, and we do an update with Y = UNPACK(RCV(Y)) + BETA * Y
! but only on the elements involved in the UNPACK operation.
! Thus: for halo data exchange, the receive section is confined in the
! halo indices, and BETA=0, whereas for overlap exchange the receive section
! is scattered in the owned indices, and BETA=1.
!
! Arguments:
! flag - integer Choose the algorithm for data exchange:
! this is chosen through bit fields.
! swap_mpi = iand(flag,psb_swap_mpi_) /= 0
! swap_sync = iand(flag,psb_swap_sync_) /= 0
! swap_send = iand(flag,psb_swap_send_) /= 0
! swap_recv = iand(flag,psb_swap_recv_) /= 0
! if (swap_mpi): use underlying MPI_ALLTOALLV.
! if (swap_sync): use PSB_SND and PSB_RCV in
! synchronized pairs
! if (swap_send .and. swap_recv): use mpi_irecv
! and mpi_send
! if (swap_send): use psb_snd (but need another
! call with swap_recv to complete)
! if (swap_recv): use psb_rcv (completing a
! previous call with swap_send)
!
!
! n - integer Number of columns in Y
! beta - X Choose overwrite or sum.
! y(:,:) - X The data area
! desc_a - type(<psb_desc_type>). The communication descriptor.
! work(:) - X Buffer space. If not sufficient, will do
! our own internal allocation.
! info - integer. return code.
! data - integer which list is to be used to exchange data
! default psb_comm_halo_
! psb_comm_halo_ use halo_index
! psb_comm_ext_ use ext_index
! psb_comm_ovrl_ use ovrl_index
!
!
subroutine psi_zswaptranm(flag,n,beta,y,desc_a,work,info,data)
use psi_mod, psb_protect_name => psi_zswaptranm
@ -442,6 +497,61 @@ end subroutine psi_zswaptranm
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! File: psi_Xswaptran.F90
!
! Subroutine: psi_Xswaptranv
! Does the data exchange among processes. This is similar to Xswapdata, but
! the list is read "in reverse", i.e. indices that are normally SENT are used
! for the RECEIVE part and vice-versa. This is the basic data exchange operation
! for doing the product of a sparse matrix by a vector.
! Essentially this is doing a variable all-to-all data exchange
! (ALLTOALLV in MPI parlance), but
! it is capable of pruning empty exchanges, which are very likely in out
! application environment. All the variants have the same structure
! In all these subroutines X may be: I Integer
! D real(kind(1.d0))
! Z complex(kind(1.d0))
! Basically the operation is as follows: on each process, we identify
! sections SND(Y) and RCV(Y); then we do a SEND(PACK(SND(Y)));
! then we receive, and we do an update with Y = UNPACK(RCV(Y)) + BETA * Y
! but only on the elements involved in the UNPACK operation.
! Thus: for halo data exchange, the receive section is confined in the
! halo indices, and BETA=0, whereas for overlap exchange the receive section
! is scattered in the owned indices, and BETA=1.
!
! Arguments:
! flag - integer Choose the algorithm for data exchange:
! this is chosen through bit fields.
! swap_mpi = iand(flag,psb_swap_mpi_) /= 0
! swap_sync = iand(flag,psb_swap_sync_) /= 0
! swap_send = iand(flag,psb_swap_send_) /= 0
! swap_recv = iand(flag,psb_swap_recv_) /= 0
! if (swap_mpi): use underlying MPI_ALLTOALLV.
! if (swap_sync): use PSB_SND and PSB_RCV in
! synchronized pairs
! if (swap_send .and. swap_recv): use mpi_irecv
! and mpi_send
! if (swap_send): use psb_snd (but need another
! call with swap_recv to complete)
! if (swap_recv): use psb_rcv (completing a
! previous call with swap_send)
!
!
! n - integer Number of columns in Y
! beta - X Choose overwrite or sum.
! y(:) - X The data area
! desc_a - type(<psb_desc_type>). The communication descriptor.
! work(:) - X Buffer space. If not sufficient, will do
! our own internal allocation.
! info - integer. return code.
! data - integer which list is to be used to exchange data
! default psb_comm_halo_
! psb_comm_halo_ use halo_index
! psb_comm_ext_ use ext_index
! psb_comm_ovrl_ use ovrl_index
!
!
subroutine psi_zswaptranv(flag,beta,y,desc_a,work,info,data)
use psb_error_mod

@ -421,6 +421,14 @@ contains
integer, intent(inout) :: x(:)
integer :: i, ih, key, idx,nh,tmp,lb,ub,lm
!
! When a large descriptor is assembled the indices
! are kept in a (hashed) list of ordered lists.
! Thus we first hash the index, then we do a binary search on the
! ordered sublist. The hashing is based on the low-order bits
! for a width of psb_hash_bits
!
do i=1, n
key = x(i)
ih = iand(key,hashmask)
@ -460,6 +468,13 @@ contains
integer, intent(out) :: y(:)
integer :: i, ih, key, idx,nh,tmp,lb,ub,lm
!
! When a large descriptor is assembled the indices
! are kept in a (hashed) list of ordered lists.
! Thus we first hash the index, then we do a binary search on the
! ordered sublist. The hashing is based on the low-order bits
! for a width of psb_hash_bits
!
do i=1, n
key = x(i)

@ -37,7 +37,7 @@
!
! where sub( X ) denotes X(1:N,JX:).
!
! Parameters:
! Arguments:
! x - real,dimension(:,:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -164,7 +164,7 @@ end function psb_damax
!
! normi := max(abs(X(i))
!
! Parameters:
! Arguments:
! x - real,dimension(:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -285,7 +285,7 @@ end function psb_damaxv
!
! where sub( X ) denotes X(1:N,JX:).
!
! Parameters:
! Arguments:
! res - real. The result.
! x - real,dimension(:,:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
@ -407,7 +407,7 @@ end subroutine psb_damaxvs
!
! normi := max(abs(X(i))
!
! Parameters:
! Arguments:
! res - real. The result.
! x - real,dimension(:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.

@ -37,7 +37,7 @@
!
! where sub( X ) denotes X(1:N,JX:).
!
! Parameters:
! Arguments:
! x - real,dimension(:,:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -182,7 +182,7 @@ end function psb_dasum
!
! norm1 := sum(X(i))
!
! Parameters:
! Arguments:
! x - real,dimension(:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -319,7 +319,7 @@ end function psb_dasumv
!
! norm1 := sum(X(i))
!
! Parameters:
! Arguments:
! res - real. The result.
! x - real,dimension(:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.

@ -39,7 +39,7 @@
!
! sub( Y ) denotes Y(:,JY).
!
! Parameters:
! Arguments:
! alpha - real. The scalar used to multiply each component of sub( X ).
! x - real,dimension(:,:). The input vector containing the entries of sub( X ).
! beta - real. The scalar used to multiply each component of sub( Y ).
@ -195,7 +195,7 @@ end subroutine psb_daxpby
!
! Y := beta * Y + alpha * X
!
! Parameters:
! Arguments:
! alpha - real. The scalar used to multiply each component of X.
! x - real,dimension(:). The input vector containing the entries of X.
! beta - real. The scalar used to multiply each component of Y.

@ -39,7 +39,7 @@
!
! sub( Y ) denotes Y(:,JY).
!
! Parameters:
! Arguments:
! x - real,dimension(:,:). The input vector containing the entries of sub( X ).
! y - real,dimension(:,:). The input vector containing the entries of sub( Y ).
! desc_a - type(<psb_desc_type>). The communication descriptor.
@ -196,7 +196,7 @@ end function psb_ddot
!
! dot := X**T * Y
!
! Parameters:
! Arguments:
! x - real,dimension(:). The input vector containing the entries of X.
! y - real,dimension(:). The input vector containing the entries of Y.
! desc_a - type(<psb_desc_type>). The communication descriptor.
@ -333,7 +333,7 @@ end function psb_ddotv
!
! dot := X**T * Y
!
! Parameters:
! Arguments:
! res - real. The result.
! x - real,dimension(:). The input vector containing the entries of X.
! y - real,dimension(:). The input vector containing the entries of Y.
@ -474,7 +474,7 @@ end subroutine psb_ddotvs
!
! sub( Y ) denotes Y(:,JY).
!
! Parameters:
! Arguments:
! res - real. The result.
! x - real,dimension(:,:). The input vector containing the entries of sub( X ).
! y - real,dimension(:,:). The input vector containing the entries of sub( Y ).

@ -37,7 +37,7 @@
!
! where sub( X ) denotes X(:,JX).
!
! Parameters:
! Arguments:
! x - real,dimension(:,:). The input vector containing the entries of sub( X ).
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -176,7 +176,7 @@ end function psb_dnrm2
!
! norm2 := sqrt ( X**T * X)
!
! Parameters:
! Arguments:
! x - real,dimension(:). The input vector containing the entries of X.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -310,7 +310,7 @@ end function psb_dnrm2v
!
! norm2 := sqrt ( X**T * X)
!
! Parameters:
! Arguments:
! res - real. The result.
! x - real,dimension(:). The input vector containing the entries of X.
! desc_a - type(<psb_desc_type>). The communication descriptor.

@ -35,7 +35,7 @@
!
! normi := max(abs(sum(A(i,j))))
!
! Parameters:
! Arguments:
! a - type(<psb_dspmat_type>). The sparse matrix containing A.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.

@ -62,7 +62,7 @@
! alpha and beta are scalars, and sub( X ) and sub( Y ) are distributed
! vectors and A is a M-by-N distributed matrix.
!
! Parameters:
! Arguments:
! alpha - real. The scalar alpha.
! a - type(<psb_dspmat_type>). The sparse matrix containing A.
! x - real,dimension(:,:). The input vector containing the entries of sub( X ).
@ -402,7 +402,7 @@ end subroutine psb_dspmm
! alpha and beta are scalars, and X and Y are distributed
! vectors and A is a M-by-N distributed matrix.
!
! Parameters:
! Arguments:
! alpha - real. The scalar alpha.
! a - type(<psb_dspmat_type>). The sparse matrix containing A.
! x - real,dimension(:). The input vector containing the entries of X.

@ -54,7 +54,7 @@
! sub( X ) is a distributed
! vector and T is a M-by-M distributed triangular matrix.
!
! Parameters:
! Arguments:
! alpha - real. The scalar alpha.
! a - type(<psb_dspmat_type>). The sparse matrix containing A.
! x - real,dimension(:,:). The input vector containing the entries of sub( X ).
@ -364,7 +364,7 @@ end subroutine psb_dspsm
! X is a distributed
! vector and T is a M-by-M distributed triangular matrix.
!
! Parameters:
! Arguments:
! alpha - real. The scalar alpha.
! a - type(<psb_dspmat_type>). The sparse matrix containing A.
! x - real,dimension(:). The input vector containing the entries of X.

@ -37,7 +37,7 @@
!
! where sub( X ) denotes X(1:N,JX:).
!
! Parameters:
! Arguments:
! x - real,dimension(:,:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -167,7 +167,7 @@ end function psb_zamax
!
! normi := max(abs(X(i))
!
! Parameters:
! Arguments:
! x - real,dimension(:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -293,7 +293,7 @@ end function psb_zamaxv
!
! where sub( X ) denotes X(1:N,JX:).
!
! Parameters:
! Arguments:
! res - real. The result.
! x - real,dimension(:,:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
@ -419,7 +419,7 @@ end subroutine psb_zamaxvs
!
! normi := max(abs(X(i))
!
! Parameters:
! Arguments:
! res - real. The result.
! x - real,dimension(:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.

@ -37,7 +37,7 @@
!
! where sub( X ) denotes X(1:N,JX:).
!
! Parameters:
! Arguments:
! x - real,dimension(:,:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -187,7 +187,7 @@ end function psb_zasum
!
! norm1 := sum(X(i))
!
! Parameters:
! Arguments:
! x - real,dimension(:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -330,7 +330,7 @@ end function psb_zasumv
!
! norm1 := sum(X(i))
!
! Parameters:
! Arguments:
! res - real. The result.
! x - real,dimension(:). The input vector.
! desc_a - type(<psb_desc_type>). The communication descriptor.

@ -39,7 +39,7 @@
!
! sub( Y ) denotes Y(:,JY).
!
! Parameters:
! Arguments:
! alpha - real. The scalar used to multiply each component of sub( X ).
! x - real,dimension(:,:). The input vector containing the entries of sub( X ).
! beta - real. The scalar used to multiply each component of sub( Y ).
@ -193,7 +193,7 @@ end subroutine psb_zaxpby
!
! Y := beta * Y + alpha * X
!
! Parameters:
! Arguments:
! alpha - real. The scalar used to multiply each component of X.
! x - real,dimension(:). The input vector containing the entries of X.
! beta - real. The scalar used to multiply each component of Y.

@ -39,7 +39,7 @@
!
! sub( Y ) denotes Y(:,JY).
!
! Parameters:
! Arguments:
! x - real,dimension(:,:). The input vector containing the entries of sub( X ).
! y - real,dimension(:,:). The input vector containing the entries of sub( Y ).
! desc_a - type(<psb_desc_type>). The communication descriptor.
@ -195,7 +195,7 @@ end function psb_zdot
!
! dot := X**T * Y
!
! Parameters:
! Arguments:
! x - real,dimension(:). The input vector containing the entries of X.
! y - real,dimension(:). The input vector containing the entries of Y.
! desc_a - type(<psb_desc_type>). The communication descriptor.
@ -332,7 +332,7 @@ end function psb_zdotv
!
! dot := X**T * Y
!
! Parameters:
! Arguments:
! res - real. The result.
! x - real,dimension(:). The input vector containing the entries of X.
! y - real,dimension(:). The input vector containing the entries of Y.
@ -472,7 +472,7 @@ end subroutine psb_zdotvs
!
! sub( Y ) denotes Y(:,JY).
!
! Parameters:
! Arguments:
! res - real. The result.
! x - real,dimension(:,:). The input vector containing the entries of sub( X ).
! y - real,dimension(:,:). The input vector containing the entries of sub( Y ).

@ -37,7 +37,7 @@
!
! where sub( X ) denotes X(:,JX).
!
! Parameters:
! Arguments:
! x - real,dimension(:,:). The input vector containing the entries of sub( X ).
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -175,7 +175,7 @@ end function psb_znrm2
!
! norm2 := sqrt ( X**T * X)
!
! Parameters:
! Arguments:
! x - real,dimension(:). The input vector containing the entries of X.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.
@ -309,7 +309,7 @@ end function psb_znrm2v
!
! norm2 := sqrt ( X**T * X)
!
! Parameters:
! Arguments:
! res - real. The result.
! x - real,dimension(:). The input vector containing the entries of X.
! desc_a - type(<psb_desc_type>). The communication descriptor.

@ -35,7 +35,7 @@
!
! normi := max(abs(sum(A(i,j))))
!
! Parameters:
! Arguments:
! a - type(<psb_dspmat_type>). The sparse matrix containing A.
! desc_a - type(<psb_desc_type>). The communication descriptor.
! info - integer. Eventually returns an error code.

@ -62,7 +62,7 @@
! alpha and beta are scalars, and sub( X ) and sub( Y ) are distributed
! vectors and A is a M-by-N distributed matrix.
!
! Parameters:
! Arguments:
! alpha - real. The scalar alpha.
! a - type(<psb_zspmat_type>). The sparse matrix containing A.
! x - real,dimension(:,:). The input vector containing the entries of sub( X ).
@ -396,7 +396,7 @@ end subroutine psb_zspmm
! alpha and beta are scalars, and X and Y are distributed
! vectors and A is a M-by-N distributed matrix.
!
! Parameters:
! Arguments:
! alpha - real. The scalar alpha.
! a - type(<psb_zspmat_type>). The sparse matrix containing A.
! x - real,dimension(:). The input vector containing the entries of X.

@ -54,7 +54,7 @@
! sub( X ) is a distributed
! vector and T is a M-by-M distributed triangular matrix.
!
! Parameters:
! Arguments:
! alpha - real. The scalar alpha.
! a - type(<psb_zspmat_type>). The sparse matrix containing A.
! x - real,dimension(:,:). The input vector containing the entries of sub( X ).
@ -367,7 +367,7 @@ end subroutine psb_zspsm
! X is a distributed
! vector and T is a M-by-M distributed triangular matrix.
!
! Parameters:
! Arguments:
! alpha - real. The scalar alpha.
! a - type(<psb_zspmat_type>). The sparse matrix containing A.
! x - real,dimension(:). The input vector containing the entries of X.

@ -32,7 +32,7 @@
! Subroutine: msort_dw
! This subroutine sorts an integer array into ascending order.
!
! Parameters:
! Arguments:
! n - integer Input: size of the array
! k - integer(*) input: array of keys to be sorted
! l - integer(0:n+1) output: link list

@ -32,7 +32,7 @@
! Subroutine: msort_up
! This subroutine sorts an integer array into ascending order.
!
! Parameters:
! Arguments:
! n - integer Input: size of the array
! k - integer(*) input: array of keys to be sorted
! l - integer(0:n+1) output: link list

@ -30,7 +30,7 @@
!!$
! File: psb_dcsmm.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_dcsmm(alpha,a,b,beta,c,info,trans)
use psb_spmat_type
use psb_error_mod

@ -30,7 +30,7 @@
!!$
! File: psb_dcsmv.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_dcsmv(alpha,a,b,beta,c,info,trans)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_dcsnmi.f90
! Subroutine:
! Parameters:
! Arguments:
real(kind(1.d0)) function psb_dcsnmi(a,info,trans)

@ -30,7 +30,7 @@
!!$
! File: psb_dcsprt.f90
! Subroutine:
! Parameters:
! Arguments:
!*****************************************************************************
!* *

@ -35,7 +35,7 @@
! Apply a right permutation to a sparse matrix, i.e. permute the column
! indices.
!
! Parameters:
! Arguments:
! trans - character. Whether iperm or its transpose
! should be applied
! iperm - integer, dimension(:) A permutation vector; its size

@ -30,7 +30,7 @@
!!$
! File: psb_dcsrws.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_dcsrws(rw,a,info,trans)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_dcssm.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_dcssm(alpha,t,b,beta,c,info,trans,unitd,d)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_dcssv.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_dcssv(alpha,t,b,beta,c,info,trans,unitd,d)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_dfixcoo.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_dfixcoo(a,info,idir)
use psb_spmat_type

@ -34,7 +34,7 @@
! Subroutine: psb_dgelp
! Apply a left permutation to a dense matrix
!
! Parameters:
! Arguments:
! trans - character.
! iperm - integer.
! x - real, dimension(:,:).
@ -164,7 +164,7 @@ end subroutine psb_dgelp
! Subroutine: psb_dgelpv
! Apply a left permutation to a dense matrix
!
! Parameters:
! Arguments:
! trans - character.
! iperm - integer.
! x - real, dimension(:).

@ -30,7 +30,7 @@
!!$
! File: psb_dipcoo2csc.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_dipcoo2csc(a,info,clshr)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_dipcoo2csr.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_dipcoo2csr(a,info,rwshr)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_dipcsr2coo.f90
! Subroutine:
! Parameters:
! Arguments:
Subroutine psb_dipcsr2coo(a,info)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_dneigh.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_dneigh(a,idx,neigh,n,info,lev)

@ -30,7 +30,7 @@
!!$
! File: psb_dnumbmm.f90
! Subroutine:
! Parameters:
! Arguments:
!
!
! Note: This subroutine performs the numerical product of two sparse matrices.

@ -30,7 +30,7 @@
!!$
! File: psb_drwextd.f90
! Subroutine:
! Parameters:
! Arguments:
!
! We have a problem here: 1. How to handle well all the formats?
! 2. What should we do with rowscale? Does it only

@ -31,7 +31,7 @@
! File: psb_dspclip.f90
! Subroutine: psb_dspclip
! Creates a "clipped" copy of input matrix A. Output is always in COO.
! Parameters:
! Arguments:
!*****************************************************************************
!* *

@ -34,7 +34,7 @@
! This subroutine performs the assembly of
! the local part of a sparse distributed matrix
!
! Parameters:
! Arguments:
! a - type(<psb_spmat_type>). The input matrix to be assembled.
! b - type(<psb_spmat_type>). The assembled output matrix.
! info - integer. Eventually returns an error code.

@ -31,7 +31,7 @@
! File: psb_dspgetrow.f90
! Subroutine: psb_dspgetrow
! Gets one or more rows from a sparse matrix.
! Parameters:
! Arguments:
!*****************************************************************************
!* *
!* *

@ -31,7 +31,7 @@
! File: psb_dspgtblk.f90
! Subroutine: psb_dspgtblk
! Gets one or more rows from a sparse matrix.
! Parameters:
! Arguments:
!*****************************************************************************
!* *
!* Takes a specified row from matrix A and copies into matrix B (possibly *

@ -30,7 +30,7 @@
!!$
! File: psb_dspgtdiag.f90
! Subroutine:
! Parameters:
! Arguments:
!*****************************************************************************
!* *

@ -30,7 +30,7 @@
!!$
! File: psb_dspscal.f90
! Subroutine:
! Parameters:
! Arguments:
!*****************************************************************************
!* *

@ -30,7 +30,7 @@
!!$
! File: psb_dsymbmm.f90
! Subroutine:
! Parameters:
! Arguments:
!
!
! Note: This subroutine performs the symbolic product of two sparse matrices.

@ -30,7 +30,7 @@
!!$
! File: psb_dtransp.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_dtransp(a,b,c,fmt)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_zcsmm.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_zcsmm(alpha,a,b,beta,c,info,trans)
use psb_spmat_type
use psb_error_mod

@ -30,7 +30,7 @@
!!$
! File: psb_zcsmv.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_zcsmv(alpha,a,b,beta,c,info,trans)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_zcsnmi.f90
! Subroutine:
! Parameters:
! Arguments:
real(kind(1.d0)) function psb_zcsnmi(a,info,trans)

@ -30,7 +30,7 @@
!!$
! File: psb_zcsprt.f90
! Subroutine:
! Parameters:
! Arguments:
!*****************************************************************************
!* *

@ -35,7 +35,7 @@
! Apply a right permutation to a sparse matrix, i.e. permute the column
! indices.
!
! Parameters:
! Arguments:
! trans - character. Whether iperm or its transpose
! should be applied
! iperm - integer, dimension(:) A permutation vector; its size

@ -30,7 +30,7 @@
!!$
! File: psb_zcsrws.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_zcsrws(rw,a,info,trans)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_zcssm.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_zcssm(alpha,t,b,beta,c,info,trans,unitd,d)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_zcssv.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_zcssv(alpha,t,b,beta,c,info,trans,unitd,d)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_zfixcoo.f90
! Subroutine:
! Parameters:
! Arguments:
Subroutine psb_zfixcoo(a,info,idir)
use psb_spmat_type

@ -34,7 +34,7 @@
! Subroutine: psb_zgelp
! Apply a left permutation to a dense matrix
!
! Parameters:
! Arguments:
! trans - character.
! iperm - integer.
! x - real, dimension(:,:).
@ -167,7 +167,7 @@ end subroutine psb_zgelp
! Subroutine: psb_zgelpv
! Apply a left permutation to a dense matrix
!
! Parameters:
! Arguments:
! trans - character.
! iperm - integer.
! x - real, dimension(:).

@ -30,7 +30,7 @@
!!$
! File: psb_zipcoo2csc.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_zipcoo2csc(a,info,clshr)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_zipcoo2csr.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_zipcoo2csr(a,info,rwshr)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_zipcsr2coo.f90
! Subroutine:
! Parameters:
! Arguments:
Subroutine psb_zipcsr2coo(a,info)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_zneigh.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_zneigh(a,idx,neigh,n,info,lev)

@ -30,7 +30,7 @@
!!$
! File: psb_dnumbmm.f90
! Subroutine:
! Parameters:
! Arguments:
!
!
! Note: This subroutine performs the numerical product of two sparse matrices.

@ -30,7 +30,7 @@
!!$
! File: psb_zrwextd.f90
! Subroutine:
! Parameters:
! Arguments:
!
! We have a problem here: 1. How to handle well all the formats?
! 2. What should we do with rowscale? Does it only

@ -31,7 +31,7 @@
! File: psb_zspclip.f90
! Subroutine: psb_zspclip
! Creates a "clipped" copy of input matrix A. Output is always in COO.
! Parameters:
! Arguments:
!*****************************************************************************
!* *

@ -34,7 +34,7 @@
! This subroutine performs the assembly of
! the local part of a sparse distributed matrix
!
! Parameters:
! Arguments:
! a - type(<psb_spmat_type>). The input matrix to be assembled.
! b - type(<psb_spmat_type>). The assembled output matrix.
! info - integer. Eventually returns an error code.

@ -31,7 +31,7 @@
! File: psb_zspgetrow.f90
! Subroutine: psb_zspgetrow
! Gets one or more rows from a sparse matrix.
! Parameters:
! Arguments:
!*****************************************************************************
!* *
!* *

@ -31,7 +31,7 @@
! File: psb_zspgtblk.f90
! Subroutine: psb_zspgtblk
! Gets one or more rows from a sparse matrix.
! Parameters:
! Arguments:
!*****************************************************************************
!* *
!* Takes a specified row from matrix A and copies into matrix B (possibly *

@ -30,7 +30,7 @@
!!$
! File: psb_zspgtdiag.f90
! Subroutine:
! Parameters:
! Arguments:
!*****************************************************************************
!* *

@ -30,7 +30,7 @@
!!$
! File: psb_zspscal.f90
! Subroutine:
! Parameters:
! Arguments:
!*****************************************************************************
!* *

@ -30,7 +30,7 @@
!!$
! File: psb_zsymbmm.f90
! Subroutine:
! Parameters:
! Arguments:
!
!
! Note: This subroutine performs the symbolic product of two sparse matrices.

@ -30,7 +30,7 @@
!!$
! File: psb_ztransc.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_ztransc(a,b,c,fmt)
use psb_spmat_type

@ -30,7 +30,7 @@
!!$
! File: psb_ztransp.f90
! Subroutine:
! Parameters:
! Arguments:
subroutine psb_ztransp(a,b,c,fmt)
use psb_spmat_type

@ -35,7 +35,7 @@
! of indices that are assigned to the current process. The global size
! is equal to the largest index found on any process.
!
! Parameters:
! Arguments:
! v - integer, dimension(:). The array containg the partitioning scheme.
! ictxt - integer. The communication context.
! desc_a - type(<psb_desc_type>). The communication descriptor.

@ -34,7 +34,7 @@
! Allocate descriptor
! and checks correctness of PARTS subroutine
!
! Parameters:
! Arguments:
! m - integer. The number of rows.
! n - integer. The number of columns.
! parts - external subroutine. The routine that contains the

@ -36,7 +36,7 @@
! on all calling processes.
!
!
! Parameters:
! Arguments:
! v - integer, dimension(:). The array containg the partitioning scheme.
! ictxt - integer. The communication context.
! desc_a - type(<psb_desc_type>). The communication descriptor.

@ -33,7 +33,7 @@
! Subroutine: psb_cdcpy
! Produces a clone of a descriptor.
!
! Parameters:
! Arguments:
! desc_in - type(<psb_desc_type>). The communication descriptor to be cloned.
! desc_out - type(<psb_desc_type>). The output communication descriptor.
! info - integer. Return code.

@ -33,7 +33,7 @@
! Subroutine: psb_cdfree
! Frees a descriptor data structure.
!
! Parameters:
! Arguments:
! desc_a - type(<psb_desc_type>). The communication descriptor to be freed.
! info - integer. return code.
subroutine psb_cdfree(desc_a,info)

@ -33,7 +33,7 @@
! Subroutine: psb_cdins
! Takes as input a cloud of points and updates the descriptor accordingly.
!
! Parameters:
! Arguments:
! nz - integer. The number of points to insert.
! ia - integer,dimension(:). The row indices of the points.
! ja - integer,dimension(:). The column indices of the points.

@ -33,7 +33,7 @@
! Subroutine: psb_cdprt
! Prints the descriptor to an output file
!
! Parameters:
! Arguments:
! iout - integer. The output unit to print to.
! desc_p - type(<psb_desc_type>). The communication descriptor to be printed.
! glob - logical(otpional). Wheter to print out global or local data.

@ -35,7 +35,7 @@
! Subroutine: psb_cdren
! Updates a communication descriptor according to a renumbering scheme.
!
! Parameters:
! Arguments:
! trans - character. Whether iperm or its transpose
! should be applied.
! iperm - integer,dimension(:). The renumbering scheme.

Some files were not shown because too many files have changed in this diff Show More

Loading…
Cancel
Save