Merge comments and headers. To be refined for NaturalDocs.

stopcriterion
Salvatore Filippone 17 years ago
parent a8ab54f554
commit 3d191950ef

@ -259,10 +259,10 @@ contains
! 'bicgstabl', 'rgmres', 'cgs' (and all the upper/lower case
! variants). The same values except 'cg', 'bicg' and 'bicgstabl'
! are allowed in the complex case.
! a - type(<psb_dspmat_type>)/type(<psb_zspmat_type>), input.
! a - type(psb_dspmat_type)/type(psb_zspmat_type), input.
! The sparse matrix structure containing the local part of the
! matrix A.
! prec - type(<mld_dprec_type>)/type(<mld_zprec_type>), input.
! prec - type(mld_dprec_type)/type(mld_zprec_type), input.
! The preconditioner data structure containing the local part
! of the preconditioner to be applied.
! b - real(kind(1.d0))/complex(kind(1.d0)), dimension(:), input.
@ -273,7 +273,7 @@ contains
! the approximation computed by the selected Krylov solver.
! eps - real(kind(1.d0)), input.
! The tolerance used in the stopping criterion.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! info - integer, output.
! Error code.

@ -56,10 +56,10 @@
! Arguments:
! aggr_type - integer, input.
! The scalar used to identify the aggregation algorithm.
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local part of
! the fine-level matrix.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of the fine-level matrix.
! nlaggr - integer, dimension(:), allocatable.
! nlaggr(i) contains the aggregates held by process i.

@ -75,17 +75,17 @@
!
!
! Arguments:
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local part of
! the fine-level matrix.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of the fine-level matrix.
! ac - type(<psb_dspmat_type>), output.
! ac - type(psb_dspmat_type), output.
! The sparse matrix structure containing the local part of
! the coarse-level matrix.
! desc_ac - type(<psb_desc_type>), output.
! desc_ac - type(psb_desc_type), output.
! The communication descriptor of the coarse-level matrix.
! p - type(<mld_dbaseprc_type>), input/output.
! p - type(mld_dbaseprc_type), input/output.
! The base preconditioner data structure containing the local
! part of the base preconditioner to be built.
! info - integer, output.

@ -58,17 +58,17 @@
!
!
! Arguments:
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local part of
! the fine-level matrix.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of the fine-level matrix.
! ac - type(<psb_dspmat_type>), output.
! ac - type(psb_dspmat_type), output.
! The sparse matrix structure containing the local part of
! the coarse-level matrix.
! desc_ac - type(<psb_desc_type>), output.
! desc_ac - type(psb_desc_type), output.
! The communication descriptor of the coarse-level matrix.
! p - type(<mld_dbaseprc_type>), input/output.
! p - type(mld_dbaseprc_type), input/output.
! The base preconditioner data structure containing the local
! part of the base preconditioner to be built.
! info - integer, output.

@ -76,17 +76,17 @@
! 57 (2007), 1181-1196.
!
! Arguments:
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local part of
! the fine-level matrix.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of the fine-level matrix.
! ac - type(<psb_dspmat_type>), output.
! ac - type(psb_dspmat_type), output.
! The sparse matrix structure containing the local part of
! the coarse-level matrix.
! desc_ac - type(<psb_desc_type>), output.
! desc_ac - type(psb_desc_type), output.
! The communication descriptor of the coarse-level matrix.
! p - type(<mld_dbaseprc_type>), input/output.
! p - type(mld_dbaseprc_type), input/output.
! The base preconditioner data structure containing the local
! part of the base preconditioner to be built.
! info - integer, output.

@ -52,16 +52,16 @@
! mld_bjac_ and mld_as_ (see mld_prec_type.f90) are allowed.
! novr - integer, input.
! The number of overlap layers in the AS preconditioner.
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local part of the
! matrix to be preconditioned.
! blk - type(<psb_dspmat_type>), output.
! blk - type(psb_dspmat_type), output.
! The sparse matrix structure containing the remote rows that
! extend the local matrix according to novr. If novr = 0 then
! blk does not contain any row.
! desc_data - type(<psb_desc_type>), input.
! desc_data - type(psb_desc_type), input.
! The communication descriptor of the sparse matrix a.
! desc_p - type(<psb_desc_type>), output.
! desc_p - type(psb_desc_type), output.
! The communication descriptor associated to the extended
! matrices that form the AS preconditioner.
! info - integer, output.

@ -56,7 +56,7 @@
! Arguments:
! alpha - real(kind(0.d0)), input.
! The scalar alpha.
! prec - type(<mld_dbaseprc_type>), input.
! prec - type(mld_dbaseprc_type), input.
! The base preconditioner data structure containing the local part
! of the preconditioner K.
! x - real(kind(0.d0)), dimension(:), input.
@ -65,7 +65,7 @@
! The scalar beta.
! y - real(kind(0.d0)), dimension(:), input/output.
! The local part of the vector Y.
! desc_data - type(<psb_desc_type>), input.
! desc_data - type(psb_desc_type), input.
! The communication descriptor associated to the matrix to be
! preconditioned.
! trans - character, optional.

@ -50,12 +50,12 @@
!
!
! Arguments:
! a - type(<psb_dspmat_type>).
! a - type(psb_dspmat_type).
! The sparse matrix structure containing the local part of the
! matrix to be preconditioned.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of a.
! p - type(<mld_dbaseprec_type>), input/output.
! p - type(mld_dbaseprec_type), input/output.
! The 'base preconditioner' data structure containing the local
! part of the preconditioner at the selected level.
! info - integer, output.

@ -108,7 +108,7 @@
!
! alpha - real(kind(0.d0)), input.
! The scalar alpha.
! prec - type(<mld_dbaseprec_type>), input.
! prec - type(mld_dbaseprec_type), input.
! The 'base preconditioner' data structure containing the local
! part of the preconditioner or solver.
! x - real(kind(0.d0)), dimension(:), input/output.
@ -117,7 +117,7 @@
! The scalar beta.
! y - real(kind(0.d0)), dimension(:), input/output.
! The local part of the vector Y.
! desc_data - type(<psb_desc_type>), input.
! desc_data - type(psb_desc_type), input.
! The communication descriptor associated to the matrix to be
! preconditioned or 'inverted'.
! trans - character(len=1), input.

@ -86,12 +86,12 @@
!
!
! Arguments:
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local part of the
! matrix to be preconditioned or factorized.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! p - type(<mld_dbaseprec_type>), input/output.
! p - type(mld_dbaseprec_type), input/output.
! The 'base preconditioner' data structure containing the local
! part of the preconditioner or solver at the current level.
! info - integer, output.

@ -44,12 +44,12 @@
!
!
! Arguments:
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local part of the
! matrix A to be preconditioned.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to the sparse matrix A.
! p - type(<mld_dbaseprc_type>), input/output.
! p - type(mld_dbaseprc_type), input/output.
! The 'base preconditioner' data structure containing the local
! part of the diagonal preconditioner.
! info - integer, output.

@ -61,7 +61,7 @@
!
!
! Arguments:
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that if p%iprcparm(mld_n_ovr_) > 0, i.e. the
! 'base' Additive Schwarz preconditioner has overlap greater than
@ -70,9 +70,9 @@
! only the 'original' local part of the matrix to be factorized,
! i.e. the rows of the matrix held by the calling process according
! to the initial data distribution.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! p - type(<mld_dbaseprc_type>), input/output.
! p - type(mld_dbaseprc_type), input/output.
! The 'base preconditioner' data structure. In input, p%iprcparm
! contains information on the type of factorization to be computed.
! In output, p%av(mld_l_pr_) and p%av(mld_u_pr_) contain the
@ -81,7 +81,7 @@
! details on p see its description in mld_prec_type.f90.
! info - integer, output.
! Error code.
! blck - type(<psb_dspmat_type>), input, optional.
! blck - type(psb_dspmat_type), input, optional.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap

@ -68,18 +68,18 @@
! The type of incomplete factorization to be performed.
! The MILU(0) factorization is computed if ialg = 2 (= mld_milu_n_);
! the ILU(0) factorization otherwise.
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that if the 'base' Additive Schwarz preconditioner
! has overlap greater than 0 and the matrix has not been reordered
! (see mld_bjac_bld), then a contains only the 'original' local part
! of the matrix to be factorized, i.e. the rows of the matrix held
! by the calling process according to the initial data distribution.
! l - type(<psb_dspmat_type>), input/output.
! l - type(psb_dspmat_type), input/output.
! The L factor in the incomplete factorization.
! Note: its allocation is managed by the calling routine mld_ilu_bld,
! hence it cannot be only intent(out).
! u - type(<psb_dspmat_type>), input/output.
! u - type(psb_dspmat_type), input/output.
! The U factor (except its diagonal) in the incomplete factorization.
! Note: its allocation is managed by the calling routine mld_ilu_bld,
! hence it cannot be only intent(out).
@ -90,7 +90,7 @@
! hence it cannot be only intent(out).
! info - integer, output.
! Error code.
! blck - type(<psb_dspmat_type>), input, optional, target.
! blck - type(psb_dspmat_type), input, optional, target.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
@ -231,7 +231,7 @@ contains
! i.e. ma+mb.
! ma - integer, input
! The number of rows of the local submatrix stored into a.
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that, if the 'base' Additive Schwarz preconditioner
! has overlap greater than 0 and the matrix has not been reordered
@ -240,7 +240,7 @@ contains
! by the calling process according to the initial data distribution.
! mb - integer, input.
! The number of rows of the local submatrix stored into b.
! b - type(<psb_dspmat_type>), input.
! b - type(psb_dspmat_type), input.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
@ -492,7 +492,7 @@ contains
! sparse matrix structure a.
! m - integer, input.
! The number of rows of the local matrix stored into a.
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the row to be copied.
! jd - integer, input.
! The column index of the diagonal entry of the row to be

@ -64,18 +64,18 @@
! The type of incomplete factorization to be performed.
! The MILU(k) factorization is computed if ialg = 2 (= mld_milu_n_);
! the ILU(k) factorization otherwise.
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that if the 'base' Additive Schwarz preconditioner
! has overlap greater than 0 and the matrix has not been reordered
! (see mld_bjac_bld), then a contains only the 'original' local part
! of the matrix to be factorized, i.e. the rows of the matrix held
! by the calling process according to the initial data distribution.
! l - type(<psb_dspmat_type>), input/output.
! l - type(psb_dspmat_type), input/output.
! The L factor in the incomplete factorization.
! Note: its allocation is managed by the calling routine mld_ilu_bld,
! hence it cannot be only intent(out).
! u - type(<psb_dspmat_type>), input/output.
! u - type(psb_dspmat_type), input/output.
! The U factor (except its diagonal) in the incomplete factorization.
! Note: its allocation is managed by the calling routine mld_ilu_bld,
! hence it cannot be only intent(out).
@ -86,7 +86,7 @@
! hence it cannot be only intent(out).
! info - integer, output.
! Error code.
! blck - type(<psb_dspmat_type>), input, optional, target.
! blck - type(psb_dspmat_type), input, optional, target.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
@ -227,7 +227,7 @@ contains
! i.e. ma+mb.
! ma - integer, input.
! The number of rows of the local submatrix stored into a.
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that, if the 'base' Additive Schwarz preconditioner
! has overlap greater than 0 and the matrix has not been reordered
@ -236,7 +236,7 @@ contains
! by the calling process according to the initial data distribution.
! mb - integer, input.
! The number of rows of the local submatrix stored into b.
! b - type(<psb_dspmat_type>), input.
! b - type(psb_dspmat_type), input.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
@ -442,7 +442,7 @@ contains
! sparse matrix structure a.
! m - integer, input.
! The number of rows of the local matrix stored into a.
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the row to be copied.
! jmin - integer, input.
! The minimum valid column index.

@ -61,18 +61,18 @@
! The fill-in parameter k in ILU(k,t).
! thres - integer, input.
! The threshold t, i.e. the drop tolerance, in ILU(k,t).
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that if the 'base' Additive Schwarz preconditioner
! has overlap greater than 0 and the matrix has not been reordered
! (see mld_bjac_bld), then a contains only the 'original' local part
! of the matrix to be factorized, i.e. the rows of the matrix held
! by the calling process according to the initial data distribution.
! l - type(<psb_dspmat_type>), input/output.
! l - type(psb_dspmat_type), input/output.
! The L factor in the incomplete factorization.
! Note: its allocation is managed by the calling routine mld_ilu_bld,
! hence it cannot be only intent(out).
! u - type(<psb_dspmat_type>), input/output.
! u - type(psb_dspmat_type), input/output.
! The U factor (except its diagonal) in the incomplete factorization.
! Note: its allocation is managed by the calling routine mld_ilu_bld,
! hence it cannot be only intent(out).
@ -83,7 +83,7 @@
! hence it cannot be only intent(out).
! info - integer, output.
! Error code.
! blck - type(<psb_dspmat_type>), input, optional, target.
! blck - type(psb_dspmat_type), input, optional, target.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
@ -224,7 +224,7 @@ contains
! i.e. ma+mb.
! ma - integer, input.
! The number of rows of the local submatrix stored into a.
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that, if the 'base' Additive Schwarz preconditioner
! has overlap greater than 0 and the matrix has not been reordered
@ -233,7 +233,7 @@ contains
! by the calling process according to the initial data distribution.
! mb - integer, input.
! The number of rows of the local submatrix stored into b.
! b - type(<psb_dspmat_type>), input.
! b - type(psb_dspmat_type), input.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
@ -430,7 +430,7 @@ contains
! sparse matrix structure a.
! m - integer, input.
! The number of rows of the local matrix stored into a.
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the row to be
! copied.
! jd - integer, input.

@ -76,11 +76,11 @@
! Arguments:
! alpha - real(kind(0.d0)), input.
! The scalar alpha.
! baseprecv - type(<mld_dbaseprc_type>), dimension(:), input.
! baseprecv - type(mld_dbaseprc_type), dimension(:), input.
! The array of base preconditioner data structures containing the
! local parts of the preconditioners to be applied at each level.
! Note that nlev = size(baseprecv) = number of levels.
! baseprecv(ilev)%av - type(<psb_dspmat_type>), dimension(:), allocatable(:).
! baseprecv(ilev)%av - type(psb_dspmat_type), dimension(:), allocatable(:).
! The sparse matrices needed to apply the preconditioner
! at level ilev.
! baseprecv(ilev)%av(mld_l_pr_) - The L factor of the ILU factorization of the
@ -99,11 +99,11 @@
! baseprecv(ilev)%d - real(kind(1.d0)), dimension(:), allocatable.
! The diagonal entries of the U factor in the ILU
! factorization of A(ilev).
! baseprecv(ilev)%desc_data - type(<psb_desc_type>).
! baseprecv(ilev)%desc_data - type(psb_desc_type).
! The communication descriptor associated to the base
! preconditioner, i.e. to the sparse matrices needed
! to apply the base preconditioner at the current level.
! baseprecv(ilev)%desc_ac - type(<psb_desc_type>).
! baseprecv(ilev)%desc_ac - type(psb_desc_type).
! The communication descriptor associated to the sparse
! matrix A(ilev), stored in baseprecv(ilev)%av(mld_ac_).
! baseprecv(ilev)%iprcparm - integer, dimension(:), allocatable.
@ -126,14 +126,14 @@
! baseprecv(ilev)%nlaggr - integer, dimension(:), allocatable.
! The number of aggregates (rows of A(ilev)) on the
! various processes.
! baseprecv(ilev)%base_a - type(<psb_zspmat_type>), pointer.
! baseprecv(ilev)%base_a - type(psb_zspmat_type), pointer.
! Pointer (really a pointer!) to the base matrix of
! the current level, i.e. the local part of A(ilev);
! so we have a unified treatment of residuals. We
! need this to avoid passing explicitly the matrix
! A(ilev) to the routine which applies the
! preconditioner.
! baseprecv(ilev)%base_desc - type(<psb_desc_type>), pointer.
! baseprecv(ilev)%base_desc - type(psb_desc_type), pointer.
! Pointer to the communication descriptor associated
! to the sparse matrix pointed by base_a.
! baseprecv(ilev)%dorig - real(kind(1.d0)), dimension(:), allocatable.
@ -145,7 +145,7 @@
! The scalar beta.
! y - real(kind(0.d0)), dimension(:), input/output.
! The local part of the vector Y.
! desc_data - type(<psb_desc_type>), input.
! desc_data - type(psb_desc_type), input.
! The communication descriptor associated to the matrix to be
! preconditioned.
! trans - character, optional.

@ -44,12 +44,12 @@
!
!
! Arguments:
! a - type(<psb_dspmat_type>).
! a - type(psb_dspmat_type).
! The sparse matrix structure containing the local part of the
! matrix to be preconditioned.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of a.
! p - type(<mld_dbaseprc_type>), input/output.
! p - type(mld_dbaseprc_type), input/output.
! The base preconditioner data structure containing the local
! part of the base preconditioner to be built.
! info - integer, output.

@ -50,14 +50,14 @@
!
!
! Arguments:
! prec - type(<mld_dprec_type>), input.
! prec - type(mld_dprec_type), input.
! The preconditioner data structure containing the local part
! of the preconditioner to be applied.
! x - real(kind(0.d0)), dimension(:), input.
! The local part of the vector X in Y := op(M^(-1)) * X.
! y - real(kind(0.d0)), dimension(:), output.
! The local part of the vector Y in Y := op(M^(-1)) * X.
! desc_data - type(<psb_desc_type>), input.
! desc_data - type(psb_desc_type), input.
! The communication descriptor associated to the matrix to be
! preconditioned.
! info - integer, output.
@ -172,12 +172,12 @@ end subroutine mld_dprec_aply
!
!
! Arguments:
! prec - type(<mld_dprec_type>), input.
! prec - type(mld_dprec_type), input.
! The preconditioner data structure containing the local part
! of the preconditioner to be applied.
! x - real(kind(0.d0)), dimension(:), input/output.
! The local part of vector X in X := op(M^(-1)) * X.
! desc_data - type(<psb_desc_type>), input.
! desc_data - type(psb_desc_type), input.
! The communication descriptor associated to the matrix to be
! preconditioned.
! info - integer, output.

@ -50,12 +50,12 @@
!
!
! Arguments:
! a - type(<psb_dspmat_type>).
! a - type(psb_dspmat_type).
! The sparse matrix structure containing the local part of the
! matrix to be preconditioned.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of a.
! p - type(<mld_dprec_type>), input/output.
! p - type(mld_dprec_type), input/output.
! The preconditioner data structure containing the local part
! of the preconditioner to be built.
! info - integer, output.

@ -45,7 +45,7 @@
!
!
! Arguments:
! p - type(<mld_dprec_type>), input/output.
! p - type(mld_dprec_type), input/output.
! The preconditioner data structure to be deallocated.
! info - integer, output.
! Error code.

@ -69,7 +69,7 @@
!
!
! Arguments:
! p - type(<mld_dprec_type>), input/output.
! p - type(mld_dprec_type), input/output.
! The preconditioner data structure.
! ptype - character(len=*), input.
! The type of preconditioner. Its values are 'NONE',

@ -48,7 +48,7 @@
!
!
! Arguments:
! p - type(<mld_dprec_type>), input/output.
! p - type(mld_dprec_type), input/output.
! The preconditioner data structure.
! what - integer, input.
! The number identifying the parameter to be set.

@ -55,12 +55,12 @@
!
!
! Arguments:
! a - type(<psb_dspmat_type>), input/output.
! a - type(psb_dspmat_type), input/output.
! The sparse matrix structure containing the local submatrix to
! be factorized.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! p - type(<mld_dbaseprc_type>), input/output.
! p - type(mld_dbaseprc_type), input/output.
! The 'base preconditioner' data structure containing the pointer,
! p%iprcparm(mld_slu_ptr_), to the data structure used by SuperLU
! to store the L and U factors.

@ -52,12 +52,12 @@
!
!
! Arguments:
! a - type(<psb_dspmat_type>), input/output.
! a - type(psb_dspmat_type), input/output.
! The sparse matrix structure containing the local part of the
! matrix to be factorized.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! p - type(<mld_dbaseprc_type>), input/output.
! p - type(mld_dbaseprc_type), input/output.
! The 'base preconditioner' data structure containing the pointer,
! p%iprcparm(mld_slud_ptr_), to the data structure used by
! SuperLU_DIST to store the L and U factors.

@ -56,26 +56,26 @@
!
!
! Arguments:
! a - type(<psb_dspmat_type>), input.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the 'original' local
! part of the matrix to be reordered, i.e. the rows of the matrix
! held by the calling process according to the initial data
! distribution.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! blck - type(<psb_dspmat_type>), input.
! blck - type(psb_dspmat_type), input.
! The sparse matrix structure containing the remote rows of the
! matrix to be reordered, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
! greater than 0.If the overlap is 0, then blck does not contain
! any row.
! p - type(<mld_dbaseprc_type>), input/output.
! p - type(mld_dbaseprc_type), input/output.
! The base preconditioner data structure containing the local
! part of the base preconditioner to be built. In input it
! contains information on the type of reordering to be applied
! and on the matrix to be reordered. In output it contains
! information on the reordering applied.
! atmp - type(<psb_dspmat_type>), output.
! atmp - type(psb_dspmat_type), output.
! The sparse matrix structure containing the whole local reordered
! matrix.
! info - integer, output.

@ -56,16 +56,16 @@
!
!
! Arguments:
! a - type(<psb_dspmat_type>), input/output.
! a - type(psb_dspmat_type), input/output.
! The sparse matrix structure containing the local submatrix
! to be factorized. Note that a is intent(inout), and not only
! intent(in), since the row and column indices of the matrix
! stored in a are shifted by -1, and then again by +1, by the
! routine mld_dumf_factor, which is an interface to the UMFPACK
! C code performing the factorization.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! p - type(<mld_dbaseprc_type>), input/output.
! p - type(mld_dbaseprc_type), input/output.
! The 'base preconditioner' data structure containing the pointers,
! p%iprcparm(mld_umf_symptr_) and p%iprcparm(mld_umf_numptr_),
! to the data structures used by UMFPACK for computing the LU

@ -79,14 +79,14 @@ module mld_prec_type
!
! Details on mld_prec_type:
!
! baseprecv - type(<mld_dbaseprc_type>), dimension(:), allocatable.
! baseprecv - type(mld_dbaseprc_type), dimension(:), allocatable.
! baseprecv(ilev) is the base preconditioner at level ilev.
!
! Note that number of levels = size(baseprecv(:)).
!
! Details on mld_baseprc_type:
!
! av - type(<psb_dspmat_type>), dimension(:), allocatable(:).
! av - type(psb_dspmat_type), dimension(:), allocatable(:).
! The sparse matrices needed to apply the preconditioner at
! the current level ilev.
! av(mld_l_pr_) - The L factor of the ILU factorization of the local
@ -107,11 +107,11 @@ module mld_prec_type
! d - real(kind(1.d0)), dimension(:), allocatable.
! The diagonal entries of the U factor in the ILU factorization
! of A(ilev).
! desc_data - type(<psb_desc_type>).
! desc_data - type(psb_desc_type).
! The communication descriptor associated to the base preconditioner,
! i.e. to the sparse matrices needed to apply the base preconditioner
! at the current level.
! desc_ac - type(<psb_desc_type>).
! desc_ac - type(psb_desc_type).
! The communication descriptor associated to the sparse matrix
! A(ilev), stored in av(mld_ac_).
! iprcparm - integer, dimension(:), allocatable.
@ -132,12 +132,12 @@ module mld_prec_type
! nlaggr - integer, dimension(:), allocatable.
! The number of aggregates (rows of A(ilev)) on the
! various processes.
! base_a - type(<psb_zspmat_type>), pointer.
! base_a - type(psb_zspmat_type), pointer.
! Pointer (really a pointer!) to the local part of the base matrix
! of the current level, i.e. A(ilev); so we have a unified treatment
! of residuals. We need this to avoid passing explicitly the matrix
! A(ilev) to the routine which applies the preconditioner.
! base_desc - type(<psb_desc_type>), pointer.
! base_desc - type(psb_desc_type), pointer.
! Pointer to the communication descriptor associated to the sparse
! matrix pointed by base_a.
! dorig - real(kind(1.d0)), dimension(:), allocatable.
@ -467,7 +467,7 @@ contains
! preconditioner.
!
! Arguments:
! p - type(<mld_dprec_type>), input.
! p - type(mld_dprec_type), input.
! The preconditioner data structure to be printed out.
!
subroutine mld_out_prec_descr(p)
@ -492,7 +492,7 @@ contains
! iout - integer, input.
! The id of the file where the preconditioner description
! will be printed.
! p - type(<mld_dprec_type>), input.
! p - type(mld_dprec_type), input.
! The preconditioner data structure to be printed out.
!
subroutine mld_file_prec_descr(iout,p)

@ -56,10 +56,10 @@
! Arguments:
! aggr_type - integer, input.
! The scalar used to identify the aggregation algorithm.
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local part of
! the fine-level matrix.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of the fine-level matrix.
! nlaggr - integer, dimension(:), allocatable.
! nlaggr(i) contains the aggregates held by process i.

@ -75,17 +75,17 @@
!
!
! Arguments:
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local part of
! the fine-level matrix.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of the fine-level matrix.
! ac - type(<psb_zspmat_type>), output.
! ac - type(psb_zspmat_type), output.
! The sparse matrix structure containing the local part of
! the coarse-level matrix.
! desc_ac - type(<psb_desc_type>), output.
! desc_ac - type(psb_desc_type), output.
! The communication descriptor of the coarse-level matrix.
! p - type(<mld_zbaseprc_type>), input/output.
! p - type(mld_zbaseprc_type), input/output.
! The base preconditioner data structure containing the local
! part of the base preconditioner to be built.
! info - integer, output.

@ -58,17 +58,17 @@
!
!
! Arguments:
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local part of
! the fine-level matrix.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of the fine-level matrix.
! ac - type(<psb_zspmat_type>), output.
! ac - type(psb_zspmat_type), output.
! The sparse matrix structure containing the local part of
! the coarse-level matrix.
! desc_ac - type(<psb_desc_type>), output.
! desc_ac - type(psb_desc_type), output.
! The communication descriptor of the coarse-level matrix.
! p - type(<mld_zbaseprc_type>), input/output.
! p - type(mld_zbaseprc_type), input/output.
! The base preconditioner data structure containing the local
! part of the base preconditioner to be built.
! info - integer, output.

@ -76,17 +76,17 @@
! 57 (2007), 1181-1196.
!
! Arguments:
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local part of
! the fine-level matrix.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of the fine-level matrix.
! ac - type(<psb_zspmat_type>), output.
! ac - type(psb_zspmat_type), output.
! The sparse matrix structure containing the local part of
! the coarse-level matrix.
! desc_ac - type(<psb_desc_type>), output.
! desc_ac - type(psb_desc_type), output.
! The communication descriptor of the coarse-level matrix.
! p - type(<mld_zbaseprc_type>), input/output.
! p - type(mld_zbaseprc_type), input/output.
! The base preconditioner data structure containing the local
! part of the base preconditioner to be built.
! info - integer, output.

@ -52,16 +52,16 @@
! mld_bjac_ and mld_as_ (see mld_prec_type.f90) are allowed.
! novr - integer, input.
! The number of overlap layers in the AS preconditioner.
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local part of the
! matrix to be preconditioned.
! blk - type(<psb_zspmat_type>), output.
! blk - type(psb_zspmat_type), output.
! The sparse matrix structure containing the remote rows that
! extend the local matrix according to novr. If novr = 0 then
! blk does not contain any row.
! desc_data - type(<psb_desc_type>), input.
! desc_data - type(psb_desc_type), input.
! The communication descriptor of the sparse matrix a.
! desc_p - type(<psb_desc_type>), output.
! desc_p - type(psb_desc_type), output.
! The communication descriptor associated to the extended
! matrices that form the AS preconditioner.
! info - integer, output.

@ -56,7 +56,7 @@
! Arguments:
! alpha - complex(kind(0.d0)), input.
! The scalar alpha.
! prec - type(<mld_zbaseprc_type>), input.
! prec - type(mld_zbaseprc_type), input.
! The base preconditioner data structure containing the local part
! of the preconditioner K.
! x - complex(kind(0.d0)), dimension(:), input.
@ -65,7 +65,7 @@
! The scalar beta.
! y - complex(kind(0.d0)), dimension(:), input/output.
! The local part of the vector Y.
! desc_data - type(<psb_desc_type>), input.
! desc_data - type(psb_desc_type), input.
! The communication descriptor associated to the matrix to be
! preconditioned.
! trans - character, optional.

@ -50,12 +50,12 @@
!
!
! Arguments:
! a - type(<psb_zspmat_type>).
! a - type(psb_zspmat_type).
! The sparse matrix structure containing the local part of the
! matrix to be preconditioned.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of a.
! p - type(<mld_zbaseprec_type>), input/output.
! p - type(mld_zbaseprec_type), input/output.
! The 'base preconditioner' data structure containing the local
! part of the preconditioner at the selected level.
! info - integer, output.

@ -108,7 +108,7 @@
!
! alpha - complex(kind(0.d0)), input.
! The scalar alpha.
! prec - type(<mld_zbaseprec_type>), input.
! prec - type(mld_zbaseprec_type), input.
! The 'base preconditioner' data structure containing the local
! part of the preconditioner or solver.
! x - complex(kind(0.d0)), dimension(:), input/output.
@ -117,7 +117,7 @@
! The scalar beta.
! y - complex(kind(0.d0)), dimension(:), input/output.
! The local part of the vector Y.
! desc_data - type(<psb_desc_type>), input.
! desc_data - type(psb_desc_type), input.
! The communication descriptor associated to the matrix to be
! preconditioned or 'inverted'.
! trans - character(len=1), input.

@ -86,12 +86,12 @@
!
!
! Arguments:
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local part of the
! matrix to be preconditioned or factorized.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! p - type(<mld_zbaseprec_type>), input/output.
! p - type(mld_zbaseprec_type), input/output.
! The 'base preconditioner' data structure containing the local
! part of the preconditioner or solver at the current level.
! info - integer, output.

@ -44,12 +44,12 @@
!
!
! Arguments:
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local part of the
! matrix A to be preconditioned.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to the sparse matrix A.
! p - type(<mld_zbaseprc_type>), input/output.
! p - type(mld_zbaseprc_type), input/output.
! The 'base preconditioner' data structure containing the local
! part of the diagonal preconditioner.
! info - integer, output.

@ -61,7 +61,7 @@
!
!
! Arguments:
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that if p%iprcparm(mld_n_ovr_) > 0, i.e. the
! 'base' Additive Schwarz preconditioner has overlap greater than
@ -70,9 +70,9 @@
! only the 'original' local part of the matrix to be factorized,
! i.e. the rows of the matrix held by the calling process according
! to the initial data distribution.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! p - type(<mld_zbaseprc_type>), input/output.
! p - type(mld_zbaseprc_type), input/output.
! The 'base preconditioner' data structure. In input, p%iprcparm
! contains information on the type of factorization to be computed.
! In output, p%av(mld_l_pr_) and p%av(mld_u_pr_) contain the
@ -81,7 +81,7 @@
! details on p see its description in mld_prec_type.f90.
! info - integer, output.
! Error code.
! blck - type(<psb_zspmat_type>), input, optional.
! blck - type(psb_zspmat_type), input, optional.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap

@ -68,18 +68,18 @@
! The type of incomplete factorization to be performed.
! The MILU(0) factorization is computed if ialg = 2 (= mld_milu_n_);
! the ILU(0) factorization otherwise.
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that if the 'base' Additive Schwarz preconditioner
! has overlap greater than 0 and the matrix has not been reordered
! (see mld_bjac_bld), then a contains only the 'original' local part
! of the matrix to be factorized, i.e. the rows of the matrix held
! by the calling process according to the initial data distribution.
! l - type(<psb_zspmat_type>), input/output.
! l - type(psb_zspmat_type), input/output.
! The L factor in the incomplete factorization.
! Note: its allocation is managed by the calling routine mld_ilu_bld,
! hence it cannot be only intent(out).
! u - type(<psb_zspmat_type>), input/output.
! u - type(psb_zspmat_type), input/output.
! The U factor (except its diagonal) in the incomplete factorization.
! Note: its allocation is managed by the calling routine mld_ilu_bld,
! hence it cannot be only intent(out).
@ -90,7 +90,7 @@
! hence it cannot be only intent(out).
! info - integer, output.
! Error code.
! blck - type(<psb_zspmat_type>), input, optional, target.
! blck - type(psb_zspmat_type), input, optional, target.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
@ -230,7 +230,7 @@ contains
! i.e. ma+mb.
! ma - integer, input
! The number of rows of the local submatrix stored into a.
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that, if the 'base' Additive Schwarz preconditioner
! has overlap greater than 0 and the matrix has not been reordered
@ -239,7 +239,7 @@ contains
! by the calling process according to the initial data distribution.
! mb - integer, input.
! The number of rows of the local submatrix stored into b.
! b - type(<psb_zspmat_type>), input.
! b - type(psb_zspmat_type), input.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
@ -491,7 +491,7 @@ contains
! sparse matrix structure a.
! m - integer, input.
! The number of rows of the local matrix stored into a.
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the row to be copied.
! jd - integer, input.
! The column index of the diagonal entry of the row to be

@ -64,18 +64,18 @@
! The type of incomplete factorization to be performed.
! The MILU(k) factorization is computed if ialg = 2 (= mld_milu_n_);
! the ILU(k) factorization otherwise.
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that if the 'base' Additive Schwarz preconditioner
! has overlap greater than 0 and the matrix has not been reordered
! (see mld_bjac_bld), then a contains only the 'original' local part
! of the matrix to be factorized, i.e. the rows of the matrix held
! by the calling process according to the initial data distribution.
! l - type(<psb_zspmat_type>), input/output.
! l - type(psb_zspmat_type), input/output.
! The L factor in the incomplete factorization.
! Note: its allocation is managed by the calling routine mld_ilu_bld,
! hence it cannot be only intent(out).
! u - type(<psb_zspmat_type>), input/output.
! u - type(psb_zspmat_type), input/output.
! The U factor (except its diagonal) in the incomplete factorization.
! Note: its allocation is managed by the calling routine mld_ilu_bld,
! hence it cannot be only intent(out).
@ -86,7 +86,7 @@
! hence it cannot be only intent(out).
! info - integer, output.
! Error code.
! blck - type(<psb_zspmat_type>), input, optional, target.
! blck - type(psb_zspmat_type), input, optional, target.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
@ -226,7 +226,7 @@ contains
! i.e. ma+mb.
! ma - integer, input.
! The number of rows of the local submatrix stored into a.
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that, if the 'base' Additive Schwarz preconditioner
! has overlap greater than 0 and the matrix has not been reordered
@ -235,7 +235,7 @@ contains
! by the calling process according to the initial data distribution.
! mb - integer, input.
! The number of rows of the local submatrix stored into b.
! b - type(<psb_zspmat_type>), input.
! b - type(psb_zspmat_type), input.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
@ -441,7 +441,7 @@ contains
! sparse matrix structure a.
! m - integer, input.
! The number of rows of the local matrix stored into a.
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the row to be copied.
! jmin - integer, input.
! The minimum valid column index.

@ -61,18 +61,18 @@
! The fill-in parameter k in ILU(k,t).
! thres - integer, input.
! The threshold t, i.e. the drop tolerance, in ILU(k,t).
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that if the 'base' Additive Schwarz preconditioner
! has overlap greater than 0 and the matrix has not been reordered
! (see mld_bjac_bld), then a contains only the 'original' local part
! of the matrix to be factorized, i.e. the rows of the matrix held
! by the calling process according to the initial data distribution.
! l - type(<psb_zspmat_type>), input/output.
! l - type(psb_zspmat_type), input/output.
! The L factor in the incomplete factorization.
! Note: its allocation is managed by the calling routine mld_ilu_bld,
! hence it cannot be only intent(out).
! u - type(<psb_zspmat_type>), input/output.
! u - type(psb_zspmat_type), input/output.
! The U factor (except its diagonal) in the incomplete factorization.
! Note: its allocation is managed by the calling routine mld_ilu_bld,
! hence it cannot be only intent(out).
@ -83,7 +83,7 @@
! hence it cannot be only intent(out).
! info - integer, output.
! Error code.
! blck - type(<psb_zspmat_type>), input, optional, target.
! blck - type(psb_zspmat_type), input, optional, target.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
@ -223,7 +223,7 @@ contains
! i.e. ma+mb.
! ma - integer, input.
! The number of rows of the local submatrix stored into a.
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that, if the 'base' Additive Schwarz preconditioner
! has overlap greater than 0 and the matrix has not been reordered
@ -232,7 +232,7 @@ contains
! by the calling process according to the initial data distribution.
! mb - integer, input.
! The number of rows of the local submatrix stored into b.
! b - type(<psb_zspmat_type>), input.
! b - type(psb_zspmat_type), input.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
@ -429,7 +429,7 @@ contains
! sparse matrix structure a.
! m - integer, input.
! The number of rows of the local matrix stored into a.
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the row to be
! copied.
! jd - integer, input.

@ -76,11 +76,11 @@
! Arguments:
! alpha - complex(kind(0.d0)), input.
! The scalar alpha.
! baseprecv - type(<mld_zbaseprc_type>), dimension(:), input.
! baseprecv - type(mld_zbaseprc_type), dimension(:), input.
! The array of base preconditioner data structures containing the
! local parts of the preconditioners to be applied at each level.
! Note that nlev = size(baseprecv) = number of levels.
! baseprecv(ilev)%av - type(<psb_zspmat_type>), dimension(:), allocatable(:).
! baseprecv(ilev)%av - type(psb_zspmat_type), dimension(:), allocatable(:).
! The sparse matrices needed to apply the preconditioner
! at level ilev.
! baseprecv(ilev)%av(mld_l_pr_) - The L factor of the ILU factorization of the
@ -99,11 +99,11 @@
! baseprecv(ilev)%d - complex(kind(1.d0)), dimension(:), allocatable.
! The diagonal entries of the U factor in the ILU
! factorization of A(ilev).
! baseprecv(ilev)%desc_data - type(<psb_desc_type>).
! baseprecv(ilev)%desc_data - type(psb_desc_type).
! The communication descriptor associated to the base
! preconditioner, i.e. to the sparse matrices needed
! to apply the base preconditioner at the current level.
! baseprecv(ilev)%desc_ac - type(<psb_desc_type>).
! baseprecv(ilev)%desc_ac - type(psb_desc_type).
! The communication descriptor associated to the sparse
! matrix A(ilev), stored in baseprecv(ilev)%av(mld_ac_).
! baseprecv(ilev)%iprcparm - integer, dimension(:), allocatable.
@ -126,14 +126,14 @@
! baseprecv(ilev)%nlaggr - integer, dimension(:), allocatable.
! The number of aggregates (rows of A(ilev)) on the
! various processes.
! baseprecv(ilev)%base_a - type(<psb_zspmat_type>), pointer.
! baseprecv(ilev)%base_a - type(psb_zspmat_type), pointer.
! Pointer (really a pointer!) to the base matrix of
! the current level, i.e. the local part of A(ilev);
! so we have a unified treatment of residuals. We
! need this to avoid passing explicitly the matrix
! A(ilev) to the routine which applies the
! preconditioner.
! baseprecv(ilev)%base_desc - type(<psb_desc_type>), pointer.
! baseprecv(ilev)%base_desc - type(psb_desc_type), pointer.
! Pointer to the communication descriptor associated
! to the sparse matrix pointed by base_a.
! baseprecv(ilev)%dorig - complex(kind(1.d0)), dimension(:), allocatable.
@ -145,7 +145,7 @@
! The scalar beta.
! y - complex(kind(0.d0)), dimension(:), input/output.
! The local part of the vector Y.
! desc_data - type(<psb_desc_type>), input.
! desc_data - type(psb_desc_type), input.
! The communication descriptor associated to the matrix to be
! preconditioned.
! trans - character, optional.

@ -44,12 +44,12 @@
!
!
! Arguments:
! a - type(<psb_zspmat_type>).
! a - type(psb_zspmat_type).
! The sparse matrix structure containing the local part of the
! matrix to be preconditioned.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of a.
! p - type(<mld_zbaseprc_type>), input/output.
! p - type(mld_zbaseprc_type), input/output.
! The base preconditioner data structure containing the local
! part of the base preconditioner to be built.
! info - integer, output.

@ -50,14 +50,14 @@
!
!
! Arguments:
! prec - type(<mld_zprec_type>), input.
! prec - type(mld_zprec_type), input.
! The preconditioner data structure containing the local part
! of the preconditioner to be applied.
! x - complex(kind(0.d0)), dimension(:), input.
! The local part of the vector X in Y := op(M^(-1)) * X.
! y - complex(kind(0.d0)), dimension(:), output.
! The local part of the vector Y in Y := op(M^(-1)) * X.
! desc_data - type(<psb_desc_type>), input.
! desc_data - type(psb_desc_type), input.
! The communication descriptor associated to the matrix to be
! preconditioned.
! info - integer, output.
@ -173,12 +173,12 @@ end subroutine mld_zprec_aply
!
!
! Arguments:
! prec - type(<mld_zprec_type>), input.
! prec - type(mld_zprec_type), input.
! The preconditioner data structure containing the local part
! of the preconditioner to be applied.
! x - complex(kind(0.d0)), dimension(:), input/output.
! The local part of vector X in X := op(M^(-1)) * X.
! desc_data - type(<psb_desc_type>), input.
! desc_data - type(psb_desc_type), input.
! The communication descriptor associated to the matrix to be
! preconditioned.
! info - integer, output.

@ -50,12 +50,12 @@
!
!
! Arguments:
! a - type(<psb_zspmat_type>).
! a - type(psb_zspmat_type).
! The sparse matrix structure containing the local part of the
! matrix to be preconditioned.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor of a.
! p - type(<mld_zprec_type>), input/output.
! p - type(mld_zprec_type), input/output.
! The preconditioner data structure containing the local part
! of the preconditioner to be built.
! info - integer, output.

@ -45,7 +45,7 @@
!
!
! Arguments:
! p - type(<mld_zprec_type>), input/output.
! p - type(mld_zprec_type), input/output.
! The preconditioner data structure to be deallocated.
! info - integer, output.
! Error code.

@ -69,7 +69,7 @@
!
!
! Arguments:
! p - type(<mld_zprec_type>), input/output.
! p - type(mld_zprec_type), input/output.
! The preconditioner data structure.
! ptype - character(len=*), input.
! The type of preconditioner. Its values are 'NONE',

@ -48,7 +48,7 @@
!
!
! Arguments:
! p - type(<mld_zprec_type>), input/output.
! p - type(mld_zprec_type), input/output.
! The preconditioner data structure.
! what - integer, input.
! The number identifying the parameter to be set.

@ -55,12 +55,12 @@
!
!
! Arguments:
! a - type(<psb_zspmat_type>), input/output.
! a - type(psb_zspmat_type), input/output.
! The sparse matrix structure containing the local submatrix to
! be factorized.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! p - type(<mld_zbaseprc_type>), input/output.
! p - type(mld_zbaseprc_type), input/output.
! The 'base preconditioner' data structure containing the pointer,
! p%iprcparm(mld_slu_ptr_), to the data structure used by SuperLU
! to store the L and U factors.

@ -52,12 +52,12 @@
!
!
! Arguments:
! a - type(<psb_zspmat_type>), input/output.
! a - type(psb_zspmat_type), input/output.
! The sparse matrix structure containing the local part of the
! matrix to be factorized.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! p - type(<mld_zbaseprc_type>), input/output.
! p - type(mld_zbaseprc_type), input/output.
! The 'base preconditioner' data structure containing the pointer,
! p%iprcparm(mld_slud_ptr_), to the data structure used by
! SuperLU_DIST to store the L and U factors.

@ -56,26 +56,26 @@
!
!
! Arguments:
! a - type(<psb_zspmat_type>), input.
! a - type(psb_zspmat_type), input.
! The sparse matrix structure containing the 'original' local
! part of the matrix to be reordered, i.e. the rows of the matrix
! held by the calling process according to the initial data
! distribution.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! blck - type(<psb_zspmat_type>), input.
! blck - type(psb_zspmat_type), input.
! The sparse matrix structure containing the remote rows of the
! matrix to be reordered, that have been retrieved by mld_asmat_bld
! to build an Additive Schwarz base preconditioner with overlap
! greater than 0.If the overlap is 0, then blck does not contain
! any row.
! p - type(<mld_zbaseprc_type>), input/output.
! p - type(mld_zbaseprc_type), input/output.
! The base preconditioner data structure containing the local
! part of the base preconditioner to be built. In input it
! contains information on the type of reordering to be applied
! and on the matrix to be reordered. In output it contains
! information on the reordering applied.
! atmp - type(<psb_zspmat_type>), output.
! atmp - type(psb_zspmat_type), output.
! The sparse matrix structure containing the whole local reordered
! matrix.
! info - integer, output.

@ -56,16 +56,16 @@
!
!
! Arguments:
! a - type(<psb_zspmat_type>), input/output.
! a - type(psb_zspmat_type), input/output.
! The sparse matrix structure containing the local submatrix
! to be factorized. Note that a is intent(inout), and not only
! intent(in), since the row and column indices of the matrix
! stored in a are shifted by -1, and then again by +1, by the
! routine mld_zumf_factor, which is an interface to the UMFPACK
! C code performing the factorization.
! desc_a - type(<psb_desc_type>), input.
! desc_a - type(psb_desc_type), input.
! The communication descriptor associated to a.
! p - type(<mld_zbaseprc_type>), input/output.
! p - type(mld_zbaseprc_type), input/output.
! The 'base preconditioner' data structure containing the pointers,
! p%iprcparm(mld_umf_symptr_) and p%iprcparm(mld_umf_numptr_),
! to the data structures used by UMFPACK for computing the LU

Loading…
Cancel
Save